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