1:- module(test_kbest, 2 [test_kbest/0]). 3:- use_module(library(plunit)). 4 5test_kbest:- 6 run_tests([ 7 kbest_win, 8 kbest_hmm, 9 kbest_coin, 10 kbest_mendel 11 ]). 12:-use_module(library(cplint_test/cplint_test)). 13 14:- begin_tests(kbest_win, []). 15 16:-ensure_loaded(library(examples/kbest_win)). 17test(win,[true(Exp=[0.36000000000000004-[rule(0, red, [red:0.4, '':0.6], []), 18rule(1, green, [green:0.9, '':0.09999999999999998], [])]])]):- 19 run((kbest(win,1,Exp),true)). 20 21test(winP,[true(Exp=[0.36000000000000004-[rule(0, red, [red:0.4, '':0.6], []), 22rule(1, green, [green:0.9, '':0.09999999999999998], [])]])]):- 23 run((kbest(win,1,P,Exp),close_to(P,0.36))). 24 25test(win2,[true(Exp=[0.36000000000000004-[rule(0, red, [red:0.4, '':0.6], []), 26 rule(1, green, [green:0.9, '':0.09999999999999998], [])], 27 0.30000000000000004-[rule(2, blue, [blue:0.5, '':0.5], []), 28 rule(3, yellow, [yellow:0.6, '':0.4], [])]])]):- 29 kbest(win,2,Exp). 30 31test(win2P,[true(Exp=[0.36000000000000004-[rule(0, red, [red:0.4, '':0.6], []), 32 rule(1, green, [green:0.9, '':0.09999999999999998], [])], 33 0.30000000000000004-[rule(2, blue, [blue:0.5, '':0.5], []), 34 rule(3, yellow, [yellow:0.6, '':0.4], [])]])]):- 35 run((kbest(win,2,P,Exp),close_to(P,0.552))). 36 37:- end_tests(kbest_win). 38 39:- begin_tests(kbest_hmm, []). 40 41:-ensure_loaded(library(examples/kbest_hmm)). 42test(a_g_g):- 43 run((kbest(hmm([a,g,g]),1,P,_Exp),close_to(P,0.000405) 44 )). 45 46test(a_a_a):- 47 run((kbest(hmm([a,a,a]),1,P,_Exp),close_to(P,0.0008000000000000003) 48 )). 49 50:- end_tests(kbest_hmm). 51 52:- begin_tests(kbest_coin, []). 53 54:-ensure_loaded(library(examples/kbest_coin)). 55test(h_c,[true( Exp = [0.45000000000000007-[rule(0, heads(coin), [heads(coin):0.5, tails(coin):0.5], [toss(coin), \+biased(coin)]), 56 rule(2, fair(coin), [fair(coin):0.9, biased(coin):0.1], [])]])]):- 57 run((kbest(heads(coin),1,Prob,Exp),close_to(Prob,0.45))). 58 59:- end_tests(kbest_coin). 60 61:- begin_tests(kbest_mendel, []). 62 63:-ensure_loaded(library(examples/kbest_mendel)). 64test(s_p,[true(Exp = [0.5-[rule(0, cg(s, 1, p), [cg(s, 1, p):0.5, cg(s, 1, w):0.5], 65 [mother(m, s), cg(m, 1, p), cg(m, 2, w)])]])]):- 66 run((kbest(color(s,purple),1,Prob,Exp),close_to(Prob,0.5))). 67 68test(s_w,[true(Exp = [0.25-[rule(0, cg(s, 1, w), [cg(s, 1, p):0.5, cg(s, 1, w):0.5], 69 [mother(m, s), cg(m, 1, p), cg(m, 2, w)]), 70 rule(1, cg(s, 2, w), [cg(s, 2, w):0.5, cg(s, 2, p):0.5], 71 [father(f, s), cg(f, 1, w), cg(f, 2, p)])]])]):- 72 run((kbest(color(s,white),1,Prob,Exp),close_to(Prob,0.25))). 73 74test(s_p_P,[true(Exp = [0.5-[rule(1, cg(s, 2, p), [cg(s, 2, w):0.5, cg(s, 2, p):0.5], 75[father(f, s), cg(f, 1, w), cg(f, 2, p)])], 760.5-[rule(0, cg(s, 1, p), [cg(s, 1, p):0.5, cg(s, 1, w):0.5], 77[mother(m, s), cg(m, 1, p), cg(m, 2, w)])]])]):- 78 run((kbest(color(s,purple),2,Prob,Exp),close_to(Prob,0.75))). 79 80test(s_w_P,[true(Exp = [0.25-[rule(0, cg(s, 1, w), [cg(s, 1, p):0.5, cg(s, 1, w):0.5], 81 [mother(m, s), cg(m, 1, p), cg(m, 2, w)]), 82 rule(1, cg(s, 2, w), [cg(s, 2, w):0.5, cg(s, 2, p):0.5], 83 [father(f, s), cg(f, 1, w), cg(f, 2, p)])]])]):- 84 run((kbest(color(s,white),2,Prob,Exp),close_to(Prob,0.25))). 85 86:- end_tests(kbest_mendel).