View source with raw comments or as raw
    1/*  Part of SWISH
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2015-2019, VU University Amsterdam
    7			      CWI, Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(swish_trace,
   37	  [ '$swish wrapper'/2		% :Goal, ?ContextVars
   38	  ]).   39:- use_module(library(debug)).   40:- use_module(library(prolog_stack)).   41:- use_module(library(settings)).   42:- use_module(library(pengines)).   43:- use_module(library(apply)).   44:- use_module(library(lists)).   45:- use_module(library(option)).   46:- use_module(library(solution_sequences)).   47:- use_module(library(edinburgh), [debug/0]).   48:- use_module(library(pengines_io), [pengine_io_predicate/1]).   49:- use_module(library(sandbox), []).   50:- use_module(library(prolog_clause)).   51:- use_module(library(prolog_breakpoints)).   52:- use_module(library(http/term_html)).   53:- use_module(library(http/html_write)).   54:- if(exists_source(library(wfs))).   55:- use_module(library(wfs)).   56:- endif.   57
   58:- use_module(storage).   59:- use_module(config).   60
   61:- if(current_setting(swish:debug_info)).   62:- set_setting(swish:debug_info, true).   63:- endif.   64
   65:- set_prolog_flag(generate_debug_info, false).   66
   67:- meta_predicate
   68	'$swish wrapper'(0, -).

Allow tracing pengine execution under SWISH. */

   75:- multifile
   76	user:prolog_trace_interception/4,
   77	user:message_hook/3.   78
   79user:message_hook(trace_mode(_), _, _) :-
   80	pengine_self(_), !.
 trace_pengines
