swish/commit

New renderers

authorJan Wielemaker
Fri Dec 23 14:45:31 2016 +0100
committerJan Wielemaker
Fri Dec 23 14:45:31 2016 +0100
commitf9641c8f7b207191514b048dc93a55d0dd752aa9
treed406096420cbc0e0cf4286c24c53c7adc68e52a9
parent9dda5684c60e479564fb2268c8fb2407472a8eb3
Diff style: patch stat
diff --git a/lib/swish/render/chess.pl b/lib/swish/render/chess.pl
new file mode 100644
index 0000000..0f1e0e0
--- /dev/null
+++ b/lib/swish/render/chess.pl
@@ -0,0 +1,127 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (c)  2014-2016, VU University Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_render_chess,
+	  [ term_rendering//3			% +Term, +Vars, +Options
+	  ]).
+:- use_module(library(http/html_write)).
+:- use_module('../render').
+
+:- register_renderer(chess, "Render chess board representations").
+
+/** <module> SWISH chessboard renderer
+
+Render chessboards. Currently only deals with the N-queens problem. This
+file is nevertheless called =chess.pl= because   it should be trivial to
+extend this to more general chess positions.
+
+The   styling   is    a    small     modification    of    [CSS3   Chess
+Board](http://designindevelopment.com/css/css3-chess-board/)
+*/
+
+%%	term_rendering(+Term, +Vars, +Options)//
+%
+%	Render an N-queens  problem.  This   renderer  assumes  that the
+%	solution is represented by a permutation   of a list of integers
+%	1..N, where the I-th integer describes   the column of the queen
+%	at row I.
+
+term_rendering(Term, _Vars, _Options) -->
+	{ is_nqueens(Term),
+	  length(Term, N),
+	  LineHeight is 200/N
+	},
+	html(div([ style('display:inline-block;'+
+			 'line-height:'+LineHeight+'px;'+
+			 'font-size:'+LineHeight+'px;'
+			),
+		   'data-render'('Chess board')
+		 ],
+		 [ table(class('chess-board'),
+			 \nqueens(Term, N)),
+		   \chess_style
+		 ])).
+
+is_nqueens(Term) :-
+	is_list(Term),
+	maplist(integer, Term),
+	length(Term, N),
+	numlist(1, N, All),
+	sort(Term, All).
+
+nqueens([], _) --> [].
+nqueens([H|T], N) -->
+	html(tr(\nrow(0, N, H))),
+	nqueens(T, N).
+
+nrow(N, N, _) --> !.
+nrow(I, N, At) -->
+	{ I2 is I+1 },
+	(   { I2 == At }
+	->  html(td(&('#9819')))
+	;   html(td([]))
+	),
+	nrow(I2, N, At).
+
+%%	chess_style//
+%
+%	@see http://designindevelopment.com/css/css3-chess-board/
+
+chess_style -->
+	html({|html||
+<style>
+.chess-board {
+  border:2px solid #333; width:200px; height:200px;
+}
+.chess-board td {
+  background:#fff;
+  background:-moz-linear-gradient(top, #fff, #eee);
+  background:-webkit-gradient(linear,0 0, 0 100%, from(#fff), to(#eee));
+  box-shadow:inset 0 0 0 1px #fff;
+  -moz-box-shadow:inset 0 0 0 1px #fff;
+  -webkit-box-shadow:inset 0 0 0 1px #fff;
+  text-align:center;
+  vertical-align:middle;
+}
+.chess-board tr:nth-child(odd) td:nth-child(even),
+.chess-board tr:nth-child(even) td:nth-child(odd) {
+  background:#ccc;
+  background:-moz-linear-gradient(top, #ccc, #eee);
+  background:-webkit-gradient(linear,0 0, 0 100%, from(#ccc), to(#eee));
+  box-shadow:inset 0 0 10px rgba(0,0,0,.4);
+  -moz-box-shadow:inset 0 0 10px rgba(0,0,0,.4);
+  -webkit-box-shadow:inset 0 0 10px rgba(0,0,0,.4);
+}
+</style>
+	     |}).
diff --git a/lib/swish/render/codes.pl b/lib/swish/render/codes.pl
new file mode 100644
index 0000000..3bc7de9
--- /dev/null
+++ b/lib/swish/render/codes.pl
@@ -0,0 +1,163 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (c)  2014, VU University Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_render_codes,
+	  [ term_rendering//3			% +Term, +Vars, +Options
+	  ]).
+:- use_module(library(option)).
+:- use_module(library(http/html_write)).
+:- use_module('../render').
+
+:- register_renderer(codes, "Render a list of character codes").
+
+/** <module> SWISH code-list renderer
+
+Render lists of character codes as a `string`
+*/
+
+%%	term_rendering(+Codes, +Vars, +Options)//
+%
+%	Renders  a  list  of  character  codes   as  a  string.  Options
+%	processed:
+%
+%	  - min_length(+Integer)
+%	  Codes must be a list of at least Integer length. Default is
+%	  `3`.
+%	  - ellipsis(+Integer)
+%	  Write list as `bla bla ... bla` if longer than Integer.
+%	  Default is 30.
+%	  - partial(+Boolean)
+%	  It `true` (default), allow a partial list (ending in a
+%	  variable).
+%	  - charset(+Charset)
+%	  Set of characters to accept.  Currently allows for
+%	    - ascii
+%	    Allow 32..126
+%	    - iso_latin_1
+%	    Allow 32..126 and 160..255
+
+term_rendering(Codes, _Vars, Options) -->
+	{ is_code_list(Codes, Len, Options)
+	},
+	(   { option(ellipsis(Ellipsis), Options, 30),
+	      Len > Ellipsis
+	    }
+	->  { First is Ellipsis - 5,
+	      Skip is Len - 5,
+	      skip_first(Skip, Codes, Rest),
+	      phrase(put_n_codes(First, Codes), PrefixCodes),
+	      phrase(put_codes(Rest), PostfixCodes),
+	      string_codes(Prefix, PrefixCodes),
+	      string_codes(Postfix, PostfixCodes)
+	    },
+	    html(span([ 'data-render'('Truncated list of codes as a string'),
+			class('render-code-list'),
+			title('Code list of length: '+Len)
+		      ],
+		      [ '`~s'-[Prefix],
+			span(class('render-ellipsis'), ...),
+			'~s`'-[Postfix]
+		      ]))
+	;   { phrase(put_codes(Codes), TextCodes),
+	      string_codes(String, TextCodes)
+	    },
+	    html(span([ 'data-render'('List of codes as a string'),
+			class('render-code-list')
+		      ],
+		  '`~s`'-String))
+	).
+
+skip_first(N, [_|T0], T) :-
+	succ(N2, N), !,
+	skip_first(N2, T0, T).
+skip_first(_, L, L).
+
+put_n_codes(N, [H|T]) -->
+	{ succ(N2, N) }, !,
+	emit_code(H),
+	put_n_codes(N2, T).
+put_n_codes(_, _) --> [].
+
+put_codes(Var) -->
+	{ var_or_numbered(Var) }, !,
+	dcg_format('|~p', [Var]).
+put_codes([]) --> [].
+put_codes([H|T]) -->
+	emit_code(H),
+	put_codes(T).
+
+emit_code(0'\b) --> !, "\\b".
+emit_code(0'\r) --> !, "\\r".
+emit_code(0'\n) --> !, "\\n".
+emit_code(0'\t) --> !, "\\t".
+emit_code(C)	--> [C].
+
+dcg_format(Fmt, Args, List, Tail) :-
+	format(codes(List, Tail), Fmt, Args).
+
+%%	is_code_list(+Codes, -Length, +Options) is semidet.
+
+is_code_list(Codes, Length, Options) :-
+	'$skip_list'(Length, Codes, Tail),
+	code_list_tail(Tail, Options),
+	option(min_length(MinLen), Options, 3),
+	Length >= MinLen,
+	option(charset(Charset), Options, ascii),
+	all_codes(Codes, Charset).
+
+code_list_tail([], _) :- !.
+code_list_tail(Var, Options) :-
+	var_or_numbered(Var),
+	option(partial(true), Options, true).
+
+var_or_numbered(Var) :-
+	var(Var), !.
+var_or_numbered('$VAR'(_)).
+
+all_codes(Var, _) :-
+	var_or_numbered(Var), !.
+all_codes([], _).
+all_codes([H|T], Charset) :-
+	integer(H),
+	is_code(H, Charset), !,
+	all_codes(T, Charset).
+
+is_code(9,  _).
+is_code(10, _).
+is_code(13, _).
+is_code(C, Charset) :-
+	charset_code(Charset, C).
+
+charset_code(ascii,       C) :- between(32,126,C).
+charset_code(iso_latin_1, C) :- between(32,126,C) ; between(160,255,C).
diff --git a/lib/swish/render/sudoku.pl b/lib/swish/render/sudoku.pl
new file mode 100644
index 0000000..2315709
--- /dev/null
+++ b/lib/swish/render/sudoku.pl
@@ -0,0 +1,143 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (c)  2014, VU University Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_render_sudoku,
+	  [ term_rendering//3			% +Term, +Vars, +Options
+	  ]).
+:- use_module(library(apply)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/term_html)).
+:- use_module('../render').
+
+:- register_renderer(sudoku, "Render a sudoku matrix").
+
+/** <module> SWISH Sudoku renderer
+
+Renders a term like below as a _sudoku matrix_
+
+  ==
+  [[_,_,_,_,_,_,_,_,_],
+   [_,_,_,_,_,3,_,8,5],
+   [_,_,1,_,2,_,_,_,_],
+   [_,_,_,5,_,7,_,_,_],
+   [_,_,4,_,_,_,1,_,_],
+   [_,9,_,_,_,_,_,_,_],
+   [5,_,_,_,_,_,_,7,3],
+   [_,_,2,_,1,_,_,_,_],
+   [_,_,_,_,4,_,_,_,9]]
+  ==
+*/
+
+%%	term_rendering(+Term, +Vars, +Options)//
+%
+%	Renders Term as a sudoku matrix. Term must be a list of 9 lists,
+%	each of which must have  9  elements   that  are  all either the
+%	integer 1..9 or unbound.
+
+term_rendering(Term, _Vars, _Options) -->
+	{ is_sudoku(Term)
+	}, !,
+	html(div([class(sudoku),
+		  'data-render'('Sudoku matrix')
+		 ],
+		 [\rows(Term, 1), \sudoku_style])).
+
+sudoku_style -->
+	html({|html||
+	      <style>
+div.sudoku { vertical-align: top;
+	     display:inline-block;
+	     border: 3px solid black;
+	     width: 220px;
+	     height: 220px;
+	     font-size: 0;
+	   }
+div.sudoku-row     { height: 11.11%; }
+div.sudoku-row.fat { border-bottom: 2px solid black;}
+div.sudoku-cell { width: 11.11%; height: 100%;
+		  font-size: 12px;
+		  font-weight: bold;
+		  display: inline-block;
+		  box-sizing: border-box;
+		  border: 1px solid #888;
+		  margin: 0px;
+		  text-align: center;
+		  vertical-align: middle;
+		}
+div.sudoku-cell.fat { border-right: 2px solid black;}
+	      </style>
+	     |}).
+
+rows([], _) --> [].
+rows([H|T], I) -->
+	{ I2 is I+1,
+	  (   (I == 3 ; I == 6)
+	  ->  Extra = [fat]
+	  ;   Extra = []
+	  )
+	},
+	html(div(class(['sudoku-row'|Extra]), \cells(H, 1))),
+	rows(T, I2).
+
+cells([], _) --> [].
+cells([H|T], I) -->
+	{ I2 is I+1,
+	  (   (I == 3 ; I == 6)
+	  ->  Extra = [fat]
+	  ;   Extra = []
+	  )
+	},
+	html(div(class(['sudoku-cell'|Extra]), \value(H))), cells(T, I2).
+
+value(H) --> { var(H) }, !.
+value(H) --> term(H, []).
+
+
+%%	is_sudoku(+Term) is semidet.
+%
+%	Type check for a term  to  be   a  representation  for  a Sudoku
+%	puzzle.
+
+is_sudoku(Term) :-
+	is_list(Term),
+	length(Term, 9),
+	maplist(is_row, Term).
+
+is_row(Row) :-
+	is_list(Row),
+	length(Row, 9),
+	maplist(is_cell, Row).
+
+is_cell(Var) :- var(Var).
+is_cell(I)   :- integer(I), between(1, 9, I).
diff --git a/lib/swish/render/svgtree.pl b/lib/swish/render/svgtree.pl
new file mode 100644
index 0000000..d87a2ab
--- /dev/null
+++ b/lib/swish/render/svgtree.pl
@@ -0,0 +1,211 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (c)  2014-2015, VU University Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_svgtree,
+	  [ term_rendering//3			% +Term, +Vars, +Options
+	  ]).
+:- use_module(library(option)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/term_html)).
+:- use_module(library(http/js_write)).
+:- use_module(library(http/http_wrapper)).
+:- use_module(library(apply)).
+:- use_module(library(lists)).
+:- use_module(library(sandbox)).
+:- use_module('../render').
+
+:- register_renderer(svgtree, "Render term as a tree").
+
+/** <module> SWISH SVG tree renderer
+
+Render a term as an SVG tree.   This  renderer is intended to illustrate
+the shape of terms or display a simple parse tree.
+
+This renderer is also an illustration of  using a JavaScript library and
+SVG inside rendered elements. Note  that   the  use  of RequireJS avoids
+loading the library multiple times as   well  as poluting the namespace.
+
+Note that while the  script  is   being  evaluated,  `$.ajaxScript` is a
+jQuery object pointing to the executing script. This is used to find the
+`span`  element  without  using  an  `id`    attribute.  Using  `id`  is
+undesirable as it is hard  to   guarantee  their uniqueness. However, we
+must find the desired  element  immediately   and  not  in the RequireJS
+callback, so we need to put it in   a variable and scope the whole thing
+in a function to avoid conflicts.  JavaScript is fun!
+*/
+
+%%	term_rendering(+Term, +Vars, +Options)//
+%
+%	Render a compound term as a tree.  Options processed:
+%
+%	  - list(Boolean)
+%	  If `false`, do not render lists.
+%	  - filter(:NodeFilter)
+%	  If present, use call(NodeFilter, Term, Label, Children)
+%	  to extract the label and children of a term.  Operates
+%	  on terms for which this call succeeds on the top node.
+%	  If the call fails on a child, the child is rendered as
+%	  a term.
+
+term_rendering(Term, _Vars, Options) -->
+	{ is_term_tree(Term, How, Options),
+	  call(How, Term, Dict)
+	},
+	html(div([ class('render-svg-tree'),
+		   'data-render'('Term as SVG tree')
+		 ],
+		 [ span([]),
+		   \js_script({|javascript(Dict)||
+(function() {
+  if ( $.ajaxScript ) {
+    var span = $.ajaxScript.parent().find("span")[0];
+
+    require(["render/svg-tree-drawer", "jquery"], function(svgtree) {
+      var tree = new TreeDrawer(span, Dict);
+      if ( !tree.filters.label ) {
+	tree.addFilter('label', function(label,node) {
+	  return typeof(label) == "object" ? $(label.html)[0] : label;
+	});
+      }
+      tree.draw();
+    });
+  }
+})();
+		  |})
+		 ])).
+
+%%	is_term_tree(+Term, -Closure, +Options) is semidet.
+%
+%	True when Term  is  a  Prolog   term  that  can  meaningfully be
+%	displayed as a tree. The  actual   rendering  is done by calling
+%	call(Closure, Term, JSON), where the  called closure must return
+%	a nested dict and each node contains:
+%
+%	  * label
+%	  The label to display.  This is either a string or a dict
+%	  containing html:HTMLString
+%	  * children
+%	  If present, this is a list of child nodes. If not, it is
+%	  a leaf node.
+
+is_term_tree(Term, filtered_tree(QFilter, Options1), Options) :-
+	option(filter(Filter), Options),
+	callable(Filter),
+	Filter \= _:_,
+	option(module(Module), Options),
+	QFilter = Module:Filter,
+	catch(safe_filter(QFilter), _, fail),
+	call(QFilter, Term, _Label, _Children), !,
+	browser_option(Options, Options1).
+is_term_tree(Term, compound_tree(Options1), Options) :-
+	compound(Term),
+	(   is_list(Term)
+	->  \+ option(list(false), Options)
+	;   true
+	), !,
+	browser_option(Options, Options1).
+
+:- public
+	compound_tree/3,
+	filtered_tree/4.
+
+%%	compound_tree(+Options, +Term, -JSON) is det.
+%
+%	Render Term as a tree, considering every   compound term to be a
+%	node.  Renders leafs using term//1.
+
+compound_tree(Options, Term, Tree) :-
+	compound(Term), Term \= '$VAR'(_), !,
+	Tree = json{label:Label, children:Children},
+	compound_name_arguments(Term, Functor, Args),
+	term_string(Functor, Label),
+	maplist(compound_tree(Options), Args, Children).
+compound_tree(Options, Term, json{label:Label}) :-
+	term_label(Term, Label, Options).
+
+%%	term_label(+Term, -Label, +Options) is det.
+%
+%	Create a label for a term.  If   we  can, we generate HTML using
+%	term//2, which is translated into   an  SVG `foreignObject`. The
+%	Trident engine used by IE does  not support foreignObject though
+%	:-(
+
+term_label(Term, String, Options) :-
+	option(engine(trident), Options), !,
+	term_string(Term, String, Options).
+term_label(Term, json{html:String}, Options) :-
+	phrase(term(Term, Options), Tokens),
+	with_output_to(string(String), print_html(Tokens)).
+
+%%	filtered_tree(:Filter, +Options, +Term, -JSON) is det.
+%
+%	Render a filtered tree.
+
+:- meta_predicate filtered_tree(3,+,+,-).
+
+filtered_tree(Filter, Options, Term, Tree) :-
+	nonvar(Term),
+	call(Filter, Term, LabelTerm, ChildNodes),
+	is_list(ChildNodes), !,
+	Tree = json{label:Label, children:Children},
+	term_label(LabelTerm, Label, Options),
+	maplist(filtered_tree(Filter, Options), ChildNodes, Children).
+filtered_tree(_, Options, Term, json{label:Label}) :-
+	term_label(Term, Label, Options).
+
+safe_filter(Module:Filter) :-
+	Filter =.. List0,
+	append(List0, [_, _, _], List),
+	Filter1 =.. List,
+	safe_goal(Module:Filter1).
+
+
+		 /*******************************
+		 *	      BROWSER		*
+		 *******************************/
+
+browser_option(Options0, Options) :-
+	is_trident, !,
+	Options = [engine(trident)|Options0].
+browser_option(Options, Options).
+
+%%	is_trident is semidet.
+%
+%	True if we know that the client is Trident-based (IE)
+
+is_trident :-
+	http_current_request(Request),
+	option(user_agent(Agent), Request),
+	sub_string(Agent, _, _, _, " Trident/"), !.
+
diff --git a/lib/swish/render/swish.pl b/lib/swish/render/swish.pl
new file mode 100644
index 0000000..a641a42
--- /dev/null
+++ b/lib/swish/render/swish.pl
@@ -0,0 +1,62 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (c)  2016, VU University Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_render_swish,
+	  [ term_rendering//3			% +Term, +Vars, +Options
+	  ]).
+:- use_module(library(http/html_write)).
+:- use_module('../render').
+:- use_module('../storage').
+
+:- register_renderer(swish, "Render references to SWISH objects").
+
+/** <module> SWISH renderer
+
+Render references to SWISH objects
+*/
+
+%%	term_rendering(+File, +Vars, +Options)//
+%
+%	Renders a link to a SWISH file
+
+term_rendering(File, _Vars, _Options) -->
+	{ atom(File),
+	  file_name_extension(_, Ext, File),
+	  swish_extension(Ext),
+	  storage_file(File)
+	},
+	html(a([class(store),href('/p/'+File)], File)).
+
+swish_extension(pl).
+swish_extension(swinb).