Mercurial > hg > dml-open-cliopatria
comparison cpack/dml/applications/memo_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(memo_ui, []). | |
20 | |
21 /** <module> UI for viewing memoised functions | |
22 */ | |
23 :- use_module(library(http/html_write)). | |
24 :- use_module(library(http/html_head)). | |
25 :- use_module(library(http/http_dispatch)). | |
26 :- use_module(library(http/http_parameters)). | |
27 :- use_module(library(decoration)). | |
28 :- use_module(library(htmlutils)). | |
29 :- use_module(library(memo)). | |
30 :- use_module(library(async)). | |
31 :- use_module(library(listutils)). | |
32 :- use_module(library(httpfiles)). | |
33 :- use_module(components(table)). | |
34 :- use_module(components(icons)). | |
35 :- use_module(cliopatria(hooks)). | |
36 | |
37 :- set_prolog_flag(double_quotes,string). | |
38 | |
39 :- http_handler(root(dml/memo/view), memo_view, []). | |
40 :- http_handler(root(dml/jobs/view), job_view, []). | |
41 :- http_handler(root(dml/jobs/cancel), cancel_job, []). | |
42 | |
43 decoration:resource_view(URI,_) --> | |
44 { rdf(URI,rdf:type,memo:'Function'), !, | |
45 uripattern:pattern_uri(\func(Mod,Pred,Arity),URI), | |
46 format(string(Name),"~w:~w/~d",[Mod,Pred,Arity]), | |
47 http_link_to_id(pldoc_object,[object=Name],DocLink), | |
48 http_link_to_id(memo_view,[uri(URI)],ViewURL) | |
49 }, | |
50 html_requires(font_awesome), | |
51 html( [ a(href=ViewURL, [\icon(table)," View"]), ' ' | |
52 , a(href=DocLink, [\icon(book)," Documentation"]) | |
53 ]). | |
54 | |
55 decoration:resource_decoration(URI,Link) --> | |
56 { rdf(URI,rdf:type,memo:'Function'), !, | |
57 % uripattern:pattern_uri(dml: \func(Mod,Pred,Arity),URI), | |
58 % format(string(Name),"~w:~w/~d",[Mod,Pred,Arity]), | |
59 % http_link_to_id(pldoc_object,[object=Name],DocLink), | |
60 http_link_to_id(memo_view,[uri=URI],ViewLink) | |
61 }, | |
62 html_requires(font_awesome), | |
63 html( span( [ a(href(ViewLink),\icon(table)), &(nbsp) | |
64 % , a(href(DocLink),\icon(book)), &(nbsp) | |
65 , \Link ])). | |
66 | |
67 memo_view(Request) :- | |
68 http_parameters(Request, | |
69 [ uri(URI, [ optional(false), description("URI of CSV file")]) | |
70 , page(Page, [ nonneg, default(1) ]) | |
71 , limit(Limit, [ nonneg, default(50) ]) | |
72 ]), | |
73 format(string(FullTitle),"View for ~w",[URI]), | |
74 uripattern:pattern_uri(\func(Mod,Pred,Arity),URI), | |
75 length(Args,Arity), | |
76 Head =.. [Pred|Args], | |
77 aggregate_all(count,browse(Mod:Head),Total), | |
78 ( Total=0 | |
79 -> Content=p("This function has no successful memoised computations.") | |
80 ; Offset is Limit*(Page-1), | |
81 Pages is ceil(Total/Limit), | |
82 insist(Page=<Pages), | |
83 % insist(Page=Pages -> Rows1=Rows2; take(Limit,Rows1,Rows2)), | |
84 Content = [ \paginator(memo_view-[uri(URI),limit(Limit)],Page,Pages) | |
85 , \table_from_goal(goal_row(limit(Limit,offset(Offset,browse(Mod:Head))),Args),[]) | |
86 , \paginator(memo_view-[uri(URI),limit(Limit)],Page,Pages) | |
87 ] | |
88 ), | |
89 reply_html_page(cliopatria(demo), [title(FullTitle)], [ h1(FullTitle) | Content ], [unstable]). | |
90 | |
91 cancel_job(Request) :- | |
92 insist(user_db:logged_on(_),not_authorised(cancel_job)), | |
93 http_parameters(Request, | |
94 [ pool(Pool, [ atom, optional(false) ]) | |
95 , id(Id, [ atom, optional(false) ]) | |
96 , return_to(ReturnTo, [ atom, default(_) ]) | |
97 ]), | |
98 async_cancel(Pool,Id), % !!! this could throw an error | |
99 (var(ReturnTo) -> member(referer(ReturnTo),Request); true), | |
100 debug(async,'Cancelling job ~w:~w, returning to ~w',[Pool,Id,ReturnTo]), | |
101 http_redirect(see_other,ReturnTo,Request). | |
102 | |
103 job_view(Request) :- | |
104 http_parameters(Request, [pool(Pool, [atom, default(vis_cla)])]), | |
105 format(string(FullTitle),"Current jobs in thread pool ~w",[Pool]), | |
106 findall(job(Goal,ID,TSub,Status),async_current_job(Pool,Goal,ID,TSub,Status),Jobs), | |
107 reply_html_page(cliopatria(demo), [title(FullTitle)], | |
108 [h1(FullTitle), \job_tables(Pool,Jobs)], | |
109 [unstable]). | |
110 | |
111 job_tables(Pool,Jobs) --> | |
112 {partition(is_waiting, Jobs, Waiting, Running)}, | |
113 ( {Running=[]} -> html(h3("No jobs running.")) | |
114 ; html( [ h3("Running jobs") | |
115 , \table_from_goal(running_job(Pool,Running), | |
116 [headings(['Started','Elapsed','Progress','Goal','Actions'])]) | |
117 ]) | |
118 ), | |
119 ( {Waiting=[]} -> html(h3("No jobs waiting.")) | |
120 ; html( [ h3("Waiting jobs") | |
121 , \table_from_goal(waiting_job(Pool,Waiting), | |
122 [headings(['Position','Submitted','Goal','Actions'])]) | |
123 ]) | |
124 ). | |
125 | |
126 | |
127 is_waiting(job(_,_,_,waiting(_))). | |
128 | |
129 waiting_job(Pool,Jobs,[Pos,TSubmit,GoalCell,a(href(Cancel),cancel)]) :- | |
130 member(job(Goal,ID,TSubmit,waiting(Pos)),Jobs), % !!! add submit time to table? | |
131 http_link_to_id(cancel_job,[pool=Pool,id=ID],Cancel), | |
132 goal_cell(Goal,GoalCell). | |
133 running_job(Pool,Jobs,[StartS,ElapsedS,ProgressS,GoalCell,a(href(Cancel),cancel)]) :- | |
134 member(job(Goal,ID,_TSubmit,running(Thread,Start)),Jobs), | |
135 http_link_to_id(cancel_job,[pool=Pool,id=ID],Cancel), | |
136 format_time(string(StartS),'%FT%T%:z',Start), | |
137 debug(async,'Getting running job progress from thread ~w...',[Thread]), | |
138 catch(( async_thread_progress(Thread,[summary],TNow,[Progress]), | |
139 progress_string(Progress,ProgressS), | |
140 Elapsed is TNow-Start, format(string(ElapsedS),'~2f',[Elapsed]) | |
141 ), Ex, ( debug(async,'Failed to get job progress ~q',[Ex]), | |
142 ElapsedS="N/A", ProgressS="ENDED")), | |
143 copy_term(Goal,Goal1), | |
144 numbervars(Goal1,0,_), | |
145 goal_cell(Goal1,GoalCell). | |
146 | |
147 goal_cell(Mod:Head,a(href(URL),GoalS)) :- | |
148 functor(Head,Pred,Arity), | |
149 uripattern:pattern_uri(\func(Mod,Pred,Arity),URI), | |
150 http_link_to_id(list_resource,[r(URI)],URL), | |
151 term_cell(Mod:Head,GoalS). | |
152 | |
153 progress_string(Progress,String) :- memberchk(stepwise(_Desc,Done/Total), Progress), !, format(string(String),'~d/~d',[Done,Total]). | |
154 progress_string(_Terms, "-"). | |
155 | |
156 goal_row(Pred,Vals,Cells) :- call(Pred), maplist(term_cell,Vals,Cells). | |
157 term_cell(Term,Cell) :- | |
158 with_output_to(string(Cell),write_term(Term,[quoted(true),max_depth(6),numbervars(true)])). | |
159 |