If true, trace in the browser. If false, use the default tracer. This allows for debugging pengine issues using the graphical tracer from the Prolog environment using:
?- retractall(swish_trace:trace_pengines).
?- tspy(<some predicate>).
   91:- dynamic
   92	trace_pengines/0.   93
   94trace_pengines.
   95
   96user:prolog_trace_interception(Port, Frame, CHP, Action) :-
   97	trace_pengines,
   98	State = state(0),
   99	(   catch(trace_interception(Port, Frame, CHP, Action), E, true),
  100	    (   var(E)
  101	    ->  nb_setarg(1, State, Action)
  102	    ;   abort			% tracer ignores non-abort exceptions.
  103	    ),
  104	    fail
  105	;   arg(1, State, Action)
  106	).
  107
  108trace_interception(Port, Frame, _CHP, Action) :-
  109	pengine_self(Pengine),
  110	prolog_frame_attribute(Frame, predicate_indicator, PI),
  111	debug(trace, 'HOOK: ~p ~p', [Port, PI]),
  112	pengine_property(Pengine, module(Module)),
  113	wrapper_frame(Frame, WrapperFrame),
  114	debug(trace, 'Me: ~p, wrapper: ~p', [Frame, WrapperFrame]),
  115	prolog_frame_attribute(WrapperFrame, level, WrapperDepth),
  116	prolog_frame_attribute(Frame, goal, Goal0),
  117	prolog_frame_attribute(Frame, level, Depth0),
  118	Depth is Depth0 - WrapperDepth - 1,
  119	unqualify(Goal0, Module, Goal),
  120	debug(trace, '[~d] ~w: Goal ~p', [Depth0, Port, Goal]),
  121	term_html(Goal, GoalString),
  122	functor(Port, PortName, _),
  123	Prompt0 = _{type:    trace,
  124		    port:    PortName,
  125		    depth:   Depth,
  126		    goal:    GoalString,
  127		    pengine: Pengine
  128		   },
  129	add_context(Port, Frame, Prompt0, Prompt1),
  130	add_source(Port, Frame, Prompt1, Prompt),
  131	pengine_input(Prompt, Reply),
  132	trace_action(Reply, Port, Frame, Action), !,
  133	debug(trace, 'Action: ~p --> ~p', [Reply, Action]).
  134trace_interception(Port, Frame0, _CHP, nodebug) :-
  135	pengine_self(_),
  136	prolog_frame_attribute(Frame0, goal, Goal),
  137	prolog_frame_attribute(Frame0, level, Depth),
  138	debug(trace, '[~d] ~w: Goal ~p --> NODEBUG', [Depth, Port, Goal]).
  139
  140trace_action(continue, _Port, Frame, continue) :-
  141	pengine_self(Me),
  142	prolog_frame_attribute(Frame, predicate_indicator, Me:Name/Arity),
  143	functor(Head, Name, Arity),
  144	\+ pengine_io_predicate(Head), !,
  145	prolog_skip_level(_, very_deep),
  146        debug(trace, '~p', [Me:Name/Arity]).
  147trace_action(continue, Port, _, skip) :-
  148	box_enter(Port), !.
  149trace_action(continue, _, _, continue) :-
  150	prolog_skip_level(_, very_deep).
  151trace_action(nodebug,  _, _, nodebug).
  152trace_action(skip,     _, _, skip).
  153trace_action(retry,    _, _, retry).
  154trace_action(up   ,    _, _, up).
  155trace_action(abort,    _, _, abort).
  156trace_action(nodebug(Breakpoints), _, _, Action) :-
  157	catch(update_breakpoints(Breakpoints), E,
  158	      print_message(warning, E)),
  159	(   Breakpoints == []
  160	->  Action = nodebug
  161	;   Action = continue,
  162	    notrace
  163	).
  164
  165box_enter(call).
  166box_enter(redo(_)).
  167
  168wrapper_frame(Frame0, Frame) :-
  169	parent_frame(Frame0, Frame),
  170	prolog_frame_attribute(Frame, predicate_indicator, PI),
  171	debug(trace, 'Parent: ~p', [PI]),
  172	(   PI == swish_call/1
  173	->  true
  174	;   PI == swish_trace:swish_call/1
  175	), !.
  176
  177parent_frame(Frame, Frame).
  178parent_frame(Frame, Parent) :-
  179	prolog_frame_attribute(Frame, parent, Parent0),
  180	parent_frame(Parent0, Parent).
  181
  182unqualify(M:G, M, G) :- !.
  183unqualify(system:G, _, G) :- !.
  184unqualify(user:G, _, G) :- !.
  185unqualify(G, _, G).
  186
  187term_html(Term, HTMlString) :-
  188	pengine_self(Pengine),
  189	pengine_property(Pengine, module(Module)),
  190	phrase(html(\term(Term,
  191			  [ module(Module),
  192			    quoted(true)
  193			  ])), Tokens),
  194	with_output_to(string(HTMlString), print_html(Tokens)).
 add_context(+Port, +Frame, +Prompt0, -Prompt) is det
Add additional information about the context to the debug prompt.
  201add_context(exception(Exception0), _Frame, Prompt0, Prompt) :-
  202	strip_stack(Exception0, Exception),
  203	message_to_string(Exception, Msg), !,
  204	debug(trace, 'Msg = ~s', [Msg]),
  205	(   term_html(Exception, String)
  206	->  Ex = json{term_html:String, message:Msg}
  207	;   Ex = json{message:Msg}
  208	),
  209	Prompt = Prompt0.put(exception, Ex).
  210add_context(_, _, Prompt, Prompt).
  211
  212strip_stack(error(Error, context(prolog_stack(S), Msg)),
  213	    error(Error, context(_, Msg))) :-
  214	nonvar(S).
  215strip_stack(Error, Error).
 $swish wrapper(:Goal, ?ContextVars)
Wrap a SWISH goal in '$swish wrapper'. This has two advantages: we can detect that the tracer is operating on a SWISH goal by inspecting the stack and we can save/restore the debug state to deal with debugging next solutions.

ContextVars is a list of variables that have a reserved name. The hooks pre_context/3 and post_context/3 can be used to give these variables a value extracted from the environment. This allows passing more information than just the query answers.

