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(kern_analysis, []).
|
Daniel@0
|
20
|
Daniel@0
|
21 :- use_module(library(kerndata)).
|
Daniel@0
|
22 :- use_module(library(grammars)).
|
Daniel@0
|
23 :- use_module(library(compression)).
|
Daniel@0
|
24 :- use_module(library(swipe)).
|
Daniel@0
|
25
|
Daniel@0
|
26 grammars:dataset_sequences(DS,Seqs) :-
|
Daniel@0
|
27 kerndata:dataset_sequences(DS,Seqs).
|
Daniel@0
|
28
|
Daniel@0
|
29
|
Daniel@0
|
30
|
Daniel@0
|
31 write_dataset_sequences(DS) :-
|
Daniel@0
|
32 dataset_sequences(DS,SS),
|
Daniel@0
|
33 with_stream_encoding(current_output,octet,
|
Daniel@0
|
34 maplist(write_seq(notenums),SS)).
|
Daniel@0
|
35
|
Daniel@0
|
36 write_dataset(Prep,DS) :-
|
Daniel@0
|
37 dataset_sequences(DS,SS),
|
Daniel@0
|
38 with_stream_encoding(current_output,octet,
|
Daniel@0
|
39 maplist(write_seq(Prep),SS)).
|
Daniel@0
|
40
|
Daniel@0
|
41 write_item(Prep,Item) :-
|
Daniel@0
|
42 item_sequence(Item,Sequence),
|
Daniel@0
|
43 write_seq(Prep,Sequence).
|
Daniel@0
|
44
|
Daniel@0
|
45 write_seq(notenums,NS) :-
|
Daniel@0
|
46 write_bytes(NS),
|
Daniel@0
|
47 write_bytes([255]).
|
Daniel@0
|
48
|
Daniel@0
|
49 write_seq(intervals,NS) :-
|
Daniel@0
|
50 nth1(1,NS,N1),
|
Daniel@0
|
51 nnums_ivals(NS,IS),
|
Daniel@0
|
52 append(IS2,[end],IS),
|
Daniel@0
|
53 maplist(plus(127),IS2,CS),
|
Daniel@0
|
54 write_bytes([N1|CS]),
|
Daniel@0
|
55 write_bytes([255]).
|
Daniel@0
|
56
|
Daniel@0
|
57 ds_complexity(Method,Prep,DS,K) :-
|
Daniel@0
|
58 complexity(Method,
|
Daniel@0
|
59 write_dataset(Prep,DS),
|
Daniel@0
|
60 K).
|
Daniel@0
|
61
|
Daniel@0
|
62 ds_conditional_complexity(Method,Prep,Ref,DS,K) :-
|
Daniel@0
|
63 conditional_complexity(Method,
|
Daniel@0
|
64 write_dataset(Prep,Ref),
|
Daniel@0
|
65 write_dataset(Prep,DS),
|
Daniel@0
|
66 K).
|
Daniel@0
|
67
|
Daniel@0
|
68 % ds_mutual_information(Method,Prep,DS1,DS2,I) :-
|
Daniel@0
|
69 % mutual_information(Method,
|
Daniel@0
|
70 % write_dataset(Prep,DS1),
|
Daniel@0
|
71 % write_dataset(Prep,DS2),
|
Daniel@0
|
72 % I).
|
Daniel@0
|
73
|
Daniel@0
|
74 arg_min(K-Meth,Goal,KMin-Best) :-
|
Daniel@0
|
75 aggregate_all(min(K,Meth),(Goal,Meth\=naive(_,_)),min(KMin,Best)).
|
Daniel@0
|
76
|
Daniel@0
|
77 :- use_module(library(lambda)).
|
Daniel@0
|
78 :- use_module(library(mlserver)).
|
Daniel@0
|
79 :- use_module(library(uri)).
|
Daniel@0
|
80
|
Daniel@0
|
81 exp(conditioning_scat(DS,Prep,Ref)) :-
|
Daniel@0
|
82 dataset_items(DS,Items),
|
Daniel@0
|
83 findall([KMin,CKMin],
|
Daniel@0
|
84 ( member(I,Items),
|
Daniel@0
|
85 min_complexity(_,write_item(Prep,I),KMin),
|
Daniel@0
|
86 min_conditional_complexity(_,write_dataset(Prep,Ref),
|
Daniel@0
|
87 write_item(Prep,I),CKMin)
|
Daniel@0
|
88 ), XX),
|
Daniel@0
|
89 ??scat(transpose(arr(XX))),
|
Daniel@0
|
90 ??xlabel(q(complexity)),
|
Daniel@0
|
91 ??ylabel(q('conditional complexity')).
|
Daniel@0
|
92
|
Daniel@0
|
93 exp(relative_erasure(DS,Prep)) :-
|
Daniel@0
|
94 dataset_items(DS,Items),
|
Daniel@0
|
95 findall(CKRel,
|
Daniel@0
|
96 ( select(I,Items,Rest),
|
Daniel@0
|
97 min_complexity(_,write_item(Prep,I),KMin),
|
Daniel@0
|
98 min_conditional_complexity(_,maplist(write_item(Prep),Rest),
|
Daniel@0
|
99 write_item(Prep,I),CKMin),
|
Daniel@0
|
100 CKRel is 1- CKMin/KMin
|
Daniel@0
|
101 ), XX),
|
Daniel@0
|
102 ??barh(XX),
|
Daniel@0
|
103 ??xlabel(q('1 - relative erasure complexity')),
|
Daniel@0
|
104 item_yticks(Items).
|
Daniel@0
|
105
|
Daniel@0
|
106 exp(odd_one_out(Prep,DS,DS2,N)) :-
|
Daniel@0
|
107 dataset_items(DS,Items),
|
Daniel@0
|
108 dataset_items(DS2,Items2),
|
Daniel@0
|
109 nth1(N,Items2,OddBall),
|
Daniel@0
|
110 AllItems=[OddBall|Items],
|
Daniel@0
|
111 findall(CKRel,
|
Daniel@0
|
112 ( select(I,AllItems,Rest),
|
Daniel@0
|
113 min_complexity(_,write_item(Prep,I),KMin),
|
Daniel@0
|
114 min_conditional_complexity(_,maplist(write_item(Prep),Rest),
|
Daniel@0
|
115 write_item(Prep,I),CKMin),
|
Daniel@0
|
116 CKRel is 1 - CKMin/KMin
|
Daniel@0
|
117 ), XX),
|
Daniel@0
|
118 ??barh(XX),
|
Daniel@0
|
119 ??xlabel(q('1 - relative erasure complexity')),
|
Daniel@0
|
120 item_yticks(AllItems).
|
Daniel@0
|
121
|
Daniel@0
|
122 exp(erasure(DS,Prep)) :-
|
Daniel@0
|
123 dataset_items(DS,Items),
|
Daniel@0
|
124 findall([KMin,CKMin],
|
Daniel@0
|
125 ( select(I,Items,Rest),
|
Daniel@0
|
126 min_complexity(_,write_item(Prep,I),KMin),
|
Daniel@0
|
127 min_conditional_complexity(_,maplist(write_item(Prep),Rest),
|
Daniel@0
|
128 write_item(Prep,I),CKMin)
|
Daniel@0
|
129 ), XX),
|
Daniel@0
|
130 ??barh(transpose(arr(XX))),
|
Daniel@0
|
131 ??legend(cell([q(isolated),q(erasure)])),
|
Daniel@0
|
132 ??xlabel(q(bits)),
|
Daniel@0
|
133 item_yticks(Items).
|
Daniel@0
|
134
|
Daniel@0
|
135 exp(compressibility(DS,Prep,Ref)) :-
|
Daniel@0
|
136 dataset_items(DS,Items),
|
Daniel@0
|
137 findall([CKMin,KMin],
|
Daniel@0
|
138 ( member(I,Items),
|
Daniel@0
|
139 % complexity(id,write_item(Prep,I),L),
|
Daniel@0
|
140 min_complexity(_,write_item(Prep,I),KMin),
|
Daniel@0
|
141 min_conditional_complexity(_,write_dataset(Prep,Ref),
|
Daniel@0
|
142 write_item(Prep,I),CKMin)
|
Daniel@0
|
143 % arg_min(K-C, conditional_complexity(naive(C),write_dataset(Prep,Ref),
|
Daniel@0
|
144 % write_item(Prep,I),K), NCK-_)
|
Daniel@0
|
145 ), XX),
|
Daniel@0
|
146 ??barh(transpose(arr(XX))),
|
Daniel@0
|
147 item_yticks(Items),
|
Daniel@0
|
148 ??xlabel(q(bits)),
|
Daniel@0
|
149 ??legend(cell([q('delta compressed'),q(compressed)])).
|
Daniel@0
|
150
|
Daniel@0
|
151 exp(info_density(DS,Prep,Ref)) :-
|
Daniel@0
|
152 dataset_items(DS,Items),
|
Daniel@0
|
153 findall([H,HRef],
|
Daniel@0
|
154 ( member(I,Items),
|
Daniel@0
|
155 item_sequence(I,Pitches),
|
Daniel@0
|
156 length(Pitches,L),
|
Daniel@0
|
157 min_complexity(_,write_item(Prep,I),KMin),
|
Daniel@0
|
158 min_conditional_complexity(_,write_dataset(Prep,Ref),
|
Daniel@0
|
159 write_item(Prep,I),CKMin),
|
Daniel@0
|
160 H is KMin/L,
|
Daniel@0
|
161 HRef is CKMin/L
|
Daniel@0
|
162 ), XX),
|
Daniel@0
|
163 ??barh(transpose(arr(XX))),
|
Daniel@0
|
164 ??legend(cell([q(isolated),q(conditional)])),
|
Daniel@0
|
165 ??xlabel(q('bits per note')),
|
Daniel@0
|
166 item_yticks(Items).
|
Daniel@0
|
167
|
Daniel@0
|
168 exp(ds_similarity_matrix(Prep,Meth,Datasets)) :-
|
Daniel@0
|
169 ncd_matrix(ncd(Meth), write_dataset(Prep), Datasets, Matrix),
|
Daniel@0
|
170 ncd_image(Matrix),
|
Daniel@0
|
171 yticks(Datasets).
|
Daniel@0
|
172
|
Daniel@0
|
173 exp(similarity_matrix(Prep,Meth,DS)) :-
|
Daniel@0
|
174 dataset_items(DS,Items),
|
Daniel@0
|
175 ncd_matrix(ncd(Meth), write_item(Prep), Items, Matrix),
|
Daniel@0
|
176 ncd_image(Matrix),
|
Daniel@0
|
177 item_yticks(Items).
|
Daniel@0
|
178
|
Daniel@0
|
179 exp(conditional_similarity_matrix(Prep,Method,DS,Ref)) :-
|
Daniel@0
|
180 dataset_items(DS,Items),
|
Daniel@0
|
181 ncd_matrix(conditional_ncd(Method,write_dataset(Prep,Ref)), write_item(Prep), Items, Matrix),
|
Daniel@0
|
182 ncd_image(Matrix),
|
Daniel@0
|
183 item_yticks(Items).
|
Daniel@0
|
184
|
Daniel@0
|
185 exp(ds_conditional_similarity_matrix(Prep,Method,Datasets,Ref)) :-
|
Daniel@0
|
186 ncd_matrix(conditional_ncd(Method,write_dataset(Prep,Ref)), write_dataset(Prep), Datasets, Matrix),
|
Daniel@0
|
187 ncd_image(Matrix),
|
Daniel@0
|
188 yticks(Datasets).
|
Daniel@0
|
189
|
Daniel@0
|
190 ncd_image(Matrix) :- ??imagesc(1-arr(Matrix)), ??colorbar.
|
Daniel@0
|
191
|
Daniel@0
|
192 ncd_matrix(Sim,Writer,Items,Matrix) :-
|
Daniel@0
|
193 length(Items,N),
|
Daniel@0
|
194 numlist(1,N,IX),
|
Daniel@0
|
195 maplist(ncd_matrix_column(Sim,Writer,Items,IX),IX,Matrix).
|
Daniel@0
|
196
|
Daniel@0
|
197 ncd_matrix_column(Sim,Writer,Items,JX,I,Column) :-
|
Daniel@0
|
198 maplist(ncd_matrix_entry(Sim,Writer,Items,I),JX,Column).
|
Daniel@0
|
199
|
Daniel@0
|
200 ncd_matrix_entry(Sim,Writer,Items,I,J,D) :-
|
Daniel@0
|
201 ( I=J -> D=nan
|
Daniel@0
|
202 ; nth1(I,Items,XI),
|
Daniel@0
|
203 nth1(J,Items,XJ),
|
Daniel@0
|
204 call(Sim, call(Writer,XI), call(Writer,XJ), D)
|
Daniel@0
|
205 ).
|
Daniel@0
|
206
|
Daniel@0
|
207 item_yticks(Items) :-
|
Daniel@0
|
208 length(Items,NumItems),
|
Daniel@0
|
209 maplist(item_label,Items,Labels),
|
Daniel@0
|
210 ??yticks(1:NumItems,cell(Labels)).
|
Daniel@0
|
211
|
Daniel@0
|
212 item_label(Item,q(Name)) :-
|
Daniel@0
|
213 item_uri(Item,URI),
|
Daniel@0
|
214 uri_components(URI,Components),
|
Daniel@0
|
215 uri_data(path,Components,Path),
|
Daniel@0
|
216 directory_file_path(_,File,Path),
|
Daniel@0
|
217 file_name_extension(Name,_,File).
|
Daniel@0
|
218
|
Daniel@0
|
219 printfig(W,H,Name) :-
|
Daniel@0
|
220 format(atom(Path),'/Users/samer/pubs/asymmus/workshop/figs/~w.eps',[Name]),
|
Daniel@0
|
221 format(atom(Cmd),'epstopdf ~w',[Path]),
|
Daniel@0
|
222 ??fsetup(W,H,q(centimeters)),
|
Daniel@0
|
223 ??print(q('-depsc2'),q(Path)),
|
Daniel@0
|
224 shell(Cmd).
|
Daniel@0
|
225
|
Daniel@0
|
226 plot_method_rankings :-
|
Daniel@0
|
227 setof( r(MeanRank,Method,Ranks),
|
Daniel@0
|
228 ( compression:method_rankings(Method,Ranks),
|
Daniel@0
|
229 mean_list(Ranks,MeanRank)),
|
Daniel@0
|
230 Results),
|
Daniel@0
|
231 ??newplot,
|
Daniel@0
|
232 ??hold(q(on)),
|
Daniel@0
|
233 forall( nth1(I,Results,r(_,_,Ranks)),
|
Daniel@0
|
234 ??plot(Ranks,I+0.7*(rand(size(Ranks))-0.5),q('.'))),
|
Daniel@0
|
235 ??hold(q(off)),
|
Daniel@0
|
236 maplist(result_method,Results,Methods),
|
Daniel@0
|
237 yticks(Methods).
|
Daniel@0
|
238
|
Daniel@0
|
239 result_method(r(_,Method,_),Method).
|
Daniel@0
|
240
|
Daniel@0
|
241 yticks(Terms) :-
|
Daniel@0
|
242 length(Terms,N),
|
Daniel@0
|
243 maplist(term_label,Terms,Labels),
|
Daniel@0
|
244 ??yticks(1:N,cell(Labels)).
|
Daniel@0
|
245
|
Daniel@0
|
246 term_label(Term,q(Label)) :- format(atom(Label),'~w',[Term]).
|
Daniel@0
|
247
|
Daniel@0
|
248
|
Daniel@0
|
249 mean_list(L,Mean) :-
|
Daniel@0
|
250 length(L,N),
|
Daniel@0
|
251 sumlist(L,Sum),
|
Daniel@0
|
252 Mean is Sum/N.
|
Daniel@0
|
253
|
Daniel@0
|
254
|
Daniel@0
|
255 % pairwise(DS,Matrix) :-
|
Daniel@0
|
256 % dataset_items(DS,Items),
|
Daniel@0
|
257 % maplist(\I1^maplist(\I2^conditional_complexity(
|
Daniel@0
|
258
|
Daniel@0
|
259
|
Daniel@0
|
260 % rnd_state(T) :- get_rnd_state(S), rnd_state_term(S,T).
|
Daniel@0
|
261
|
Daniel@0
|
262 % with_sample(T,RV,Pred) :-
|
Daniel@0
|
263 % rnd_state_term(S1,T),
|
Daniel@0
|
264 % sample(RV,X,S1,S2),
|
Daniel@0
|
265 % set_rnd_state(S2),
|
Daniel@0
|
266 % call(Pred,X).
|
Daniel@0
|
267
|