1%%% -*- Mode: Prolog; -*-
2
3%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
4%
5%  $Date: 2010-08-24 15:14:21 +0200 (Di, 24. Aug 2010) $
6%  $Revision: 4671 $
7%
8%  This file is part of ProbLog
9%  http://dtai.cs.kuleuven.be/problog
10%
11%  ProbLog was developed at Katholieke Universiteit Leuven
12%
13%  Copyright 2008, 2009, 2010
14%  Katholieke Universiteit Leuven
15%
16%  Main authors of this file:
17%  Guy Van den Broeck
18%
19%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
20%
21% Artistic License 2.0
22%
23% Copyright (c) 2000-2006, The Perl Foundation.
24%
25% Everyone is permitted to copy and distribute verbatim copies of this
26% license document, but changing it is not allowed.  Preamble
27%
28% This license establishes the terms under which a given free software
29% Package may be copied, modified, distributed, and/or
30% redistributed. The intent is that the Copyright Holder maintains some
31% artistic control over the development of that Package while still
32% keeping the Package available as open source and free software.
33%
34% You are always permitted to make arrangements wholly outside of this
35% license directly with the Copyright Holder of a given Package. If the
36% terms of this license do not permit the full use that you propose to
37% make of the Package, you should contact the Copyright Holder and seek
38% a different licensing arrangement.  Definitions
39%
40% "Copyright Holder" means the individual(s) or organization(s) named in
41% the copyright notice for the entire Package.
42%
43% "Contributor" means any party that has contributed code or other
44% material to the Package, in accordance with the Copyright Holder's
45% procedures.
46%
47% "You" and "your" means any person who would like to copy, distribute,
48% or modify the Package.
49%
50% "Package" means the collection of files distributed by the Copyright
51% Holder, and derivatives of that collection and/or of those files. A
52% given Package may consist of either the Standard Version, or a
53% Modified Version.
54%
55% "Distribute" means providing a copy of the Package or making it
56% accessible to anyone else, or in the case of a company or
57% organization, to others outside of your company or organization.
58%
59% "Distributor Fee" means any fee that you charge for Distributing this
60% Package or providing support for this Package to another party. It
61% does not mean licensing fees.
62%
63% "Standard Version" refers to the Package if it has not been modified,
64% or has been modified only in ways explicitly requested by the
65% Copyright Holder.
66%
67% "Modified Version" means the Package, if it has been changed, and such
68% changes were not explicitly requested by the Copyright Holder.
69%
70% "Original License" means this Artistic License as Distributed with the
71% Standard Version of the Package, in its current version or as it may
72% be modified by The Perl Foundation in the future.
73%
74% "Source" form means the source code, documentation source, and
75% configuration files for the Package.
76%
77% "Compiled" form means the compiled bytecode, object code, binary, or
78% any other form resulting from mechanical transformation or translation
79% of the Source form.
80%
81%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
82%
83% Permission for Use and Modification Without Distribution
84%
85% (1) You are permitted to use the Standard Version and create and use
86% Modified Versions for any purpose without restriction, provided that
87% you do not Distribute the Modified Version.
88%
89% Permissions for Redistribution of the Standard Version
90%
91% (2) You may Distribute verbatim copies of the Source form of the
92% Standard Version of this Package in any medium without restriction,
93% either gratis or for a Distributor Fee, provided that you duplicate
94% all of the original copyright notices and associated disclaimers. At
95% your discretion, such verbatim copies may or may not include a
96% Compiled form of the Package.
97%
98% (3) You may apply any bug fixes, portability changes, and other
99% modifications made available from the Copyright Holder. The resulting
100% Package will still be considered the Standard Version, and as such
101% will be subject to the Original License.
102%
103% Distribution of Modified Versions of the Package as Source
104%
105% (4) You may Distribute your Modified Version as Source (either gratis
106% or for a Distributor Fee, and with or without a Compiled form of the
107% Modified Version) provided that you clearly document how it differs
108% from the Standard Version, including, but not limited to, documenting
109% any non-standard features, executables, or modules, and provided that
110% you do at least ONE of the following:
111%
112% (a) make the Modified Version available to the Copyright Holder of the
113% Standard Version, under the Original License, so that the Copyright
114% Holder may include your modifications in the Standard Version.  (b)
115% ensure that installation of your Modified Version does not prevent the
116% user installing or running the Standard Version. In addition, the
117% modified Version must bear a name that is different from the name of
118% the Standard Version.  (c) allow anyone who receives a copy of the
119% Modified Version to make the Source form of the Modified Version
120% available to others under (i) the Original License or (ii) a license
121% that permits the licensee to freely copy, modify and redistribute the
122% Modified Version using the same licensing terms that apply to the copy
123% that the licensee received, and requires that the Source form of the
124% Modified Version, and of any works derived from it, be made freely
125% available in that license fees are prohibited but Distributor Fees are
126% allowed.
127%
128% Distribution of Compiled Forms of the Standard Version or
129% Modified Versions without the Source
130%
131% (5) You may Distribute Compiled forms of the Standard Version without
132% the Source, provided that you include complete instructions on how to
133% get the Source of the Standard Version. Such instructions must be
134% valid at the time of your distribution. If these instructions, at any
135% time while you are carrying out such distribution, become invalid, you
136% must provide new instructions on demand or cease further
137% distribution. If you provide valid instructions or cease distribution
138% within thirty days after you become aware that the instructions are
139% invalid, then you do not forfeit any of your rights under this
140% license.
141%
142% (6) You may Distribute a Modified Version in Compiled form without the
143% Source, provided that you comply with Section 4 with respect to the
144% Source of the Modified Version.
145%
146% Aggregating or Linking the Package
147%
148% (7) You may aggregate the Package (either the Standard Version or
149% Modified Version) with other packages and Distribute the resulting
150% aggregation provided that you do not charge a licensing fee for the
151% Package. Distributor Fees are permitted, and licensing fees for other
152% components in the aggregation are permitted. The terms of this license
153% apply to the use and Distribution of the Standard or Modified Versions
154% as included in the aggregation.
155%
156% (8) You are permitted to link Modified and Standard Versions with
157% other works, to embed the Package in a larger work of your own, or to
158% build stand-alone binary or bytecode versions of applications that
159% include the Package, and Distribute the result without restriction,
160% provided the result does not expose a direct interface to the Package.
161%
162% Items That are Not Considered Part of a Modified Version
163%
164% (9) Works (including, but not limited to, modules and scripts) that
165% merely extend or make use of the Package, do not, by themselves, cause
166% the Package to be a Modified Version. In addition, such works are not
167% considered parts of the Package itself, and are not subject to the
168% terms of this license.
169%
170% General Provisions
171%
172% (10) Any use, modification, and distribution of the Standard or
173% Modified Versions is governed by this Artistic License. By using,
174% modifying or distributing the Package, you accept this license. Do not
175% use, modify, or distribute the Package, if you do not accept this
176% license.
177%
178% (11) If your Modified Version has been derived from a Modified Version
179% made by someone other than you, you are nevertheless required to
180% ensure that your Modified Version complies with the requirements of
181% this license.
182%
183% (12) This license does not grant you the right to use any trademark,
184% service mark, tradename, or logo of the Copyright Holder.
185%
186% (13) This license includes the non-exclusive, worldwide,
187% free-of-charge patent license to make, have made, use, offer to sell,
188% sell, import and otherwise transfer the Package with respect to any
189% patent claims licensable by the Copyright Holder that are necessarily
190% infringed by the Package. If you institute patent litigation
191% (including a cross-claim or counterclaim) against any party alleging
192% that the Package constitutes direct or contributory patent
193% infringement, then this Artistic License to you shall terminate on the
194% date that such litigation is filed.
195%
196% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
197% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
198% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
199% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
200% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
201% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
202% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
203% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
204%
205%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
206
207%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
208% DECISION-THEORETIC PROBLOG
209%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
210
211:- module(dtproblog, [
212    problog_delta/5,
213    problog_threshold/5,
214    problog_low/4,
215    problog_kbest/4,
216    problog_kbest_save/6,
217    problog_max/3,
218    problog_exact/3,
219    problog_montecarlo/3,
220    problog_dnf_sampling/3,
221    problog_answers/2,
222    problog_kbest_answers/3,
223    problog_table/1,
224    clear_retained_tables/0,
225    problog_neg/1,
226    get_fact_probability/2,
227    set_fact_probability/2,
228    get_continuous_fact_parameters/2,
229    set_continuous_fact_parameters/2,
230    get_fact/2,
231    tunable_fact/2,
232    continuous_fact/1,
233    non_ground_fact/1,
234    export_facts/1,
235    problog_help/0,
236    show_inference/0,
237    problog_dir/1,
238    set_problog_flag/2,
239    problog_flag/2,
240    problog_flags/0,
241    reset_problog_flags/0,
242    problog_assert/1,
243    problog_assert/2,
244    problog_retractall/1,
245    problog_statistics/2,
246    problog_statistics/0,
247    grow_atom_table/1,
248    problog_exact_nested/3,
249    problog_tabling_negated_synonym/2,
250    build_trie/2,
251    build_trie/3,
252    problog_infer/2,
253    problog_infer/3,
254    problog_infer_forest/2,
255    write_bdd_struct_script/3,
256    problog_bdd_forest/1,
257    require/1,
258    unrequire/1,
259    '::'/2,
260    probabilistic_fact/3,
261    problog_real_kbest/4,
262    in_interval/3,
263    below/2,
264    above/2,
265    op( 550, yfx, :: ),
266    op( 550, fx, ?:: ),
267    op( 1150, fx, problog_table ),
268
269    % DTProbLog
270    set_strategy/1,
271    unset_strategy/1,
272    dtproblog_utility_facts/1,
273    dtproblog_utility_attributes/1,
274    dtproblog_ev/2,
275    dtproblog_ev/3,
276    dtproblog_ev/4,
277    dtproblog_decisions/1,
278    dtproblog_decision_ids/1,
279    dtproblog_decision_ids/2,
280    dtproblog_solve/2,
281    dtproblog_solve_specialized/2,
282    dtproblog_solve_general/2,
283    dtproblog_solve_local/4,
284    dtproblog_solve_naive/2,
285    op( 550, yfx, => )
286  ]).
287
288:- style_check(all).
289:- yap_flag(unknown,error).
290
291% problog-related modules
292
293:- use_module('problog').
294
295:- use_module('problog/flags',[
296    problog_define_flag/4,
297    problog_define_flag/5,
298    problog_define_flag/6,
299    set_problog_flag/2,
300    reset_problog_flags/0,
301    problog_flag/2
302  ]).
303
304:- use_module('problog/os', [convert_filename_to_working_path/2,
305                             convert_filename_to_problog_path/2]).
306
307:- use_module('problog/ptree', [delete_ptree/1]).
308
309:- use_module('problog/tabling', [clear_tabling/0]).
310
311
312% general yap modules
313:- use_module(library(system), [delete_file/2, shell/2]).
314
315:- initialization((
316	problog_define_flag(optimization, problog_flag_validate_atom, 'optimization algorithm [local/global]', global, dtproblog),
317	problog_define_flag(forest_type, problog_flag_validate_atom, 'type of BDD forest [dependent/independent]', dependent, dtproblog)
318)).
319
320init_dtproblog :-
321	problog_control(off,find_decisions),
322	problog_control(off,internal_strategy).
323
324:- initialization(init_dtproblog).
325
326:- op( 550, yfx, :: ).
327
328%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
329% Utility Attributes
330%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
331
332% op for utility attributes
333:- op( 550, yfx, => ).
334
335% SETOF DOESNT WORK!!! BUT all/3 is A LOT slower because it doesn't sort the solutions?
336dtproblog_utility_facts(Facts) :-
337  all((Attr => Util),user:(Attr => Util),Facts).
338
339dtproblog_utility_attributes(Attrs) :-
340  dtproblog_utility_facts(Facts),
341  facts_to_attributes(Facts,Attrs).
342
343facts_to_attributes([],[]).
344facts_to_attributes([A => _|FR],[A|AR]) :- facts_to_attributes(FR,AR).
345
346conditioned_utility_facts([],_,[],[]).
347conditioned_utility_facts([(Attr => Reward)|Facts],Condition,[(Condition,Attr)|Attrs],[Reward|Rewards]):-
348    conditioned_utility_facts(Facts,Condition,Attrs,Rewards).
349
350%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
351% Strategies (getting/setting/transforming)
352%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
353
354% Internal strategy representation
355% for GROUND strategies (one can specify a ground strategy for a non-ground decision clause)
356% e.g. 1 :: market(guy) for ? :: market(P).
357set_ground_strategy(GID,LogProb) :- bb_put(GID,LogProb).
358get_ground_strategy(GID,LogProb) :- bb_get(GID,LogProb),!.
359get_ground_strategy(_,never).
360
361% Internal strategy representation
362% for NON-GROUND strategies
363% e.g. 1 :: market(guy) for ? :: market(P)
364:- dynamic(non_ground_strategy/2).
365
366% Get Strategy
367strategy(_,_,_) :-
368    \+ problog_control(check,internal_strategy),
369    throw(error('Trying to get a strategy that is not set.')).
370strategy(ID,Decision,Prob) :-
371	grounding_id(ID,Decision,GID),
372	bb_get(GID,LogProb), % because we don't want the default, maybe there is a non-ground strategy
373    !,
374    logprob_prob(LogProb, Prob).
375strategy(_,Decision,Prob) :-
376	non_ground_strategy(Decision,LogProb),
377    !,
378    logprob_prob(LogProb, Prob).
379strategy(_,_,never).
380
381strategy_log(ID,Decision,LogProb) :-
382  strategy(ID,Decision,Prob),
383  logprob_prob(LogProb, Prob).
384
385% convert from/to probabilities and their logarithms
386logprob_prob(always,always) :- !.
387logprob_prob(never,never) :- !.
388logprob_prob(0,always) :- !.
389logprob_prob(-inf,never) :- !.
390logprob_prob(always,1) :- !.
391logprob_prob(never,0) :- !.
392logprob_prob(LogP,P) :-
393  number(LogP),
394  !,
395  P is exp(LogP).
396logprob_prob(LogP,P) :-
397  number(P),
398  !,
399  LogP is log(p).
400
401% Set Strategy
402% expects a list of (p :: decision) terms
403%   - (decision) is interpreted as (1 :: decision)
404%   - decisions that are not set will evaluate to (0 :: decision)
405set_strategy(_) :-
406  problog_control(check,internal_strategy),
407  throw(error('A strategy is already set, unset first.')).
408set_strategy([]) :- problog_control(on,internal_strategy).
409set_strategy([Term|R]) :-
410  strategy_entry(Term,LogProb,Decision),
411  (user:problog_user_ground(Decision)->
412      decision_fact(ID,Decision),
413      grounding_id(ID,Decision,ID2),
414      %format("Setting ~q/~q to ~q~n",[Decision,ID2,Prob]),
415      set_ground_strategy(ID2,LogProb)
416  ;
417      copy_term(Decision, Decision2),
418      assertz(non_ground_strategy(Decision2,LogProb))
419  ),
420  set_strategy(R).
421
422unset_strategy(_) :-
423  \+ problog_control(check,internal_strategy),
424  throw(error('Cannot unset a strategy when no strategy is set.')).
425unset_strategy([]) :-
426  retractall(non_ground_strategy(_,_)),
427  problog_control(off,internal_strategy).
428unset_strategy([Term|R]) :-
429  strategy_entry(Term,LogProb,Decision),
430  (user:problog_user_ground(Decision)->
431      decision_fact(ID,Decision),
432      grounding_id(ID,Decision,ID2),
433      %format("Unsetting ~q/~q to ~q~n",[Decision,ID2,Prob]),
434      bb_delete(ID2,LogProb)
435  ;
436      true
437  ),
438  unset_strategy(R).
439
440strategy_entry('::'(Prob,Decision),LogProb,Decision) :-
441  !,logprob_prob(LogProb, Prob).
442strategy_entry(Decision,always,Decision).
443
444% Get strategy for a list of decision IDs
445% only use when grounding ids are known and strategy is stored internally!
446strategy_as_term_list(IDs,List) :- strategy_as_term_list(IDs,[],List).
447strategy_as_term_list([],In,In).
448strategy_as_term_list([ID|R],In,Out) :-
449	strategy_as_term(ID,In,In2),
450	strategy_as_term_list(R,In2,Out).
451
452% Get strategy for a decision ID
453strategy_as_term(ID,In,Out) :-
454	%findall(grounding_is_known(D,I),grounding_is_known(D,I),LGround),
455	%findall(decision_fact(D,I),decision_fact(D,I),LBasic),
456	%format("Known IDs: ~q~n",[LGround]),
457	%format("Known IDs: ~q~n",[LBasic]),
458	((recover_grounding_id(ID,GID),grounding_is_known(Decision,GID)) ->
459		 %original fact was non-ground
460		 true
461	;
462		% original fact was ground
463		decision_fact(ID,Decision)
464	),
465	strategy(ID,Decision,Prob),
466	strategy_as_term_entry(Decision,Prob,In,Out).
467
468% Convert strategy for a decision to term representation
469strategy_as_term_entry(_,0,In,In) :- !.
470strategy_as_term_entry(Decision,1,In,[Decision|In]) :- !.
471strategy_as_term_entry(_,never,In,In) :- !.
472strategy_as_term_entry(Decision,always,In,[Decision|In]) :- !.
473strategy_as_term_entry(Decision,P,In,[P'::'Decision|In]).
474
475%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
476% Utility inference
477%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
478
479% Unconditional expected value for all utilities
480dtproblog_ev(Strategy,Ev) :- dtproblog_ev(Strategy,true,Ev).
481
482% Conditional expected value for a given strategy and all utility attributes
483dtproblog_ev(Strategy,Condition,Ev) :-
484    (dtproblog_utility_facts(UtilFacts) ->
485         dtproblog_ev(Strategy,Condition,UtilFacts,Ev)
486    ;
487         format('There are no utility facts in the program.~n',[]),
488         Ev = 0
489    ).
490
491% Conditional expected value for a given strategy and utility attributes
492dtproblog_ev(Strategy,Condition,UtilFacts,Ev) :-
493	require(keep_ground_ids),
494	set_strategy(Strategy),
495	ev_for_internal_strategy(Condition,UtilFacts,Ev),
496	unset_strategy(Strategy),
497	unrequire(keep_ground_ids),
498	reset_non_ground_facts.
499
500% Conditional expected value for internal strategy and given utility attributes
501% assumes that problog_control(on,internal_strategy)
502ev_for_internal_strategy(Condition,UtilFacts,Ev) :-
503  require(keep_ground_ids),
504  (problog_infer_forest_supported ->
505    % specialized version for inference using forests
506    conditioned_utility_facts(UtilFacts,Condition,Goals,Utilities),
507    problog_infer_forest([Condition|Goals],[CondProb|GoalProbs]),
508    !, % forest inference was supported, don't try general purpose
509    summed_utils(Utilities,GoalProbs,0,EvUncond),
510    Ev is EvUncond/CondProb
511  ;
512    % general-purpose version
513    ev_loop(Condition, UtilFacts, 0, EvUnnormalized),
514    problog_infer(Condition, Prob),
515    %format("Dividing the utilities by the conditional probability ~q~n",[Prob]),
516    (Prob > 0.000001 ->
517      Ev is EvUnnormalized/Prob
518    ;
519      format('Impossible condition: ~q has probability ~q.~n', [Condition,Prob]),
520      %throw(error(improbable_condition(Condition)))
521      Ev = -inf
522    )
523  ),
524  unrequire(keep_ground_ids),
525  reset_non_ground_facts.
526
527summed_utils([],[],Ev,Ev).
528summed_utils([Util|Utils],[Prob|Probs],Acc,Ev) :-
529	Acc2 is Acc + (Util * Prob),
530	summed_utils(Utils,Probs,Acc2,Ev).
531
532ev_loop(_, [],Acc,Acc).
533ev_loop(Condition,[(Attr => Util)|R],Acc,Ev) :-
534        problog_infer((Condition,Attr), Prob),
535        Acc2 is Acc + (Prob * Util),
536        %format('The probability of ~q is ~q, yielding a utility of ~q.~n', [(Condition,Attr),Prob,Prob * Util]),
537        ev_loop(Condition,R,Acc2,Ev).
538
539%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
540% Finding all decisions used in proofs
541%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
542
543% Finding all decisions used in proofs
544dtproblog_decisions(Decisions) :-
545	require(keep_ground_ids),
546	dtproblog_decision_ids(IDs),
547	ids_as_decisions(IDs,Decisions),
548	unrequire(keep_ground_ids),
549	reset_non_ground_facts.
550
551
552% Get decisions for a list of IDs
553ids_as_decisions(IDs,List) :- ids_as_decisions(IDs,[],List).
554
555ids_as_decisions([],In,In).
556ids_as_decisions([ID|R],In,Out) :-
557    id_as_decision(ID,In,In2),
558    ids_as_decisions(R,In2,Out).
559
560id_as_decision(ID,In,[Decision|In]) :-
561    %findall(grounding_is_known(D,I),grounding_is_known(D,I),LGround),
562    %findall(decision_fact(D,I),decision_fact(D,I),LBasic),
563    %format("Known IDs: ~q~n",[LGround]),
564    %format("Known IDs: ~q~n",[LBasic]),
565    ((recover_grounding_id(ID,GID),grounding_is_known(Decision,GID)) ->
566        % original fact was non-ground
567        true
568    ;
569        % original fact was ground
570        decision_fact(ID,Decision)
571    ).
572
573% Finding all decision IDs used in proofs
574dtproblog_decision_ids(Decisions) :-
575	(dtproblog_utility_attributes(UtilityAttrs) ->
576    	 dtproblog_decision_ids(UtilityAttrs,Decisions)
577    ;
578         Decisions = []
579    ).
580
581dtproblog_decision_ids(UtilityAttrs,Decisions) :-
582	require(keep_ground_ids),
583	problog_control(on,find_decisions),
584	reset_decisions,
585	add_decisions_all(UtilityAttrs),
586	unrequire(keep_ground_ids),
587	reset_non_ground_facts,
588	get_decisions(Decisions),
589	problog_control(off,find_decisions),
590	reset_decisions.
591
592% TODO generalize so that it works with every inference method, not just exact.
593add_decisions_all([]) :-
594    clear_tabling.
595add_decisions_all([Goal|R]) :-
596	add_decisions(Goal),
597	add_decisions_all(R).
598
599% UGLY - needs to actually build tries for tabling to work.
600% TODO change tabling.yap to do nothing when problog_control(on,find_decisions)
601% then, simplify this predicate so that it doesn't build tries
602% setting problog_control(on,mc) might work, but will maybe prune some decisions away?
603add_decisions(Goal) :-
604    problog_control(on, exact),
605    build_trie(exact, Goal, Trie),
606    delete_ptree(Trie),
607    problog_control(off, exact).
608
609reset_decisions :- bb_put(problog:decisions,[]).
610
611get_decisions(D) :- bb_get(problog:decisions,D).
612
613
614%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
615%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
616%
617% Strategy optimization
618%
619%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
620%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
621
622dtproblog_solve(Strategy,EV) :-
623	(dtproblog_solve_specialized_supported -> % try to go specialized
624      dtproblog_solve_specialized(Strategy,EV)
625	;
626        format('Flag settings not supported by specialized solution algorithm.~nTrying general purpose version.~n',[]),
627		(dtproblog_solve_general_supported -> % try to go general
628          dtproblog_solve_general(Strategy,EV)
629        ;
630          throw(error('Flag settings not supported by dtproblog_solve/2.'))
631        )
632    ).
633
634%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
635% Strategy optimization (specialized in BDD)
636%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
637
638dtproblog_solve_specialized(Strategy,EV) :-
639  (dtproblog_solve_specialized_supported ->
640    require(keep_ground_ids),
641    dtproblog_utility_facts(UtilFacts),
642    conditioned_utility_facts(UtilFacts,true,Goals,Utilities),
643    write_util_file(Utilities),
644    problog_bdd_forest(Goals),
645    length(Goals,N),
646    bdd_optimization(N,EV,DecisionIDs,ok),
647    (problog_flag(save_bdd,true) -> true ; delete_util_file ),
648    strategy_as_term_list(DecisionIDs,Strategy),
649    unset_strategy(Strategy), % was set by bdd_optimization/4
650    require(keep_ground_ids),
651    reset_non_ground_facts
652  ;
653    throw(error('Flag settings not supported by dtproblog_solve_specialized/2.'))
654  ).
655
656dtproblog_solve_specialized_supported :-
657  problog_bdd_forest_supported,
658  (
659    problog_flag(forest_type, dependent)
660  ;
661    problog_flag(optimization, local)
662  ).
663
664
665% Write a utility file, with for every utility attribute BDD, its reward value on a new line
666write_util_file(Utils) :-
667	bdd_util_file(UtilFile),
668	open(UtilFile,'write',UtilFileStream),
669	tell(UtilFileStream),
670	length(Utils,N),
671	format("~w~n",[N]),
672	write_util_file_line(Utils),
673	flush_output,
674	told.
675
676write_util_file_line([]).
677write_util_file_line([U|R]) :-
678	format("~w~n",[U]),
679	write_util_file_line(R).
680
681bdd_util_file(UtilFile) :-
682	problog_flag(bdd_file,BDDFileFlag),
683    atomic_concat([BDDFileFlag,'_',utils],UtilFileName),
684	convert_filename_to_working_path(UtilFileName, UtilFile).
685
686delete_util_file :-
687    bdd_util_file(UtilFile),
688    delete_file(UtilFile,[]).
689
690bdd_optimization(N,EV,Decisions,Status) :-
691    bdd_files(BDDFile,BDDParFile),
692    problog_flag(bdd_time,BDDTime),
693    (problog_flag(dynamic_reorder, true) -> ParamD = '' ; ParamD = ' -dreorder'),
694    (problog_flag(bdd_static_order, true) ->
695      problog_flag(static_order_file, FileName),
696      convert_filename_to_working_path(FileName, SOFileName),
697      atomic_concat([ParamD, ' -sord ', SOFileName], Param)
698    ;
699      Param = ParamD
700    ),
701    convert_filename_to_problog_path('problogbdd', ProblogBDD),
702    problog_flag(bdd_result,ResultFileFlag),
703    convert_filename_to_working_path(ResultFileFlag, ResultFile),
704	bdd_util_file(UtilFile),
705	(problog_flag(optimization,local) -> LocalPar = ' -lo';LocalPar = ''),
706	(problog_flag(forest_type,independent) -> Forest = ' -if';Forest = ''),
707	%(problog_flag(verbose,true) -> Debug = ' -d';Debug = ''), % messes up result parsing
708    atomic_concat([ProblogBDD, Param, ' -l ',BDDFile,' -i ',BDDParFile,' -u ',UtilFile,' -m s',LocalPar,Forest,' -t ', BDDTime,' > ', ResultFile],Command),
709	statistics(walltime,_),
710% 	format(user,'$ ~w~n',[Command]),
711	shell(Command,Return),
712	(Return =\= 0 ->
713	    Status = timeout
714	;
715	    statistics(walltime,[_,E3]),
716		(problog_flag(verbose,true) -> format(user,'~w ms BDD processing~n',[E3]);true),
717		see(ResultFile),
718		read(expected_value(EV)),
719		read_strategy(Decisions),
720		seen,
721		Status = ok,
722		% cleanup
723		(problog_flag(save_bdd,true) ->
724			true
725		;
726			delete_file(BDDFile,[]),
727			delete_file(BDDParFile,[]),
728			delete_file(ResultFile,[]),
729			delete_bdd_forest_files(N)
730		)
731	).
732
733% set the strategy in the internal format and returns a list of all decisions
734read_strategy(_) :-
735  problog_control(check,internal_strategy),
736  throw(error('A strategy is already set, unset first.')).
737read_strategy(DecisionIDs) :-
738  problog_control(on,internal_strategy),
739  read_strategy_intern(DecisionIDs).
740read_strategy_intern(DecisionIDs) :-
741	read(T),
742	(T = end_of_file ->
743		DecisionIDs = []
744	;
745		T = strategy(ID,Prob),
746        logprob_prob(LProb,Prob),
747		set_ground_strategy(ID,LProb),
748		DecisionIDs = [ID|Rest],
749		read_strategy_intern(Rest)
750	).
751
752%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
753% Strategy optimization (general purpose)
754%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
755
756dtproblog_solve_general(Strategy,EV) :-
757  (dtproblog_solve_general_supported ->
758    dtproblog_utility_facts(UtilFacts),
759    dtproblog_solve_local(true,UtilFacts,Strategy,EV)
760  ;
761    throw(error('Flag settings not supported by dtproblog_solve_specialized/2.'))
762  ).
763
764dtproblog_solve_general_supported :- problog_flag(optimization, local).
765
766dtproblog_solve_local(Condition,Utils,Strategy,EV) :-
767  require(keep_ground_ids),
768  facts_to_attributes(Utils,Attrs),
769  dtproblog_decision_ids(Attrs,DecisionIDs),
770  problog_control(on,internal_strategy), % consider strategy set, even though everything is default
771  ev_for_internal_strategy(Condition,Utils,EvStart),
772  optimization_iteration_loop(DecisionIDs,Condition,Utils,EvStart,EV),
773  strategy_as_term_list(DecisionIDs,Strategy),
774  unset_strategy(Strategy),
775  unrequire(keep_ground_ids),
776  reset_non_ground_facts.
777
778optimization_iteration_loop(Decisions,Condition,Utils,EVIn,EVOut) :-
779	optimization_decision_loop(Decisions,Condition,Utils,EVIn,EVTemp),
780	strategy_as_term_list(Decisions,Strategy),
781	(problog_flag(verbose,true) -> format("Found strategy ~q with EV=~q~n",[Strategy,EVTemp]);true),
782	(EVIn == EVTemp ->
783		EVOut = EVTemp
784	;
785		optimization_iteration_loop(Decisions,Condition,Utils,EVTemp,EVOut)
786	).
787
788optimization_decision_loop([],_,_,Ev,Ev).
789optimization_decision_loop([ID|Rest],Condition,Utils,EvIn,EvOut) :-
790	get_ground_strategy(ID,ProbBefore),
791	flip(ProbBefore, ProbAfter),
792	set_ground_strategy(ID,ProbAfter),
793	ev_for_internal_strategy(Condition,Utils,EvTest),
794	(EvTest>EvIn ->
795		EvTemp = EvTest,
796		(problog_flag(verbose,true) -> format("Changing strategy for #~q to ~q for EV of ~q~n",[ID,ProbAfter,EvTest]);true)
797	;
798		EvTemp = EvIn,
799		set_ground_strategy(ID,ProbBefore),
800		(problog_flag(verbose,true) -> format("Keeping strategy for #~q at ~q because EV is ~q~n",[ID,ProbBefore,EvTest]);true)
801	),
802	optimization_decision_loop(Rest,Condition,Utils,EvTemp,EvOut).
803
804flip(always,never) :- !.
805flip(never,always) :- !.
806flip(P,always) :- P<1, !.
807flip(_,never).
808
809%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
810% Naive Search
811%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
812
813dtproblog_solve_naive(Strategy,EV) :-
814  require(keep_ground_ids),
815  dtproblog_decisions(Decisions),
816  all_subsets(Decisions,Strategies),
817  max_strategy(Strategies,[],-inf,Strategy,EV),
818  unrequire(keep_ground_ids),
819  reset_non_ground_facts.
820
821max_strategy([],Strategy,EV,Strategy,EV).
822max_strategy([S1|Rest],S2,U2,S3,U3) :-
823  dtproblog_ev(S1,true,U1),
824  %format("EV of ~q is ~q~n",[S1,U1]),
825  (U1>U2 ->
826    max_strategy(Rest,S1,U1,S3,U3)
827  ;
828    max_strategy(Rest,S2,U2,S3,U3)
829  ).
830
831% List of all sublists
832all_subsets([], [[]]).
833all_subsets([X|Xs], Subsets) :-
834    all_subsets(Xs, Subsets1),
835    attach_first_element(Subsets1, X, Subsets, Subsets1).
836
837attach_first_element([], _, S, S).
838attach_first_element([Sub|Subs], X, [[X|Sub]|XSubs], S) :-
839    attach_first_element(Subs, X, XSubs, S).
840
841
842