The binding _residuals = '$residuals'(Residuals) is added to the residual goals by pengines:event_to_json/3 from pengines_io.pl.

  233:- meta_predicate swish_call(0).  234
  235:- if(\+current_predicate(call_delays/2)).  236:- meta_predicate
  237	call_delays(0, :),
  238	delays_residual_program(:, :).  239
  240call_delays(Goal, _:true) :-
  241	call(Goal).
  242
  243delays_residual_program(_, _:[]).
  244:- endif.  245
  246'$swish wrapper'(Goal, Extra) :-
  247	(   nb_current('$variable_names', Bindings)
  248	->  true
  249	;   Bindings = []
  250	),
  251	debug(projection, 'Pre-context-pre ~p, extra=~p', [Bindings, Extra]),
  252	maplist(call_pre_context(Goal, Bindings), Extra),
  253	debug(projection, 'Pre-context-post ~p, extra=~p', [Bindings, Extra]),
  254	call_delays(catch_with_backtrace(swish_call(Goal),
  255					 E, throw_backtrace(E)), Delays),
  256	deterministic(Det),
  257	(   tracing,
  258	    Det == false
  259	->  (   notrace,
  260	        debug(trace, 'Saved tracer', [])
  261	    ;	debug(trace, 'Restoring tracer', []),
  262	        trace,
  263		fail
  264	    )
  265	;   notrace
  266	),
  267	call_post_context(_{goal:Goal, bindings:Bindings,
  268			    delays:Delays, context:Extra}),
  269	maplist(call_post_context(Goal, Bindings, Delays), Extra).
  270
  271throw_backtrace(error(Formal, context(prolog_stack(Stack0), Msg))) :-
  272	append(Stack1, [Guard|_], Stack0),
  273	is_guard(Guard),
  274	!,
  275	last(Stack1, Frame),
  276	arg(1, Frame, Level),
  277	maplist(re_level(Level), Stack1, Stack),
  278	throw(error(Formal, context(prolog_stack(Stack), Msg))).
  279throw_backtrace(E) :-
  280	throw(E).
  281
  282re_level(Sub,
  283	 frame(Level0, Clause, Goal),
  284	 frame(Level, Clause, Goal)) :-
  285	Level is 1 + Level0 - Sub.
  286
  287is_guard(frame(_Level, _Clause, swish_trace:swish_call(_))).
  288
  289swish_call(Goal) :-
  290	Goal,
  291	no_lco.
  292
  293no_lco.
  294
  295:- '$hide'(swish_call/1).  296:- '$hide'(no_lco/0).
 pre_context(Name, Goal, Var) is semidet
 post_context(Name, Goal, Var) is semidet
Multifile hooks to extract additional information from the Pengine, either just before Goal is started or after an answer was produced. Extracting the information is triggered by introducing a variable with a reserved name.
  306:- multifile
  307	pre_context/3,
  308	post_context/1,
  309	post_context/3,
  310	post_context/4.  311
  312call_pre_context(Goal, Bindings, Var) :-
  313	binding(Bindings, Var, Name),
  314	pre_context(Name, Goal, Var), !.
  315call_pre_context(_, _, _).
 call_post_context(+Dict)
  319call_post_context(Dict) :-
  320	post_context(Dict), !.
  321call_post_context(_).
 call_post_context(+Goal, +Bindings, +Delays, +Var)
Hook to allow filling Var from the context. I.e., there is a binding Name=Var in Bindings that gives us the name of what is expected in Var.
  329call_post_context(Goal, Bindings, Delays, Var) :-
  330	binding(Bindings, Var, Name),
  331	post_context(Name, Goal, Delays, Var), !.
  332call_post_context(_, _, _, _).
  333
  334post_context(Name, Goal, _Delays, Extra) :-
  335	post_context(Name, Goal, Extra), !.
  336post_context(Name, M:_Goal, _, '$residuals'(Residuals)) :-
  337	swish_config(residuals_var, Name), !,
  338	residuals(M, Residuals).
  339post_context(Name, M:_Goal, Delays,
  340	     '$wfs_residual_program'(TheDelays, Program)) :-
  341	Delays \== true,
  342	swish_config(wfs_residual_program_var, Name), !,
  343	(   current_prolog_flag(toplevel_list_wfs_residual_program, true)
  344	->  delays_residual_program(Delays, M:Program),
  345	    TheDelays = Delays
  346	;   TheDelays = undefined,
  347	    Program = []
  348	).
  349
  350binding([Name=Var|_], V, Name) :-
  351	Var == V, !.
  352binding([_|Bindings], V, Name) :-
  353	binding(Bindings, V, Name).
 residuals(+PengineModule, -Goals:list(callable)) is det
