comparison cpack/dml/applications/callgraph_ui.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
comparison
equal deleted inserted replaced
-1:000000000000 0:718306e29690
1 /* Part of DML (Digital Music Laboratory)
2 Copyright 2014-2015 Samer Abdallah, University of London
3
4 This program is free software; you can redistribute it and/or
5 modify it under the terms of the GNU General Public License
6 as published by the Free Software Foundation; either version 2
7 of the License, or (at your option) any later version.
8
9 This program is distributed in the hope that it will be useful,
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 GNU General Public License for more details.
13
14 You should have received a copy of the GNU General Public
15 License along with this library; if not, write to the Free Software
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
17 */
18
19 :- module(callgraph_ui, []).
20
21 :- use_module(library(http/html_write)).
22 :- use_module(library(http/html_head)).
23 :- use_module(library(http/http_dispatch)).
24 :- use_module(library(http/http_parameters)).
25 :- use_module(library(http/http_host)).
26 :- use_module(library(http/js_write)).
27 :- use_module(library(semweb/rdfs)).
28 :- use_module(library(dcg_core)).
29 :- use_module(library(fileutils)).
30 :- use_module(library(callgraph)).
31 :- use_module(library(decoration)).
32 :- use_module(library(httpfiles)).
33 :- use_module(components(icons)).
34
35
36 :- http_handler(root(dml/callgraph/ui), callgraph_ui, []).
37 :- http_handler(root(dml/callgraph/view), callgraph_viewer, []).
38 :- http_handler(api(callgraph/render), callgraph_render, []).
39
40 :- html_resource(js('callgraph.js'), [requires(jquery)]).
41
42 cliopatria:menu_item(500=help/callgraph_ui,'Module callgraph').
43
44 % adds a cube icon to all module URIs to link to rendered callgraph
45 decoration:resource_decoration(URI,Link) -->
46 {rdfs_individual_of(URI,memo:'Module')}, !,
47 {uripattern:pattern_uri(dml:module/prolog/enc(Mod),URI)},
48 {http_link_to_id(callgraph_viewer,[module(Mod)],URL)},
49 html_requires("//maxcdn.bootstrapcdn.com/font-awesome/4.1.0/css/font-awesome.min.css"),
50 html(span([ a(href(URL),[' ',\icon(cube)]), \Link])).
51
52 %% callgraph_viewer(+Request) is det.
53 % Web page displaying the callgraph for a given module.
54 % Uses the callgraph_view//1 component for the view area.
55 callgraph_viewer(Request) :-
56 http_parameters(Request,
57 [ module(Module, [ optional(false), description("Name of module to graph") ]) ]),
58 reply_html_page(cliopatria(wide), [title(["Module callgraph: ",Module])],
59 [ h1(["Module callgraph: ",Module]), \callgraph_view(Module) ],
60 [ stable ]).
61
62
63 %% callgraph_view(+Module:module)// is det.
64 %
65 % HTML component containing a pannable/zoomable SVG callgraph of the named module.
66 % The graph itself is rendered by callgraph_render/1 via an HTTP request made just
67 % by Javascript code inserted directly after the view element.
68 callgraph_view(Module) -->
69 html_requires(js('callgraph.js')),
70 html_requires(js('svg-pan-zoom.min.js')),
71 html_requires(jquery),
72 html_post(head,style("svg text {font-family:Times}")),
73 {http_link_to_id(callgraph_render,[module(Module),format(svg)],URL)},
74 html( [ div([style="width:100%;height:25em;padding:0em",id=output,class="output-box"],[])
75 , \js_script({|javascript(URL)|| load_svg('#output',URL);|})
76 ]).
77
78 %% callgraph_render(+Request) is det.
79 %
80 % Replies with a the predicate dependency graph for a given module, created using library(callgraph).
81 % Default reply format is SVG. In some formats, each predicate contains a link to the documentation
82 % for that predicate.
83 callgraph_render(Request) :-
84 http_parameters(Request,
85 [ module(Module, [ optional(false), description("Name of module to graph") ]),
86 chain(Chain, [ optional(true), default(4), nonneg, description("unflatten -c parameter") ]),
87 link(Link, [ optional(true), default(4), nonneg, description("unflatten -l parameter") ]),
88 format(Fmt, [ optional(true), default(svg), atom, description("Graphviz output format") ])
89 ]),
90 debug(callgraph_ui,"Calling callgraph on ~w.",[Module]),
91 http_link_to_id(pldoc_object,[object=''],DocBase),
92 Method=unflatten([fl(Link),c(Chain)]),
93 with_mutex(callgraph,
94 with_temp_dir(Dir, (
95 atomic_list_concat([Dir,'/',Module,'.',Fmt],File),
96 with_output_to(string(_), module_render(Module,[ filename(File), linkbase(DocBase), format(Fmt), method(Method)])),
97 reply_file(File,Fmt)))).
98
99
100 %% callgraph_ui(+Request) is det.
101 % Web page containing a form for a module name and an output area for
102 % rendered graphs. The form and view area are created using the callgraph_view//1 component.
103 callgraph_ui(_) :-
104 reply_html_page(cliopatria(wide), [title("Module callgraph")],
105 [ h1("Module callgraph") , \callgraph ],
106 [ stable ]).
107
108 callgraph -->
109 {http_location_by_id(callgraph_render,Loc)},
110 html_requires(js('callgraph.js')),
111 html_requires(js('svg-pan-zoom.min.js')),
112 html_requires(jquery),
113 html_post(head,style("svg text {font-family:Times}")),
114 % html_post(head,script(type("text/javascript"),
115 % "$(document).ready(function() { $('#output').on('load',activate_obj); });")),
116 html( div(class="callgraph-ui",
117 [ form([class=forms,target=dummy,method=post,action="about:blank",onsubmit="return false;"],
118 [ label(["Module"
119 , div(class="input-groups",
120 [ input([type=text,autocomplete=on,name=module,id=module],[])
121 , \seqmap( append_control,
122 [ %number(chain,1-10,4)
123 button(graph,"update_svg('~w');"-[Loc], "graph")
124 , button(clear,"clear_output();", "clear")
125 ])
126 ])])
127 , label(["Output"
128 , div([style="width:100%;height:25em;padding:0em",id=output,class="output-box"],[])])
129 ])
130 , iframe([id=dummy,style="display:none",src="about:blank"],["Dummy"])
131 ])).
132
133 append_control(B1) --> html(span(class="btn-append",\B1)).
134
135 number(Id,Min-Max,Val) -->
136 html(input([type=number,id=Id,name=Id,min=Min,max=Max,value=Val,style="min-width:7ex"],[])).
137
138 button(Id,OnClick,Label) -->
139 html(button([class="btn", onclick=OnClick,id=Id], Label)).