Daniel@0
|
1 /* Part of DML (Digital Music Laboratory)
|
Daniel@0
|
2 Copyright 2014-2015 Samer Abdallah, University of London
|
Daniel@0
|
3
|
Daniel@0
|
4 This program is free software; you can redistribute it and/or
|
Daniel@0
|
5 modify it under the terms of the GNU General Public License
|
Daniel@0
|
6 as published by the Free Software Foundation; either version 2
|
Daniel@0
|
7 of the License, or (at your option) any later version.
|
Daniel@0
|
8
|
Daniel@0
|
9 This program is distributed in the hope that it will be useful,
|
Daniel@0
|
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Daniel@0
|
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Daniel@0
|
12 GNU General Public License for more details.
|
Daniel@0
|
13
|
Daniel@0
|
14 You should have received a copy of the GNU General Public
|
Daniel@0
|
15 License along with this library; if not, write to the Free Software
|
Daniel@0
|
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
|
Daniel@0
|
17 */
|
Daniel@0
|
18
|
Daniel@0
|
19 :- module(memo_ui, []).
|
Daniel@0
|
20
|
Daniel@0
|
21 /** <module> UI for viewing memoised functions
|
Daniel@0
|
22 */
|
Daniel@0
|
23 :- use_module(library(http/html_write)).
|
Daniel@0
|
24 :- use_module(library(http/html_head)).
|
Daniel@0
|
25 :- use_module(library(http/http_dispatch)).
|
Daniel@0
|
26 :- use_module(library(http/http_parameters)).
|
Daniel@0
|
27 :- use_module(library(decoration)).
|
Daniel@0
|
28 :- use_module(library(htmlutils)).
|
Daniel@0
|
29 :- use_module(library(memo)).
|
Daniel@0
|
30 :- use_module(library(async)).
|
Daniel@0
|
31 :- use_module(library(listutils)).
|
Daniel@0
|
32 :- use_module(library(httpfiles)).
|
Daniel@0
|
33 :- use_module(components(table)).
|
Daniel@0
|
34 :- use_module(components(icons)).
|
Daniel@0
|
35 :- use_module(cliopatria(hooks)).
|
Daniel@0
|
36
|
Daniel@0
|
37 :- set_prolog_flag(double_quotes,string).
|
Daniel@0
|
38
|
Daniel@0
|
39 :- http_handler(root(dml/memo/view), memo_view, []).
|
Daniel@0
|
40 :- http_handler(root(dml/jobs/view), job_view, []).
|
Daniel@0
|
41 :- http_handler(root(dml/jobs/cancel), cancel_job, []).
|
Daniel@0
|
42
|
Daniel@0
|
43 decoration:resource_view(URI,_) -->
|
Daniel@0
|
44 { rdf(URI,rdf:type,memo:'Function'), !,
|
Daniel@0
|
45 uripattern:pattern_uri(\func(Mod,Pred,Arity),URI),
|
Daniel@0
|
46 format(string(Name),"~w:~w/~d",[Mod,Pred,Arity]),
|
Daniel@0
|
47 http_link_to_id(pldoc_object,[object=Name],DocLink),
|
Daniel@0
|
48 http_link_to_id(memo_view,[uri(URI)],ViewURL)
|
Daniel@0
|
49 },
|
Daniel@0
|
50 html_requires(font_awesome),
|
Daniel@0
|
51 html( [ a(href=ViewURL, [\icon(table)," View"]), ' '
|
Daniel@0
|
52 , a(href=DocLink, [\icon(book)," Documentation"])
|
Daniel@0
|
53 ]).
|
Daniel@0
|
54
|
Daniel@0
|
55 decoration:resource_decoration(URI,Link) -->
|
Daniel@0
|
56 { rdf(URI,rdf:type,memo:'Function'), !,
|
Daniel@0
|
57 % uripattern:pattern_uri(dml: \func(Mod,Pred,Arity),URI),
|
Daniel@0
|
58 % format(string(Name),"~w:~w/~d",[Mod,Pred,Arity]),
|
Daniel@0
|
59 % http_link_to_id(pldoc_object,[object=Name],DocLink),
|
Daniel@0
|
60 http_link_to_id(memo_view,[uri=URI],ViewLink)
|
Daniel@0
|
61 },
|
Daniel@0
|
62 html_requires(font_awesome),
|
Daniel@0
|
63 html( span( [ a(href(ViewLink),\icon(table)), &(nbsp)
|
Daniel@0
|
64 % , a(href(DocLink),\icon(book)), &(nbsp)
|
Daniel@0
|
65 , \Link ])).
|
Daniel@0
|
66
|
Daniel@0
|
67 memo_view(Request) :-
|
Daniel@0
|
68 http_parameters(Request,
|
Daniel@0
|
69 [ uri(URI, [ optional(false), description("URI of CSV file")])
|
Daniel@0
|
70 , page(Page, [ nonneg, default(1) ])
|
Daniel@0
|
71 , limit(Limit, [ nonneg, default(50) ])
|
Daniel@0
|
72 ]),
|
Daniel@0
|
73 format(string(FullTitle),"View for ~w",[URI]),
|
Daniel@0
|
74 uripattern:pattern_uri(\func(Mod,Pred,Arity),URI),
|
Daniel@0
|
75 length(Args,Arity),
|
Daniel@0
|
76 Head =.. [Pred|Args],
|
Daniel@0
|
77 aggregate_all(count,browse(Mod:Head),Total),
|
Daniel@0
|
78 ( Total=0
|
Daniel@0
|
79 -> Content=p("This function has no successful memoised computations.")
|
Daniel@0
|
80 ; Offset is Limit*(Page-1),
|
Daniel@0
|
81 Pages is ceil(Total/Limit),
|
Daniel@0
|
82 insist(Page=<Pages),
|
Daniel@0
|
83 % insist(Page=Pages -> Rows1=Rows2; take(Limit,Rows1,Rows2)),
|
Daniel@0
|
84 Content = [ \paginator(memo_view-[uri(URI),limit(Limit)],Page,Pages)
|
Daniel@0
|
85 , \table_from_goal(goal_row(limit(Limit,offset(Offset,browse(Mod:Head))),Args),[])
|
Daniel@0
|
86 , \paginator(memo_view-[uri(URI),limit(Limit)],Page,Pages)
|
Daniel@0
|
87 ]
|
Daniel@0
|
88 ),
|
Daniel@0
|
89 reply_html_page(cliopatria(demo), [title(FullTitle)], [ h1(FullTitle) | Content ], [unstable]).
|
Daniel@0
|
90
|
Daniel@0
|
91 cancel_job(Request) :-
|
Daniel@0
|
92 insist(user_db:logged_on(_),not_authorised(cancel_job)),
|
Daniel@0
|
93 http_parameters(Request,
|
Daniel@0
|
94 [ pool(Pool, [ atom, optional(false) ])
|
Daniel@0
|
95 , id(Id, [ atom, optional(false) ])
|
Daniel@0
|
96 , return_to(ReturnTo, [ atom, default(_) ])
|
Daniel@0
|
97 ]),
|
Daniel@0
|
98 async_cancel(Pool,Id), % !!! this could throw an error
|
Daniel@0
|
99 (var(ReturnTo) -> member(referer(ReturnTo),Request); true),
|
Daniel@0
|
100 debug(async,'Cancelling job ~w:~w, returning to ~w',[Pool,Id,ReturnTo]),
|
Daniel@0
|
101 http_redirect(see_other,ReturnTo,Request).
|
Daniel@0
|
102
|
Daniel@0
|
103 job_view(Request) :-
|
Daniel@0
|
104 http_parameters(Request, [pool(Pool, [atom, default(vis_cla)])]),
|
Daniel@0
|
105 format(string(FullTitle),"Current jobs in thread pool ~w",[Pool]),
|
Daniel@0
|
106 findall(job(Goal,ID,TSub,Status),async_current_job(Pool,Goal,ID,TSub,Status),Jobs),
|
Daniel@0
|
107 reply_html_page(cliopatria(demo), [title(FullTitle)],
|
Daniel@0
|
108 [h1(FullTitle), \job_tables(Pool,Jobs)],
|
Daniel@0
|
109 [unstable]).
|
Daniel@0
|
110
|
Daniel@0
|
111 job_tables(Pool,Jobs) -->
|
Daniel@0
|
112 {partition(is_waiting, Jobs, Waiting, Running)},
|
Daniel@0
|
113 ( {Running=[]} -> html(h3("No jobs running."))
|
Daniel@0
|
114 ; html( [ h3("Running jobs")
|
Daniel@0
|
115 , \table_from_goal(running_job(Pool,Running),
|
Daniel@0
|
116 [headings(['Started','Elapsed','Progress','Goal','Actions'])])
|
Daniel@0
|
117 ])
|
Daniel@0
|
118 ),
|
Daniel@0
|
119 ( {Waiting=[]} -> html(h3("No jobs waiting."))
|
Daniel@0
|
120 ; html( [ h3("Waiting jobs")
|
Daniel@0
|
121 , \table_from_goal(waiting_job(Pool,Waiting),
|
Daniel@0
|
122 [headings(['Position','Submitted','Goal','Actions'])])
|
Daniel@0
|
123 ])
|
Daniel@0
|
124 ).
|
Daniel@0
|
125
|
Daniel@0
|
126
|
Daniel@0
|
127 is_waiting(job(_,_,_,waiting(_))).
|
Daniel@0
|
128
|
Daniel@0
|
129 waiting_job(Pool,Jobs,[Pos,TSubmit,GoalCell,a(href(Cancel),cancel)]) :-
|
Daniel@0
|
130 member(job(Goal,ID,TSubmit,waiting(Pos)),Jobs), % !!! add submit time to table?
|
Daniel@0
|
131 http_link_to_id(cancel_job,[pool=Pool,id=ID],Cancel),
|
Daniel@0
|
132 goal_cell(Goal,GoalCell).
|
Daniel@0
|
133 running_job(Pool,Jobs,[StartS,ElapsedS,ProgressS,GoalCell,a(href(Cancel),cancel)]) :-
|
Daniel@0
|
134 member(job(Goal,ID,_TSubmit,running(Thread,Start)),Jobs),
|
Daniel@0
|
135 http_link_to_id(cancel_job,[pool=Pool,id=ID],Cancel),
|
Daniel@0
|
136 format_time(string(StartS),'%FT%T%:z',Start),
|
Daniel@0
|
137 debug(async,'Getting running job progress from thread ~w...',[Thread]),
|
Daniel@0
|
138 catch(( async_thread_progress(Thread,[summary],TNow,[Progress]),
|
Daniel@0
|
139 progress_string(Progress,ProgressS),
|
Daniel@0
|
140 Elapsed is TNow-Start, format(string(ElapsedS),'~2f',[Elapsed])
|
Daniel@0
|
141 ), Ex, ( debug(async,'Failed to get job progress ~q',[Ex]),
|
Daniel@0
|
142 ElapsedS="N/A", ProgressS="ENDED")),
|
Daniel@0
|
143 copy_term(Goal,Goal1),
|
Daniel@0
|
144 numbervars(Goal1,0,_),
|
Daniel@0
|
145 goal_cell(Goal1,GoalCell).
|
Daniel@0
|
146
|
Daniel@0
|
147 goal_cell(Mod:Head,a(href(URL),GoalS)) :-
|
Daniel@0
|
148 functor(Head,Pred,Arity),
|
Daniel@0
|
149 uripattern:pattern_uri(\func(Mod,Pred,Arity),URI),
|
Daniel@0
|
150 http_link_to_id(list_resource,[r(URI)],URL),
|
Daniel@0
|
151 term_cell(Mod:Head,GoalS).
|
Daniel@0
|
152
|
Daniel@0
|
153 progress_string(Progress,String) :- memberchk(stepwise(_Desc,Done/Total), Progress), !, format(string(String),'~d/~d',[Done,Total]).
|
Daniel@0
|
154 progress_string(_Terms, "-").
|
Daniel@0
|
155
|
Daniel@0
|
156 goal_row(Pred,Vals,Cells) :- call(Pred), maplist(term_cell,Vals,Cells).
|
Daniel@0
|
157 term_cell(Term,Cell) :-
|
Daniel@0
|
158 with_output_to(string(Cell),write_term(Term,[quoted(true),max_depth(6),numbervars(true)])).
|
Daniel@0
|
159
|