Find residual goals that are not bound to the projection variables. We must do so while we are in the Pengine as the goals typically live in global variables that are not visible when formulating the answer from the projection variables as done in library(pengines_io).
  364residuals(TypeIn, Goals) :-
  365	phrase(prolog:residual_goals, Goals0),
  366	maplist(unqualify_residual(TypeIn), Goals0, Goals).
  367
  368unqualify_residual(M, M:G, G) :- !.
  369unqualify_residual(T, M:G, G) :-
  370	predicate_property(T:G, imported_from(M)), !.
  371unqualify_residual(_, G, G).
  372
  373
  374		 /*******************************
  375		 *	  SOURCE LOCATION	*
  376		 *******************************/
  377
  378add_source(Port, Frame, Prompt0, Prompt) :-
  379	debug(trace(line), 'Add source?', []),
  380	source_location(Frame, Port, Location), !,
  381	Prompt = Prompt0.put(source, Location),
  382	debug(trace(line), 'Source ~p ~p: ~p', [Port, Frame, Location]).
  383add_source(_, _, Prompt, Prompt).
 source_location(+Frame, +Port, -Location) is semidet
Determine the appropriate location to show for Frame at Port.
  1. If we have a PC (integer), we have a concrete clause-location, so use it if it is in the current file.
  2. If we have a port, but the parent is not associated with our file, use it. This ensures that the initial query is shown in the source window.
  395source_location(Frame, Port, Location) :-
  396	parent_frame(Frame, Port, _Steps, ShowFrame, PC),
  397	(   clause_position(PC)
  398	->  true			% real PC
  399	;   prolog_frame_attribute(ShowFrame, parent, Parent),
  400	    frame_file(Parent, ParentFile),
  401	    \+ pengine_file(ParentFile)
  402	),
  403	(   debugging(trace(file))
  404	->  prolog_frame_attribute(ShowFrame, level, Level),
  405	    prolog_frame_attribute(ShowFrame, predicate_indicator, PI),
  406	    debug(trace(file), '\t[~d]: ~p', [Level, PI])
  407	;   true
  408	),
  409	frame_file(ShowFrame, File),
  410	pengine_file(File), !,
  411	source_position(ShowFrame, PC, Location).
 parent_frame(+FrameIn, +PCOrPortIn, -Steps, -FrameOut, -PCOrPortOut) is nondet
True when FrameOut/PCOrPortOut is a parent environment of FrameIn/PCOrPortIn. Backtracking yields higher frames.
  419parent_frame(Frame0, Port0, Steps, Frame, Port) :-
  420	parent_frame(Frame0, Port0, 0, Steps, Frame, Port).
  421
  422parent_frame(Frame, Port, Steps, Steps, Frame, Port).
  423parent_frame(Frame, _Port, Steps0, Steps, Parent, PC) :-
  424	direct_parent_frame(Frame, DirectParent, ParentPC),
  425	Steps1 is Steps0+1,
  426	parent_frame(DirectParent, ParentPC, Steps1, Steps, Parent, PC).
  427
  428direct_parent_frame(Frame, Parent, PC) :-
  429	prolog_frame_attribute(Frame, parent, Parent),
  430	prolog_frame_attribute(Frame, pc, PC).
 frame_file(+Frame, -File) is semidet
