18
22:- multifile setting_trill_default/2. 23setting_trill_default(det_rules,[o_rule,and_rule,unfold_rule,add_exists_rule,forall_rule,forall_plus_rule,exists_rule,min_rule]).
24setting_trill_default(nondet_rules,[or_rule,max_rule,ch_rule]).
25
26set_up(M):-
27 utility_translation:set_up(M),
28 init_delta(M),
29 M:(dynamic exp_found/2, setting_trill/2, tab_end/1, query_option/2),
30 retractall(M:setting_trill(_,_)),
31 retractall(M:query_option(_,_)),
32 retractall(M:tab_end(_)).
33 34
35clean_up(M):-
36 utility_translation:clean_up(M),
37 M:(dynamic exp_found/2, setting_trill/2, tab_end/1, query_option/2),
38 retractall(M:exp_found(_,_)),
39 retractall(M:setting_trill(_,_)),
40 retractall(M:query_option(_,_)),
41 retractall(M:tab_end(_)),
42 retractall(M:delta(_,_)).
43
47
49find_n_explanations(M,QueryType,QueryArgs,Expls,all):-
50 !, 51 findall(Expl,find_single_explanation(M,QueryType,QueryArgs,Expl),Expls).
52
54find_n_explanations(M,QueryType,QueryArgs,Expl,bt):-
55 !, 56 find_single_explanation(M,QueryType,QueryArgs,Expl).
57
59find_n_explanations(M,QueryType,QueryArgs,Expls,N):-
60 (number(N) -> 61 (findnsols(N,Expl,find_single_explanation(M,QueryType,QueryArgs,Expl),Expls),!) 62 ;
63 (print_message(warning,wrong_number_max_expl),!,false)
64 ).
65
66
68all_sub_class_int(M:ClassEx,SupClassEx,Exps):-
69 all_unsat_int(M:intersectionOf([ClassEx,complementOf(SupClassEx)]),Exps).
70
71all_instanceOf_int(M:ClassEx,IndEx,Exps):-
72 findall(Expl,instanceOf(M:ClassEx,IndEx,Expl),Exps).
73
74all_property_value_int(M:PropEx,Ind1Ex,Ind2Ex,Exps):-
75 findall(Expl,property_value(M:PropEx,Ind1Ex,Ind2Ex,Expl),Exps).
76
77all_unsat_int(M:ConceptEx,Exps):-
78 findall(Expl,unsat_internal(M:ConceptEx,Expl),Exps).
79
80
81all_inconsistent_theory_int(M:Exps):-
82 findall(Expl,inconsistent_theory(M:Expl),Exps).
83
84
85compute_prob_and_close(M,Expl,QueryOptions):-
86 M:query_option(compute_prob,expl),!,
87 get_from_query_options(QueryOptions,compute_prob,expl,Prob),
88 compute_prob_single_explanation(M,Expl,Prob),!.
89
90compute_prob_and_close(M,_,QueryOptions):-
91 M:query_option(compute_prob,query),!,
92 get_from_query_options(QueryOptions,compute_prob,query,Prob),
93 findall(Exp,M:exp_found(qp,Exp),Exps),
94 compute_prob(M,Exps,Prob),!.
95
96compute_prob_and_close(_M,_,_):-!.
97
99check_and_close(_,Expl0,Expl):-
100 dif(Expl0,[]),
101 sort(Expl0,Expl).
102
103is_expl(M,Expl):-
104 dif(Expl,[]),
105 dif(Expl,[[]]),
106 initial_expl(M,EExpl),
107 dif(Expl,EExpl).
108
125find_expls(M,[Clash|_],Tab,E):- 126 clash(M,Clash,Tab,EL0),
127 member(E0-CPs0,EL0),
128 sort(CPs0,CPs1),
129 dif(E0,[]),
130 sort(E0,E),
131 132 133 consistency_check(CPs1,[],Q),
134 135 136 ( dif(Q,['inconsistent','kb']) -> true ; print_message(warning,inconsistent)),
137 \+ M:exp_found(Q,E),
138 assert(M:exp_found(Q,E)). 139
140find_expls(M,[_Clash|Clashes],Tab,E):-
141 find_expls(M,Clashes,Tab,E).
142
144find_expls_from_tab_list(M,[],E):- 145 146 147 findall(Ex0,find_expls_from_choice_point_list(M,Ex0),L0),
148 findall(Ex1,M:exp_found(_,Ex1),L1),
149 append(L0,L1,L),
150 remove_supersets(L,Ls),
151 member(E,Ls),
152 \+ M:exp_found(_,E),
153 assert(M:exp_found(tc,E)).
154
155find_expls_from_tab_list(M,[Tab|_T],E):- 156 get_solved_clashes(Tab,Clashes),
157 member(Clash,Clashes),
158 clash(M,Clash,Tab,EL0),
159 member(E0-CPs0,EL0),
160 sort(CPs0,CPs1),
161 dif(E0,[]),
162 sort(E0,E),
163 164 165 consistency_check(CPs1,CPs2,_),
166 167 get_latest_choice(CPs2,ID,Choice),
168 subtract(CPs1,[cpp(ID,Choice)],CPs), 169 update_choice_point_list(M,ID,Choice,E,CPs),
170 fail.
171
172
173find_expls_from_tab_list(M,[_Tab|T],Expl):-
174 175 find_expls_from_tab_list(M,T,Expl).
176
177
178combine_expls_from_nondet_rules(M,cp(_,_,_,_,_,Expl),E):- 179 check_non_empty_choice(Expl,ExplList),
180 and_all_f(M,ExplList,ExplanationsList),
181 182 member(E0-Choices0,ExplanationsList),
183 sort(E0,E),
184 sort(Choices0,Choices1),
185 186 187 consistency_check(Choices1,Choices,Q),
188 (
189 dif(Choices,[]) ->
190 (
191 192 get_latest_choice(Choices,ID,Choice),
193 subtract(Choices0,[cpp(ID,Choice)],CPs), 194 update_choice_point_list(M,ID,Choice,E,CPs),
195 fail 196 ) ;
197 (
198 ( dif(Q,['inconsistent','kb']) -> true ; print_message(warning,inconsistent)),
199 \+ M:exp_found(Q,E)
200 )
201 ).
202
203find_expls_from_choice_point_list(M,E):-
204 extract_choice_point_list(M,CP),
205 (
206 combine_expls_from_nondet_rules(M,CP,E) ;
207 find_expls_from_choice_point_list(M,E)
208 ).
209
210
211check_non_empty_choice(Expl,ExplList):-
212 dict_pairs(Expl,_,PairsList),
213 findall(Ex,member(_-Ex,PairsList),ExplList),
214 \+ memberchk([],ExplList).
215
216
217check_presence_of_other_choices([],[],[]).
218
219check_presence_of_other_choices([E-[]|ExplanationsList],[E|Explanations],Choices):- !,
220 check_presence_of_other_choices(ExplanationsList,Explanations,Choices).
221
222check_presence_of_other_choices([E-CP|ExplanationsList],[E|Explanations],[CP|Choices]):-
223 check_presence_of_other_choices(ExplanationsList,Explanations,Choices).
224
225check_CP([],_).
226
227check_CP([cp(CP,N)|CPT],L):-
228 findall(cp,member(_-[cp(CP,N)|CPT],L),ExplPartsList),
229 length(ExplPartsList,N),
230 check_CP(CPT,L).
231
232
233not_already_found(_M,[],_Q,_E):-!.
234
235not_already_found(_M,[H|_T],_Q,E):-
236 subset(H,E),!,
237 fail.
238
239not_already_found(M,[H|_T],Q,E):-
240 subset(E,H),!,
241 retract(M:exp_found(Q,H)).
242
243not_already_found(M,[_H|T],Q,E):-
244 not_already_found(M,T,Q,E).
245
246
247get_latest_choice([],0,0).
248
249get_latest_choice(CPs,ID,Choice):-
250 get_latest_choice_point(CPs,0,ID),
251 get_latest_choice_of_cp(CPs,ID,0,Choice).
252
253get_latest_choice_point([],ID,ID).
254
255get_latest_choice_point([cpp(ID0,_)|T],ID1,ID):-
256 ID2 is max(ID1,ID0),
257 get_latest_choice_point(T,ID2,ID).
258
259
260get_latest_choice_of_cp([],_,C,C).
261
262get_latest_choice_of_cp([cpp(ID,C0)|T],ID,C1,C):- !,
263 C2 is max(C1,C0),
264 get_latest_choice_of_cp(T,ID,C2,C).
265
266get_latest_choice_of_cp([_|T],ID,C1,C):-
267 get_latest_choice_of_cp(T,ID,C1,C).
268
269
270remove_supersets([H|T],ExplanationsList):-
271 remove_supersets([H],T,ExplanationsList).
272
273remove_supersets(E,[],E).
274
275remove_supersets(E0,[H|T],ExplanationsList):-
276 remove_supersets_int(E0,H,E),
277 remove_supersets(E,T,ExplanationsList).
278
279remove_supersets_int(E0,H,E0):-
280 memberchk(H,E0),!.
281
282remove_supersets_int(E0,H,E0):-
283 member(H1,E0),
284 subset(H1,H),!.
285
286remove_supersets_int(E0,H,E):-
287 member(H1,E0),
288 subset(H,H1),!,
289 nth0(_,E0,H1,E1),
290 remove_supersets_int(E1,H,E).
291
292remove_supersets_int(E,H,[H|E]).
293
294
298
299consistency_check(CPs0,CPs,Q):-
300 (nth0(_,CPs0,qp,CPs) -> (Q=qp) ; (Q=['inconsistent','kb'],CPs=CPs0)).
301
302
304
308
310findClassAssertion4OWLNothing(_M,ABox,Expl):-
311 findClassAssertion('http://www.w3.org/2002/07/owl#Nothing',_Ind,Expl,ABox).
312
313
316
318:- multifile clash/4. 319
391
393
394make_expl(_,_,_,[],Expl,_,Expl).
395
396make_expl(M,Ind,S,[H|T],Expl0,ABox,Expl):-
397 findPropertyAssertion(S,Ind,H,Expl2,ABox),
398 and_f(M,Expl2,Expl0,Expl1),
399 make_expl(M,Ind,S,T,Expl1,ABox,Expl).
401
402
406
411
414:- multifile find_neg_class/2. 415
416find_neg_class(exactCardinality(N,R,C),unionOf([maxCardinality(NMax,R,C),minCardinality(NMin,R,C)])):-
417 NMax is N - 1,
418 NMin is N + 1.
419
420find_neg_class(minCardinality(N,R,C),maxCardinality(NMax,R,C)):-
421 NMax is N - 1.
422
423find_neg_class(maxCardinality(N,R,C),minCardinality(NMin,R,C)):-
424 NMin is N + 1.
425
427:- multifile find_sub_sup_class/4. 428
430find_sub_sup_class(M,exactCardinality(N,R),exactCardinality(N,S),subPropertyOf(R,S)):-
431 M:subPropertyOf(R,S).
432
434find_sub_sup_class(M,exactCardinality(N,R,C),exactCardinality(N,R,D),Ax):-
435 find_sub_sup_class(M,C,D,Ax),
436 atomic(D).
437
439find_sub_sup_class(M,exactCardinality(N,R,C),exactCardinality(N,S,C),subPropertyOf(R,S)):-
440 M:subPropertyOf(R,S).
441
443find_sub_sup_class(M,maxCardinality(N,R),maxCardinality(N,S),subPropertyOf(R,S)):-
444 M:subPropertyOf(R,S).
445
447find_sub_sup_class(M,maxCardinality(N,R,C),maxCardinality(N,R,D),Ax):-
448 find_sub_sup_class(M,C,D,Ax),
449 atomic(D).
450
452find_sub_sup_class(M,maxCardinality(N,R,C),maxCardinality(N,S,C),subPropertyOf(R,S)):-
453 M:subPropertyOf(R,S).
454
456find_sub_sup_class(M,minCardinality(N,R),minCardinality(N,S),subPropertyOf(R,S)):-
457 M:subPropertyOf(R,S).
458
460find_sub_sup_class(M,minCardinality(N,R,C),minCardinality(N,R,D),Ax):-
461 find_sub_sup_class(M,C,D,Ax),
462 atomic(D).
463
465find_sub_sup_class(M,minCardinality(N,R,C),minCardinality(N,S,C),subPropertyOf(R,S)):-
466 M:subPropertyOf(R,S).
467
469
474modify_ABox(_,Tab,sameIndividual(LF),_Expl1,Tab):-
475 length(LF,1),!.
476
477modify_ABox(M,Tab0,sameIndividual(LF),Expl1,Tab):-
478 get_abox(Tab0,ABox0),
479 ( find((sameIndividual(L),Expl0),ABox0) ->
480 ( sort(L,LS),
481 sort(LF,LFS),
482 LS = LFS,!,
483 absent(Expl0,Expl1,Expl),
484 remove_from_abox(ABox0,[(sameIndividual(L),Expl0)],ABox)
485 )
486 ;
487 (ABox = ABox0,Expl = Expl1,L = LF)
488 ),
489 add_clash_to_tableau(M,Tab0,sameIndividual(LF),Tab1),
490 set_abox(Tab1,[(sameIndividual(L),Expl)|ABox],Tab).
491
492modify_ABox(_,Tab,differentIndividuals(LF),_Expl1,Tab):-
493 length(LF,1),!.
494
495modify_ABox(M,Tab0,differentIndividuals(LF),Expl1,Tab):-
496 get_abox(Tab0,ABox0),
497 ( find((differentIndividuals(L),Expl0),ABox0) ->
498 ( sort(L,LS),
499 sort(LF,LFS),
500 LS = LFS,!,
501 absent(Expl0,Expl1,Expl),
502 remove_from_abox(ABox0,[(differentIndividuals(L),Expl0)],ABox)
503 )
504 ;
505 (ABox = ABox0,Expl = Expl1,L = LF)
506 ),
507 add_clash_to_tableau(M,Tab0,differentIndividuals(LF),Tab1),
508 set_abox(Tab1,[(differentIndividuals(L),Expl)|ABox],Tab).
509
510modify_ABox(M,Tab0,C,Ind,Expl1,Tab):-
511 get_abox(Tab0,ABox0),
512 ( find((classAssertion(C,Ind),Expl0),ABox0) ->
513 ( absent(Expl0,Expl1,Expl),
514 remove_from_abox(ABox0,(classAssertion(C,Ind),Expl0),ABox)
515 )
516 ;
517 (ABox = ABox0,Expl = Expl1)
518 ),
519 add_clash_to_tableau(M,Tab0,C-Ind,Tab1),
520 set_abox(Tab1,[(classAssertion(C,Ind),Expl)|ABox],Tab2),
521 update_expansion_queue_in_tableau(M,C,Ind,Tab2,Tab).
522
523modify_ABox(M,Tab0,P,Ind1,Ind2,Expl1,Tab):-
524 get_abox(Tab0,ABox0),
525 ( find((propertyAssertion(P,Ind1,Ind2),Expl0),ABox0) ->
526 ( absent(Expl0,Expl1,Expl),
527 remove_from_abox(ABox0,(propertyAssertion(P,Ind1,Ind2),Expl0),ABox)
528 )
529 ;
530 (ABox = ABox0,Expl = Expl1)
531 ),
532 add_clash_to_tableau(M,Tab0,P-Ind1-Ind2,Tab1),
533 set_abox(Tab1,[(propertyAssertion(P,Ind1,Ind2),Expl)|ABox],Tab2),
534 update_expansion_queue_in_tableau(M,P,Ind1,Ind2,Tab2,Tab).
535
537
539notDifferentIndividuals(M,X,Y,ABox):-
540 \+ inAssertDifferentIndividuals(M,X,Y),
541 \+ inABoxDifferentIndividuals(X,Y,ABox).
542
544
545inAssertDifferentIndividuals(M,differentIndividuals(X),differentIndividuals(Y)):-
546 !,
547 M:differentIndividuals(LI),
548 member(X0,X),
549 member(X0,LI),
550 member(Y0,Y),
551 member(Y0,LI).
552
553inAssertDifferentIndividuals(M,X,sameIndividual(Y)):-
554 !,
555 M:differentIndividuals(LI),
556 member(X,LI),
557 member(Y0,Y),
558 member(Y0,LI).
559
560inAssertDifferentIndividuals(M,sameIndividual(X),Y):-
561 !,
562 M:differentIndividuals(LI),
563 member(X0,X),
564 member(X0,LI),
565 member(Y,LI).
566
567inAssertDifferentIndividuals(M,X,Y):-
568 M:differentIndividuals(LI),
569 member(X,LI),
570 member(Y,LI).
571
573
574inABoxDifferentIndividuals(sameIndividual(X),sameIndividual(Y),ABox):-
575 !,
576 find((differentIndividuals(LI),_),ABox),
577 member(X0,X),
578 member(X0,LI),
579 member(Y0,Y),
580 member(Y0,LI).
581
582inABoxDifferentIndividuals(X,sameIndividual(Y),ABox):-
583 !,
584 find((differentIndividuals(LI),_),ABox),
585 member(X,LI),
586 member(Y0,Y),
587 member(Y0,LI).
588
589inABoxDifferentIndividuals(sameIndividual(X),Y,ABox):-
590 !,
591 find((differentIndividuals(LI),_),ABox),
592 member(X0,X),
593 member(X0,LI),
594 member(Y,LI).
595
596inABoxDifferentIndividuals(X,Y,ABox):-
597 find((differentIndividuals(LI),_),ABox),
598 member(X,LI),
599 member(Y,LI).
600
602
603listIntersection([],_,[]).
604
605listIntersection([HX|TX],LCY,TI):-
606 \+ member(HX,LCY),
607 listIntersection(TX,LCY,TI).
608
609listIntersection([HX|TX],LCY,[HX|TI]):-
610 member(HX,LCY),
611 listIntersection(TX,LCY,TI).
612
614
615findExplForClassOf(LC,LI,ABox0,Expl):-
616 member(C,LC),
617 member(I,LI),
618 findClassAssertion(C,I,Expl,ABox0).
620
622
623
627absent(Expl0,Expl1,Expl):- 628 absent0(Expl0,Expl1,Expl),!.
629
631absent0(Expl0,Expl1,Expl):-
632 absent1(Expl0,Expl1,Expl,Added),
633 dif(Added,0).
634
635absent1(Expl,[],Expl,0).
636
637absent1(Expl0,[H-CP|T],[H-CP|Expl],1):-
638 absent2(Expl0,H),!,
639 absent1(Expl0,T,Expl,_).
640
641absent1(Expl0,[_|T],Expl,Added):-
642 absent1(Expl0,T,Expl,Added).
643
644absent2([H-_],Expl):- !,
645 \+ subset(H,Expl).
646
647absent2([H-_|T],Expl):-
648 \+ subset(H,Expl),!,
649 absent2(T,Expl).
650
652
657
667
668
669build_abox(M,Tableau,QueryType,QueryArgs):-
670 retractall(M:final_abox(_)),
671 collect_individuals(M,QueryType,QueryArgs,ConnectedInds),
672 get_axioms_of_individuals(M,ConnectedInds,LCA,LPA,LNA,LDIA,LSIA),
673 new_abox(ABox0),
674 new_tabs(Tabs0),
675 init_expansion_queue(LCA,LPA,ExpansionQueue),
676 init_tableau(ABox0,Tabs0,ExpansionQueue,Tableau0),
677 678 679 append([LCA,LPA,LNA,LDIA],AddAllList),
680 add_all_to_tableau(M,AddAllList,Tableau0,Tableau2),
681 merge_all_individuals(M,LSIA,Tableau2,Tableau3),
682 add_owlThing_list(M,Tableau3,Tableau),
683 !.
684
685
686get_axioms_of_individuals(M,IndividualsList,LCA,LPA,LNA,LDIA,LSIA):-
687 ( dif(IndividualsList,[]) ->
688 ( findall((classAssertion(Class,Individual),[[classAssertion(Class,Individual)]-[]]),(member(Individual,IndividualsList),M:classAssertion(Class,Individual)),LCA),
689 findall((propertyAssertion(Property,Subject, Object),[[propertyAssertion(Property,Subject, Object)]-[]]),(member(Subject,IndividualsList),M:propertyAssertion(Property,Subject, Object),dif('http://www.w3.org/2000/01/rdf-schema#comment',Property)),LPA),
690 findall(nominal(NominalIndividual),(member(NominalIndividual,IndividualsList),M:classAssertion(oneOf(_),NominalIndividual)),LNA),
691 findall((differentIndividuals(Ld),[[differentIndividuals(Ld)]-[]]),(M:differentIndividuals(Ld),intersect(Ld,IndividualsList)),LDIA),
692 findall((sameIndividual(L),[[sameIndividual(L)]-[]]),(M:sameIndividual(L),intersect(L,IndividualsList)),LSIA)
693 )
694 ; 695 ( findall((classAssertion(Class,Individual),[[classAssertion(Class,Individual)]-[]]),M:classAssertion(Class,Individual),LCA),
696 findall((propertyAssertion(Property,Subject, Object),[[propertyAssertion(Property,Subject, Object)]-[]]),(M:propertyAssertion(Property,Subject, Object),dif('http://www.w3.org/2000/01/rdf-schema#comment',Property)),LPA),
697 findall(nominal(NominalIndividual),M:classAssertion(oneOf(_),NominalIndividual),LNA),
698 findall((differentIndividuals(Ld),[[differentIndividuals(Ld)]-[]]),M:differentIndividuals(Ld),LDIA),
699 findall((sameIndividual(L),[[sameIndividual(L)]-[]]),M:sameIndividual(L),LSIA)
700 )
701 ).
702
703
705
711
712and_all_f(M,ExplPartsList,E) :-
713 empty_expl(M,EmptyE),
714 and_all_f(M,ExplPartsList,EmptyE,E).
715
716and_all_f(_,[],E,E) :- !.
717
718and_all_f(M,[H|T],E0,E):-
719 and_f(M,E0,H,E1),
720 and_all_f(M,T,E1,E).
721
722initial_expl(_M,[[]-[]]):-!.
723
724empty_expl(_M,[[]-[]]):-!.
725
726and_f_ax(M,Axiom,F0,F):-
727 and_f(M,[[Axiom]-[]],F0,F).
728
729and_f(_M,[],[],[]):- !.
730
731and_f(_M,[],L,L):- !.
732
733and_f(_M,L,[],L):- !.
734
735and_f(_M,L1,L2,F):-
736 and_f1(L1,L2,[],F).
737
738and_f1([],_,L,L).
739
740and_f1([H1-CP1|T1],L2,L3,L):-
741 and_f2(H1,CP1,L2,L12),
742 append(L3,L12,L4),
743 and_f1(T1,L2,L4,L).
744
745and_f2(_,_,[],[]):- !.
746
762
763
764and_f2(L1,CP1,[H2-CP2|T2],[H-CP|T]):- 765 append(L1,H2,H),
766 append(CP1,CP2,CP),
767 and_f2(L1,CP1,T2,T).
768
769
770can_i_and(L1,CP1,H2,CP2):-
771 dif(L1,[]),
772 dif(H2,[]),
773 (member(A,CP1),
774 member(A,CP2)),!.
775
776same_cpp_or_not(CP1,CP2):-
777 (\+ member(cpp(_,_),CP1) ; \+ member(cpp(_,_),CP2)),!.
778
779or_f([],E,E).
780
781or_f([E0|T],E1,E):-
782 memberchk(E0,E1),!,
783 or_f(T,E1,E).
784
785or_f([E0|T],E1,[E0|E]):-
786 or_f(T,E1,E).
787
793
803init_delta(M):-
804 retractall(M:delta(_,_)),
805 assert(M:delta([],0)).
806
807get_choice_point_id(M,ID):-
808 M:delta(_,ID).
809
811create_choice_point(M,Ind,Rule,Class,Choices,ID0):-
812 init_expl_per_choice(Choices,ExplPerChoice),
813 M:delta(CPList,ID0),
814 ID is ID0 + 1,
815 retractall(M:delta(_,_)),
816 assert(M:delta([cp(ID0,Ind,Rule,Class,Choices,ExplPerChoice)|CPList],ID)).
817
818
819init_expl_per_choice(Choices,ExplPerChoice):-
820 length(Choices,N),
821 init_expl_per_choice_int(0,N,epc{0:[]},ExplPerChoice).
822
823init_expl_per_choice_int(N,N,ExplPerChoice,ExplPerChoice).
824
825init_expl_per_choice_int(N0,N,ExplPerChoice0,ExplPerChoice):-
826 ExplPerChoice1 = ExplPerChoice0.put(N0,[]),
827 N1 is N0 + 1,
828 init_expl_per_choice_int(N1,N,ExplPerChoice1,ExplPerChoice).
829
830
833add_choice_point(_,_,[],[]).
834
835add_choice_point(_,CPP,[Expl-CP0|T0],[Expl-CP|T]):- 836 (
837 dif(CP0,[]) ->
838 (
839 append([CPP],CP0,CP)
840 )
841 ;
842 (
843 CP = [CPP]
844 )
845 ),
846 add_choice_point(_,CPP,T0,T).
847
848
849get_choice_point_list(M,CP):-
850 M:delta(CP,_).
851
(M,CP):-
853 M:delta([CP|CPList],ID),
854 retractall(M:delta(_,_)),
855 assert(M:delta(CPList,ID)).
856
857update_choice_point_list(M,ID,Choice,E,CPs):-
858 M:delta(CPList0,ID0),
859 memberchk(cp(ID,Ind,Rule,Class,Choices,ExplPerChoice0),CPList0),
860 ExplToUpdate = ExplPerChoice0.get(Choice),
861 ( 862 863 864 dif(ExplToUpdate,[]) ->
865 (
866 or_f(ExplToUpdate,[E-CPs],ExplUpdated)
867 ) ;
868 (
869 ExplUpdated=[E-CPs]
870 )
871 ),
872 ExplPerChoice = ExplPerChoice0.put(Choice,ExplUpdated),
873 update_choice_point_list_int(CPList0,cp(ID,Ind,Rule,Class,Choices,ExplPerChoice0),ExplPerChoice,CPList),
874 retractall(M:delta(_,_)),
875 assert(M:delta(CPList,ID0)).
876
877update_choice_point_list_int([],_,_,[]):-
878 writeln("Probably something wrong happened. Please report the problem opening an issue on github!").
879 880
881update_choice_point_list_int([cp(ID,Ind,Rule,Class,Choices,ExplPerChoice0)|T],
882 cp(ID,Ind,Rule,Class,Choices,ExplPerChoice0),ExplPerChoice,
883 [cp(ID,Ind,Rule,Class,Choices,ExplPerChoice)|T]) :- !.
884
885update_choice_point_list_int([H|T],
886 cp(ID,Ind,Rule,Class,Choices,ExplPerChoice0),ExplPerChoice,
887 [H|T1]):-
888 update_choice_point_list_int(T,cp(ID,Ind,Rule,Class,Choices,ExplPerChoice0),ExplPerChoice,T1).
889
895
896get_bdd_environment(_M,Env):-
897 init(Env).
898
899clean_environment(_M,Env):-
900 end(Env).
901
902
903build_bdd(M,Env,[X],BDD):- !,
904 bdd_and(M,Env,X,BDD).
905
906build_bdd(M,Env, [H|T],BDD):-
907 build_bdd(M,Env,T,BDDT),
908 bdd_and(M,Env,H,BDDH),
909 or(Env,BDDH,BDDT,BDD).
910
911build_bdd(_M,Env,[],BDD):- !,
912 zero(Env,BDD).
913
914
915bdd_and(M,Env,[X],BDDX):-
916 get_prob_ax(M,X,AxN,Prob),!,
917 ProbN is 1-Prob,
918 get_var_n(Env,AxN,[],[Prob,ProbN],VX),
919 equality(Env,VX,0,BDDX),!.
920
921bdd_and(_M,Env,[_X],BDDX):- !,
922 one(Env,BDDX).
923
924bdd_and(M,Env,[H|T],BDDAnd):-
925 get_prob_ax(M,H,AxN,Prob),!,
926 ProbN is 1-Prob,
927 get_var_n(Env,AxN,[],[Prob,ProbN],VH),
928 equality(Env,VH,0,BDDH),
929 bdd_and(M,Env,T,BDDT),
930 and(Env,BDDH,BDDT,BDDAnd).
931
932bdd_and(M,Env,[_H|T],BDDAnd):- !,
933 one(Env,BDDH),
934 bdd_and(M,Env,T,BDDT),
935 and(Env,BDDH,BDDT,BDDAnd)