annotate cpack/dml/lib/grammars.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
rev   line source
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(grammars,
Daniel@0 20 [ model_name/2
Daniel@0 21 , model_module_prep/3
Daniel@0 22 , build_options/2
Daniel@0 23 , build_subset_options/2
Daniel@0 24 , learn/6
Daniel@0 25 , learn_bpe/6
Daniel@0 26 , learn_model/7
Daniel@0 27 , model_sequence_parses/4
Daniel@0 28 , nnums_ivals/2
Daniel@0 29 , restart_prism/0
Daniel@0 30 , best_first/6
Daniel@0 31 , method_model_dataset_results/4
Daniel@0 32 , dataset_num_events/2
Daniel@0 33 ]).
Daniel@0 34
Daniel@0 35 :- multifile dataset_sequences/2.
Daniel@0 36
Daniel@0 37 :- use_module(library(memo)).
Daniel@0 38 :- use_module(library(typedef)).
Daniel@0 39 :- use_module(library(lambda)).
Daniel@0 40 :- use_module(library(plml)).
Daniel@0 41 :- use_module(library(prism/prism)).
Daniel@0 42 :- use_module(library(argutils)).
Daniel@0 43 :- use_module(library(snobol)).
Daniel@0 44
Daniel@0 45 :- type pmodule == ground.
Daniel@0 46 :- type natural == nonneg.
Daniel@0 47 :- type prep == callable.
Daniel@0 48 :- type options == ordset.
Daniel@0 49 :- type model ---> model(atom, list, prep, list(pair(ground,list(number)))).
Daniel@0 50 :- type method ---> vb(ground) ; map(ground).
Daniel@0 51 :- type matlab_method ---> vb ; map.
Daniel@0 52
Daniel@0 53 % % hmmmn.. maybe module issues here...
Daniel@0 54 % error:has_type(\Checker,Term) :- call(Checker,Term).
Daniel@0 55 error:has_type(ordset,Term) :- is_ordset(Term).
Daniel@0 56
Daniel@0 57 :- persistent_memo
Daniel@0 58 learn( +method, +pmodule, +prep, +dataset:ground, +options, -scores:list),
Daniel@0 59 learn_model( +method, +pmodule, +prep, +dataset:ground, +options, -scores:list, -model),
Daniel@0 60 dataset_num_events( +dataset:ground, -num_events:nonneg).
Daniel@0 61
Daniel@0 62 dataset_num_events(Dataset,NumEvents) :-
Daniel@0 63 dataset_sequences(Dataset,Seqs),
Daniel@0 64 maplist(length,Seqs,Lens),
Daniel@0 65 sumlist(Lens,NumEvents).
Daniel@0 66 % aggregate_all(sum(L),(member(S,Seqs),length(S,L)),NumEvents).
Daniel@0 67
Daniel@0 68 :- initialization memo_attach(memo(learned),[]).
Daniel@0 69 :- setting(timeout, number, 900, 'Time limit for learning in seconds').
Daniel@0 70
Daniel@0 71 user:file_search_path(prism,'psm').
Daniel@0 72 user:matlab_path(grammars,['stats/hmm']).
Daniel@0 73
Daniel@0 74 partition_options([],[],[],[]).
Daniel@0 75 partition_options([O|OX],[O|MO],IO,LO) :- option_class(O,model), partition_options(OX,MO,IO,LO).
Daniel@0 76 partition_options([O|OX],MO,[O|IO],LO) :- option_class(O,init), partition_options(OX,MO,IO,LO).
Daniel@0 77 partition_options([O|OX],MO,IO,[O|LO]) :- option_class(O,learn), partition_options(OX,MO,IO,LO).
Daniel@0 78
Daniel@0 79 option_class(switch_mode(_),model).
Daniel@0 80 option_class(prior_weight(_),model).
Daniel@0 81 option_class(gamut(_),model).
Daniel@0 82 option_class(leap_range(_),model).
Daniel@0 83 option_class(log_scale(_),learn).
Daniel@0 84 option_class(O,init) :- \+option_class(O,model), \+option_class(O,learn).
Daniel@0 85
Daniel@0 86 option_mlopt(gamut(X-Y),gamut:[X,Y]) :- !.
Daniel@0 87 option_mlopt(init(none),perturb:0) :- !.
Daniel@0 88 option_mlopt(init(perturb(U)),perturb:U) :- !.
Daniel@0 89 option_mlopt(F,N:V) :- F=..[N,V].
Daniel@0 90
Daniel@0 91 learn(vb(InitMeth),matlab(Function),Prepare,DataSet,Opts,[free_energy(FE)]) :- !,
Daniel@0 92 dataset_sequences(DataSet, D1),
Daniel@0 93 maplist(Prepare,D1,D),
Daniel@0 94 maplist(option_mlopt,[init(InitMeth)|Opts],Opts1),
Daniel@0 95 compileoptions(Opts1,Opts2),
Daniel@0 96 [float(FE)]===feval(@Function,cell(D),Opts2).
Daniel@0 97
Daniel@0 98 % method dependent options
Daniel@0 99
Daniel@0 100 learn(Method,Module,Prepare,DataSet,Opts,Scores) :-
Daniel@0 101 member(Method,[vb(_),map(_)]),
Daniel@0 102 % prepare data
Daniel@0 103 dataset_sequences(DataSet, D1),
Daniel@0 104 maplist(Prepare,D1,D),
Daniel@0 105 % method dependent options
Daniel@0 106 method_switch_mode(Method,Mode),
Daniel@0 107 option(log_scale(LS), Opts, on),
Daniel@0 108 % load up prism and initialise
Daniel@0 109 restart_prism, load_prism(prism(Module)),
Daniel@0 110 #init_model([switch_mode(Mode)|Opts]),
Daniel@0 111 #init_switches(Opts),
Daniel@0 112 set_prism_flag(log_scale,LS),
Daniel@0 113 % allow 15 minutes for learning
Daniel@0 114 setting(timeout, TimeLimit),
Daniel@0 115 get_time(Time),
Daniel@0 116 debug(learn,'Calling PRISM with time limit ~w at ~@...',
Daniel@0 117 [TimeLimit, format_time(current_output,'%T',Time)]),
Daniel@0 118 call_with_time_limit(TimeLimit, prism_learn(Method, D, [], Scores)).
Daniel@0 119
Daniel@0 120 method_switch_mode(vb(_),a).
Daniel@0 121 method_switch_mode(map(_),d).
Daniel@0 122
Daniel@0 123 learn_model(Method,Module,Prepare,DataSet,Opts,Scores,model(Module,ModelOpts,Prepare,Counts)) :-
Daniel@0 124 % must re-compute to get final state
Daniel@0 125 compute(learn(Method,Module,Prepare,DataSet,Opts,Scores)),
Daniel@0 126 partition_options(Opts,ModelOpts,_,_),
Daniel@0 127 get_prism_state(ps(_,_,Counts1,_,_,_)),
Daniel@0 128 map_filter(unfixed_count,Counts1,Counts).
Daniel@0 129
Daniel@0 130 unfixed_count(sw(SW,a,set(unfixed,Counts)), SW-Counts).
Daniel@0 131
Daniel@0 132 model_initial_state(model(Module,MO,_,_),State) :-
Daniel@0 133 restart_prism,
Daniel@0 134 load_prism(prism(Module)),
Daniel@0 135 #init_model([switch_mode(a)|MO]),
Daniel@0 136 get_prism_state(State).
Daniel@0 137
Daniel@0 138 with_model_data(model(Module,MO,Prepare,Counts),Data,Goal) :-
Daniel@0 139 restart_prism, load_prism(prism(Module)),
Daniel@0 140 #init_model([switch_mode(a)|MO]),
Daniel@0 141 #maplist(SW-C,set_sw_a(SW,C),Counts),
Daniel@0 142 call(Prepare,Data,D),
Daniel@0 143 call(Goal,D).
Daniel@0 144
Daniel@0 145 learn_bpe(Method,Module,Prepare,DataSet,Opts,BPE) :-
Daniel@0 146 browse(learn(Method,Module,Prepare,DataSet,Opts,Scores)),
Daniel@0 147 catch( bits_per_event(Method,DataSet,Scores,BPE), _, fail).
Daniel@0 148
Daniel@0 149 bits_per_event(Method,DS,Scores,BPE) :-
Daniel@0 150 dataset_num_events(DS,NumEvents),
Daniel@0 151 score(Method,NumEvents,Scores,BPE).
Daniel@0 152
Daniel@0 153 score(map(_),NumEvents,Scores,BitsPerEvent) :-
Daniel@0 154 member(log_lik(LL), Scores),
Daniel@0 155 BitsPerEvent is -(LL/NumEvents)/log(2).
Daniel@0 156
Daniel@0 157 score(vb(_),NumEvents,Scores,BitsPerEvent) :-
Daniel@0 158 member(free_energy(LL), Scores),
Daniel@0 159 BitsPerEvent is -(LL/NumEvents)/log(2).
Daniel@0 160
Daniel@0 161 score(vb_pm(_),NumEvents,Scores,BitsPerEvent) :-
Daniel@0 162 member(free_energy(LL), Scores),
Daniel@0 163 BitsPerEvent is -(LL/NumEvents)/log(2).
Daniel@0 164
Daniel@0 165 %% tree_syntax(+Mod:module,+Tree:prism_tree,-Syntax:tree) is det.
Daniel@0 166 %
Daniel@0 167 % Create a parse tree from a PRISM Viterbi tree.
Daniel@0 168 % Works for models gilbert1, gilbert2, gilbert2a, gilbert3 and gilbert2m.
Daniel@0 169 tree_syntax(Mod,[s(_),TT],T2) :- tree_parse_tree(Mod,TT,T2).
Daniel@0 170
Daniel@0 171 tree_parse_tree(_,msw(i(I),terminal),node(t(I),[])).
Daniel@0 172 tree_parse_tree(Mod,[pp(s,_,_)|Children],Term) :- member(Mod,[gilbert2,gilbert2a,gilbert3,gilbert2m]), !,
Daniel@0 173 member(msw(s,Rule),Children),
Daniel@0 174 map_filter(tree_parse_tree(Mod),Children,CN),
Daniel@0 175 ( Rule=grow -> CN=[Child1,T1], T1=node(s,Tail), Term=node(s,[Child1|Tail])
Daniel@0 176 ; Rule=last -> CN=[Child], Term=node(s,[Child])
Daniel@0 177 ).
Daniel@0 178 tree_parse_tree(Mod,[pp(s,_,_)|Children],Term) :- Mod=gilbert1, !,
Daniel@0 179 member(msw(s,Rule),Children),
Daniel@0 180 map_filter(tree_parse_tree(Mod),Children,CN),
Daniel@0 181 ( Rule=grow -> CN=[Child1,T1], T1=node(s,Tail), Term=node(s,[Child1|Tail])
Daniel@0 182 ; Rule=first -> CN=[], Term=node(s,[])
Daniel@0 183 ).
Daniel@0 184 tree_parse_tree(Mod,[pp(H,_,_)|Children],Term) :- !,
Daniel@0 185 map_filter(tree_parse_tree(Mod),Children,CN),
Daniel@0 186 member(msw(H,Rule1),Children),
Daniel@0 187 ( Rule1=terminal -> Rule=t; Rule=Rule1),
Daniel@0 188 Term = node(H-Rule,CN).
Daniel@0 189
Daniel@0 190 :- volatile_memo model_sequence_parses(+ground,+list(ground),+natural,-ground).
Daniel@0 191
Daniel@0 192 model_sequence_parses(Model,Seq,N,Parses) :-
Daniel@0 193 Model=model(Mod,_,_,_),
Daniel@0 194 with_model_data(Model,Seq,parses(Mod,N,Parses)).
Daniel@0 195
Daniel@0 196 parses(Mod,N,Parses,Goal) :-
Daniel@0 197 succ(N,M),
Daniel@0 198 findall(P-T,viterbi_tree(M,Goal,P,[],T),ProbsTrees),
Daniel@0 199 append(NProbsTrees,[P0-_],ProbsTrees),
Daniel@0 200 maplist(tree_parse(Mod,P0),NProbsTrees,Parses).
Daniel@0 201
Daniel@0 202 tree_parse(Mod,P0,P-T,RP-S) :- tree_syntax(Mod,T,S), RP is P/P0.
Daniel@0 203
Daniel@0 204
Daniel@0 205 % model declarations
Daniel@0 206 decl_model(markov(nnum,0), p1gram, markovp, with_nnums(s0)).
Daniel@0 207 decl_model(markov(nnum,1), p2gram, markovp, with_nnums(s1)).
Daniel@0 208 decl_model(markov(ival,0), i1gram, markovi, with_ivals(s0)).
Daniel@0 209 decl_model(markov(ival,1), i2gram, markovi, with_ivals(s1)).
Daniel@0 210 decl_model(gilbert(1), gilbert1, gilbert1, with_pre_ivals(s)).
Daniel@0 211 decl_model(gilbert(2), gilbert2, gilbert2, with_ivals(s)).
Daniel@0 212 decl_model(gilbert(3), gilbert3, gilbert3, with_ivals(s)).
Daniel@0 213 decl_model(gilbert(2-a), gilbert2a, gilbert2a, with_ivals(s)).
Daniel@0 214 decl_model(gilbert(2-m), gilbert2m, gilbert2m, with_ivals(s)).
Daniel@0 215 % decl_model(gilbert(4), gilbert1, gilbert1a, with_pre_ivals(s)).
Daniel@0 216 % decl_model(gilbert(5), gilbert2, gilbert2a, with_ivals(s)).
Daniel@0 217 % decl_model(gilbert(6), gilbert3, gilbert3a, with_ivals(s)).
Daniel@0 218 decl_model(hmm(nnum), phmm, phmm, with_nnums(s)).
Daniel@0 219 decl_model(hmm(nnum,NS), Name, phmm, with_nnums(s)) :- atom_concat(phmm,NS,Name).
Daniel@0 220 %decl_model(hmm(ival), ihmm, ihmm, with_ivals(s)).
Daniel@0 221 decl_model(matlab(p1gram), 'ml-p1gram', matlab(p1gram), (=)).
Daniel@0 222 decl_model(matlab(p2gram), 'ml-p2gram', matlab(p2gram), (=)).
Daniel@0 223 decl_model(matlab(phmm), 'ml-phmm', matlab(phmm), (=)).
Daniel@0 224
Daniel@0 225 model_name(Model,Name) :- decl_model(Model,Name,_,_).
Daniel@0 226 model_module_prep(Model,Module,Prepare) :- decl_model(Model,_,Module,Prepare).
Daniel@0 227
Daniel@0 228 with_nnums(Head, Seq, Head1) :-
Daniel@0 229 addargs(Head,[Seq],Head1).
Daniel@0 230
Daniel@0 231 with_ivals(Head, Seq, Head1) :-
Daniel@0 232 nnums_ivals(Seq,Seq1),
Daniel@0 233 addargs(Head,[Seq1],Head1).
Daniel@0 234
Daniel@0 235 with_pre_ivals(Head, Seq, Head1) :-
Daniel@0 236 nnums_pre_ivals(Seq,Seq1),
Daniel@0 237 addargs(Head,[Seq1],Head1).
Daniel@0 238
Daniel@0 239 nnums_ivals(NNums,Ivals) :- nnums_post_ivals(NNums,Ivals).
Daniel@0 240 nnums_post_ivals(NNums,Ivals) :- phrase((ivals(NNums),[end]),Ivals,[]).
Daniel@0 241 nnums_pre_ivals(NNums,Ivals) :- phrase(([start],ivals(NNums)),Ivals,[]).
Daniel@0 242
Daniel@0 243 ivals([X0,X1|Xs]) --> {I1 is X1-X0}, [I1], ivals([X1|Xs]).
Daniel@0 244 ivals([_]) --> [].
Daniel@0 245
Daniel@0 246 % NB option defaults here must match those in PRISM source files.
Daniel@0 247 model_options(markov(nnum,_)) -->
Daniel@0 248 optopt(prior_shape, [binomial+0.1*uniform, binomial+uniform, uniform]),
Daniel@0 249 optopt(gamut,[40-100]).
Daniel@0 250
Daniel@0 251 model_options(markov(ival,_)) -->
Daniel@0 252 optopt(prior_shape, [uniform, binomial+uniform, binomial+0.1*uniform]).
Daniel@0 253
Daniel@0 254 model_options(gilbert(_)) -->
Daniel@0 255 [leap_range((-20)-(20))],
Daniel@0 256 optopt(leap_shape, [uniform, binomial+uniform, binomial+0.1*uniform]),
Daniel@0 257 optopt(pass_shape, [binomial, binomial+uniform, binomial+0.1*uniform]).
Daniel@0 258
Daniel@0 259 model_options(hmm(nnum)) -->
Daniel@0 260 optopt(prior_shape, [binomial+0.1*uniform, binomial+uniform, uniform]),
Daniel@0 261 anyopt(num_states, [1,2,3,5,7,12,18]),
Daniel@0 262 optopt(trans_self, [1]),
Daniel@0 263 % optopt(gamut,[40-100]).
Daniel@0 264 % anyopt(trans_self, [1]),
Daniel@0 265 anyopt(gamut,[40-100]).
Daniel@0 266
Daniel@0 267 model_options(hmm(nnum,NS)) -->
Daniel@0 268 [num_states(NS)],
Daniel@0 269 optopt(prior_shape, [binomial+0.1*uniform, binomial+uniform, uniform]),
Daniel@0 270 optopt(trans_self, [1]),
Daniel@0 271 % optopt(gamut,[40-100]).
Daniel@0 272 % anyopt(trans_self, [1]),
Daniel@0 273 anyopt(gamut,[40-100]).
Daniel@0 274
Daniel@0 275 model_options(hmm(ival)) -->
Daniel@0 276 optopt(prior_shape, [binomial+0.1*uniform, binomial+uniform, uniform]),
Daniel@0 277 anyopt(num_states, [5,7,12,24]),
Daniel@0 278 [leap_range((-20)-(20))].
Daniel@0 279
Daniel@0 280 model_options(matlab(p1gram)) -->
Daniel@0 281 optopt(prior_shape, [binomial+0.1*uniform, binomial+uniform, uniform]),
Daniel@0 282 optopt(gamut,[40-100]).
Daniel@0 283
Daniel@0 284 model_options(matlab(p2gram)) -->
Daniel@0 285 optopt(prior_shape, [binomial+0.1*uniform, binomial+uniform, uniform]),
Daniel@0 286 optopt(gamut,[40-100]).
Daniel@0 287
Daniel@0 288 model_options(matlab(phmm)) -->
Daniel@0 289 optopt(prior_shape, [binomial+0.1*uniform, binomial+uniform, uniform]),
Daniel@0 290 anyopt(num_states, [1,2,3,5,7,12,18]),
Daniel@0 291 optopt(gamut,[40-100]).
Daniel@0 292
Daniel@0 293 model_subset_options(markov(nnum,_)) --> [prior_shape(binomial+0.1*uniform)].
Daniel@0 294 model_subset_options(markov(ival,_)) --> [prior_shape(binomial+0.1*uniform)].
Daniel@0 295 model_subset_options(gilbert(_)) --> [].
Daniel@0 296 model_subset_options(hmm(nnum)) -->
Daniel@0 297 [prior_shape(binomial+0.1*uniform)],
Daniel@0 298 anyopt(num_states,[2,5,7,12,18]).
Daniel@0 299 model_subset_options(hmm(ival)) -->
Daniel@0 300 [prior_shape(binomial+0.1*uniform), leap_range((-20)-(20))],
Daniel@0 301 anyopt(num_states,[2,5,7,12]).
Daniel@0 302
Daniel@0 303 build_options(Model,Opts) :-
Daniel@0 304 build_options(Model,Opts1,[]),
Daniel@0 305 sort(Opts1,Opts).
Daniel@0 306
Daniel@0 307 build_options(Model) -->
Daniel@0 308 optopt(prior_weight,[0.3,3,10]), % NB have removed 0.1 and 30
Daniel@0 309 model_options(Model).
Daniel@0 310
Daniel@0 311 build_subset_options(Model,Opts) :-
Daniel@0 312 build_subset_options(Model,Opts1,[]),
Daniel@0 313 sort(Opts1,Opts).
Daniel@0 314
Daniel@0 315 build_subset_options(Model) -->
Daniel@0 316 optopt(prior_weight,[0.1,0.3,3,10,30]),
Daniel@0 317 model_subset_options(Model).
Daniel@0 318
Daniel@0 319 anyopt(Name,Vals) --> {maplist(\X^Y^(Y=..[Name,X]),Vals,Opts)}, any(Opts).
Daniel@0 320 optopt(Name,Vals) --> []; anyopt(Name,Vals).
Daniel@0 321
Daniel@0 322 best_first(Meth,Mod,Prepare,DS,Opts,learn(Meth,Mod,Prepare,DS,Opts,F)) :-
Daniel@0 323 order_by([asc(F)], learn_bpe(Meth,Mod,Prepare,DS,Opts,F)).
Daniel@0 324
Daniel@0 325 /* TODO:
Daniel@0 326 Sort out HMM init options. They are all wrong:
Daniel@0 327 init_shape : shape of prior over initial state {uniform}
Daniel@0 328 trans_shape : shape of prior over transition distribution {uniform}
Daniel@0 329 trans_persistence : add self transtion counts {0,1,3}
Daniel@0 330 init_noise : perturbation of initial obs counts {0,0.1}
Daniel@0 331 restarts: {3}
Daniel@0 332
Daniel@0 333
Daniel@0 334
Daniel@0 335 compare p2gram with hmm(1)
Daniel@0 336 */
Daniel@0 337
Daniel@0 338
Daniel@0 339 %% map_filter(+P:pred(A,B),+Xs:list(A),-Ys:list(B)) is det.
Daniel@0 340 %
Daniel@0 341 % map_filter(P,Xs,Ys) is similar to maplist(P,Xs,Ys), except that P is allowed to
Daniel@0 342 % fail and the resulting list Ys contains only those elements Y for which call(P,X,Y).
Daniel@0 343 % P is used as if it was semi-deterministic: only the first solution is accepted.
Daniel@0 344 map_filter(_,[],[]).
Daniel@0 345 map_filter(P,[X|XX],[Y|YY]) :- call(P,X,Y), !, map_filter(P,XX,YY).
Daniel@0 346 map_filter(P,[_|XX],YY) :- map_filter(P,XX,YY).
Daniel@0 347
Daniel@0 348 user:file_search_path(home,X) :- expand_file_name('~',[X]).
Daniel@0 349 user:file_search_path(prism,home('src/probprog/prism/psm')).
Daniel@0 350 restart_prism :- prism_start('prism.log').
Daniel@0 351
Daniel@0 352 retry_on_error(G,M) :-
Daniel@0 353 catch((restart_prism,G,Status=ok), Ex, Status=error(Ex)),
Daniel@0 354 ( Status=ok -> true
Daniel@0 355 ; format('*** terminated with ~w.\n',[Ex]),
Daniel@0 356 shell('say ALERT: THERE WAS AN ERROR!'),
Daniel@0 357 ( succ(N,M) -> retry_on_error(G,N)
Daniel@0 358 ; writeln('failing after too many retries.'),
Daniel@0 359 shell('say ALERT: I AM GIVING UP!'),
Daniel@0 360 shell('say ALERT: I AM GIVING UP!'),
Daniel@0 361 fail
Daniel@0 362 )
Daniel@0 363 ).
Daniel@0 364
Daniel@0 365 %% summary_array(+Meth:method,+Models:list(model),+Datasets:list(dataset),-Summary) is det.
Daniel@0 366 summary_array(Meth,Models,Datasets,arr(Summary)) :-
Daniel@0 367 maplist( \Model^RR^maplist(\DS^{arr(R)}^method_model_dataset_results(Meth,Model,DS,R),Datasets,RR), Models,Summary).
Daniel@0 368
Daniel@0 369 %% method_model_dataset_results(+Method,+Model,+Dataset,Results:list(list(number))) is det.
Daniel@0 370 method_model_dataset_results(Meth,Model,DS,Results) :- bagof( Row, datum(Meth,Model,DS,Row), Results).
Daniel@0 371
Daniel@0 372 %% datum(+Method:method,+Model:model,+Dataset,-Datum:list(number)) is nondet.
Daniel@0 373 %
Daniel@0 374 % Maps trained models to a numerical tuple consisting of
Daniel@0 375 % the free energy (in bits per event), the prior weight parameter, and one or two
Daniel@0 376 % shape parameters, depending on the model. The shape parameter is 0 for a uniform
Daniel@0 377 % prior, 1 for a binomial prior, and between 0 and 1 for linear interpolation between
Daniel@0 378 % the two.
Daniel@0 379 %
Daniel@0 380 % Grammar models have leap_shape and pass_shape parameters, while the others
Daniel@0 381 % have a single prior_shape parameter.
Daniel@0 382 datum(Meth,gilbert(I),DS,[FE,W,K1,K2]) :-
Daniel@0 383 model_module_prep(gilbert(I),Mod,Prep),
Daniel@0 384 learn_bpe(Meth,Mod,Prep,DS,Opts,FE),
Daniel@0 385 option(prior_weight(W),Opts,1),
Daniel@0 386 option(leap_shape(Sh1),Opts,binomial),
Daniel@0 387 option(pass_shape(Sh2),Opts,uniform),
Daniel@0 388 shape_param(Sh1,K1),
Daniel@0 389 shape_param(Sh2,K2).
Daniel@0 390
Daniel@0 391 datum(Meth,markov(Rep,Ord),DS,[FE,W,K]) :-
Daniel@0 392 model_module_prep(markov(Rep,Ord),Mod,Prep),
Daniel@0 393 learn_bpe(Meth,Mod,Prep,DS,Opts,FE),
Daniel@0 394 option(prior_weight(W),Opts,1),
Daniel@0 395 option(prior_shape(Sh),Opts,binomial),
Daniel@0 396 shape_param(Sh,K).
Daniel@0 397
Daniel@0 398 datum(Meth,hmm(Rep),DS,[FE,W,K]) :-
Daniel@0 399 model_module_prep(hmm(Rep),Mod,Prep),
Daniel@0 400 learn_bpe(Meth,Mod,Prep,DS,Opts,FE),
Daniel@0 401 option(prior_weight(W),Opts,1),
Daniel@0 402 option(prior_shape(Sh),Opts,binomial),
Daniel@0 403 shape_param(Sh,K).
Daniel@0 404
Daniel@0 405 datum(Meth,hmm(Rep,NS),DS,[FE,W,K]) :-
Daniel@0 406 model_module_prep(hmm(Rep),Mod,Prep),
Daniel@0 407 learn_bpe(Meth,Mod,Prep,DS,Opts,FE),
Daniel@0 408 option(num_states(NS),Opts),
Daniel@0 409 option(prior_weight(W),Opts,1),
Daniel@0 410 option(prior_shape(Sh),Opts,binomial),
Daniel@0 411 shape_param(Sh,K).
Daniel@0 412
Daniel@0 413 datum(Meth,matlab(F),DS,[FE,W,K]) :-
Daniel@0 414 model_module_prep(matlab(F),Mod,Prep),
Daniel@0 415 learn_bpe(Meth,Mod,Prep,DS,Opts,FE),
Daniel@0 416 option(prior_weight(W),Opts,1),
Daniel@0 417 option(prior_shape(Sh),Opts,binomial),
Daniel@0 418 shape_param(Sh,K).
Daniel@0 419
Daniel@0 420 shape_param(uniform,0).
Daniel@0 421 shape_param(binomial,1).
Daniel@0 422 shape_param(binomial+uniform,0.5).
Daniel@0 423 shape_param(uniform+binomial,0.5).
Daniel@0 424 shape_param(binomial+K*uniform,Lam) :- Lam = 1/(1+K).
Daniel@0 425