True when Frame is associated with a predicate that is defined in File.
  438frame_file(Frame, File) :-
  439	prolog_frame_attribute(Frame, clause, ClauseRef), !,
  440	(   clause_property(ClauseRef, predicate(system:'<meta-call>'/1))
  441	->  prolog_frame_attribute(Frame, parent, Parent),
  442	    frame_file(Parent, File)
  443	;   clause_property(ClauseRef, file(File))
  444	).
  445frame_file(Frame, File) :-
  446	prolog_frame_attribute(Frame, goal, Goal),
  447	qualify(Goal, QGoal),
  448	\+ predicate_property(QGoal, foreign),
  449	clause(QGoal, _Body, ClauseRef), !,
  450	clause_property(ClauseRef, file(File)).
 pengine_file(+File) is semidet
True if File is a Pengine controlled file. This is currently the main file (pengine://) and (swish://) for included files.
  457pengine_file(File) :-
  458	sub_atom(File, 0, _, _, 'pengine://'), !.
  459pengine_file(File) :-
  460	sub_atom(File, 0, _, _, 'swish://').
 clause_position(+PC) is semidet
True if the position can be related to a clause.
  466clause_position(PC) :- integer(PC), !.
  467clause_position(exit).
  468clause_position(unify).
  469clause_position(choice(_)).
 subgoal_position(+Clause, +PortOrPC, -File, -CharA, -CharZ) is semidet
Character range CharA..CharZ in File is the location to highlight for the given clause at the given location.
  477subgoal_position(ClauseRef, PortOrPC, _, _, _) :-
  478	debugging(trace(save_pc)),
  479	debug(trace(save_pc), 'Position for ~p at ~p', [ClauseRef, PortOrPC]),
  480	asserta(subgoal_position(ClauseRef, PortOrPC)),
  481	fail.
  482subgoal_position(ClauseRef, unify, File, CharA, CharZ) :- !,
  483	clause_info(ClauseRef, File, TPos, _),
  484	head_pos(ClauseRef, TPos, PosTerm),
  485	nonvar(PosTerm),
  486	arg(1, PosTerm, CharA),
  487	arg(2, PosTerm, CharZ).
  488subgoal_position(ClauseRef, choice(CHP), File, CharA, CharZ) :- !,
  489	(   prolog_choice_attribute(CHP, type, jump),
  490	    prolog_choice_attribute(CHP, pc, To)
  491	->  debug(gtrace(position), 'Term-position: choice-jump to ~w', [To]),
  492	    subgoal_position(ClauseRef, To, File, CharA, CharZ)
  493	;   clause_end(ClauseRef, File, CharA, CharZ)
  494	).
  495subgoal_position(ClauseRef, Port, File, CharA, CharZ) :-
  496	end_port(Port), !,
  497	clause_end(ClauseRef, File, CharA, CharZ).
  498subgoal_position(ClauseRef, PC, File, CharA, CharZ) :-
  499	debug(trace(source), 'In clause ~p at ~p', [ClauseRef, PC]),
  500	clause_info(ClauseRef, File, TPos, _),
  501	(   '$clause_term_position'(ClauseRef, PC, List)
  502	->  debug(trace(source), 'Term-position: for ref=~w at PC=~w: ~w',
  503		  [ClauseRef, PC, List]),
  504	    (   find_subgoal(List, TPos, PosTerm)
  505	    ->  true
  506	    ;   PosTerm = TPos,
  507		debug(trace(source),
  508		      'Clause source-info could not be parsed', []),
  509		fail
  510	    ),
  511	    nonvar(PosTerm),
  512	    arg(1, PosTerm, CharA),
  513	    arg(2, PosTerm, CharZ)
  514	;   debug(trace(source),
  515		  'No clause-term-position for ref=~p at PC=~p',
  516		  [ClauseRef, PC]),
  517	    fail
  518	).
  519
  520end_port(exit).
  521end_port(fail).
  522end_port(exception).
  523
  524clause_end(ClauseRef, File, CharA, CharZ) :-
  525	clause_info(ClauseRef, File, TPos, _),
  526	nonvar(TPos),
  527	arg(2, TPos, CharA),
  528	CharZ is CharA + 1.
  529
  530head_pos(Ref, Pos, HPos) :-
  531	clause_property(Ref, fact), !,
  532	HPos = Pos.
  533head_pos(_, term_position(_, _, _, _, [HPos,_]), HPos).
  534
  535%	warning, ((a,b),c)) --> compiled to (a, (b, c))!!!  We try to correct
  536%	that in clause.pl.  This is work in progress.
  537
  538find_subgoal([A|T], term_position(_, _, _, _, PosL), SPos) :-
  539	nth1(A, PosL, Pos), !,
  540	find_subgoal(T, Pos, SPos).
  541find_subgoal([1|T], brace_term_position(_,_,Pos), SPos) :- !,
  542	find_subgoal(T, Pos, SPos).
  543find_subgoal(_, Pos, Pos).
  544
  545
  546%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  547% Extracted from show_source/2 from library(trace/trace)
 source_position(Frame, PCOrPort, -Position)
