+
+
+# C3 Rendering examples
+
+This is an example of how to use C3 graphics to illustrate the content in the DML collection.
+
+
+
+:- use_rendering(c3).
+
+%% collection(-C:oneof([charm,bl]), -X:uri) is nondet.
+collection(charm,X) :- rdf(X,charm:file_name,_).
+collection(bl,X) :- rdf(X,rdf:type,mo:'Signal',bl_p2r).
+
+collection_property_value_count(Collection,Property,Value,Count) :-
+ aggregate(count, R^(collection(Collection,R), rdf_has(R,Property,Value)), Count).
+
+% Unfortunately rdf_meta is not legal in sandbox yet.
+%:- rdf_meta collection_property_hist(+,r,+,-).
+%% collection_property_hist(+C:atom, +P:uri, +Min:nonneg, -Chart:dict) is det.
+collection_property_hist(Coll,P,Min,c3{data:_{columns:Pairs, type:pie}}) :-
+ rdf_global_id(P,Prop), % expand Namespace:Local resource representation
+ setof( [C,N], (collection_property_value_count(Coll,Prop,literal(C),N),N>Min), Pairs).
+
+
+
+Next a little test that we can use this to get pairs of composer and count.
+
+
+
+aggregate(count, X^(collection(charm,X), rdf_has(X,dml:composer,C)), N).
+
+
+
+Next a pie chart showing the proportions of different composers in the CHARM collection. (This query should run automatically when this notebook loads). If you click on the labels in the legend, that segment is removed and the pie redrawn.
+
+
+
+collection_property_hist(charm,dml:composer,25,Pairs).
+
+
+
+Finally, a couple more distributions over language and composer in the BL collection. Press the white-on-green arrow to run the query.
+
+
+
+collection_property_hist(bl,dc:language,150,Pairs).
+
+
+
+% top 20 composers
+collection_property_hist(bl,dml:composer,20,Pairs).
+
+
+
diff -r 000000000000 -r 718306e29690 cpack/dml/examples/csv_op_viewer.swinb
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/examples/csv_op_viewer.swinb Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,65 @@
+
+
+
+:- use_module(library(computations)).
+:- use_module(library(mlserver)).
+:- use_module(library(real)).
+:- use_module(library(dml_c3)).
+:- include(search).
+:- use_rendering(rdf,[resource_format(nslabel)]).
+:- use_rendering(c3).
+
+transform_memo(Class,Transform,In,Out) :-
+ transform(Class,Transform),
+ computation_memo(Transform,In,Out).
+
+op_chart(Op,CSV,Chart) :-
+ csv_op(Op,CSV,Result),
+ csv_op_chart(Op,Result,Chart).
+
+
+
+Histogram of durations of computations on CSV files.
+
+
+
+findall(Dur,browse(computations:csv_op_memo(A,B,_C),comp(_,_,Dur)-ok),_Durs),
+[Counts,Map] === hist1d(transpose(_Durs),edgemap(0:0.01:2)),
+array_list(Counts,_LC),
+c3_hist(steps,dur,Map,_LC,Chart).
+
+
+
+Recording level analyses...
+
+
+
+distinct(A,browse(computations:csv_op_memo(A,B,_C),comp(_,_,Dur)-ok)),
+computation(_,Rec,B),
+writeln(doing(A,B)),
+csv_op_chart(A,_C,D).
+
+
+
+Collection level analyses...
+
+
+
+distinct(Name/Arity,
+ ( browse(perspectives:cla_memo(A,B,_C),comp(_,_,Dur)-ok),
+ functor(A,Name,Arity))),
+cla_op_chart(A,_C,Chart),
+dataset_size(B,Size).
+
+
+
+This example shows how VAMP computations can be triggered on demand.
+
+
+
+X :: title(piano) /\ title(sonata),
+transform_memo(tempo,_,X,Y),
+op_chart(uniform_tempo_r(linear,2),Y,Chart).
+
+
+
diff -r 000000000000 -r 718306e29690 cpack/dml/examples/index.json
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/examples/index.json Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,9 @@
+// list of examples, represented as a JSON list
+[
+"--",
+{ "file":"c3examples.swinb", "title":"Using C3 graphics to visualise collection statistics" },
+{ "file":"csv_op_viewer.swinb", "title":"Graphical viewers for recording level analyses" },
+{ "file":"system_metrics.swinb","title":"Analytics on collection level performance" },
+"--",
+{ "file":"visuals.pl", "title":"Plots and term renderings" }
+]
diff -r 000000000000 -r 718306e29690 cpack/dml/examples/system_metrics.swinb
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/examples/system_metrics.swinb Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,217 @@
+
+
+
+## Analysis of collection level computation performance
+
+This following block of code defines some predicates for browsing the database of collection level computations and tagging them by what kind of computation it was, what the implementation language was, the date and time of the computation, the size of the collection and the duration of the computation.
+
+Scroll down the query boxes below and press the green arrow to run each query.
+
+
+
+:- use_module(library(computations)).
+:- use_module(library(mlserver)).
+:- use_module(library(real)).
+:- use_module(library(dml_c3)).
+
+:- use_rendering(rdf,[resource_format(nslabel)]).
+:- use_rendering(matlab,[format(svg),size(15,10)]).
+:- use_rendering(c3).
+
+% Enumerates collection level analysis events, providing
+% Func=Label/Lang, collection size, and computation duration.
+cla_op(Lab,Size,Dur) :- cla_op(label>>relabel-size-dur,Lab-Size-Dur).
+
+% main CLA browser predicate. Uses Filter to determine which computations
+% are returned and what information is provided.
+cla_op(Filter,Out) :-
+ browse(perspectives:cla_memo(Op,CID,_),comp(_,Time,Dur)-ok),
+ dataset_size(CID,Size),
+ x(Filter,op(Op,Time,Size,Dur),Out).
+
+% field extractor predicate (a v. small arrow interpreter!)
+x(id,X,X).
+x(F>>G,X,Y) :- x(F,X,Z), x(G,Z,Y).
+x(fst(F),X1-Y,X2-Y) :- x(F,X1,X2).
+x(snd(F),X-Y1,X-Y2) :- x(F,Y1,Y2).
+x(F1-F2,X,Y1-Y2) :- x(F1,X,Y1), x(F2,X,Y2).
+x(H,X,Y) :- defx(H,F), x(F,X,Y).
+x(add(N),X,Y) :- Y is X+N.
+x(arg(N),X,Y) :- arg(N,X,Y).
+x(log,X,Y) :- Y is log10(X).
+x(jitter(L,U),X,Y) :- random(D), Y is L+(U-L)*D+X.
+x(divide,X-Y,Z) :- Z is X/Y.
+x(diff,X-Y,Z) :- Z is Y-X.
+x(quant(Q),X,Y) :- Y is Q*floor(X/Q).
+x(event,T1-_,T1-start).
+x(event,T1-DT,T2-stop) :- T2 is T1+DT.
+
+% gets month number and name from timestamp
+x(month_num_name,Time,Num-Name) :-
+ format_time(atom(Name),'%B',Time),
+ stamp_date_time(Time,Date,local),
+ date_time_value(month,Date,Num).
+
+% Transforms collection level operation spec to Label/Lang,
+% where Lang is in { ml, pl, r, py }.
+x(relabel,Op,Label/Lang) :- cla_label_lang(Op,Label,Lang).
+x(lang,_/Lang,Lang).
+
+defx(op, arg(1)).
+defx(time, arg(2)).
+defx(size, arg(3)).
+defx(dur, arg(4)).
+defx(month, time>>month_num_name).
+
+normalise_hist(Name-Pairs,Name-Pairs2) :-
+ unzip(Pairs,Vals,Counts),
+ stoch(Counts,Probs),
+ unzip(Pairs2,Vals,Probs).
+
+stoch(Xs,Ys) :- sumlist(Xs,Total), maplist(divby(Total),Xs,Ys).
+divby(Z,X,Y) :- Y is X/Z.
+
+concurrency([T0-start|StartStopEvents],ConcurrencyEvents) :-
+ foldl(conc,StartStopEvents,ConcurrencyEvents,T0-1,_).
+
+conc(T2-Event,(T1-T2)-N1,T1-N1,T2-N2) :-
+ ( Event=start -> succ(N1,N2)
+ ; Event=stop -> succ(N2,N1)
+ ).
+
+% ------- tools for building C3 charts -----------
+
+%% add_points(+Data:pair(term,list(pair(number,number))))// is det.
+% Adds a set of points to a scatter plot
+add_points(Name-Pairs) -->
+ {unzip(Pairs,Xs,Ys)},
+ add_points(Name,Xs,Ys).
+
+%% add_points(+Name:term,+X:list(number),+Y:list(number),+C1:c3,-C2:c3) is det.
+% adds a named set of points to a C3 scatter plot.
+add_points(Name1,Xs,Ys,Ch1,Ch2) :-
+ term_to_atom(Name1,Name),
+ atom_concat(Name,'_x',NameX),
+ Ch2=Ch1.put(data/columns,[[NameX|Xs],[Name|Ys]|Ch1.data.columns])
+ .put(data/xs/Name,NameX).
+
+
+
+This query shows the relationship between collection size and computation time for all collection level analyses, grouped by month of computation. Note that the axis scales
+are _logarithmic_.
+
+
+
+setof(Size-Dur,
+ cla_op(month-size>>log>>jitter(0,0.05)-dur>>log,(_-M)-Size-Dur),
+ _Points),
+call_dcg(( c3:scat('log size','log dur'),
+ add_points(all-_Points),
+ c3:legend(false),
+ c3:zoom(true)
+ ),
+ c3{},Ch0).
+
+
+
+Histogram of logarithm of computation time per item, quantised to 0.1 bins (a ratio of about 1.26).
+
+
+
+Q=0.1, % size of quantisation bin (in log domain)
+histof(T, cla_op((dur-size)>>divide>>log>>quant(Q),T), _Hist),
+call_dcg(( c3:bar('log dur','count'),
+ add_points(all-_Hist),
+ c3:put(bar/width/ratio,Q)
+ ), c3{},Chart).
+
+
+
+Histogram of logarithm of computation time per item, quantised to bins of width 0.25, grouped computation label and language.
+
+
+
+findall(L-Hist,
+ histof(T,
+ cla_op(op>>relabel-(dur-size)>>divide>>log>>quant(0.25),L-T),
+ Hist),
+ _Hists),
+maplist(normalise_hist,_Hists,_Dists),
+call_dcg(( c3:bar('log dur','count'),
+ foldl(add_points,_Dists),
+ c3:put(bar/width/ratio,0.5)
+ ), c3{}, Ch0).
+
+
+
+Histogram of logarithm of computation time per item, quantised to bins of width 0.25, grouped language.
+
+
+
+findall(L-Hist,
+ histof(T,
+ cla_op(op>>relabel>>lang - (dur-size)>>divide>>log>>quant(0.25),L-T),
+ Hist),
+ Hists),
+maplist(normalise_hist,Hists,_Dists),
+call_dcg(( c3:bar('log dur','fraction'),
+ foldl(add_points,_Dists),
+ c3:put(bar/width/ratio,0.45)
+ ), c3{}, Ch0).
+
+
+
+This next query shows how collection size vs computation duration varies with the kind of analysis being done and the implementation language. Note that computations in Prolog have the lowest overheads, and that computations in Matlab seem to have the most variable range of durations for a given collection size.
+
+
+
+findall(Op-_Ps,
+ setof(Size-Dur,
+ cla_op(op>>relabel-(size>>log)-dur>>log,Op-Size-Dur),
+ _Ps),
+ _Rs),
+foldl(add_points,_Rs,c3{}.scat('log size','log dur'),Ch1).
+
+
+
+This query is like the previous one, but grouped by language only.
+
+
+
+findall(Op-_Ps,
+ setof(Size-Dur,
+ cla_op(op>>relabel>>lang-(size>>log)-dur>>log,Op-Size-Dur),
+ _Ps),
+ _Rs),
+foldl(add_points,_Rs,c3{}.scat('log size','log dur'),Ch1).
+
+
+
+This query breaks down the performance of analysis method by month. There does not seem to be any significant pattern in this other than the overall volume of computation done in each month.
+
+
+
+setof(Month-_Ps,
+ setof(Size-Dur,
+ cla_op( month - op>>relabel - size>>log - dur>>log,
+ Month - Label - Size - Dur),
+ _Ps),
+ _Rs),
+call(foldl(add_points,_Rs), c3{}.scat(log_size,log_dur), Ch).
+
+
+
+This query analyses the degree of concurrency of collection level computations. It works by getting a complete set of point events describing the beginning and ending times of computations. Then the predicate concurrency/2 (defined in the initial code block) folds over these events and produces a list of time interval events of the form (StartTime-EndTime)-Concurrency, where Concurrency is the number of concurrent computations occuring over that interval. Then, the time intervals are mapped to durations and a histogram of concurrency weighted by duration is produced.
+
+
+
+setof(Ev,cla_op((time-dur)>>event,Ev),_Evs),
+concurrency(_Evs,_CEvs),
+maplist(x(fst(diff)),_CEvs,_CEvs2),
+weighted_histof(Dur,Conc,member(Dur-Conc,_CEvs2),Hist),
+select(0-_,Hist,_Hist1),
+unzip(_Hist1,_Values,_Durs),
+c3_bar(concurrency-_Values,duration-_Durs,Chart).
+
+
+
diff -r 000000000000 -r 718306e29690 cpack/dml/examples/visuals.pl
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/examples/visuals.pl Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,62 @@
+:- use_module(library(mlserver)).
+:- use_module(library(semweb/rdf_label)).
+:- use_module(components(matlab)).
+:- use_module(components(audio)).
+:- use_module(components(score)).
+:- use_rendering(matlab,[size(12,8),cache(true)]).
+:- use_rendering(html).
+
+%:- include(search).
+
+/**