Chris@0
|
1 /* $Id: rdf_statistics.pl,v 1.16 2007/01/16 09:37:10 jan Exp $
|
Chris@0
|
2
|
Chris@0
|
3 Part of SWI-Prolog
|
Chris@0
|
4
|
Chris@0
|
5 Author: Jan Wielemaker
|
Chris@0
|
6 E-mail: jan@swi.psy.uva.nl
|
Chris@0
|
7 WWW: http://www.swi-prolog.org
|
Chris@0
|
8 Copyright (C): 1985-2002, University of Amsterdam
|
Chris@0
|
9
|
Chris@0
|
10 This program is free software; you can redistribute it and/or
|
Chris@0
|
11 modify it under the terms of the GNU General Public License
|
Chris@0
|
12 as published by the Free Software Foundation; either version 2
|
Chris@0
|
13 of the License, or (at your option) any later version.
|
Chris@0
|
14
|
Chris@0
|
15 This program is distributed in the hope that it will be useful,
|
Chris@0
|
16 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Chris@0
|
17 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Chris@0
|
18 GNU General Public License for more details.
|
Chris@0
|
19
|
Chris@0
|
20 You should have received a copy of the GNU Lesser General Public
|
Chris@0
|
21 License along with this library; if not, write to the Free Software
|
Chris@0
|
22 Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
Chris@0
|
23
|
Chris@0
|
24 As a special exception, if you link this library with other files,
|
Chris@0
|
25 compiled with a Free Software compiler, to produce an executable, this
|
Chris@0
|
26 library does not by itself cause the resulting executable to be covered
|
Chris@0
|
27 by the GNU General Public License. This exception does not however
|
Chris@0
|
28 invalidate any other reasons why the executable file might be covered by
|
Chris@0
|
29 the GNU General Public License.
|
Chris@0
|
30 */
|
Chris@0
|
31
|
Chris@0
|
32
|
Chris@0
|
33 :- module(rdf_statistics,
|
Chris@0
|
34 [
|
Chris@0
|
35 ]).
|
Chris@0
|
36 :- use_module(library(pce)).
|
Chris@0
|
37 :- use_module(library(tabular)).
|
Chris@0
|
38 :- use_module(library(broadcast)).
|
Chris@0
|
39 :- use_module(library('semweb/rdf_db')).
|
Chris@0
|
40 :- use_module(library('semweb/rdf_edit')).
|
Chris@0
|
41 :- use_module(rdf_cache).
|
Chris@0
|
42 :- use_module(rdf_util).
|
Chris@0
|
43 :- use_module(rdf_create). % namespace menu
|
Chris@0
|
44
|
Chris@0
|
45 :- pce_begin_class(rdf_statistics_dialog, tabbed_window,
|
Chris@0
|
46 "Show various statistics").
|
Chris@0
|
47
|
Chris@0
|
48 initialise(SD) :->
|
Chris@0
|
49 send_super(SD, initialise, 'RDF Statistics'),
|
Chris@0
|
50 send(SD, append, new(rdf_file_dialog), files),
|
Chris@0
|
51 send(SD, append, new(rdf_call_dialog), statistics),
|
Chris@0
|
52 send(new(D2, dialog), below, SD),
|
Chris@0
|
53 send(D2, resize_message, message(D2, layout, @arg2)),
|
Chris@0
|
54 send(D2, append, button(ok, message(SD, destroy))).
|
Chris@0
|
55
|
Chris@0
|
56
|
Chris@0
|
57 :- pce_end_class(rdf_statistics_dialog).
|
Chris@0
|
58
|
Chris@0
|
59
|
Chris@0
|
60 /*******************************
|
Chris@0
|
61 * FILES *
|
Chris@0
|
62 *******************************/
|
Chris@0
|
63
|
Chris@0
|
64 :- pce_begin_class(rdf_file_dialog, table_window,
|
Chris@0
|
65 "Show statistics").
|
Chris@0
|
66
|
Chris@0
|
67 initialise(D) :->
|
Chris@0
|
68 send_super(D, initialise, 'Loaded files', new(rdf_file_table)).
|
Chris@0
|
69
|
Chris@0
|
70 :- pce_end_class(rdf_file_dialog).
|
Chris@0
|
71
|
Chris@0
|
72
|
Chris@0
|
73 :- pce_begin_class(rdf_file_table, tabular,
|
Chris@0
|
74 "Table with statistical information").
|
Chris@0
|
75
|
Chris@0
|
76
|
Chris@0
|
77 initialise(ST) :->
|
Chris@0
|
78 send_super(ST, initialise),
|
Chris@0
|
79 send(ST, rules, all),
|
Chris@0
|
80 send(ST, cell_spacing, -1),
|
Chris@0
|
81 send(ST, cell_padding, size(5,3)),
|
Chris@0
|
82 send(ST, show_sources).
|
Chris@0
|
83
|
Chris@0
|
84 clear(ST) :->
|
Chris@0
|
85 "Delete all rows"::
|
Chris@0
|
86 send(ST, delete_rows).
|
Chris@0
|
87
|
Chris@0
|
88 show_sources(ST) :->
|
Chris@0
|
89 send(ST, append, 'Loaded source', bold, center, background := khaki1),
|
Chris@0
|
90 send(ST, append, 'Namespace', bold, center, background := khaki1),
|
Chris@0
|
91 send(ST, append, 'Triples', bold, center, background := khaki1),
|
Chris@0
|
92 send(ST, append, 'Loaded', bold, center, background := khaki1),
|
Chris@0
|
93 send(ST, append, 'Access', bold, center, background := khaki1),
|
Chris@0
|
94 send(ST, next_row),
|
Chris@0
|
95 flag(rdf_triples, Old, 0),
|
Chris@0
|
96 ( rdf_source(Source),
|
Chris@0
|
97 rdf_statistics(triples_by_file(Source, Triples)),
|
Chris@0
|
98 flag(rdf_triples, C, C+Triples),
|
Chris@0
|
99 send(ST, show_source, Source),
|
Chris@0
|
100 fail
|
Chris@0
|
101 ; flag(rdf_triples, Total, Old)
|
Chris@0
|
102 ),
|
Chris@0
|
103 send(ST, append, 'Total on files:', bold, halign := right),
|
Chris@0
|
104 send(ST, append, Total, bold, halign := right),
|
Chris@0
|
105 send(ST, next_row),
|
Chris@0
|
106 send(ST, append, 'Total:', bold, halign := right),
|
Chris@0
|
107 rdf_statistics(triples(TotalDB)),
|
Chris@0
|
108 send(ST, append, TotalDB, bold, halign := right),
|
Chris@0
|
109 send(ST, next_row).
|
Chris@0
|
110
|
Chris@0
|
111 show_source(ST, Source:name) :->
|
Chris@0
|
112 get(ST, layout_manager, LM), % TBD: move to tabular
|
Chris@0
|
113 get(LM, current, point(_, Y)),
|
Chris@0
|
114 get(LM, row, Y, @on, Row),
|
Chris@0
|
115 send(Row, valign, center),
|
Chris@0
|
116 send(ST, append, rdf_file_text(Source)),
|
Chris@0
|
117 rdf_default_ns(Source, NS),
|
Chris@0
|
118 send(ST, append, % TBD: listen to broadcast
|
Chris@0
|
119 rdf_ns_menu(NS, message(ST, default_ns, Source, @arg1))),
|
Chris@0
|
120 rdf_statistics(triples_by_file(Source, Triples)),
|
Chris@0
|
121 send(ST, append, Triples, halign := right),
|
Chris@0
|
122 ( rdf_db:rdf_source(Source, _, Loaded, _MD5)
|
Chris@0
|
123 -> true
|
Chris@0
|
124 ; Loaded = 0
|
Chris@0
|
125 ),
|
Chris@0
|
126 send(ST, append, Loaded, halign := right),
|
Chris@0
|
127 send(ST, append, new(AM, rdf_file_access_menu(Source)),
|
Chris@0
|
128 halign := center),
|
Chris@0
|
129 send(AM, border, 2), % narrow version to improve layout
|
Chris@0
|
130 send(ST, next_row).
|
Chris@0
|
131
|
Chris@0
|
132 default_ns(_ST, Source:name, DefNS:name) :->
|
Chris@0
|
133 rdf_set_default_ns(Source, DefNS).
|
Chris@0
|
134
|
Chris@0
|
135 :- pce_end_class(rdf_file_table).
|
Chris@0
|
136
|
Chris@0
|
137
|
Chris@0
|
138 :- pce_begin_class(rdf_file_text, text,
|
Chris@0
|
139 "Represent a filename").
|
Chris@0
|
140
|
Chris@0
|
141 initialise(T, Name:name) :->
|
Chris@0
|
142 send_super(T, initialise, Name).
|
Chris@0
|
143
|
Chris@0
|
144 :- pce_global(@rdf_file_text_recogniser,
|
Chris@0
|
145 make_rdf_file_text_recogniser).
|
Chris@0
|
146
|
Chris@0
|
147 make_rdf_file_text_recogniser(G) :-
|
Chris@0
|
148 new(G, popup_gesture(new(P, popup(actions, message(@arg2, @arg1))))),
|
Chris@0
|
149 send_list(P, append,
|
Chris@0
|
150 [ show_roots,
|
Chris@0
|
151 edit,
|
Chris@0
|
152 gap,
|
Chris@0
|
153 save,
|
Chris@0
|
154 remove
|
Chris@0
|
155 ]).
|
Chris@0
|
156
|
Chris@0
|
157 event(T, Ev:event) :->
|
Chris@0
|
158 ( send_super(T, event, Ev)
|
Chris@0
|
159 -> true
|
Chris@0
|
160 ; send(@rdf_file_text_recogniser, event, Ev)
|
Chris@0
|
161 ).
|
Chris@0
|
162
|
Chris@0
|
163 show_roots(T) :->
|
Chris@0
|
164 "Show roots belonging to this file"::
|
Chris@0
|
165 get(T?frame, transient_for, Triple20),
|
Chris@0
|
166 get(T?string, value, Name),
|
Chris@0
|
167 send(Triple20, show_roots_for_file, Name).
|
Chris@0
|
168
|
Chris@0
|
169 edit(T) :->
|
Chris@0
|
170 "Edit file using PceEmacs"::
|
Chris@0
|
171 get(T?string, value, Name),
|
Chris@0
|
172 edit(file(Name)).
|
Chris@0
|
173
|
Chris@0
|
174 save(T) :->
|
Chris@0
|
175 "Save data back to a file"::
|
Chris@0
|
176 get(T?string, value, Name),
|
Chris@0
|
177 rdf_save(Name, [db(Name)]).
|
Chris@0
|
178
|
Chris@0
|
179 remove(T) :->
|
Chris@0
|
180 "Remove all associated triples"::
|
Chris@0
|
181 get(T?string, value, DB),
|
Chris@0
|
182 rdfe_transaction(rdfe_retractall(_,_,_,DB), remove_db(DB)).
|
Chris@0
|
183
|
Chris@0
|
184 :- pce_end_class(rdf_file_text).
|
Chris@0
|
185
|
Chris@0
|
186
|
Chris@0
|
187 :- pce_begin_class(rdf_file_access_menu, menu,
|
Chris@0
|
188 "Control access to the file").
|
Chris@0
|
189
|
Chris@0
|
190 variable(file, name, get, "Controlled file").
|
Chris@0
|
191
|
Chris@0
|
192 initialise(AM, File:name) :->
|
Chris@0
|
193 "Create access menu for file"::
|
Chris@0
|
194 send_super(AM, initialise, access, cycle, message(AM, access, @arg1)),
|
Chris@0
|
195 send(AM, show_label, @off),
|
Chris@0
|
196 send_list(AM, append, [rw, ro, all, fallback]),
|
Chris@0
|
197 send(AM, slot, file, File),
|
Chris@0
|
198 send(AM, update),
|
Chris@0
|
199 listen(AM, rdf_file_property(_, _), send(AM, update)).
|
Chris@0
|
200
|
Chris@0
|
201 unlink(AM) :->
|
Chris@0
|
202 unlisten(AM),
|
Chris@0
|
203 send_super(AM, unlink).
|
Chris@0
|
204
|
Chris@0
|
205 update(AM) :->
|
Chris@0
|
206 get(AM, file, File),
|
Chris@0
|
207 ( rdfe_get_file_property(F, default(Mode)),
|
Chris@0
|
208 F == File
|
Chris@0
|
209 -> send(AM, selection, Mode)
|
Chris@0
|
210 ; rdfe_get_file_property(File, access(Access))
|
Chris@0
|
211 -> send(AM, selection, Access)
|
Chris@0
|
212 ).
|
Chris@0
|
213
|
Chris@0
|
214 access(AM, Mode:name) :->
|
Chris@0
|
215 "Modify the access"::
|
Chris@0
|
216 get(AM, file, File),
|
Chris@0
|
217 ( ( Mode == all
|
Chris@0
|
218 ; Mode == fallback
|
Chris@0
|
219 )
|
Chris@0
|
220 -> rdfe_set_file_property(File, default(Mode))
|
Chris@0
|
221 ; rdfe_set_file_property(File, access(Mode))
|
Chris@0
|
222 ).
|
Chris@0
|
223
|
Chris@0
|
224 :- pce_end_class(rdf_file_access_menu).
|
Chris@0
|
225
|
Chris@0
|
226
|
Chris@0
|
227 /*******************************
|
Chris@0
|
228 * CALLS *
|
Chris@0
|
229 *******************************/
|
Chris@0
|
230
|
Chris@0
|
231 :- pce_begin_class(rdf_call_dialog, table_window,
|
Chris@0
|
232 "Show call statistics").
|
Chris@0
|
233
|
Chris@0
|
234 initialise(D) :->
|
Chris@0
|
235 Khaki = (background := khaki1),
|
Chris@0
|
236 send_super(D, initialise, 'RDF call statistics', new(T, tabular)),
|
Chris@0
|
237 send(T, rules, all),
|
Chris@0
|
238 send(T, cell_spacing, -1),
|
Chris@0
|
239 send(T, cell_padding, size(5,3)),
|
Chris@0
|
240 send(T, append, 'Indexed', bold, center, Khaki, colspan := 3),
|
Chris@0
|
241 send(T, append, 'Calls', bold, center, Khaki,
|
Chris@0
|
242 rowspan := 2, valign := center),
|
Chris@0
|
243 send(T, next_row),
|
Chris@0
|
244 send(T, append, 'Subject', bold, center, Khaki),
|
Chris@0
|
245 send(T, append, 'Object', bold, center, Khaki),
|
Chris@0
|
246 send(T, append, 'Predicate', bold, center, Khaki),
|
Chris@0
|
247 send(T, next_row),
|
Chris@0
|
248 ( rdf_statistics(lookup(rdf(S,P,O), Calls)),
|
Chris@0
|
249 send(T, append, S, bold, center),
|
Chris@0
|
250 send(T, append, P, bold, center),
|
Chris@0
|
251 send(T, append, O, bold, center),
|
Chris@0
|
252 send(T, append, Calls, normal, right),
|
Chris@0
|
253 send(T, next_row),
|
Chris@0
|
254 fail
|
Chris@0
|
255 ; true
|
Chris@0
|
256 ),
|
Chris@0
|
257 send(T, append, 'Statistics', bold, center, Khaki, colspan := 4),
|
Chris@0
|
258 send(T, next_row),
|
Chris@0
|
259 rdf_statistics(core(Core)),
|
Chris@0
|
260 MB is round(Core/(1024*1024)),
|
Chris@0
|
261 sformat(CoreMB, '~D MB', [MB]),
|
Chris@0
|
262 send(D, count, memory_usage, CoreMB),
|
Chris@0
|
263 rdf_statistics(gc(GC, GCTime)),
|
Chris@0
|
264 rdf_statistics(rehash(Rehash, RehashTime)),
|
Chris@0
|
265 send(D, rehash, 'GC', GC, GCTime),
|
Chris@0
|
266 send(D, rehash, rehash, Rehash, RehashTime),
|
Chris@0
|
267
|
Chris@0
|
268 ( rdf_statistics(searched_nodes(Nodes))
|
Chris@0
|
269 -> send(D, count, searched_nodes, Nodes)
|
Chris@0
|
270 ; true
|
Chris@0
|
271 ),
|
Chris@0
|
272 rdf_cache_statistics(count(Caches)),
|
Chris@0
|
273 rdf_cache_statistics(attached(Attached)),
|
Chris@0
|
274 send(D, count, cached_queries, Caches),
|
Chris@0
|
275 send(D, count, attached_cached_queries, Attached).
|
Chris@0
|
276
|
Chris@0
|
277 count(D, Name:name, Count:any) :->
|
Chris@0
|
278 get(D, member, tabular, T),
|
Chris@0
|
279 send(T, append, Name?label_name, bold, right, colspan := 3),
|
Chris@0
|
280 send(T, append, Count, normal, right),
|
Chris@0
|
281 send(T, next_row).
|
Chris@0
|
282
|
Chris@0
|
283 rehash(D, Name, Times:int, Time:prolog) :->
|
Chris@0
|
284 get(D, member, tabular, T),
|
Chris@0
|
285 send(T, append, Name?label_name, bold, right, colspan := 3),
|
Chris@0
|
286 sformat(Value, '~D in ~2f sec', [Times, Time]),
|
Chris@0
|
287 send(T, append, Value, normal, right),
|
Chris@0
|
288 send(T, next_row).
|
Chris@0
|
289
|
Chris@0
|
290 :- pce_end_class(rdf_call_dialog).
|