Get the source location for Frame at PCOrPort. Position is a dict.
  554source_position(Frame, PC, _{file:File, from:CharA, to:CharZ}) :-
  555	debug(trace(pos), '~p', [source_position(Frame, PC, _)]),
  556	clause_position(PC),
  557	prolog_frame_attribute(Frame, clause, ClauseRef), !,
  558	subgoal_position(ClauseRef, PC, File, CharA, CharZ).
  559source_position(Frame, _PC, Position) :-
  560	prolog_frame_attribute(Frame, goal, Goal),
  561	qualify(Goal, QGoal),
  562	\+ predicate_property(QGoal, foreign),
  563	(   clause(QGoal, _Body, ClauseRef)
  564	->  subgoal_position(ClauseRef, unify, File, CharA, CharZ),
  565	    Position = _{file:File, from:CharA, to:CharZ}
  566	;   functor(Goal, Functor, Arity),
  567	    functor(GoalTemplate, Functor, Arity),
  568	    qualify(GoalTemplate, QGoalTemplate),
  569	    clause(QGoalTemplate, _TBody, ClauseRef)
  570	->  subgoal_position(ClauseRef, unify, File, CharA, CharZ),
  571	    Position = _{file:File, from:CharA, to:CharZ}
  572	;   find_source(QGoal, File, Line),
  573	    debug(trace(source), 'At ~w:~d', [File, Line]),
  574	    Position = _{file:File, line:Line}
  575	).
  576
  577qualify(Goal, Goal) :-
  578	functor(Goal, :, 2), !.
  579qualify(Goal, user:Goal).
  580
  581find_source(Predicate, File, Line) :-
  582	predicate_property(Predicate, file(File)),
  583	predicate_property(Predicate, line_count(Line)), !.
 pengines:prepare_goal(+GoalIn, -GoalOut, +Options) is semidet
Handle the breakpoints(List) option to set breakpoints prior to execution of the query. If breakpoints are present and enabled, the goal is executed in debug mode. List is a list, holding a dict for each source that has breakpoints. The dict contains these keys:
  598:- multifile pengines:prepare_goal/3.  599
  600pengines:prepare_goal(Goal0, Goal, Options) :-
  601	forall(set_screen_property(Options), true),
  602	option(breakpoints(Breakpoints), Options),
  603	Breakpoints \== [],
  604	pengine_self(Pengine),
  605	pengine_property(Pengine, source(File, Text)),
  606	maplist(set_file_breakpoints(Pengine, File, Text), Breakpoints),
  607	Goal = (debug, Goal0).
 swish:tty_size(-Rows, -Cols)
Emulate obtaining the screen size. Note that the reported number of columns is the height of the container as the height of answer pane itself is determined by the content.
  615set_screen_property(Options) :-
  616	pengine_self(Pengine),
  617	screen_property_decl(Property),
  618	option(Property, Options),
  619	assertz(Pengine:screen_property(Property)).
  620
  621screen_property_decl(height(_)).
  622screen_property_decl(width(_)).
  623screen_property_decl(rows(_)).
  624screen_property_decl(cols(_)).
  625screen_property_decl(tabled(_)).
 swish:tty_size(-Rows, -Cols) is det
