diff 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
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/applications/callgraph_ui.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,139 @@
+/* Part of DML (Digital Music Laboratory)
+	Copyright 2014-2015 Samer Abdallah, University of London
+	 
+	This program is free software; you can redistribute it and/or
+	modify it under the terms of the GNU General Public License
+	as published by the Free Software Foundation; either version 2
+	of the License, or (at your option) any later version.
+
+	This program is distributed in the hope that it will be useful,
+	but WITHOUT ANY WARRANTY; without even the implied warranty of
+	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+	GNU General Public License for more details.
+
+	You should have received a copy of the GNU General Public
+	License along with this library; if not, write to the Free Software
+	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+*/
+
+:- module(callgraph_ui, []).
+
+:- use_module(library(http/html_write)).
+:- use_module(library(http/html_head)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_parameters)).
+:- use_module(library(http/http_host)).
+:- use_module(library(http/js_write)).
+:- use_module(library(semweb/rdfs)).
+:- use_module(library(dcg_core)).
+:- use_module(library(fileutils)).
+:- use_module(library(callgraph)).
+:- use_module(library(decoration)).
+:- use_module(library(httpfiles)).
+:- use_module(components(icons)).
+
+
+:- http_handler(root(dml/callgraph/ui), callgraph_ui, []).
+:- http_handler(root(dml/callgraph/view), callgraph_viewer, []).
+:- http_handler(api(callgraph/render), callgraph_render, []).
+
+:- html_resource(js('callgraph.js'), [requires(jquery)]).
+
+cliopatria:menu_item(500=help/callgraph_ui,'Module callgraph').
+
+% adds a cube icon to all module URIs to link to rendered callgraph
+decoration:resource_decoration(URI,Link) -->
+   {rdfs_individual_of(URI,memo:'Module')}, !,
+   {uripattern:pattern_uri(dml:module/prolog/enc(Mod),URI)},
+   {http_link_to_id(callgraph_viewer,[module(Mod)],URL)},
+   html_requires("//maxcdn.bootstrapcdn.com/font-awesome/4.1.0/css/font-awesome.min.css"),
+   html(span([ a(href(URL),[' ',\icon(cube)]), \Link])).
+
+%% callgraph_viewer(+Request) is det.
+%  Web page displaying the callgraph for a given module.
+%  Uses the callgraph_view//1 component for the view area.
+callgraph_viewer(Request) :-
+   http_parameters(Request,
+      [ module(Module, [ optional(false), description("Name of module to graph") ]) ]),
+   reply_html_page(cliopatria(wide), [title(["Module callgraph: ",Module])],
+                   [ h1(["Module callgraph: ",Module]), \callgraph_view(Module) ],
+                   [ stable ]).
+
+
+%% callgraph_view(+Module:module)// is det.
+%
+%  HTML component containing a pannable/zoomable SVG callgraph of the named module.
+%  The graph itself is rendered by callgraph_render/1 via an HTTP request made just
+%  by Javascript code inserted directly after the view element.
+callgraph_view(Module) -->
+   html_requires(js('callgraph.js')),
+   html_requires(js('svg-pan-zoom.min.js')),
+   html_requires(jquery),
+   html_post(head,style("svg text {font-family:Times}")),
+   {http_link_to_id(callgraph_render,[module(Module),format(svg)],URL)},
+   html( [ div([style="width:100%;height:25em;padding:0em",id=output,class="output-box"],[])
+         , \js_script({|javascript(URL)|| load_svg('#output',URL);|})
+         ]).
+
+%% callgraph_render(+Request) is det.
+%
+% Replies with a the predicate dependency graph for a given module, created using library(callgraph).
+% Default reply format is SVG. In some formats, each predicate contains a link to the documentation
+% for that predicate.
+callgraph_render(Request) :-
+   http_parameters(Request,
+               [ module(Module, [ optional(false), description("Name of module to graph") ]),
+                 chain(Chain,   [ optional(true), default(4), nonneg, description("unflatten -c parameter") ]),
+                 link(Link,     [ optional(true), default(4), nonneg, description("unflatten -l parameter") ]),
+                 format(Fmt,    [ optional(true), default(svg), atom, description("Graphviz output format") ]) 
+               ]),
+   debug(callgraph_ui,"Calling callgraph on ~w.",[Module]),
+   http_link_to_id(pldoc_object,[object=''],DocBase),
+   Method=unflatten([fl(Link),c(Chain)]),
+   with_mutex(callgraph,
+      with_temp_dir(Dir, (
+         atomic_list_concat([Dir,'/',Module,'.',Fmt],File),
+         with_output_to(string(_), module_render(Module,[ filename(File), linkbase(DocBase), format(Fmt), method(Method)])),
+         reply_file(File,Fmt)))).
+
+
+%% callgraph_ui(+Request) is det.
+%  Web page containing a form for a module name and an output area for 
+%  rendered graphs. The form and view area are created using the callgraph_view//1 component. 
+callgraph_ui(_) :-
+   reply_html_page(cliopatria(wide), [title("Module callgraph")],
+                   [ h1("Module callgraph") , \callgraph ],
+                   [ stable ]).
+
+callgraph -->
+   {http_location_by_id(callgraph_render,Loc)},
+   html_requires(js('callgraph.js')),
+   html_requires(js('svg-pan-zoom.min.js')),
+   html_requires(jquery),
+   html_post(head,style("svg text {font-family:Times}")),
+   % html_post(head,script(type("text/javascript"),
+   %    "$(document).ready(function() { $('#output').on('load',activate_obj); });")),
+   html( div(class="callgraph-ui",
+            [ form([class=forms,target=dummy,method=post,action="about:blank",onsubmit="return false;"],
+               [  label(["Module"
+                  , div(class="input-groups",
+                      [ input([type=text,autocomplete=on,name=module,id=module],[])
+                      , \seqmap( append_control, 
+                                 [ %number(chain,1-10,4)
+                                   button(graph,"update_svg('~w');"-[Loc], "graph")
+                                 , button(clear,"clear_output();", "clear")
+                                 ])
+                      ])])
+               , label(["Output"
+                  , div([style="width:100%;height:25em;padding:0em",id=output,class="output-box"],[])])
+               ])
+            , iframe([id=dummy,style="display:none",src="about:blank"],["Dummy"])
+            ])).
+
+append_control(B1) --> html(span(class="btn-append",\B1)).
+
+number(Id,Min-Max,Val) -->
+   html(input([type=number,id=Id,name=Id,min=Min,max=Max,value=Val,style="min-width:7ex"],[])).
+
+button(Id,OnClick,Label) --> 
+   html(button([class="btn", onclick=OnClick,id=Id], Label)).