34
35:- module(swish_svgtree,
36 [ term_rendering//3 37 ]). 38:- use_module(library(option)). 39:- use_module(library(http/html_write)). 40:- use_module(library(http/term_html)). 41:- use_module(library(http/js_write)). 42:- use_module(library(http/http_wrapper)). 43:- use_module(library(apply)). 44:- use_module(library(lists)). 45:- use_module(library(sandbox)). 46:- use_module('../render'). 47
48:- register_renderer(svgtree, "Render term as a tree").
81term_rendering(Term, _Vars, Options) -->
82 { is_term_tree(Term, How, Options),
83 call(How, Term, Dict)
84 },
85 html(div([ class('render-svg-tree'),
86 'data-render'('Term as SVG tree')
87 ],
88 [ span([]),
89 \js_script({|javascript(Dict)||
90(function() {
91 if ( $.ajaxScript ) {
92 var span = $.ajaxScript.parent().find("span")[0];
93
94 require(["render/svg-tree-drawer", "jquery"], function(svgtree) {
95 var tree = new TreeDrawer(span, Dict);
96 if ( !tree.filters.label ) {
97 tree.addFilter('label', function(label,node) {
98 return typeof(label) == "object" ? $(label.html)[0] : label;
99 });
100 }
101 tree.draw();
102 });
103 }
104})();
105 |})
106 ])).
122is_term_tree(Term, filtered_tree(QFilter, Options1), Options) :-
123 option(filter(Filter), Options),
124 callable(Filter),
125 Filter \= _:_,
126 option(module(Module), Options),
127 QFilter = Module:Filter,
128 catch(safe_filter(QFilter), _, fail),
129 call(QFilter, Term, _Label, _Children), !,
130 browser_option(Options, Options1).
131is_term_tree(Term, compound_tree(Options1), Options) :-
132 compound(Term),
133 ( is_list(Term)
134 -> \+ option(list(false), Options)
135 ; true
136 ), !,
137 browser_option(Options, Options1).
138
139:- public
140 compound_tree/3,
141 filtered_tree/4.
148compound_tree(Options, Term, Tree) :-
149 compound(Term), Term \= '$VAR'(_), !,
150 Tree = json{label:Label, children:Children},
151 compound_name_arguments(Term, Functor, Args),
152 term_string(Functor, Label),
153 maplist(compound_tree(Options), Args, Children).
154compound_tree(Options, Term, json{label:Label}) :-
155 term_label(Term, Label, Options).
164term_label(Term, String, Options) :-
165 option(engine(trident), Options), !,
166 term_string(Term, String, Options).
167term_label(Term, json{html:String}, Options) :-
168 phrase(term(Term, Options), Tokens),
169 with_output_to(string(String), print_html(Tokens)).
175:- meta_predicate filtered_tree(3,+,+,-). 176
177filtered_tree(Filter, Options, Term, Tree) :-
178 nonvar(Term),
179 call(Filter, Term, LabelTerm, ChildNodes),
180 is_list(ChildNodes), !,
181 Tree = json{label:Label, children:Children},
182 term_label(LabelTerm, Label, Options),
183 maplist(filtered_tree(Filter, Options), ChildNodes, Children).
184filtered_tree(_, Options, Term, json{label:Label}) :-
185 term_label(Term, Label, Options).
186
187safe_filter(Module:Filter) :-
188 Filter =.. List0,
189 append(List0, [_, _, _], List),
190 Filter1 =.. List,
191 safe_goal(Module:Filter1).
192
193
194 197
198browser_option(Options0, Options) :-
199 is_trident, !,
200 Options = [engine(trident)|Options0].
201browser_option(Options, Options).
207is_trident :-
208 http_current_request(Request),
209 option(user_agent(Agent), Request),
210 sub_string(Agent, _, _, _, " Trident/"), !
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 anid
attribute. Usingid
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! */