Find the size of the output window. This is only registered when running ask. Notably during compilation it is not known. We provided dummy values to avoid failing.
  633swish:tty_size(Rows, Cols) :-
  634	pengine_self(Pengine),
  635	current_predicate(Pengine:screen_property/1), !,
  636	Pengine:screen_property(rows(Rows)),
  637	Pengine:screen_property(cols(Cols)).
  638swish:tty_size(24, 80).
 set_file_breakpoints(+Pengine, +File, +Text, +Dict)
Set breakpoints for included files.
  644set_file_breakpoints(_Pengine, PFile, Text, Dict) :-
  645	debug(trace(break), 'Set breakpoints at ~p', [Dict]),
  646	_{file:FileS, breakpoints:List} :< Dict,
  647	atom_string(File, FileS),
  648	(   PFile == File
  649	->  debug(trace(break), 'Pengine main source', []),
  650	    maplist(set_pengine_breakpoint(File, File, Text), List)
  651	;   source_file_property(PFile, includes(File, _Time)),
  652	    atom_concat('swish://', StoreFile, File)
  653	->  debug(trace(break), 'Pengine included source ~p', [StoreFile]),
  654	    storage_file(StoreFile, IncludedText, _Meta),
  655	    maplist(set_pengine_breakpoint(PFile, File, IncludedText), List)
  656	;   debug(trace(break), 'Not in included source', [])
  657	).
 set_pengine_breakpoint(+Pengine, +File, +Text, +Dict)
Set breakpoints on the main Pengine source
  663set_pengine_breakpoint(Owner, File, Text, Line) :-
  664	debug(trace(break), 'Try break at ~q:~d', [File, Line]),
  665	line_start(Line, Text, Char),
  666	(   set_breakpoint(Owner, File, Line, Char, _0Break)
  667	->  !, debug(trace(break), 'Created breakpoint ~p', [_0Break])
  668	;   print_message(warning, breakpoint(failed(File, Line, 0)))
  669	).
  670
  671line_start(1, _, 0) :- !.
  672line_start(N, Text, Start) :-
  673	N0 is N - 2,
  674	offset(N0, sub_string(Text, Start, _, _, '\n')), !.
 update_breakpoints(+Breakpoints)
Update the active breakpoint by comparing with the set of currently active breakpoints.
  681update_breakpoints(Breakpoints) :-
  682	breakpoint_by_file(Breakpoints, NewBPS),
  683	pengine_self(Pengine),
  684	pengine_property(Pengine, source(PFile, Text)),
  685	current_pengine_source_breakpoints(PFile, ByFile),
  686	forall(( member(File-FBPS, ByFile),
  687		 member(Id-Line, FBPS),
  688		 \+ ( member(File-NFBPS, NewBPS),
  689		      member(Line, NFBPS))),
  690	       delete_breakpoint(Id)),
  691	forall(( member(File-NFBPS, NewBPS),
  692		 member(Line, NFBPS),
  693		 \+ ( member(File-FBPS, ByFile),
  694		      member(_-Line, FBPS))),
  695	       add_breakpoint(PFile, File, Text, Line)).
  696
  697breakpoint_by_file(Breakpoints, NewBPS) :-
  698	maplist(bp_by_file, Breakpoints, NewBPS).
  699
  700bp_by_file(Dict, File-Lines) :-
  701	_{file:FileS, breakpoints:Lines} :< Dict,
  702	atom_string(File, FileS).
  703
  704add_breakpoint(PFile, PFile, Text, Line) :- !,
  705	set_pengine_breakpoint(PFile, PFile, Text, Line).
  706add_breakpoint(PFile, File, _Text, Line) :-
  707	atom_concat('swish://', Store, File), !,
  708	storage_file(Store, Text, _Meta),
  709	set_pengine_breakpoint(PFile, File, Text, Line).
  710add_breakpoint(_, _, _, _Line).			% not in our files.
 current_pengine_source_breakpoints(+PengineFile, -Pairs) is det
