YAP 7.1.0
top.yap
2 :- '$live'.
3
4'$live' :-
5 ,
6 current_source_module(Module,Module),
7 set_prolog_flag(verbose,normal),
8 ( Module==user ->
9 true % '$compile_mode'(_,0)
10 ;
11 format(user_error,'[~w]~n', [Module])
12 ),
13 '$system_catch'('$enter_top_level',Module,Error,'$Error'(Error)).
14
15% Start file for yap
16
17%% *//* main execution loop */
18'$read_toplevel'(Goal, Bindings, Pos) :-
19 '$prompt',
20 catch(read_term(user_input,
21 Goal,
22 [variable_names(Bindings), syntax_errors(dec10), term_position(Pos)]),
23 E, '$Error'( E) ).
24
25
26
27/** @pred stream_property( Stream, Prop )
28
29*/
30
31% reset alarms when entering top-level.
32'$enter_top_level' :-
33 alarm(0, 0, _, _),
34 alarm.
35'$enter_top_level' :-
36 '$clean_up_dead_clauses',
37 alarm.
38'$enter_top_level' :-
39 current_prolog_flag(debug, DebugOK),
40 '$set_debugger_state'(debug, DebugOK),
41 '$set_debugger_state'.
42'$enter_top_level' :-
43 get_value('$top_level_goal',GA), GA \= [], ,
44 set_value('$top_level_goal',[]),
45 '$run_atom_goal'(GA),
46 '$run_atom_goal'.
47'$enter_top_level' :-
48 '$run_atom_goal',
49 '$run_toplevel_hooks',
50 prompt1(' ?- '),
51 '$read_toplevel'(Command,Varnames,Pos),
52 nb_setval('$spy_gn',1),
53 % stop at spy-points if debugging is on.
54 '$init_debugger_trace',
55 '$command'(Command,Varnames,Pos,top),
56 ( current_prolog_flag(break_level, BreakLevel),
57
58 BreakLevel \= 0
59 ->
60 current_prolog_flag
61 ;
62 '$pred_exists'(halt(_), user)
63 ->
64 halt(0)
65 ;
66 '$halt'(0)
67 ).
68
69'$erase_sets' :-
70 eraseall('$'),
71 eraseall('$$set'),
72 eraseall('$$one'),
73 eraseall('$reconsulted'), eraseall.
74'$erase_sets' :- \+ recorded('$path',_,_), recorda('$path',[],_).
75'$erase_sets'.
76
77'$start_corouts' :-
78 eraseall('$corout'),
79 eraseall('$result'),
80 eraseall('$actual'),
81 eraseall.
82'$start_corouts' :-
83 recorda('$actual',main,_),
84 recordz('$corout','$corout'(main,main,'$corout'([],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[])),_Ref),
85 recorda('$result',going,_).
86
87%
88% Hack in case expand_term has created a list of commands.
89%
90'$execute_commands'(V,_,_,_,_,_) :- var(V), '$error'(instantiation_error).
91'$execute_commands'([],_,_,_,_,_) :- '$execute_commands'.
92'$execute_commands'([C|Cs],M,VL,Pos,Con,Source) :-
93 '$execute_commands',
94 (
95 '$system_catch'('$execute_command'(C,M,VL,Pos,Con,Source),prolog,Error,'$LoopError'(Error, Con)),
96 '$system_catch'
97 ;
98 '$execute_commands'(Cs,M,VL,Pos,Con,Source)
99 ).
100'$execute_commands'(C,M,VL,Pos,Con,Source) :-
102 '$system_catch'('$execute_command'(C,M,VL,Pos,Con,Source),prolog,Error,'$LoopError'(Error, Con)).
103
104%
105%
106%
107
108'$execute_command'(end_of_file,_,_,_,_,_) :- '$execute_command'.
109'$execute_command'(Command,_,_,_,_,_) :-
110 '__NB_getval__'('$if_skip_mode', skip, fail),
111 \+ '$if_directive'(Command),
112 '$if_directive',
113 '$if_directive'.
114'$execute_command'((:-G),M,VL,Pos,Option,_) :-
115 '$execute_command', % allow user expansion
116 '$expand_term'((:- M:G), O),
117 '$yap_strip_module'(O, NM, NO),
118 (
119 NO = (:- G1)
120 ->
122 '$process_directive'(G1, Option, NM, VL, Pos)
123 ;
124 '$execute_commands'(G1,NM,VL,Pos,Option,O)
125 ),
126 fail.
127'$execute_command'((?-G), M, VL, Pos, top, Source) :-
128 '$execute_command',
129 '$execute_command'(G, M, VL, Pos, top, Source).
130'$execute_command'(G, M, VL, Pos, Option, Source) :-
131 '$continue_with_command'(Option, VL, Pos, M:G, Source).
132
133'$expand_term'(T,O) :-
134 '$expand_term'(T,top,O).
135
136'$expand_term'(T,Con,O) :-
137 catch( '$expand_term0'(T,Con,O), _,( '$disable_debugging', fail) ),
138 catch.
139
140'$expand_term0'(T,consult,O) :-
141 expand_term( T, O).
142'$expand_term0'(T,reconsult,O) :-
143 expand_term( T, O).
144'$expand_term0'(T,top,O) :-
145 expand_term( T, T1),
146 expand_term,
147 '$expand_term1'(T1,O).
148'$expand_term0'(T,_,T).
149
150'$expand_term1'(T,O) :-
151 expand_goal(T,O),
152 expand_goal.
153'$expand_term1'(O,O).
154
155'$continue_with_command'(consult,V,Pos,G,Source) :-
156 '$go_compile_clause'(G,V,Pos,consult,Source),
157 '$go_compile_clause',
158 '$go_compile_clause'.
159'$continue_with_command'(reconsult,V,Pos,G,Source) :-
160 '$go_compile_clause'(G,V,Pos,reconsult,Source),
161 '$go_compile_clause',
162 '$go_compile_clause'.
163'$continue_with_command'(top,Names,_,G,_) :-
164 prolog_flag(prompt_alternatives_on, OPT),
165 (
166 query_to_answer(G,Names,Port,GVs,LGs)
167 *->
168 '$another'(Names, GVs, LGs, Port, OPT)
169 ;
170 print_message(help,false)
171 ),
172 !,
173 fail.
174
175
176
177%%
178% @pred '$go_compile_clause'(G,Vs,Pos, Where, Source) is det
179%
180% interfaces the loader and the compiler
181% not 100% compatible with SICStus Prolog, as SICStus Prolog would put
182% module prefixes all over the place, although unnecessarily so.
183%
184% @param [in] _G_ is the clause to compile
185% @param [in] _Vs_ a list of variables and their name
186% @param [in] _Pos_ the source-code position
187% @param [in] _N_ a flag telling whether to add first or last
188% @param [out] _Source_ the user-tranasformed clause
189'$go_compile_clause'(G, _Vs, _Pos, Where, Source) :-
190 '$precompile_term'(G, Source, G1),
191 '$precompile_term',
192 '$$compile'(G1, Where, Source, _).
193'$go_compile_clause'(G,_Vs,_Pos, _Where, _Source) :-
194 throw(error(system, compilation_failed(G))).
195
196'$$compile'(C, Where, C0, R) :-
197 '$head_and_body'( C, MH, B ),
198 strip_module( MH, Mod, H),
199 (
200 '$undefined'(H, Mod)
201 ->
202 '$init_pred'(H, Mod, Where)
203 ;
204 '$init_pred'
205 ),
206% writeln(Mod:((H:-B))),
207 '$compile'((H:-B), Where, C0, Mod, R).
208
209'$init_pred'(H, Mod, _Where ) :-
210 recorded('$import','$import'(NM,Mod,NH,H,_,_),RI),
211 % NM \= Mod,
212 functor(NH,N,Ar),
213 functor(H,ON,Ar),
214 print_message(warning,redefine_imported(Mod,NM,Mod:N/Ar)),
215 abolish(Mod:ON/Ar),
216 erase(RI),
217 erase.
218'$init_pred'(H, Mod, Where ) :-
219 '$init_as_dynamic'(Where),
220 '$init_as_dynamic',
221 functor(H, Na, Ar),
222 '$dynamic'(Na/Ar, Mod).
223'$init_pred'(_H, _Mod, _Where ).
224
225'$init_as_dynamic'( asserta ).
226'$init_as_dynamic'( assertz ).
227'$init_as_dynamic'( consult ) :-
228 '__NB_getval__'('$assert_all',on,fail).
229'$init_as_dynamic'( reconsult ) :-
230 '__NB_getval__'('$assert_all',on,fail).
231
232'$check_if_reconsulted'(N,A) :-
233 once(recorded('$reconsulted',N/A,_)),
234 recorded('$reconsulted',X,_),
235 ( X = N/A , !;
236 X = '$', !, fail;
237 fail
238 ).
239
240'$inform_as_reconsulted'(N,A) :-
241 recorda('$reconsulted',N/A,_).
242
243'$clear_reconsulting' :-
244 recorded('$reconsulted',X,Ref),
245 erase(Ref),
246 X == '$',
247 erase,
248 ( recorded('$reconsulting',_,R) -> erase(R) ).
249
250'$prompt_alternatives_on'(determinism).
251
252/* Executing a query */
253
254/* Executing a query */
255
256query_to_answer(end_of_file,_,exit,[],[]) :-
257 query_to_answer.
258query_to_answer(G,Vs,Port, GVs, LGs) :-
259 '$query'(G,Vs,Port),
260 '$query':delayed_goals(G, Vs, GVs, LGs).
261
262'$query'(G,[]) :-
263 '$query'(G,[],_Port).
264
265
266'$query'(G,_Vs,Port) :-
267 prolog_flag(debug,true),
268 '$get_debugger_state'(trace,on),
269 '$get_debugger_state'(creep,Creep),
270 Creep \= '$get_debugger_state',
271 '$get_debugger_state',
272 gated_call(
273 true,
274 '$spy'(G),
275 Port,
276 true
277 ).
278'$query'(G,_,Port) :-
279 catch(
280 gated_call(
281 true,
282 G,
283 Port,
284 true
285 ),
286 Error,
287 '$Error'(Error)
288 ).
289
290%
291'$another'([], _, _, _, _) :-
292 '$another',
293 print_message(help, answer([],[],[],'.~n')).
294'$another'(Names, GVs,LGs, exit, determinism) :-
295 '$another',
296 print_message(help, answer(Names, GVs,LGs,'.~n')),
297 print_message(help,yes).
298'$another'(_,_, _, fail, _) :-
299 '$another',
300 print_message(help,no).
301'$another'(Names, GVs,LGs,_,_) :-
302 print_message(help, answer(Names, GVs,LGs,' ? ') ),
303 '$clear_input'(user_input),
304 get_code(user_input,C),
305 '$do_another'(C).
306
307'$do_another'(C) :-
308 ( C=:= ";" ->
309 skip(user_input,10),
310 skip,
311 skip
312 ;
313 C== 10
314 ->
315 '$add_nl_outside_console'
316 ),
317 !.
318
319%'$add_nl_outside_console' :-
320% '$is_same_tty'(user_input, user_error), !.
321'$add_nl_outside_console' :-
322 format(user_error,'~n',[]).
323
324'$ask_again_for_another' :-
325 prompt(_Old,'Action (\";\" for more choices, <return> for exit)', []),
326 '$another'.
327
328
329
330
331%
332% standard meta-call, called if $execute could not do everything.
333%
334
335'$disable_debugging_on_port'(retry) :-
336 '$disable_debugging_on_port',
337 current_prolog_flag(debug,true),
338 '$set_debugger_state'(debug, true).
339'$disable_debugging_on_port'(_Port) :-
340 '$set_debugger_state'(debug, false).
341
342
343
344% enable creeping
345'$enable_debugging':-
346 prolog_flag(debug, false), prolog_flag.
347'$enable_debugging' :-
348 '$get_debugger_state'(trace,on),
349 '$get_debugger_state',
350 '$set_debugger_state'(creep, 0, stop, on, true),
351 '$creep'.
352'$enable_debugging' :-
353 '$set_debugger_state'(zip, 0, stop, on, true).
354
355'$trace_on' :-
356 '$get_debugger_state'(debug, true),
357 '$set_debugger_state'(trace, on).
358
359
360
361
362'$trace_off' :-
363 '$get_debugger_state'(debug, true),
364 '$set_debugger_state'(trace, off).
365
366
367%
368% do it in ISO mode.
369%
370'$call'(G, CP, G0, _, M) :- /* iso version */
371 '$iso_check_goal'(G,G0),
372 '$call'(G, CP, G0, M).
373
374
375'$call'(M:_,_,G0,_) :- var(M), var,
376 '$do_error'(instantiation_error,call(G0)).
377
378'$call'(M:G,CP,G0,_M0) :- '$call',
379 '$yap_strip_module'(M:G,NM,NC),
380 '$call'(NC,CP,G0,NM).
381
382'$call'('$call'(X,CP,_G0,M),_,G0,_) :-
383 '$call',
384 '$call'(X,CP,G0,M).
385'$call'((X,Y),CP,G0,M) :- '$call',
386 '$call'(X,CP,G0,M),
387 '$call'(Y,CP,G0,M).
388'$call'((X->Y),CP,G0,M) :- '$call',
389 (
391 '$call'(X,CP1,G0,M)
392 ->
393 '$call'(Y,CP,G0,M)
394 ).
395
396'$call'((X*->Y),CP,G0,M) :- '$call',
398 '$call'(X,CP1,G0,M),
399 '$call'(Y,CP,G0,M).
400'$call'((X->Y; Z),CP,G0,M) :- '$call',
401 (
403 '$call'(X,CP1,G0,M)
404 ->
405 '$call'(Y,CP,G0,M)
406 ;
407 '$call'(Z,CP,G0,M)
408 ).
409'$call'((X*->Y; Z),CP,G0,M) :- '$call',
410 (
412 '$call'(X,CP1,G0,M)
413 *->
414 '$call'(Y,CP,G0,M)
415 ;
416 '$call'(Z,CP,G0,M)
417 ).
418'$call'((A;B),CP,G0,M) :- '$call',
419 (
420 '$call'(A,CP,G0,M)
421 ;
422 '$call'(B,CP,G0,M)
423 ).
424'$call'((X->Y| Z),CP,G0,M) :- '$call',
425 (
427 '$call'(X,CP1,G0,M)
428 ->
429 '$call'(Y,CP,G0,M)
430 ;
431 '$call'(Z,CP,G0,M)
432 ).
433'$call'((X*->Y| Z),CP,G0,M) :- '$call',
434 (
436 '$call'(X,CP1,G0,M)
437*->
438 '$call'(Y,CP,G0,M)
439 ;
440 '$call'(Z,CP,G0,M)
441 ).
442'$call'((A|B),CP, G0,M) :- '$call',
443 (
444 '$call'(A,CP,G0,M)
445 ;
446 '$call'(B,CP,G0,M)
447 ).
448'$call'(\+ X, _CP, G0, M) :- '$call',
449 \+ (current_choice_point(CP),
450 '$call'(X,CP,G0,M) ).
451'$call'(not(X), _CP, G0, M) :- '$call',
452 \+ (current_choice_point(CP),
453 '$call'(X,CP,G0,M) ).
454'$call'(!, CP, _,_) :- '$call',
455 cut_by(CP).
456'$call'([A|B], _, _, M) :- '$call',
457 '$csult'([A|B], M).
458'$call'(G, _CP, _G0, CurMod) :-
459 % /*
460 % (
461 % '$is_meta_predicate'(G,CurMod)
462 % ->
463 % '$disable_debugging',
464 % ( '$expand_meta_call'(CurMod:G, [], NG) -> true ; true ),
465 % '$enable_debugging'
466 % ;
467 % NG = G
468 % ),
469 % */
470 '$execute0'(G, CurMod).
471
472
473'$check_callable'(V,G) :- var(V), var,
474 '$do_error'(instantiation_error,G).
475'$check_callable'(M:_G1,G) :- var(M), var,
476 '$do_error'(instantiation_error,G).
477'$check_callable'(_:G1,G) :- '$check_callable',
478 '$check_callable'(G1,G).
479'$check_callable'(A,G) :- number(A), number,
480 '$do_error'(type_error(callable,A),G).
481'$check_callable'(R,G) :- db_reference(R), db_reference,
482 '$do_error'(type_error(callable,R),G).
483'$check_callable'(_,_).
484
485'__$loop_'(Stream,Status) :-
486 '__$loop_',
487 '$current_module'( OldModule, OldModule ),
488 '$enter_command'(Stream,OldModule,Status),
489 '$enter_command'.
490
491'$boot_loop'(Stream,Where) :-
492 '$boot_loop',
493 '$current_module'( OldModule, OldModule ),
494 read_clause(Stream, Command, [module(OldModule), syntax_errors(dec10),variable_names( Vars), term_position(_Pos)]),
495 (Command == end_of_file
496 ->
497 !
498 ;
499 Command = (:- Goal) ->
500 query(Goal, []),
501 query
502;
503 Command = (?- Goal) ->
504 query(Goal, Vars),
505 query
506 ;
507 Command = (H --> B) ->
508 '$system_catch'('$boot_dcg'(H,B, Where), prolog, Error,
509 user:'$LoopError'(Error, consult) ),
510
511 '$system_catch'
512 ;
513 '$system_catch'('$boot_clause'( Command, Where ), prolog, Error,
514 user:'$LoopError'(Error, consult) ),
515 '$system_catch'
516 ).
517
518'$boot_execute'( Goal ) :-
519 '$execute'( Goal ),
520 '$execute'.
521'$boot_execute'( Goal ) :-
522 format(user_error, ':- ~w failed.~n', [Goal]).
523
524'$boot_dcg'( H, B, Where ) :-
525 '$translate_rule'((H --> B), (NH :- NB) ),
526 '$$compile'((NH :- NB), Where, ( H --> B), _R),
527 '$$compile'.
528'$boot_dcg'( H, B, _ ) :-
529 format(user_error, ' ~w --> ~w failed.~n', [H,B]).
530
531'$boot_clause'( Command, Where ) :-
532 '$$compile'(Command, Where, Command, _R),
533 '$$compile'.
534'$boot_clause'( Command, _ ) :-
535 format(user_error, ' ~w failed.~n', [Command]).
536
537
538
539'$enter_command'(Stream, Mod, Status) :-
540 prompt1(': '), prompt(_,' '),
541 Options = [module(Mod), syntax_errors(dec10),variable_names(Vars), term_position(Pos)],
542 (
543 Status ==
544 ->
545 read_term(Stream, Command, Options)
546 ;
547 read_clause(Stream, Command, Options)
548 ),
549 '$command'(Command,Vars,Pos, Status).
550
551/** @pred user:expand_term( _T_,- _X_) is dynamic,multifile.
552
553 This user-defined predicate is called by YAP after
554 reading goals and clauses.
555
556 - _Module_:`expand_term(` _T_ , _X_) is called first on the
557 current source module _Module_ ; if i
558 - `user:expand_term(` _T_ , _X_ `)` is available on every module.
559
560 */
561
562/* General purpose predicates */
563
564'$head_and_body'((H:-B),H,B) :- '$head_and_body'.
565'$head_and_body'(H,H,true).
566
567
568gated_call(Setup, Goal, Catcher, Cleanup) :-
569 '$setup_call_catcher_cleanup'(Setup),
570 '$gated_call'( true , Goal, Catcher, Cleanup) .
571
572'$gated_call'( All , Goal, Catcher, Cleanup) :-
573 Task0 = cleanup( All, Catcher, Cleanup, Tag, true, CP0),
574 TaskF = cleanup( All, Catcher, Cleanup, Tag, false, CP0),
575 '$tag_cleanup'(CP0, Task0),
576 '$execute'( Goal ),
577 '$cleanup_on_exit'(CP0, TaskF).
578
579
580%
581% split head and body, generate an error if body is unbound.
582%
583'$check_head_and_body'(C,M,H,B,_P) :-
584 '$yap_strip_module'(C,M1,(MH:-B0)),
585 '$yap_strip_module',
586 '$yap_strip_module'(M1:MH,M,H),
587 ( M == M1 -> B = B0 ; B = M1:B0),
588 must_be_callable(M:H).
589
590'$check_head_and_body'(MH, M, H, true, _P) :-
591 '$yap_strip_module'(MH,M,H),
592 must_be_callable(M:H ).
593% term expansion
594%
595% return two arguments: Expanded0 is the term after "USER" expansion.
596% Expanded is the final expanded term.
597%
598'$precompile_term'(Term, ExpandedUser, Expanded) :-
599 %format('[ ~w~n',[Term]),
600 '$expand_clause'(Term, ExpandedUser, ExpandedI),
601 '$expand_clause',
602 %format(' -> ~w~n',[Expanded0]),
603 (
604 current_prolog_flag(strict_iso, true) /* strict_iso on */
605 ->
606 Expanded = ExpandedI,
607 '$check_iso_strict_clause'(ExpandedUser)
608 ;
609 '$expand_array_accesses_in_term'(ExpandedI,Expanded)
610 -> '$expand_array_accesses_in_term'
611 ;
612 Expanded = ExpandedI
613 ).
614'$precompile_term'(Term, Term, Term).
615
616'$expand_clause'(InputCl, C1, CO) :-
617 source_module(SM),
618 '$expand_a_clause'( InputCl, SM, C1, CO),
619 '$expand_a_clause'.
620'$expand_clause'(Cl, Cl, Cl).
621
622/** @pred expand_term( _T_,- _X_)
623
624This predicate is used by YAP for preprocessing each top level
625term read when consulting a file and before asserting or executing it.
626It rewrites a term _T_ to a term _X_ according to the following
627rules: first try term_expansion/2 in the current module, and then try to use the user defined predicate user:term_expansion/2`. If this call fails then the translating process
628for DCG rules is applied, together with the arithmetic optimizer
629whenever the compilation of arithmetic expressions is in progress.
630
631
632*/
633expand_term(Term,Expanded) :-
634 (
635 '$do_term_expansion'(Term,TermI)
636 ->
637 '$do_term_expansion'
638 ;
639 Term=TermI
640 ),
641 '$expand_term_grammar'(TermI,Expanded).
642
643
644%
645% Grammar Rules expansion
646%
647'$expand_term_grammar'((A-->B), C) :-
648 '$expand_term_grammar':'$translate_rule'((A-->B),C), '$translate_rule'.
649'$expand_term_grammar'(A, A).
650
651%
652% Arithmetic expansion
653%
654'$expand_array_accesses_in_term'(Expanded0,ExpandedF) :-
655 '$array_refs_compiled',
656 '$arrays':'$c_arrays'(Expanded0,ExpandedF), '$c_arrays'.
657'$expand_array_accesses_in_term'(Expanded,Expanded).
658
659
660%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
661% catch/throw implementation
662
663% at each catch point I need to know:
664% what is ball;
665% where was the previous catch
666/** @pred catch( : _Goal_,+ _Exception_,+ _Action_) is iso
667
668
669The goal `catch( _Goal_, _Exception_, _Action_)` tries to
670execute goal _Goal_. If during its execution, _Goal_ throws an
671exception _E'_ and this exception unifies with _Exception_, the
672exception is considered to be caught and _Action_ is executed. If
673the exception _E'_ does not unify with _Exception_, control
674again throws the exception.
675
676The top-level of YAP maintains a default exception handler that
677is responsible to capture uncaught exceptions.
678
679
680*/
681catch(MG,_,_) :-
683 '$execute'(MG),
685 (CP0 == CPF -> ! ; true ).
686catch(_,E,G) :-
687 '$drop_exception'(E0),
688 (
689 E = E0
690 ->
691 '$run_catch'(E0, E, G)
692 ;
693 throw(E0)
694 ).
695
696% makes sure we have an environment.
697'$true'.
698
699
700% system_catch is like catch, but it avoids the overhead of a full
701% meta-call by calling '$execute0' instead of $execute.
702% This way it
703% also avoids module preprocessing and goal_expansion
704%
705'$system_catch'(G, M, C, A) :-
706 % check current trail
707 catch(M:G,C,A).
708
709
710
711'$run_catch'(error(Event,_ ),_, G) :-
712 functor(Event, event, N),
713 N > 0,
714 arg(1, Event, Error),
715 arg,
716 '$run_catch'(Error, Error, G).
717'$run_catch'( abort,abort,_) :-
718 '$run_catch'.
719'$run_catch'(_E,_E,G) :-
720 is_callable(G),
721 is_callable,
722 '$execute'(G).
723'$run_catch'(error(A, B), error(A, B), _) :-
724 '$run_catch',
725 '$LoopError'(error(A, B), error).
726'$run_catch'(E,E,_).
727
728'$run_toplevel_hooks' :-
729 current_prolog_flag(break_level, 0 ),
730 recorded('$toplevel_hooks',H,_),
731 H \= recorded,
732 recorded,
733 ( call(user:H) -> call ; call).
734'$run_toplevel_hooks'.
735
736'$run_at_thread_start' :-
737 recorded('$thread_initialization',M:D,_),
738 '$execute'(M:D),
739 '$execute'.
740'$run_at_thread_start'.
741
742log_event( String, Args ) :-
743 format( atom( M ), String, Args),
744 log_event( M ).
745
746'$prompt' :-
747 current_prolog_flag(break_level, BreakLevel),
748 (
749 BreakLevel == 0
750 ->
751 LF = LD
752 ;
753 LF = ['[Break (level ', BreakLevel, ')] '|LD]
754 ),
755 (
756 current_prolog_flag(debug,true),
757 '$get_debugger_state'(trace, on)
758 ->
759 LD = ['[trace] '|L]
760 ;
761 current_prolog_flag(debug,true)
762 ->
763 LD = ['[debug] '|L]
764 ;
765
766 ),
767 yap_flag(toplevel_prompt, P),
768 L = [P],
769 atomic_concat(L, PF),
770 prompt1(PF),
771 prompt(_,' | '),
772 '$ensure_prompting'.
773
774'$loop'(Stream,Status) :-
775 '$system_catch'(
776 '__$loop_'(Stream,Status),
777 prolog,
778 Error,
779 '$Error'(Error)).
780
781
782/**
783@} @}
784*/
785
abolish(+ PredSpec)
catch( : Goal,+ Exception,+ Action)
expand_term( T,- X)
is_callable( ?_Goal_ )
module(+M)
must_be_callable( ?_Goal_ )
prompt1(+ _A__)
prompt(- A,+ B)
read_clause( +Stream, -Clause, ?Opts)
source_module(-Mod)
throw(+ Ball)
yap_flag( ?Param, ?Value)
get_code(+ S,- C)
skip(+ S,- C)
nb_setval(+ Name,+ Value)
erase(+ R)
eraseall(+ K)
recordz(+ K, T,- R)
call( 0:P )
halt(+ I)
once( 0:G)
current_prolog_flag(? Flag,- Value)
set_prolog_flag(+ Flag,+ Value)
print_message(+ Severity, +Term)
get_value(+ A,- V)
set_value(+ A,+ C)
arg(+ N,+ T, A)
current_choice_point( -CP )
db_reference( T)
functor( T, F, N)
number( T)
var( T)