Find the currently set breakpoints for the Pengine with the given source file PengineFile. Pairs is a list File-BreakPoints, where BreakPoints is a list of breakpoint-ID - Line pairs.
  718current_pengine_source_breakpoints(PFile, ByFile) :-
  719	findall(Pair, current_pengine_breakpoint(PFile, Pair), Pairs0),
  720	keysort(Pairs0, Pairs),
  721	group_pairs_by_key(Pairs, ByFile).
  722
  723current_pengine_breakpoint(PFile, PFile-(Id-Line)) :-
  724	breakpoint_property(Id, file(PFile)),
  725	breakpoint_property(Id, line_count(Line)).
  726current_pengine_breakpoint(PFile, File-(Id-Line)) :-
  727	source_file_property(PFile, includes(File, _Time)),
  728	breakpoint_property(Id, file(File)),
  729	breakpoint_property(Id, line_count(Line)).
 prolog_clause:open_source(+File, -Stream) is semidet
Open SWISH non-file sources.
  736:- multifile prolog_clause:open_source/2.  737
  738prolog_clause:open_source(File, Stream) :-
  739	sub_atom(File, 0, _, _, 'pengine://'), !,
  740	(   pengine_self(Pengine)
  741	->  true
  742	;   debugging(trace(_))
  743	),
  744	pengine_property(Pengine, source(File, Source)),
  745	open_string(Source, Stream).
  746prolog_clause:open_source(File, Stream) :-
  747	atom_concat('swish://', GittyFile, File), !,
  748	storage_file(GittyFile, Data, _Meta),
  749	open_string(Data, Stream).
  750
  751
  752		 /*******************************
  753		 *	 TRAP EXCEPTIONS	*
  754		 *******************************/
  755
  756:- dynamic
  757	user:prolog_exception_hook/4,
  758	installed/1.  759
  760:- volatile
  761	installed/1.  762
  763exception_hook(Ex, Ex, _Frame, Catcher) :-
  764	Catcher \== none,
  765	Catcher \== 'C',
  766	prolog_frame_attribute(Catcher, predicate_indicator, PI),
  767	debug(trace(exception), 'Ex: ~p, catcher: ~p', [Ex, PI]),
  768	PI == '$swish wrapper'/1,
  769	trace,
  770	fail.
 install_exception_hook
Make sure our handler is the first of the hook predicate.
  776install_exception_hook :-
  777	installed(Ref),
  778	(   nth_clause(_, I, Ref)
  779	->  I == 1, !			% Ok, we are the first
  780	;   retractall(installed(Ref)),
  781	    erase(Ref),			% Someone before us!
  782	    fail
  783	).
  784install_exception_hook :-
  785	asserta((user:prolog_exception_hook(Ex, Out, Frame, Catcher) :-
  786			exception_hook(Ex, Out, Frame, Catcher)), Ref),
  787	assert(installed(Ref)).
  788
  789:- initialization install_exception_hook.  790
  791
  792		 /*******************************
  793		 *	 ALLOW DEBUGGING	*
  794		 *******************************/
  795
  796:- multifile
  797	sandbox:safe_primitive/1,
  798	sandbox:safe_meta_predicate/1.  799
  800sandbox:safe_primitive(system:trace).
  801sandbox:safe_primitive(system:notrace).
  802sandbox:safe_primitive(system:tracing).
  803sandbox:safe_primitive(edinburgh:debug).
  804sandbox:safe_primitive(system:deterministic(_)).
  805sandbox:safe_primitive(swish_trace:residuals(_,_)).
  806sandbox:safe_primitive(swish:tty_size(_Rows, _Cols)).
  807
  808sandbox:safe_meta_predicate(swish_trace:'$swish wrapper'/2).
  809
  810
  811		 /*******************************
  812		 *	      MESSAGES		*
  813		 *******************************/
  814
  815:- multifile
  816	prolog:message/3.  817
  818prolog:message(breakpoint(failed(File, Line, _Char))) -->
  819	[ 'Failed to set breakpoint at ~w:~d'-[File,Line] ]