New ProbLog Distribution Version

This commit is contained in:
Theofrastos Mantadelis 2010-08-26 14:40:50 +02:00
parent 6e17b2053f
commit 87f2588752
19 changed files with 7552 additions and 988 deletions

View File

@ -0,0 +1,838 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2010-08-24 15:14:21 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4671 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Guy Van den Broeck
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
% ensure that installation of your Modified Version does not prevent the
% user installing or running the Standard Version. In addition, the
% modified Version must bear a name that is different from the name of
% the Standard Version. (c) allow anyone who receives a copy of the
% Modified Version to make the Source form of the Modified Version
% available to others under (i) the Original License or (ii) a license
% that permits the licensee to freely copy, modify and redistribute the
% Modified Version using the same licensing terms that apply to the copy
% that the licensee received, and requires that the Source form of the
% Modified Version, and of any works derived from it, be made freely
% available in that license fees are prohibited but Distributor Fees are
% allowed.
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
% valid at the time of your distribution. If these instructions, at any
% time while you are carrying out such distribution, become invalid, you
% must provide new instructions on demand or cease further
% distribution. If you provide valid instructions or cease distribution
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
% Package. Distributor Fees are permitted, and licensing fees for other
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
% include the Package, and Distribute the result without restriction,
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
% considered parts of the Package itself, and are not subject to the
% terms of this license.
%
% General Provisions
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
% patent claims licensable by the Copyright Holder that are necessarily
% infringed by the Package. If you institute patent litigation
% (including a cross-claim or counterclaim) against any party alleging
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% DECISION-THEORETIC PROBLOG
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(dtproblog, [
problog_delta/5,
problog_threshold/5,
problog_low/4,
problog_kbest/4,
problog_kbest_save/6,
problog_max/3,
problog_exact/3,
problog_montecarlo/3,
problog_dnf_sampling/3,
problog_answers/2,
problog_kbest_answers/3,
problog_table/1,
clear_retained_tables/0,
problog_neg/1,
get_fact_probability/2,
set_fact_probability/2,
get_continuous_fact_parameters/2,
set_continuous_fact_parameters/2,
get_fact/2,
tunable_fact/2,
continuous_fact/1,
non_ground_fact/1,
export_facts/1,
problog_help/0,
show_inference/0,
problog_dir/1,
set_problog_flag/2,
problog_flag/2,
problog_flags/0,
reset_problog_flags/0,
problog_assert/1,
problog_assert/2,
problog_retractall/1,
problog_statistics/2,
problog_statistics/0,
grow_atom_table/1,
problog_exact_nested/3,
problog_tabling_negated_synonym/2,
build_trie/2,
build_trie/3,
problog_infer/2,
problog_infer/3,
problog_infer_forest/2,
write_bdd_struct_script/3,
problog_bdd_forest/1,
require/1,
unrequire/1,
'::'/2,
probabilistic_fact/3,
problog_real_kbest/4,
in_interval/3,
below/2,
above/2,
op( 550, yfx, :: ),
op( 550, fx, ?:: ),
op( 1150, fx, problog_table ),
% DTProbLog
set_strategy/1,
unset_strategy/1,
dtproblog_utility_facts/1,
dtproblog_utility_attributes/1,
dtproblog_ev/2,
dtproblog_ev/3,
dtproblog_ev/4,
dtproblog_decisions/1,
dtproblog_decision_ids/1,
dtproblog_decision_ids/2,
dtproblog_solve/2,
dtproblog_solve_specialized/2,
dtproblog_solve_general/2,
dtproblog_solve_local/4,
dtproblog_solve_naive/2,
op( 550, yfx, => )
]).
:- style_check(all).
:- yap_flag(unknown,error).
% problog-related modules
:- use_module('problog').
:- use_module('problog/flags',[
problog_define_flag/4,
problog_define_flag/5,
problog_define_flag/6,
set_problog_flag/2,
reset_problog_flags/0,
problog_flag/2
]).
:- use_module('problog/os', [convert_filename_to_working_path/2,
convert_filename_to_problog_path/2]).
:- use_module('problog/tptree', [delete_ptree/1]).
:- use_module('problog/tabling', [clear_tabling/0]).
% general yap modules
:- ensure_loaded(library(system)).
:- problog_define_flag(optimization, problog_flag_validate_atom, 'optimization algorithm [local/global]', global, dtproblog).
:- problog_define_flag(forest_type, problog_flag_validate_atom, 'type of BDD forest [dependent/independent]', dependent, dtproblog).
init_dtproblog :-
problog_control(off,find_decisions),
problog_control(off,internal_strategy).
:- init_dtproblog.
:- op( 550, yfx, :: ).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Utility Attributes
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% op for utility attributes
:- op( 550, yfx, => ).
% SETOF DOESNT WORK!!! BUT all/3 is A LOT slower because it doesn't sort the solutions?
dtproblog_utility_facts(Facts) :-
all((Attr => Util),user:(Attr => Util),Facts).
dtproblog_utility_attributes(Attrs) :-
dtproblog_utility_facts(Facts),
facts_to_attributes(Facts,Attrs).
facts_to_attributes([],[]).
facts_to_attributes([A => _|FR],[A|AR]) :- facts_to_attributes(FR,AR).
conditioned_utility_facts([],_,[],[]).
conditioned_utility_facts([(Attr => Reward)|Facts],Condition,[(Condition,Attr)|Attrs],[Reward|Rewards]):-
conditioned_utility_facts(Facts,Condition,Attrs,Rewards).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Strategies (getting/setting/transforming)
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Internal strategy representation
% for GROUND strategies (one can specify a ground strategy for a non-ground decision clause)
% e.g. 1 :: market(guy) for ? :: market(P).
set_ground_strategy(GID,LogProb) :- bb_put(GID,LogProb).
get_ground_strategy(GID,LogProb) :- bb_get(GID,LogProb),!.
get_ground_strategy(_,never).
% Internal strategy representation
% for NON-GROUND strategies
% e.g. 1 :: market(guy) for ? :: market(P)
:- dynamic non_ground_strategy/2.
% Get Strategy
strategy(_,_,_) :-
\+ problog_control(check,internal_strategy),
throw(error('Trying to get a strategy that is not set.')).
strategy(ID,Decision,Prob) :-
grounding_id(ID,Decision,GID),
bb_get(GID,LogProb), % because we don't want the default, maybe there is a non-ground strategy
!,
logprob_prob(LogProb, Prob).
strategy(_,Decision,Prob) :-
non_ground_strategy(Decision,LogProb),
!,
logprob_prob(LogProb, Prob).
strategy(_,_,never).
strategy_log(ID,Decision,LogProb) :-
strategy(ID,Decision,Prob),
logprob_prob(LogProb, Prob).
% convert from/to probabilities and their logarithms
logprob_prob(always,always) :- !.
logprob_prob(never,never) :- !.
logprob_prob(0,always) :- !.
logprob_prob(-inf,never) :- !.
logprob_prob(always,1) :- !.
logprob_prob(never,0) :- !.
logprob_prob(LogP,P) :-
number(LogP),
!,
P is exp(LogP).
logprob_prob(LogP,P) :-
number(P),
!,
LogP is log(p).
% Set Strategy
% expects a list of (p :: decision) terms
% - (decision) is interpreted as (1 :: decision)
% - decisions that are not set will evaluate to (0 :: decision)
set_strategy(_) :-
problog_control(check,internal_strategy),
throw(error('A strategy is already set, unset first.')).
set_strategy([]) :- problog_control(on,internal_strategy).
set_strategy([Term|R]) :-
strategy_entry(Term,LogProb,Decision),
(ground(Decision)->
decision_fact(ID,Decision),
grounding_id(ID,Decision,ID2),
%format("Setting ~q/~q to ~q~n",[Decision,ID2,Prob]),
set_ground_strategy(ID2,LogProb)
;
copy_term(Decision, Decision2),
assert(non_ground_strategy(Decision2,LogProb))
),
set_strategy(R).
unset_strategy(_) :-
\+ problog_control(check,internal_strategy),
throw(error('Cannot unset a strategy when no strategy is set.')).
unset_strategy([]) :-
retractall(non_ground_strategy(_,_)),
problog_control(off,internal_strategy).
unset_strategy([Term|R]) :-
strategy_entry(Term,LogProb,Decision),
(ground(Decision)->
decision_fact(ID,Decision),
grounding_id(ID,Decision,ID2),
%format("Unsetting ~q/~q to ~q~n",[Decision,ID2,Prob]),
bb_delete(ID2,LogProb)
;
true
),
unset_strategy(R).
strategy_entry('::'(Prob,Decision),LogProb,Decision) :-
!,logprob_prob(LogProb, Prob).
strategy_entry(Decision,always,Decision).
% Get strategy for a list of decision IDs
% only use when grounding ids are known and strategy is stored internally!
strategy_as_term_list(IDs,List) :- strategy_as_term_list(IDs,[],List).
strategy_as_term_list([],In,In).
strategy_as_term_list([ID|R],In,Out) :-
strategy_as_term(ID,In,In2),
strategy_as_term_list(R,In2,Out).
% Get strategy for a decision ID
strategy_as_term(ID,In,Out) :-
%findall(grounding_is_known(D,I),grounding_is_known(D,I),LGround),
%findall(decision_fact(D,I),decision_fact(D,I),LBasic),
%format("Known IDs: ~q~n",[LGround]),
%format("Known IDs: ~q~n",[LBasic]),
((recover_grounding_id(ID,GID),grounding_is_known(Decision,GID)) ->
%original fact was non-ground
true
;
% original fact was ground
decision_fact(ID,Decision)
),
strategy(ID,Decision,Prob),
strategy_as_term_entry(Decision,Prob,In,Out).
% Convert strategy for a decision to term representation
strategy_as_term_entry(_,0,In,In) :- !.
strategy_as_term_entry(Decision,1,In,[Decision|In]) :- !.
strategy_as_term_entry(_,never,In,In) :- !.
strategy_as_term_entry(Decision,always,In,[Decision|In]) :- !.
strategy_as_term_entry(Decision,P,In,[P'::'Decision|In]).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Utility inference
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Unconditional expected value for all utilities
dtproblog_ev(Strategy,Ev) :- dtproblog_ev(Strategy,true,Ev).
% Conditional expected value for a given strategy and all utility attributes
dtproblog_ev(Strategy,Condition,Ev) :-
(dtproblog_utility_facts(UtilFacts) ->
dtproblog_ev(Strategy,Condition,UtilFacts,Ev)
;
format('There are no utility facts in the program.~n',[]),
Ev = 0
).
% Conditional expected value for a given strategy and utility attributes
dtproblog_ev(Strategy,Condition,UtilFacts,Ev) :-
require(keep_ground_ids),
set_strategy(Strategy),
ev_for_internal_strategy(Condition,UtilFacts,Ev),
unset_strategy(Strategy),
unrequire(keep_ground_ids),
reset_non_ground_facts.
% Conditional expected value for internal strategy and given utility attributes
% assumes that problog_control(on,internal_strategy)
ev_for_internal_strategy(Condition,UtilFacts,Ev) :-
require(keep_ground_ids),
(problog_infer_forest_supported ->
% specialized version for inference using forests
conditioned_utility_facts(UtilFacts,Condition,Goals,Utilities),
problog_infer_forest([Condition|Goals],[CondProb|GoalProbs]),
!, % forest inference was supported, don't try general purpose
summed_utils(Utilities,GoalProbs,0,EvUncond),
Ev is EvUncond/CondProb
;
% general-purpose version
ev_loop(Condition, UtilFacts, 0, EvUnnormalized),
problog_infer(Condition, Prob),
%format("Dividing the utilities by the conditional probability ~q~n",[Prob]),
(Prob > 0.000001 ->
Ev is EvUnnormalized/Prob
;
format('Impossible condition: ~q has probability ~q.~n', [Condition,Prob]),
%throw(error(improbable_condition(Condition)))
Ev = -inf
)
),
unrequire(keep_ground_ids),
reset_non_ground_facts.
summed_utils([],[],Ev,Ev).
summed_utils([Util|Utils],[Prob|Probs],Acc,Ev) :-
Acc2 is Acc + (Util * Prob),
summed_utils(Utils,Probs,Acc2,Ev).
ev_loop(_, [],Acc,Acc).
ev_loop(Condition,[(Attr => Util)|R],Acc,Ev) :-
problog_infer((Condition,Attr), Prob),
Acc2 is Acc + (Prob * Util),
%format('The probability of ~q is ~q, yielding a utility of ~q.~n', [(Condition,Attr),Prob,Prob * Util]),
ev_loop(Condition,R,Acc2,Ev).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Finding all decisions used in proofs
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Finding all decisions used in proofs
dtproblog_decisions(Decisions) :-
require(keep_ground_ids),
dtproblog_decision_ids(IDs),
ids_as_decisions(IDs,Decisions),
unrequire(keep_ground_ids),
reset_non_ground_facts.
% Get decisions for a list of IDs
ids_as_decisions(IDs,List) :- ids_as_decisions(IDs,[],List).
ids_as_decisions([],In,In).
ids_as_decisions([ID|R],In,Out) :-
id_as_decision(ID,In,In2),
ids_as_decisions(R,In2,Out).
id_as_decision(ID,In,[Decision|In]) :-
%findall(grounding_is_known(D,I),grounding_is_known(D,I),LGround),
%findall(decision_fact(D,I),decision_fact(D,I),LBasic),
%format("Known IDs: ~q~n",[LGround]),
%format("Known IDs: ~q~n",[LBasic]),
((recover_grounding_id(ID,GID),grounding_is_known(Decision,GID)) ->
% original fact was non-ground
true
;
% original fact was ground
decision_fact(ID,Decision)
).
% Finding all decision IDs used in proofs
dtproblog_decision_ids(Decisions) :-
(dtproblog_utility_attributes(UtilityAttrs) ->
dtproblog_decision_ids(UtilityAttrs,Decisions)
;
Decisions = []
).
dtproblog_decision_ids(UtilityAttrs,Decisions) :-
require(keep_ground_ids),
problog_control(on,find_decisions),
reset_decisions,
add_decisions_all(UtilityAttrs),
unrequire(keep_ground_ids),
reset_non_ground_facts,
get_decisions(Decisions),
problog_control(off,find_decisions),
reset_decisions.
% TODO generalize so that it works with every inference method, not just exact.
add_decisions_all([]) :-
clear_tabling.
add_decisions_all([Goal|R]) :-
add_decisions(Goal),
add_decisions_all(R).
% UGLY - needs to actually build tries for tabling to work.
% TODO change tabling.yap to do nothing when problog_control(on,find_decisions)
% then, simplify this predicate so that it doesn't build tries
% setting problog_control(on,mc) might work, but will maybe prune some decisions away?
add_decisions(Goal) :-
problog_control(on, exact),
build_trie(exact, Goal, Trie),
delete_ptree(Trie),
problog_control(off, exact).
reset_decisions :- bb_put(problog:decisions,[]).
get_decisions(D) :- bb_get(problog:decisions,D).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Strategy optimization
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
dtproblog_solve(Strategy,EV) :-
(dtproblog_solve_specialized_supported -> % try to go specialized
dtproblog_solve_specialized(Strategy,EV)
;
format('Flag settings not supported by specialized solution algorithm.~nTrying general purpose version.~n',[]),
(dtproblog_solve_general_supported -> % try to go general
dtproblog_solve_general(Strategy,EV)
;
throw(error('Flag settings not supported by dtproblog_solve/2.'))
)
).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Strategy optimization (specialized in BDD)
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
dtproblog_solve_specialized(Strategy,EV) :-
(dtproblog_solve_specialized_supported ->
require(keep_ground_ids),
dtproblog_utility_facts(UtilFacts),
conditioned_utility_facts(UtilFacts,true,Goals,Utilities),
write_util_file(Utilities),
problog_bdd_forest(Goals),
length(Goals,N),
bdd_optimization(N,EV,DecisionIDs,ok),
(problog_flag(save_bdd,true) -> true ; delete_util_file ),
strategy_as_term_list(DecisionIDs,Strategy),
unset_strategy(Strategy), % was set by bdd_optimization/4
require(keep_ground_ids),
reset_non_ground_facts
;
throw(error('Flag settings not supported by dtproblog_solve_specialized/2.'))
).
dtproblog_solve_specialized_supported :-
problog_bdd_forest_supported,
(
problog_flag(forest_type, dependent)
;
problog_flag(optimization, local)
).
% Write a utility file, with for every utility attribute BDD, its reward value on a new line
write_util_file(Utils) :-
bdd_util_file(UtilFile),
open(UtilFile,'write',UtilFileStream),
tell(UtilFileStream),
length(Utils,N),
format("~w~n",[N]),
write_util_file_line(Utils),
flush_output,
told.
write_util_file_line([]).
write_util_file_line([U|R]) :-
format("~w~n",[U]),
write_util_file_line(R).
bdd_util_file(UtilFile) :-
problog_flag(bdd_file,BDDFileFlag),
atomic_concat([BDDFileFlag,'_',utils],UtilFileName),
convert_filename_to_working_path(UtilFileName, UtilFile).
delete_util_file :-
bdd_util_file(UtilFile),
delete_file(UtilFile,[]).
bdd_optimization(N,EV,Decisions,Status) :-
bdd_files(BDDFile,BDDParFile),
problog_flag(bdd_time,BDDTime),
(problog_flag(dynamic_reorder, true) -> ParamD = '' ; ParamD = ' -dreorder'),
(problog_flag(bdd_static_order, true) ->
problog_flag(static_order_file, FileName),
convert_filename_to_working_path(FileName, SOFileName),
atomic_concat([ParamD, ' -sord ', SOFileName], Param)
;
Param = ParamD
),
convert_filename_to_problog_path('problogbdd', ProblogBDD),
problog_flag(bdd_result,ResultFileFlag),
convert_filename_to_working_path(ResultFileFlag, ResultFile),
bdd_util_file(UtilFile),
(problog_flag(optimization,local) -> LocalPar = ' -lo';LocalPar = ''),
(problog_flag(forest_type,independent) -> Forest = ' -if';Forest = ''),
%(problog_flag(verbose,true) -> Debug = ' -d';Debug = ''), % messes up result parsing
atomic_concat([ProblogBDD, Param, ' -l ',BDDFile,' -i ',BDDParFile,' -u ',UtilFile,' -m s',LocalPar,Forest,' -t ', BDDTime,' > ', ResultFile],Command),
statistics(walltime,_),
shell(Command,Return),
(Return =\= 0 ->
Status = timeout
;
statistics(walltime,[_,E3]),
(problog_flag(verbose,true) -> format(user,'~w ms BDD processing~n',[E3]);true),
see(ResultFile),
read(expected_value(EV)),
read_strategy(Decisions),
seen,
Status = ok,
% cleanup
(problog_flag(save_bdd,true) ->
true
;
delete_file(BDDFile,[]),
delete_file(BDDParFile,[]),
delete_file(ResultFile,[]),
delete_bdd_forest_files(N)
)
).
% set the strategy in the internal format and returns a list of all decisions
read_strategy(_) :-
problog_control(check,internal_strategy),
throw(error('A strategy is already set, unset first.')).
read_strategy(DecisionIDs) :-
problog_control(on,internal_strategy),
read_strategy_intern(DecisionIDs).
read_strategy_intern(DecisionIDs) :-
read(T),
(T = end_of_file ->
DecisionIDs = []
;
T = strategy(ID,Prob),
logprob_prob(LProb,Prob),
set_ground_strategy(ID,LProb),
DecisionIDs = [ID|Rest],
read_strategy_intern(Rest)
).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Strategy optimization (general purpose)
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
dtproblog_solve_general(Strategy,EV) :-
(dtproblog_solve_general_supported ->
dtproblog_utility_facts(UtilFacts),
dtproblog_solve_local(true,UtilFacts,Strategy,EV)
;
throw(error('Flag settings not supported by dtproblog_solve_specialized/2.'))
).
dtproblog_solve_general_supported :- problog_flag(optimization, local).
dtproblog_solve_local(Condition,Utils,Strategy,EV) :-
require(keep_ground_ids),
facts_to_attributes(Utils,Attrs),
dtproblog_decision_ids(Attrs,DecisionIDs),
problog_control(on,internal_strategy), % consider strategy set, even though everything is default
ev_for_internal_strategy(Condition,Utils,EvStart),
optimization_iteration_loop(DecisionIDs,Condition,Utils,EvStart,EV),
strategy_as_term_list(DecisionIDs,Strategy),
unset_strategy(Strategy),
unrequire(keep_ground_ids),
reset_non_ground_facts.
optimization_iteration_loop(Decisions,Condition,Utils,EVIn,EVOut) :-
optimization_decision_loop(Decisions,Condition,Utils,EVIn,EVTemp),
strategy_as_term_list(Decisions,Strategy),
(problog_flag(verbose,true) -> format("Found strategy ~q with EV=~q~n",[Strategy,EVTemp]);true),
(EVIn == EVTemp ->
EVOut = EVTemp
;
optimization_iteration_loop(Decisions,Condition,Utils,EVTemp,EVOut)
).
optimization_decision_loop([],_,_,Ev,Ev).
optimization_decision_loop([ID|Rest],Condition,Utils,EvIn,EvOut) :-
get_ground_strategy(ID,ProbBefore),
flip(ProbBefore, ProbAfter),
set_ground_strategy(ID,ProbAfter),
ev_for_internal_strategy(Condition,Utils,EvTest),
(EvTest>EvIn ->
EvTemp = EvTest,
(problog_flag(verbose,true) -> format("Changing strategy for #~q to ~q for EV of ~q~n",[ID,ProbAfter,EvTest]);true)
;
EvTemp = EvIn,
set_ground_strategy(ID,ProbBefore),
(problog_flag(verbose,true) -> format("Keeping strategy for #~q at ~q because EV is ~q~n",[ID,ProbBefore,EvTest]);true)
),
optimization_decision_loop(Rest,Condition,Utils,EvTemp,EvOut).
flip(always,never) :- !.
flip(never,always) :- !.
flip(P,always) :- P<1, !.
flip(_,never).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Naive Search
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
dtproblog_solve_naive(Strategy,EV) :-
require(keep_ground_ids),
dtproblog_decisions(Decisions),
all_subsets(Decisions,Strategies),
max_strategy(Strategies,[],-inf,Strategy,EV),
unrequire(keep_ground_ids),
reset_non_ground_facts.
max_strategy([],Strategy,EV,Strategy,EV).
max_strategy([S1|Rest],S2,U2,S3,U3) :-
dtproblog_ev(S1,true,U1),
%format("EV of ~q is ~q~n",[S1,U1]),
(U1>U2 ->
max_strategy(Rest,S1,U1,S3,U3)
;
max_strategy(Rest,S2,U2,S3,U3)
).
% List of all sublists
all_subsets([], [[]]).
all_subsets([X|Xs], Subsets) :-
all_subsets(Xs, Subsets1),
attach_first_element(Subsets1, X, Subsets, Subsets1).
attach_first_element([], _, S, S).
attach_first_element([Sub|Subs], X, [[X|Sub]|XSubs], S) :-
attach_first_element(Subs, X, XSubs, S).

View File

@ -0,0 +1,232 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Theofrastos Mantadelis
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
% ensure that installation of your Modified Version does not prevent the
% user installing or running the Standard Version. In addition, the
% modified Version must bear a name that is different from the name of
% the Standard Version. (c) allow anyone who receives a copy of the
% Modified Version to make the Source form of the Modified Version
% available to others under (i) the Original License or (ii) a license
% that permits the licensee to freely copy, modify and redistribute the
% Modified Version using the same licensing terms that apply to the copy
% that the licensee received, and requires that the Source form of the
% Modified Version, and of any works derived from it, be made freely
% available in that license fees are prohibited but Distributor Fees are
% allowed.
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
% valid at the time of your distribution. If these instructions, at any
% time while you are carrying out such distribution, become invalid, you
% must provide new instructions on demand or cease further
% distribution. If you provide valid instructions or cease distribution
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
% Package. Distributor Fees are permitted, and licensing fees for other
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
% include the Package, and Distribute the result without restriction,
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
% considered parts of the Package itself, and are not subject to the
% terms of this license.
%
% General Provisions
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
% patent claims licensable by the Copyright Holder that are necessarily
% infringed by the Package. If you institute patent litigation
% (including a cross-claim or counterclaim) against any party alleging
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Extented list manipulation
% Open ended lists
% And others
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(extlists, [open_end_memberchk/2, open_end_add/3, open_end_add_unique/3, open_end_close_end/2]).
:- ensure_loaded(library(lists)).
open_end_memberchk(_A, []):-!, fail.
open_end_memberchk(A, L-E):-
memberchk(A, L), var(E).
open_end_add(A, [], [A|E]-E):-!.
open_end_add(A, L-E, L-NE):-
E = [A|NE].
open_end_add_unique(A, [], [A|E]-E):-!.
open_end_add_unique(A, L-E, L-E):-
memberchk(A, L), var(E), !.
open_end_add_unique(A, L-E, L-NE):-
E = [A|NE].
open_end_close_end([], []):-!.
open_end_close_end(L-[], L).

View File

@ -2,79 +2,78 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2009-06-17 22:22:00 +0200 (Mi, 17 Jun 2009) $
% $Revision: 1550 $
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% Copyright 2009 Katholieke Universiteit Leuven
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Authors: Luc De Raedt, Bernd Gutmann, Angelika Kimmig,
% Vitor Santos Costa
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
%
% Main authors of this file:
% Angelika Kimmig, Vitor Santos Costa
% Theofrastos Mantadelis, Bernd Gutmann
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
@ -82,34 +81,34 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
@ -128,7 +127,7 @@
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
@ -139,13 +138,13 @@
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
@ -153,7 +152,7 @@
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
@ -161,7 +160,7 @@
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
@ -169,21 +168,21 @@
% terms of this license.
%
% General Provisions
%
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
@ -193,7 +192,7 @@
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
@ -205,324 +204,164 @@
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(flags, [set_problog_flag/2,
problog_flag/2,
problog_flags/0]).
:- style_check(all).
:- yap_flag(unknown,error).
:- use_module(print, [print_param/4,
print_sep_line/0]).
:- ensure_loaded(library(system)).
:- dynamic bdd_time/1, first_threshold/1, last_threshold/1, id_stepsize/1, prunecheck/1, maxsteps/1, mc_batchsize/1, mc_logfile/1, bdd_file/1, bdd_par_file/1, bdd_result/1, work_dir/1, save_bdd/1, problog_verbose/1, fast_proofs/1.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% global parameters that can be set using set_problog_flag/2
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
problog_flag(Flag,Option) :-
get_problog_flag(Flag,Option).
get_problog_flag(bdd_time,X) :-
bdd_time(X).
get_problog_flag(first_threshold,X) :-
first_threshold(X).
get_problog_flag(last_threshold,X) :-
last_threshold(L),
X is exp(L).
get_problog_flag(last_threshold_log,X) :-
last_threshold(X).
get_problog_flag(id_stepsize,X) :-
id_stepsize(L),
X is exp(L).
get_problog_flag(id_stepsize_log,X) :-
id_stepsize(X).
get_problog_flag(prunecheck,X) :-
prunecheck(X).
get_problog_flag(maxsteps,X) :-
maxsteps(X).
get_problog_flag(mc_batchsize,X) :-
mc_batchsize(X).
get_problog_flag(mc_logfile,X) :-
mc_logfile(X).
get_problog_flag(bdd_file,X) :-
bdd_file(X).
get_problog_flag(bdd_par_file,X) :-
bdd_par_file(X).
get_problog_flag(bdd_result,X) :-
bdd_result(X).
get_problog_flag(dir,X) :-
work_dir(X).
get_problog_flag(save_bdd,X) :-
save_bdd(X).
get_problog_flag(verbose,X) :-
problog_verbose(X).
get_problog_flag(fast_proofs,X) :-
fast_proofs(X).
:-module(flags, [problog_define_flag/4,
problog_define_flag/5,
problog_define_flag/6,
problog_defined_flag/5,
problog_defined_flag_group/1,
set_problog_flag/2,
reset_problog_flags/0,
problog_flag/2]).
%%%%%%%%%%%%
% BDD timeout in seconds, used as option in BDD tool
%%%%%%%%%%%%
:-ensure_loaded(gflags).
:-ensure_loaded(os).
:-ensure_loaded(logger).
set_problog_flag(bdd_time,X) :-
(\+ integer(X); X<0),
!,
format(user,'\% ERROR: value must be positive integer!~n',[]),
flush_output(user),
fail.
set_problog_flag(bdd_time,X) :-
retractall(bdd_time(_)),
assert(bdd_time(X)).
problog_define_flag(Flag, Type, Description, DefaultValue):-
flag_define(Flag, Type, DefaultValue, Description).
problog_define_flag(Flag, Type, Description, DefaultValue, FlagGroup):-
flag_define(Flag, FlagGroup, Type, DefaultValue, Description).
problog_define_flag(Flag, Type, Description, DefaultValue, FlagGroup, Handler):-
flag_define(Flag, FlagGroup, Type, DefaultValue, Handler, Description).
problog_defined_flag(Flag, Group, DefaultValue, Domain, Message):-
flag_defined(Flag, Group, DefaultValue, Domain, Message).
problog_defined_flag_group(Group):-
flag_group_defined(Group).
set_problog_flag(Flag, Value):-
flag_set(Flag, Value).
problog_flag(Flag, Value):-
flag_get(Flag, Value).
reset_problog_flags:- flags_reset.
:- flag_add_validation_syntactic_sugar(problog_flag_validate_dummy, flag_validate_dummy).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_atom, flag_validate_atom).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_atomic, flag_validate_atomic).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_number, flag_validate_number).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_integer, flag_validate_integer).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_directory, flag_validate_directory).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_file, flag_validate_file).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_in_list(L), flag_validate_in_list(L)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_in_interval(I, Type), flag_validate_in_interval(I, Type)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_in_interval_closed([L, U]), flag_validate_in_interval([L, U], number)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_in_interval_open([L, U]), flag_validate_in_interval((L, U), number)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_in_interval_left_open([L, U]), flag_validate_in_interval((L, [U]), number)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_in_interval_right_open([L, U]), flag_validate_in_interval(([L], U), number)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_integer_in_interval_closed([L, U]), flag_validate_in_interval([L, U], integer)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_integer_in_interval_open([L, U]), flag_validate_in_interval((L, U), integer)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_integer_in_interval_left_open([L, U]), flag_validate_in_interval((L, [U]), integer)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_integer_in_interval_right_open([L, U]), flag_validate_in_interval(([L], U), integer)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_float_in_interval_closed([L, U]), flag_validate_in_interval([L, U], float)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_float_in_interval_open([L, U]), flag_validate_in_interval((L, U), float)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_float_in_interval_left_open([L, U]), flag_validate_in_interval((L, [U]), float)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_float_in_interval_right_open([L, U]), flag_validate_in_interval(([L], U), float)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_posnumber, flag_validate_in_interval((0, [+inf]), number)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_posint, flag_validate_in_interval((0, +inf), integer)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_nonegint, flag_validate_in_interval(([0], +inf), integer)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_boolean, flag_validate_in_list([true, false])).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_switch, flag_validate_in_list([on, off])).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_method, flag_validate_in_list([max, delta, exact, montecarlo, low, kbest])).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_aggregate, flag_validate_in_list([sum, prod, soft_prod])).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_indomain_0_1_open, flag_validate_in_interval((0, 1), number)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_indomain_0_1_close, flag_validate_in_interval([0, 1], number)).
:- flag_add_validation_syntactic_sugar(problog_flag_validate_0to5, flag_validate_in_interval([0, 5], integer)).
last_threshold_handler(message, '').
last_threshold_handler(validating, _Value).
last_threshold_handler(validated, _Value).
last_threshold_handler(stored, Value):-
ValueLog is log(Value),
flag_store(last_threshold_log, ValueLog).
id_stepsize_handler(message, '').
id_stepsize_handler(validating, _Value).
id_stepsize_handler(validated, _Value).
id_stepsize_handler(stored, Value):-
ValueLog is log(Value),
flag_store(id_stepsize_log, ValueLog).
bdd_file_handler(message, '').
bdd_file_handler(validating, _Value).
bdd_file_handler(validated, _Value).
bdd_file_handler(stored, Value):-
atomic_concat(Value, '_probs', ParValue),
flag_set(bdd_par_file, ParValue),
atomic_concat(Value, '_res', ResValue),
flag_set(bdd_result, ResValue).
auto_handler(message, 'auto non-zero').
auto_handler(validating, Value) :-
number(Value),
Value =\= 0.
auto_handler(validate, Value):-
Value == auto.
auto_handler(validated, _Value).
auto_handler(stored, _Value).
%%%%%%%%%%%%
% iterative deepening on minimal probabilities (delta, max, kbest):
% - first threshold (not in log-space as only used to retrieve argument for init_threshold/1, which is also used with user-supplied argument)
% - last threshold to ensure termination in case infinite search space (saved in log-space for easy comparison with current values during search)
% - factor used to decrease threshold for next level, NewMin=Factor*OldMin (saved in log-space)
%%%%%%%%%%%%
set_problog_flag(first_threshold,X) :-
(\+ number(X); X<0 ; X>1),
!,
format(user,'\% ERROR: value must be in [0,1]!~n',[]),
flush_output(user),
fail.
set_problog_flag(first_threshold,X) :-
retractall(first_threshold(_)),
assert(first_threshold(X)).
set_problog_flag(last_threshold,X) :-
(\+ number(X); X<0 ; X>1),
!,
format(user,'\% ERROR: value must be in [0,1]!~n',[]),
flush_output(user),
fail.
set_problog_flag(last_threshold,X) :-
retractall(last_threshold(_)),
L is log(X),
assert(last_threshold(L)).
set_problog_flag(id_stepsize,X) :-
(\+ number(X); X=<0 ; X>=1),
!,
format(user,'\% ERROR: value must be in ]0,1[!~n',[]),
flush_output(user),
fail.
set_problog_flag(id_stepsize,X) :-
retractall(id_stepsize(_)),
L is log(X),
assert(id_stepsize(L)).
examples_handler(message, 'examples').
examples_handler(validating, _Value).
examples_handler(validate, Value):-
Value == examples.
examples_handler(validated, _Value).
examples_handler(stored, _Value).
%%%%%%%%%%%%
% prune check stops derivations if they use a superset of facts already known to form a proof
% (very) costly test, can be switched on/off here
%%%%%%%%%%%%
learning_init_handler(message, '(Q,P,BDDFile,ProbFile,Query)').
learning_init_handler(validating, (_,_,_,_,_)).
%learning_init_handler(validate, V_).
learning_init_handler(validated, _Value).
learning_init_handler(stored, _Value).
set_problog_flag(prunecheck,on) :-
!,
format(user,'WARNING: prune check not implemented, will fail~n',[]),
flush_output(user),
retractall(prunecheck(_)),
assert(prunecheck(on)).
set_problog_flag(prunecheck,off) :-
!,
retractall(prunecheck(_)),
assert(prunecheck(off)).
set_problog_flag(prunecheck,_) :-
format(user,'\% ERROR: value must be \'on\' or \'off\'!~n',[]),
flush_output(user),
fail.
%%%%%%%%%%%%
% max number of calls to probabilistic facts per derivation (to ensure termination)
%%%%%%%%%%%%
set_problog_flag(maxsteps,X) :-
(\+ integer(X); X<0),
!,
format(user,'\% ERROR: value must be positive integer!~n',[]),
flush_output(user),
fail.
set_problog_flag(maxsteps,X) :-
retractall(maxsteps(_)),
assert(maxsteps(X)).
learning_prob_init_handler(message, '(Q,P,Query)').
learning_prob_init_handler(validating, (_,_,_)).
%learning_prob_init_handler(validate, V_).
learning_prob_init_handler(validated, _Value).
learning_prob_init_handler(stored, _Value).
%%%%%%%%%%%%
% montecarlo: recalculate current approximation after N samples
%%%%%%%%%%%%
set_problog_flag(mc_batchsize,X) :-
(\+ integer(X); X<0),
!,
format(user,'\% ERROR: value must be positive integer!~n',[]),
flush_output(user),
fail.
set_problog_flag(mc_batchsize,X) :-
retractall(mc_batchsize(_)),
assert(mc_batchsize(X)).
%%%%%%%%%%%%
% montecarlo: write log to this file
%%%%%%%%%%%%
set_problog_flag(mc_logfile,X) :-
\+ atom(X),
!,
format(user,'\% ERROR: value must be atom!~n',[]),
flush_output(user),
fail.
set_problog_flag(mc_logfile,X) :-
retractall(mc_logfile(_)),
assert(mc_logfile(X)).
%%%%%%%%%%%%
% files to write BDD script and pars
% bdd_file overwrites bdd_par_file with matching extended name
% if different name wanted, respect order when setting
%%%%%%%%%%%%
set_problog_flag(bdd_file,X) :-
\+ atom(X),
!,
format(user,'\% ERROR: value must be atom!~n',[]),
flush_output(user),
fail.
set_problog_flag(bdd_file,X) :-
retractall(bdd_file(_)),
atomic_concat(X,'_probs',Y),
set_problog_flag(bdd_par_file,Y),
atomic_concat(X,'_res',Z),
set_problog_flag(bdd_result,Z),
assert(bdd_file(X)).
set_problog_flag(bdd_par_file,X) :-
\+ atom(X),
!,
format(user,'\% ERROR: value must be atom!~n',[]),
flush_output(user),
fail.
set_problog_flag(bdd_par_file,X) :-
retractall(bdd_par_file(_)),
assert(bdd_par_file(X)).
set_problog_flag(bdd_result,X) :-
\+ atom(X),
!,
format(user,'\% ERROR: value must be atom!~n',[]),
flush_output(user),
fail.
set_problog_flag(bdd_result,X) :-
retractall(bdd_result(_)),
assert(bdd_result(X)).
%%%%%%%%%%%%
% working directory: all the temporary and output files will be located there
% it assumes a subdirectory of the current working dir
% on initialization, the current dir is the one where the user's file is located
%%%%%%%%%%%%
set_problog_flag(dir,X) :-
\+ atom(X),
!,
format(user,'\% ERROR: value must be atom!~n',[]),
flush_output(user),
fail.
set_problog_flag(dir,X) :-
retractall(work_dir(_)),
working_directory(PWD,PWD),
atomic_concat([PWD,'/',X,'/'],D),
atomic_concat(['mkdir ',D],Mkdir),
(file_exists(X) -> true; shell(Mkdir)),
assert(work_dir(D)).
%%%%%%%%%%%%
% save BDD information for the (last) lower bound BDD used during inference
% produces three files named save_script, save_params, save_map
% located in the directory given by problog_flag dir
%%%%%%%%%%%%
set_problog_flag(save_bdd,true) :-
!,
retractall(save_bdd(_)),
assert(save_bdd(true)).
set_problog_flag(save_bdd,false) :-
!,
retractall(save_bdd(_)),
assert(save_bdd(false)).
set_problog_flag(save_bdd,_) :-
format(user,'\% ERROR: value must be \'true\' or \'false\'!~n',[]),
flush_output(user),
fail.
%%%%%%%%%%%%
% determine whether ProbLog outputs information (number of proofs, intermediate results, ...)
% default is true, as otherwise problog_delta won't output intermediate bounds
%%%%%%%%%%%%
set_problog_flag(verbose,true) :-
!,
retractall(problog_verbose(_)),
assert(problog_verbose(true)).
set_problog_flag(verbose,false) :-
!,
retractall(problog_verbose(_)),
assert(problog_verbose(false)).
set_problog_flag(verbose,_) :-
format(user,'\% ERROR: value must be \'true\' or \'false\'!~n',[]),
flush_output(user),
fail.
set_problog_flag(fast_proofs,true) :-
retractall(fast_proofs(_)),
assert(fast_proofs(true)).
set_problog_flag(fast_proofs,false) :-
retractall(fast_proofs(_)),
assert(fast_proofs(false)).
set_problog_flag(fast_proofs,V) :-
format(user,'\% ERROR: value ~w should be \'true\' or \'false\'!~n',[V]),
flush_output(user),
fail.
linesearch_interval_handler(message,'nonempty interval(L,H)').
linesearch_interval_handler(validating,V):-
V=(L,H),
number(L),
number(H),
L<H.
%linesearch_interval_handler(validate,_).
linesearch_interval_handler(validated,_).
linesearch_interval_handler(stored,_).
%%%%%%%%%%%%%%%%%%%%%%%%
% show values
%%%%%%%%%%%%%%%%%%%%%%%%
problog_flags :-
format('~n',[]),
print_sep_line,
format('problog flags: use set_problog_flag(Flag,Option) to change, problog_flag(Flag,Option) to view~n',[]),
print_sep_line,
print_param(description,value,flag,option),
print_sep_line,
problog_flag(bdd_time,StopBDD),
print_param('BDD computation timeout in seconds',StopBDD,'bdd_time','positive integer'),
problog_flag(first_threshold,First),
print_param('starting threshold iterative deepening',First,'first_threshold','0 =< Option =< 1'),
problog_flag(last_threshold,Last),
print_param('stopping threshold iterative deepening',Last,'last_threshold','0 =< Option =< 1'),
problog_flag(id_stepsize,Decrease),
print_param('threshold shrinking factor iterative deepening',Decrease,'id_stepsize','0 < Option < 1'),
problog_flag(prunecheck,Check),
print_param('stop derivations including all facts of known proof',Check,'prunecheck','on/off'),
problog_flag(maxsteps,Steps),
print_param('max. number of prob. steps per derivation',Steps,'maxsteps','positive integer'),
problog_flag(mc_batchsize,MCBatch),
print_param('number of samples before update in montecarlo',MCBatch,'mc_batchsize','positive integer'),
problog_flag(mc_logfile,MCFile),
print_param('logfile for montecarlo',MCFile,'mc_logfile','atom'),
problog_flag(bdd_file,BDDFile),
print_param('file for BDD script',BDDFile,'bdd_file','atom'),
problog_flag(dir,WorkDir),
print_param('directory for files',WorkDir,'dir','atom'),
problog_flag(save_bdd,Save),
print_param('save BDD files for (last) lower bound',Save,'save_bdd','true/false'),
problog_flag(verbose,Verbose),
print_param('output intermediate information',Verbose,'verbose','true/false'),
print_sep_line,
format('~n',[]),
flush_output.
learning_output_dir_handler(message, '').
learning_output_dir_handler(validating, _Value).
learning_output_dir_handler(validated, _Value).
learning_output_dir_handler(stored, Value):-
concat_path_with_filename(Value,'out.dat',Filename),
logger_set_filename(Filename).
/*
problog_flag_validate_learninginit
problog_flag_validate_interval
validation_type_values(problog_flag_validate_learninginit,'(QueryID,P, BDD,Probs,Call)').
validation_type_values(problog_flag_validate_learningprobinit,'(FactID,P,Call)').
validation_type_values(problog_flag_validate_interval,'any nonempty interval (a,b)').
problog_flag_validate_interval.
problog_flag_validate_interval( (V1,V2) ) :-
number(V1),
number(V2),
V1<V2.
*/

View File

@ -0,0 +1,597 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Theofrastos Mantadelis
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
% ensure that installation of your Modified Version does not prevent the
% user installing or running the Standard Version. In addition, the
% modified Version must bear a name that is different from the name of
% the Standard Version. (c) allow anyone who receives a copy of the
% Modified Version to make the Source form of the Modified Version
% available to others under (i) the Original License or (ii) a license
% that permits the licensee to freely copy, modify and redistribute the
% Modified Version using the same licensing terms that apply to the copy
% that the licensee received, and requires that the Source form of the
% Modified Version, and of any works derived from it, be made freely
% available in that license fees are prohibited but Distributor Fees are
% allowed.
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
% valid at the time of your distribution. If these instructions, at any
% time while you are carrying out such distribution, become invalid, you
% must provide new instructions on demand or cease further
% distribution. If you provide valid instructions or cease distribution
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
% Package. Distributor Fees are permitted, and licensing fees for other
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
% include the Package, and Distribute the result without restriction,
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
% considered parts of the Package itself, and are not subject to the
% terms of this license.
%
% General Provisions
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
% patent claims licensable by the Copyright Holder that are necessarily
% infringed by the Package. If you institute patent litigation
% (including a cross-claim or counterclaim) against any party alleging
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% To define flags do: defined_flag(Flag, Type, Description, DefaultValue).
% Available predifined types:
% flag_validate_dummy
% flag_validate_atom
% flag_validate_atomic
% flag_validate_number
% flag_validate_integer
% flag_validate_directory
% flag_validate_file
% flag_validate_in_list(L)
% flag_validate_in_interval(I, Type)
% flag_validate_in_interval_closed(I)
% flag_validate_in_interval_open(I)
% flag_validate_in_interval_left_open(I)
% flag_validate_in_interval_right_open(I)
% flag_validate_integer_in_interval_closed(I)
% flag_validate_integer_in_interval_open(I)
% flag_validate_integer_in_interval_left_open(I)
% flag_validate_integer_in_interval_right_open(I)
% flag_validate_float_in_interval_closed(I)
% flag_validate_float_in_interval_open(I)
% flag_validate_float_in_interval_left_open(I)
% flag_validate_float_in_interval_right_open(I)
% flag_validate_posnumber
% flag_validate_posint
% flag_validate_nonegint
% flag_validate_boolean
% flag_validate_switch
%
:-module(gflags, [flag_define/4,
flag_define/5,
flag_define/6,
flag_add_validation_syntactic_sugar/2,
flag_group_defined/1, % messaging purposes
flag_defined/5, % messaging purposes
flag_set/2,
flag_store/2, % sets flag with no validation, useful for handler
flag_get/2,
flags_reset/0]).
:-ensure_loaded(library(lists)).
:-ensure_loaded(library(system)). % for file operations
flag_define(Flag, Type, DefaultValue, Message):-
flag_define(Flag, general, Type, DefaultValue, flags:true, Message).
flag_define(Flag, Group, Type, DefaultValue, Message):-
flag_define(Flag, Group, Type, DefaultValue, flags:true, Message).
flag_define(Flag, Group, Type, DefaultValue, Handler, Message):-
recorded(flags, defined_flag(Flag, _Group, _Type, _DefaultValue, _Handler, _Message), _Ref),
throw(duplicate_flag_definition(flag_define(Flag, Group, Type, DefaultValue, Handler, Message))).
flag_define(Flag, Group, Type, DefaultValue, Handler, Message):-
(catch(call(Type), _, fail)->
fail
;
\+ (flag_validation_syntactic_sugar(Type, SyntacticSugar), catch(call(SyntacticSugar), _, fail)),
throw(unknown_flag_type(flag_define(Flag, Group, Type, DefaultValue, Handler, Message)))
).
flag_define(Flag, Group, Type, DefaultValue, Handler, Message):-
\+ Handler = _M:_Atom,
throw(non_module_aware_flag_handler(flag_define(Flag, Group, Type, DefaultValue, Handler, Message))).
flag_define(Flag, Group, Type, DefaultValue, M:Handler, Message):-
\+ (callable(Handler), atom(Handler), atom(M)),
throw(non_callable_atom_flag_handler(flag_define(Flag, Group, Type, DefaultValue, M:Handler, Message))).
flag_define(Flag, Group, Type, DefaultValue, Handler, Message):-
\+ flag_validate(Flag, DefaultValue, Type, Handler),
throw(erroneous_flag_default_value(flag_define(Flag, Group, Type, DefaultValue, Handler, Message))).
flag_define(_Flag, Group, Type, DefaultValue, Handler, Message):-
\+ Group == general,
(var(Group) ->
throw(erroneous_flag_group(flag_define(_Flag, Group, Type, DefaultValue, Handler, Message)))
;
recordzifnot(flags, flag_group(Group), _Ref),
fail
).
flag_define(Flag, Group, Type, DefaultValue, Handler, Message):-
recordz(flags, defined_flag(Flag, Group, Type, DefaultValue, Handler, Message), Ref),
(catch(flag_set(Flag, DefaultValue), Exception, (erase(Ref), throw(Exception))) ->
true
;
erase(Ref),
throw(handler_error(flag_define(Flag, Group, Type, DefaultValue, Handler, Message)))
).
flag_group_defined(general).
flag_group_defined(Group):-
recorded(flags, flag_group(Group), _Ref).
flag_defined(Flag, Group, DefaultValue, Domain, Message):-
recorded(flags, defined_flag(Flag, Group, Type, DefaultValue, Handler, Message), _Ref),
flag_get_domain_message(Type, Handler, Domain).
flag_get_domain_message(Type, M:Handler, Message):-
validation_type_values(Type, Domain),
(Handler == true ->
Message = Domain
;
Goal =.. [Handler, message, CustomDomain],
call(M:Goal),
((nonvar(CustomDomain), CustomDomain \= '') ->
(Domain == '' ->
Message = CustomDomain
;
atomic_concat([CustomDomain, '/', Domain], Message)
)
;
Message = Domain
)
).
flag_set(Flag, _Value):-
var(Flag), throw(not_defined_flag_exception('free variable')).
flag_set(Flag, _Value):-
\+ recorded(flags, defined_flag(Flag, _Group, _Type, _DefaultValue, _Handler, _Message), _Ref),
throw(not_defined_flag_exception(Flag)).
flag_set(Flag, Value):-
recorded(flags, defined_flag(Flag, _Group, Type, _DefaultValue, M:Handler, _Message), _Ref),
(Handler == true ->
GoalValidated = true,
GoalStored = true
;
GoalValidated =.. [Handler, validated, Value],
GoalStored =.. [Handler, stored, Value]
),
flag_validate(Flag, Value, Type, M:Handler),
call(M:GoalValidated),
flag_store(Flag, Value),
call(M:GoalStored).
flag_get(Flag, Value):-
recorded(flag_values, flag(Flag, Value), _Ref).
flag_store(Flag, Value):-
(recorded(flag_values, flag(Flag, _), Ref) ->
erase(Ref)
;
true
),
recordz(flag_values, flag(Flag, Value), _Ref).
flags_reset:-
recorded(flags, defined_flag(Flag, _Group, _Type, DefaultValue, _Handler, _Message), _Ref),
flag_set(Flag, DefaultValue),
fail.
flags_reset.
flag_validate(_Flag, Value, _Type, M:Handler):-
Handler \= true,
GoalValidate =.. [Handler, validate, Value],
call(M:GoalValidate), !.
flag_validate(_Flag, Value, Type, M:Handler):-
Handler \= true,
GoalValidating =.. [Handler, validating, Value],
Type =.. LType,
append(LType, [Value], LGoal),
G =.. LGoal,
catch((call(M:GoalValidating), call(G)), _, fail), !.
flag_validate(_Flag, Value, Type, _M:Handler):-
Handler == true,
Type =.. LType,
append(LType, [Value], LGoal),
G =.. LGoal,
catch(call(G), _, fail), !.
flag_validate(_Flag, Value, SyntacticSugar, M:Handler):-
Handler \= true,
GoalValidating =.. [Handler, validating, Value],
flag_validation_syntactic_sugar(SyntacticSugar, Type),
Type =.. LType,
append(LType, [Value], LGoal),
G =.. LGoal,
catch((call(M:GoalValidating), call(G)), _, fail), !.
flag_validate(_Flag, Value, SyntacticSugar, _M:Handler):-
Handler == true,
flag_validation_syntactic_sugar(SyntacticSugar, Type),
Type =.. LType,
append(LType, [Value], LGoal),
G =.. LGoal,
catch(call(G), _, fail), !.
flag_validate(Flag, Value, Type, Handler):-
(var(Value) ->
Value = 'free variable'
;
true
),
flag_get_domain_message(Type, Handler, Domain),
throw(out_of_domain_exception(Flag, Value, Domain)).
%
% The validation predicates
%
flag_validate_dummy.
flag_validate_dummy(Value):-
nonvar(Value).
flag_validate_atom.
flag_validate_atom(Value):-
atom(Value).
flag_validate_atomic.
flag_validate_atomic(Value):-
atomic(Value).
flag_validate_number.
flag_validate_number(Value):-
number(Value).
flag_validate_integer.
flag_validate_integer(Value):-
integer(Value).
flag_validate_directory.
flag_validate_directory(Value):-
atomic(Value),
catch(file_exists(Value), _, fail),
file_property(Value, type(directory)), !.
flag_validate_directory(Value):-
atomic(Value),
% fixme : why not inform the user???
catch((not(file_exists(Value)), make_directory(Value)), _, fail).
flag_validate_file.
flag_validate_file(Value):-
catch(file_exists(Value), _, fail), file_property(Value, type(regular)), !.
flag_validate_file(Value):-
atomic(Value),
catch((not(file_exists(Value)), tell(Value)), _, fail),
told,
delete_file(Value).
flag_validate_in_list(Domain):-
is_list(Domain), ground(Domain), \+ Domain = [].
flag_validate_in_list(Domain, Value):-
ground(Value),
memberchk(Value, Domain).
flag_validate_in_interval([L, U], Type):-
nonvar(Type),
(Type = number ->
number(L), number(U), L =< U
;
(Type = float ->
float(L), float(U), L =< U
;
Type = integer, integer(L), integer(U), L =< U
)
).
flag_validate_in_interval((L, U), Type):-
nonvar(Type),
(Type = number ->
number(L), number(U), L < U
;
(Type = float ->
float(L), float(U), L < U
;
Type = integer, (integer(L);L is -inf), (integer(U);U is +inf), L < U
)
).
flag_validate_in_interval(([L], U), Type):-
nonvar(Type),
(Type = number ->
number(L), number(U), L < U
;
(Type = float ->
float(L), float(U), L < U
;
Type = integer, integer(L), (integer(U);U is +inf), L < U
)
).
flag_validate_in_interval((L, [U]), Type):-
nonvar(Type),
(Type = number ->
number(L), number(U), L < U
;
(Type = float ->
float(L), float(U), L < U
;
Type = integer, (integer(L);L is -inf), integer(U), L < U
)
).
flag_validate_in_interval(([L], [U]), Type):-
nonvar(Type),
(Type = number ->
number(L), number(U), L =< U
;
(Type = float ->
float(L), float(U), L =< U
;
Type = integer, integer(L), integer(U), L =< U
)
).
flag_validate_in_interval([L, U], Type, Value):-
check_same_type(Type, Value, L, U),
Value >= L,
Value =< U, !.
flag_validate_in_interval((L, U), Type, Value):-
check_same_type(Type, Value, L, U),
Value > L,
Value < U, !.
flag_validate_in_interval(([L], U), Type, Value):-
check_same_type(Type, Value, L, U),
Value >= L,
Value < U, !.
flag_validate_in_interval((L, [U]), Type, Value):-
check_same_type(Type, Value, L, U),
Value > L,
Value =< U, !.
flag_validate_in_interval(([L], [U]), Type, Value):-
check_same_type(Type, Value, L, U),
Value >= L,
Value =< U.
check_same_type(integer, Value, L, U):-
integer(L), integer(U), integer(Value), !.
check_same_type(integer, Value, L, +inf):-
integer(L), integer(Value), !.
check_same_type(integer, Value, -inf, U):-
integer(U), integer(Value), !.
check_same_type(integer, Value, -inf, +inf):-
integer(Value), !.
check_same_type(float, Value, L, U):-
float(L), float(U), float(Value).
check_same_type(number, Value, L, U):-
number(L), number(U), number(Value).
% This is only for messaging purposes. Each validation type should have one.
make_list_msg([H], H).
make_list_msg([H|T], Msg/H):-
make_list_msg(T, Msg).
validation_type_values(flag_validate_dummy, '').
validation_type_values(flag_validate_atom, 'any atom').
validation_type_values(flag_validate_atomic, 'any atomic').
validation_type_values(flag_validate_number, 'any number').
validation_type_values(flag_validate_integer, 'any integer').
validation_type_values(flag_validate_directory, 'any valid directory').
validation_type_values(flag_validate_file, 'any valid file').
validation_type_values(flag_validate_in_list(L), Msg):-
reverse(L, R),
make_list_msg(R, Msg).
validation_type_values(flag_validate_in_interval((L, U), Type), Domain):-
number(L), number(U),
atomic_concat([Type,' in (', L, ',', U, ')'], Domain).
validation_type_values(flag_validate_in_interval(([L], U), Type), Domain):-
number(L), number(U),
atomic_concat([Type,' in [', L, ',', U, ')'], Domain).
validation_type_values(flag_validate_in_interval((L, [U]), Type), Domain):-
number(L), number(U),
atomic_concat([Type,' in (', L, ',', U, ']'], Domain).
validation_type_values(flag_validate_in_interval(([L], [U]), Type), Domain):-
number(L), number(U),
atomic_concat([Type,' in [', L, ',', U, ']'], Domain).
validation_type_values(flag_validate_in_interval([L, U], Type), Domain):-
number(L), number(U),
atomic_concat([Type,' in [', L, ',', U, ']'], Domain).
validation_type_values(ValidationType, Domain):-
flag_validation_syntactic_sugar(ValidationType, SyntacticSugar),
validation_type_values(SyntacticSugar, Domain).
%
% Syntactic sugar validation types
%
flag_validation_syntactic_sugar(SyntacticSugar, Type):-
recorded(flags, validation_syntactic_sugar(SyntacticSugar, Type), _Ref).
flag_add_validation_syntactic_sugar(SyntacticSugar, Type):-
recordzifnot(flags, validation_syntactic_sugar(SyntacticSugar, Type), _Ref).
% End of validation predicates

View File

@ -0,0 +1,747 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Theofrastos Mantadelis
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
% ensure that installation of your Modified Version does not prevent the
% user installing or running the Standard Version. In addition, the
% modified Version must bear a name that is different from the name of
% the Standard Version. (c) allow anyone who receives a copy of the
% Modified Version to make the Source form of the Modified Version
% available to others under (i) the Original License or (ii) a license
% that permits the licensee to freely copy, modify and redistribute the
% Modified Version using the same licensing terms that apply to the copy
% that the licensee received, and requires that the Source form of the
% Modified Version, and of any works derived from it, be made freely
% available in that license fees are prohibited but Distributor Fees are
% allowed.
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
% valid at the time of your distribution. If these instructions, at any
% time while you are carrying out such distribution, become invalid, you
% must provide new instructions on demand or cease further
% distribution. If you provide valid instructions or cease distribution
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
% Package. Distributor Fees are permitted, and licensing fees for other
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
% include the Package, and Distribute the result without restriction,
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
% considered parts of the Package itself, and are not subject to the
% terms of this license.
%
% General Provisions
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
% patent claims licensable by the Copyright Holder that are necessarily
% infringed by the Package. If you institute patent litigation
% (including a cross-claim or counterclaim) against any party alleging
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Module hash_table.
%
% Maps tuples of form (x1,x2,...,xn) to incremental IDs.
% Ensures lookup time for tuple = O(n) with n being the size of tuple lookup
% time is independed from the amount of entries in the table when +Size big.
% If +Size not big enought then lookup time linear per +Size entries.
% To return from ID to tuple again constant time but based on +TuppleSize.
%
% Exports:
%
% hash_table_init(+Size, -HashTable)
% hash_table_init(+Size, +TupleSize, -HashTable)
%
% Initializes a hash table with internal array size of +Size, and #tuples
% of +TupleSize.
% +Size ~> # of problog different prob facts.
% +TupleSize ~> estimated tuples to be used.
%
% hash_table_set_domain_size(+HashTable, +Tuple, +TupleSize)
%
% Useful to define that a specific +Tuple mask will have specific internal
% size. It also pre initialized an array for the ID.
% Examples: if problog fact ID1 is a non-ground and we now that it has
% 1000 possible groundings then: hash_table_set_domain_size(HT, ID1, 1000).
% problog fact ID2 is an mvs with 5 possible values and each is non
% ground with 100 possible values then: hash_table_set_domain_size(HT, ID2, 5),
% hash_table_set_domain_size(HT, (ID2,'*'), 100).
% When emmitted the internal array will assume the defined size from father.
%
% hash_table_delete(+HashTable)
%
% Clears the +HashTable
%
% hash_table_display(+HashTable, +ColSize, +PaneSize)
%
% Debug only purposes currently.
%
% hash_table_lookup(+HashTable, +Tuple, -ID)
% hash_table_lookup(+HashTable, -Tuple, +ID)
%
% This is the lookup function. Either takes a +Tuple and retuns an -ID
% or vice versa. Handles collisions, automatically grows array by a chain
% of arrays.
%
% hash_table_contains(+HashTable, +Tuple, -ID)
%
% Similar with lookup but only checks if +Tuple has been seen and returns -ID.
%
% hash_table_get_entries(+HashTable, -Count)
%
% Returns the # of tuples seen up to now.
%
% problog_key_to_tuple(+Key, -Tuple)
%
% Takes a +Key of format "ID1_ID2" and makes a tuple (ID1, ID2)
%
%
% IMPORTANT: Currently it under performs for some reason...
%
:- module(hash_table, [hash_table_init/2,
hash_table_init/3,
hash_table_set_domain_size/3,
hash_table_delete/1,
hash_table_reset/1,
hash_table_lookup/3,
hash_table_contains/3,
hash_table_get_entries/2,
hash_table_display/3,
problog_key_to_tuple/2]).
:- ensure_loaded(library(lists)).
%
% General use predicates
%
int(N):-
int(0, N).
int(N, N).
int(P, R):-
N is P + 1,
int(N, R).
get_digits(Num, Digits):-
get_digits(Num, Digits, 1).
get_digits(Num, Digits, Digits):-
Num < 10, !.
get_digits(Num, Digits, Acc):-
NNum is Num / 10,
NAcc is Acc + 1,
get_digits(NNum, Digits, NAcc).
%
% Simple Counters
%
:- bb_put(array_count, 1).
get_next_array(ID, Name):-
bb_get(array_count, ID),
NewID is ID + 1,
bb_put(array_count, NewID),
number_atom(ID, Name).
get_next_identifier(Identifier, Next):-
bb_get(Identifier, Next),
NewNext is Next + 1,
bb_put(Identifier, NewNext).
%
% Syntactic Sugar
%
get_array_name(ID, Array):- % if you change this, you need to change also get_next_array
% char_code(Array, ID).
number_atom(ID, Array).
% atomic_concat(array, ID, Array).
get_array_identifier(ID, Identifier):-
atomic_concat(array_identifier, ID, Identifier).
%
% hash_table_init(+Size, -HashTable)
% initializes a HashTable with Size positions, collitions are handled
% by expanding a new array that is kept at the last array element
%
hash_table_init(Size, HashTable):-
hash_table_init(Size, Size, HashTable).
hash_table_init(Size, RevSize, HashTable):-
ArraySize is Size + 1,
get_next_array(ID, Array),
get_array_identifier(ID, Identifier),
static_array(Array, ArraySize, int),
bb_put(Identifier, 1),
RevArraySize is RevSize + 1,
get_next_array(_RevID, RevArray),
static_array(RevArray, RevArraySize, term),
recordz(hash_table, hash(Array, Size, Identifier, RevArray, RevSize), HashTable).
hash_table_expand_array(Array, Size, NewArray):-
ArraySize is Size + 1,
get_next_array(ID, NewArray),
static_array(NewArray, ArraySize, int),
update_array(Array, Size, ID).
hash_table_sub_array_init(Array, Index, NewArray, Size):-
ArraySize is Size + 1,
get_next_array(ID, NewArray),
static_array(NewArray, ArraySize, int),
recordz(hash_table_arrays, array(ID, NewArray, Size, Array), _),
update_array(Array, Index, ID).
%
% hash_table_set_domain_size(HashTable, Index, DomainSize)
%
hash_table_set_domain_size(HashTable, Index, DomainSize):-
ground(Index),
ground(HashTable),
recorded(hash_table, hash(Array, Size, _Identifier, _RevArray, _RevSize), HashTable),
hash_table_set_domain_size(Array, Size, Index, DomainSize).
hash_table_set_domain_size(Array, Size, Index, DomainSize):-
integer(Index),
Index < Size, !,
array_element(Array, Index, A),
(A is 0 ->
hash_table_sub_array_init(Array, Index, _NewArray, DomainSize)
;
throw(hash_table_exception(set_domain_size_fail(duplicate_definition(Index, DomainSize))))
).
hash_table_set_domain_size(Array, Size, Index, DomainSize):-
integer(Index), !,
NewIndex is Index - Size,
array_element(Array, Size, SubArrayID),
(SubArrayID is 0->
hash_table_expand_array(Array, Size, NewArray)
;
get_array_name(SubArrayID, NewArray)
),
hash_table_set_domain_size(NewArray, Size, NewIndex, DomainSize).
hash_table_set_domain_size(Array, Size, Index, DomainSize):-
Index == '*', !,
int(N),
hash_table_set_domain_size(Array, Size, N, DomainSize),
N is Size - 1, !.
hash_table_set_domain_size(Array, Size, (Index, Rest), DomainSize):-
integer(Index),
Index < Size, !,
array_element(Array, Index, SubArrayID),
(SubArrayID is 0->
throw(hash_table_exception(set_domain_size_fail(sub_array_missing((Index, Rest), DomainSize))))
;
recorded(hash_table_arrays, array(SubArrayID, SubArray, SubArraySize, Array), _)
),
hash_table_set_domain_size(SubArray, SubArraySize, Rest, DomainSize).
hash_table_set_domain_size(Array, Size, (Index, Rest), DomainSize):-
integer(Index),
NewIndex is Index - Size,
array_element(Array, Size, SubArrayID),
(SubArrayID is 0->
hash_table_expand_array(Array, Size, NewArray)
;
get_array_name(SubArrayID, NewArray)
),
hash_table_set_domain_size(NewArray, Size, (NewIndex, Rest), DomainSize).
%
% hash_table_delete(+HashTable)
% deletes the arrays, records, and blackboard variables related with the hashtable
%
hash_table_delete(HashTable):-
ground(HashTable),
recorded(hash_table, hash(Array, Size, Identifier, RevArray, RevSize), HashTable),
bb_delete(Identifier, _),
erase(HashTable),
hash_table_delete_array(Array, Size),
hash_table_delete_rev_array(RevArray, RevSize).
hash_table_delete_array(Array, Size):-
hash_table_delete_chain(Array, Size),
hash_table_delete_subarrays(Array),
close_static_array(Array).
hash_table_delete_chain(Array, Size):-
array_element(Array, Size, ChainArrayID),
(ChainArrayID is 0 ->
true
;
get_array_name(ChainArrayID, ChainArray),
hash_table_delete_array(ChainArray, Size)
).
hash_table_delete_subarrays(Array):- % I can improve the performance of this by making a second record with Array infront
forall(recorded(hash_table_arrays, array(_SubArrayID, SubArray, Size, Array) , Ref),
(erase(Ref), hash_table_delete_array(SubArray, Size))).
hash_table_delete_rev_array(Array, Size):-
(array_element(Array, Size, ChainArray) ->
hash_table_delete_rev_array(ChainArray, Size)
;
true
),
close_static_array(Array).
%
% hash_table_reset(+HashTable)
%
% resets the table values, retains the structure
%
hash_table_reset(HashTable):-
ground(HashTable),
recorded(hash_table, hash(Array, Size, Identifier, RevArray, RevSize), HashTable),
hash_table_get_entries(HashTable, Count),
int(Index),
hash_table_lookup(HashTable, Tuple, Index),
hash_table_reset_element(Array, Size, Tuple),
Index is Count - 1, !,
hash_table_reset_rev_array(RevArray, RevSize),
bb_put(Identifier, 1).
hash_table_reset_element(Array, Size, Index):-
integer(Index),
Index < Size, !,
update_array(Array, Index, 0).
hash_table_reset_element(Array, Size, Index):-
integer(Index),
NewIndex is Index - Size,
array_element(Array, Size, SubArrayID),
get_array_name(SubArrayID, SubArray),
hash_table_reset_element(SubArray, Size, NewIndex).
hash_table_reset_element(Array, Size, (Index, Rest)):-
integer(Index),
Index < Size, !,
array_element(Array, Index, SubArrayID),
recorded(hash_table_arrays, array(SubArrayID, SubArray, SubArraySize, Array), _),
hash_table_reset_element(SubArray, SubArraySize, Rest).
hash_table_reset_element(Array, Size, (Index, Rest)):-
integer(Index),
NewIndex is Index - Size,
array_element(Array, Size, SubArrayID),
get_array_name(SubArrayID, SubArray),
hash_table_reset_element(SubArray, Size, (NewIndex, Rest)).
hash_table_reset_rev_array(RevArray, RevSize):-
array_element(RevArray, RevSize, ChainArray), !,
reset_static_array(RevArray),
update_array(RevArray, RevSize, ChainArray),
hash_table_reset_rev_array(ChainArray, RevSize).
hash_table_reset_rev_array(RevArray, _RevSize):-
reset_static_array(RevArray).
%
% hash_table_lookup(+HashTable, +Tuple, -ID)
% hash_table_lookup(+HashTable, -Tuple, +ID)
% lookup Tuple in HashTable and insert, return ID
% lookup ID in HashTable and return Tuple
%
% Known bug: If HashTable contains a Tuple of form (ID, _) looking up ID succeeds
% and returns the SubArrayID.
% This is safe under the assumption that ID is unique to start from.
%
hash_table_lookup(HashTable, Tuple, ID):-
ground(Tuple),
ground(HashTable), !,
recorded(hash_table, hash(Array, Size, Identifier, RevArray, RevSize), HashTable),
hash_table_lookup(Array, Size, Identifier, Tuple, ID),
hash_table_update_rev_array(RevArray, RevSize, ID, Tuple).
hash_table_lookup(HashTable, Tuple, ID):-
integer(ID),
ground(HashTable),
recorded(hash_table, hash(_Array, _Size, _Identifier, RevArray, RevSize), HashTable),
hash_table_element_rev_array(RevArray, RevSize, ID, Tuple).
hash_table_lookup(Array, Size, Identifier, Index, RID):-
integer(Index),
Index < Size, !,
array_element(Array, Index, StoredID),
(StoredID is 0 ->
get_next_identifier(Identifier, ID),
update_array(Array, Index, ID)
;
ID = StoredID
),
RID is ID - 1.
hash_table_lookup(Array, Size, Identifier, Index, ID):-
integer(Index), !,
NewIndex is Index - Size,
array_element(Array, Size, ArrayID),
(ArrayID is 0 ->
hash_table_expand_array(Array, Size, SubArray)
;
get_array_name(ArrayID, SubArray)
),
hash_table_lookup(SubArray, Size, Identifier, NewIndex, ID).
hash_table_lookup(Array, Size, Identifier, (Index,Tuple), ID):-
integer(Index),
Index < Size, !,
array_element(Array, Index, ArrayID),
(ArrayID is 0 ->
NewSize = Size,
hash_table_sub_array_init(Array, Index, SubArray, Size)
;
recorded(hash_table_arrays, array(ArrayID, SubArray, NewSize, Array), _)
),
hash_table_lookup(SubArray, NewSize, Identifier, Tuple, ID).
hash_table_lookup(Array, Size, Identifier, (Index,Tuple), ID):-
integer(Index),
NewIndex is Index - Size,
array_element(Array, Size, ArrayID),
(ArrayID is 0 ->
hash_table_expand_array(Array, Size, SubArray)
;
get_array_name(ArrayID, SubArray)
),
hash_table_lookup(SubArray, Size, Identifier, (NewIndex, Tuple), ID).
hash_table_update_rev_array(Array, Size, Index, Tuple):-
integer(Index),
Index < Size, !,
update_array(Array, Index, Tuple).
hash_table_update_rev_array(Array, Size, Index, Tuple):-
integer(Index),
NewIndex is Index - Size,
(array_element(Array, Size, SubArray) ->
true
;
SubArraySize is Size + 1,
get_next_array(_SubArrayID, SubArray),
static_array(SubArray, SubArraySize, term),
update_array(Array, Size, SubArray)
),
hash_table_update_rev_array(SubArray, Size, NewIndex, Tuple).
hash_table_element_rev_array(Array, Size, Index, Tuple):-
integer(Index),
Index < Size, !,
array_element(Array, Index, Tuple).
hash_table_element_rev_array(Array, Size, Index, Tuple):-
integer(Index),
NewIndex is Index - Size,
array_element(Array, Size, SubArray),
hash_table_element_rev_array(SubArray, Size, NewIndex, Tuple).
%
% hash_table_contains(+HashTable, +Tuple, -ID)
% search the hash_table to see if it contains a Tuple and return the ID
%
% Known bug: If HashTable contains a Tuple of form (ID, _) asking if HashTable
% contains ID it succeeds.
% This is safe under the assumption that ID is unique to start from.
%
hash_table_contains(HashTable, Tuple, ID):-
ground(Tuple),
ground(HashTable), !,
recorded(hash_table, hash(Array, Size, _Identifier, _RevArray, _RevSize), HashTable),
hash_table_contains(Array, Size, Tuple, ID).
hash_table_contains(Array, Size, Index, RID):-
integer(Index),
Index < Size, !,
array_element(Array, Index, ID),
ID > 0,
RID is ID - 1.
hash_table_contains(Array, Size, Index, ID):-
integer(Index), !,
NewIndex is Index - Size,
array_element(Array, Size, SubArrayID),
SubArrayID > 0,
get_array_name(SubArrayID, SubArray),
hash_table_contains(SubArray, Size, NewIndex, ID).
hash_table_contains(Array, Size, (Index,Tuple), ID):-
integer(Index),
Index < Size, !,
array_element(Array, Index, SubArrayID),
SubArrayID > 0,
recorded(hash_table_arrays, array(SubArrayID, SubArray, NewSize, Array), _),
hash_table_contains(SubArray, NewSize, Tuple, ID).
hash_table_contains(Array, Size, (Index,Tuple), ID):-
integer(Index),
NewIndex is Index - Size,
array_element(Array, Size, SubArrayID),
SubArrayID > 0,
get_array_name(SubArrayID, SubArray),
hash_table_contains(SubArray, Size, (NewIndex, Tuple), ID).
%
% hash_table_get_entries(+HashTable, -Count)
%
% returns the number of entries inside the hash table
%
hash_table_get_entries(HashTable, Count):-
ground(HashTable),
recorded(hash_table, hash(_Array, _Size, Identifier, _RevArray, _RevSize), HashTable),
bb_get(Identifier, Num),
Count is Num - 1.
%
% hash_table_display(+HashTable, +ColSize, +PaneSize)
%
% Only for debugging reasons.
%
hash_table_display(HashTable, ColSize, PaneSize):-
ground(HashTable), integer(ColSize), integer(PaneSize), ColSize =< PaneSize,
recorded(hash_table, hash(Array, Size, Identifier, RevArray, RevSize), HashTable),
hash_table_get_entries(HashTable, Count),
format('Hash Table: ~q~n Entries: ~d~n Identifier: ~w~n', [HashTable, Count, Identifier]),
hash_table_display_array(Array, Size),
hash_table_display_rev_array(RevArray, RevSize, Identifier, ColSize, PaneSize).
hash_table_display_array(Array, Size):-
hash_table_get_chains(Array, Size, Chains),
findall(SubArray, recorded(hash_table_arrays, array(_, SubArray, _, Array),_), SubArrays),
format('Array: ~q~n Size: ~d~n Chains: ~q~n Sub Arrays: ~q~n',[Array, Size, Chains, SubArrays]),
forall(member(SubArray, SubArrays), (
recorded(hash_table_arrays, array(_, SubArray, SubSize, Array),_),
hash_table_display_array(SubArray, SubSize)
)).
hash_table_display_rev_array(RevArray, RevSize, Identifier, ColSize, PaneSize):-
hash_table_get_chains(RevArray, RevSize, Chains),
format('Array: ~q~n Size: ~d~n Chains: ~q~n', [RevArray, RevSize, Chains]),
bb_get(Identifier, Num),
get_digits(Num, Digits),
hash_table_get_elements(RevArray, RevSize, 0, Tupples),
hash_table_display_elements(0, Tupples, Digits, ColSize, PaneSize).
hash_table_get_elements(RevArray, RevSize, Current, [Tupple|Tupples]):-
Current < RevSize,
array_element(RevArray, Current, Tupple), !,
Next is Current + 1,
hash_table_get_elements(RevArray, RevSize, Next, Tupples).
hash_table_get_elements(_RevArray, RevSize, Current, []):-
Current < RevSize, !.
hash_table_get_elements(RevArray, RevSize, RevSize, Tupples):-
array_element(RevArray, RevSize, NextArray), !,
hash_table_get_elements(NextArray, RevSize, 0, Tupples).
hash_table_get_elements(_RevArray, RevSize, RevSize, []).
hash_table_get_chains(Array, Size, Chains):-
((array_element(Array, Size, ChainID), not(ChainID == 0)) ->
(integer(ChainID) ->
get_array_name(ChainID, ChainName)
;
ChainName = ChainID
),
hash_table_get_chains(ChainName, Size, RestChains),
Chains = [ChainName|RestChains]
;
Chains = []
).
hash_table_display_elements(_Index, [], _Digits, _ColSize, _PaneSize):- format('~n',[]), !.
hash_table_display_elements(Index, [Element|T], Digits, ColSize, PaneSize):-
NL is Index mod integer(PaneSize / ColSize),
RealColSize is ColSize - Digits - 3,
((NL > 0; Index =:= 0) -> true; format('~n',[])),
format('~t~d~*+ = ~q~*+', [Index, Digits, Element, RealColSize]),
NewIndex is Index + 1,
hash_table_display_elements(NewIndex, T, Digits, ColSize, PaneSize).
%
% problog_key_to_tuple(+Key, -Tuple)
%
% This should be removed in new implementation
%
problog_key_to_tuple(Key, Key):-
integer(Key), !.
problog_key_to_tuple(Key, (PID, SID)):-
atomic(Key),
atom_chars(Key, ID_Chars),
break_list_at(ID_Chars, 95, Part1, Part2),
% once(append(Part1, [95|Part2], ID_Chars)), % 95 = '_'
number_chars(PID, Part1),
number_chars(SID, Part2).
break_list_at([H|T], H, [], T):-!.
break_list_at([H|T], At, [H|Part1], Part2):-
break_list_at(T, At, Part1, Part2).

View File

@ -2,16 +2,16 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2009-07-31 14:57:09 +0200 (Fri, 31 Jul 2009) $
% $Revision: 1826 $
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2009
% Angelika Kimmig, Vitor Santos Costa, Bernd Gutmann
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Bernd Gutmann
@ -204,295 +204,296 @@
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(flags_learning, [set_learning_flag/2,
learning_flag/2,
learning_flags/0]).
:- module(intervals, [intervals_merge/3,
intervals_disjoin/3,
intervals_disjoin/4,
intervals_partition/2,
intervals_encode/2]).
:- style_check(all).
:- yap_flag(unknown,error).
:- use_module(logger).
:- use_module('../problog/flags').
:- use_module('../problog/print').
:- ensure_loaded(library(system)).
:- dynamic init_method/5.
:- dynamic rebuild_bdds/1.
:- dynamic reuse_initialized_bdds/1.
:- dynamic learning_rate/1.
:- dynamic probability_initializer/3.
:- dynamic check_duplicate_bdds/1.
:- dynamic output_directory/1.
:- dynamic query_directory/1.
:- dynamic log_frequency/1.
:- dynamic alpha/1.
:- dynamic sigmoid_slope/1.
:- dynamic line_search/1.
:- dynamic line_search_tolerance/1.
:- dynamic line_search_tau/1.
:- dynamic line_search_never_stop/1.
:- dynamic line_search_interval/2.
:- dynamic verbosity_level/1.
:- use_module(library(lists)).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% global parameters that can be set using set_learning_flag/2
% intervals_merge(+Interval1,+Interval2,-ResultingInterval)
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
intervals_merge(all,X,X).
intervals_merge(none,_,none).
intervals_merge(above(X),Other,Result) :-
number(X),
intervals_merge_above(Other,X,Result).
intervals_merge(below(X),Other,Result) :-
number(X),
intervals_merge_below(Other,X,Result).
intervals_merge(interval(X1,X2),Other,Result) :-
number(X1),
number(X2),
intervals_merge_interval(Other,X1,X2,Result).
learning_flag(Flag,Option) :-
get_learning_flag(Flag,Option).
get_learning_flag(init_method,(Query,Probability,BDDFile,ProbFile,Call)) :-
init_method(Query,Probability,BDDFile,ProbFile,Call).
get_learning_flag(rebuild_bdds,Iteration) :-
rebuild_bdds(Iteration).
get_learning_flag(reuse_initialized_bdds,Flag) :-
reuse_initialized_bdds(Flag).
get_learning_flag(learning_rate,R) :-
learning_rate(R).
get_learning_flag(probability_initializer,(FactID,Probability,Query)) :-
probability_initializer(FactID,Probability,Query).
get_learning_flag(check_duplicate_bdds,Flag) :-
check_duplicate_bdds(Flag).
get_learning_flag(output_directory,Directory) :-
output_directory(Directory).
get_learning_flag(query_directory,Directory) :-
query_directory(Directory).
get_learning_flag(log_frequency,Frequency) :-
log_frequency(Frequency).
get_learning_flag(alpha,Alpha) :-
alpha(Alpha).
get_learning_flag(sigmoid_slope,Slope) :-
sigmoid_slope(Slope).
get_learning_flag(line_search,Flag) :-
line_search(Flag).
get_learning_flag(line_search_tolerance,Tolerance) :-
line_search_tolerance(Tolerance).
get_learning_flag(line_search_interval,(L,R)) :-
line_search_interval(L,R).
get_learning_flag(line_search_tau,Tau) :-
line_search_tau(Tau).
get_learning_flag(line_search_never_stop,Flag) :-
line_search_never_stop(Flag).
get_learning_flag(verbosity_level,Number) :-
verbosity_level(Number).
set_learning_flag(init_method,(Query,Probability,BDDFile,ProbFile,Call)) :-
retractall(init_method(_,_,_,_,_)),
assert(init_method(Query,Probability,BDDFile,ProbFile,Call)).
set_learning_flag(rebuild_bdds,Frequency) :-
integer(Frequency),
Frequency>=0,
retractall(rebuild_bdds(_)),
assert(rebuild_bdds(Frequency)).
set_learning_flag(reuse_initialized_bdds,Flag) :-
(Flag==true;Flag==false),
!,
retractall(reuse_initialized_bdds(_)),
assert(reuse_initialized_bdds(Flag)).
set_learning_flag(learning_rate,V) :-
(V=examples -> true;(number(V),V>=0)),
!,
retractall(learning_rate(_)),
assert(learning_rate(V)).
set_learning_flag(probability_initializer,(FactID,Probability,Query)) :-
var(FactID),
var(Probability),
callable(Query),
retractall(probability_initializer(_,_,_)),
assert(probability_initializer(FactID,Probability,Query)).
set_learning_flag(check_duplicate_bdds,Flag) :-
(Flag==true;Flag==false),
!,
retractall(check_duplicate_bdds(_)),
assert(check_duplicate_bdds(Flag)).
set_learning_flag(output_directory,Directory) :-
intervals_merge_above(all,X,above(X)).
intervals_merge_above(none,_,none).
intervals_merge_above(above(Y),X,above(Z)) :-
number(Y),
Z is max(X,Y).
intervals_merge_above(below(Y),X,Result) :-
number(Y),
(
file_exists(Directory)
X=<Y
->
file_property(Directory,type(directory));
make_directory(Directory)
),
absolute_file_name(Directory,Path),
atomic_concat([Path,'/'],PathSlash),
atomic_concat([Path,'/log.dat'],Log_File),
retractall(output_directory(_)),
assert(output_directory(PathSlash)),
logger_set_filename(Log_File),
set_problog_flag(dir,Directory).
set_learning_flag(query_directory,Directory) :-
(
file_exists(Directory)
->
file_property(Directory,type(directory));
make_directory(Directory)
),
absolute_file_name(Directory,Path),
atomic_concat([Path,'/'],PathSlash),
retractall(query_directory(_)),
assert(query_directory(PathSlash)).
set_learning_flag(log_frequency,Frequency) :-
integer(Frequency),
Frequency>=0,
retractall(log_frequency(_)),
assert(log_frequency(Frequency)).
set_learning_flag(alpha,Alpha) :-
(number(Alpha);Alpha==auto),
!,
retractall(alpha(_)),
assert(alpha(Alpha)).
set_learning_flag(sigmoid_slope,Slope) :-
number(Slope),
Slope>0,
retractall(sigmoid_slope(_)),
assert(sigmoid_slope(Slope)).
set_learning_flag(line_search,Flag) :-
(Flag==true;Flag==false),
!,
retractall(line_search(_)),
assert(line_search(Flag)).
set_learning_flag(line_search_tolerance,Number) :-
number(Number),
Number>0,
retractall(line_search_tolerance(_)),
assert(line_search_tolerance(Number)).
set_learning_flag(line_search_interval,(L,R)) :-
number(L),
number(R),
L<R,
retractall(line_search_interval(_,_)),
assert(line_search_interval(L,R)).
set_learning_flag(line_search_tau,Number) :-
number(Number),
Number>0,
retractall(line_search_tau(_)),
assert(line_search_tau(Number)).
set_learning_flag(line_search_never_stop,Flag) :-
(Flag==true;Flag==false),
!,
retractall(line_search_nerver_stop(_)),
assert(line_search_never_stop(Flag)).
set_learning_flag(verbosity_level,Level) :-
integer(Level),
retractall(verbosity_level(_)),
assert(verbosity_level(Level)),
(
Level<4
->
set_problog_flag(verbose,false);
set_problog_flag(verbose,true)
Result=interval(X,Y);
Result=none
).
intervals_merge_above(interval(Y1,Y2),X,Result):-
number(Y1),
number(Y2),
(
X=<Y1
->
Result=interval(Y1,Y2);
(
X=<Y2
->
Result=interval(X,Y2);
Result=none
)
).
intervals_merge_below(all,X,below(X)).
intervals_merge_below(none,_,none).
intervals_merge_below(above(Y),X,Result) :-
number(Y),
(
Y=<X
->
Result=interval(Y,X);
Result=none
).
intervals_merge_below(below(Y),X,below(Z)) :-
number(Y),
Z is min(X,Y).
intervals_merge_below(interval(Y1,Y2),X,Result) :-
number(Y1),
number(Y2),
(
X>=Y2
->
Result=interval(Y1,Y2);
(
X>=Y1
->
Result=interval(Y1,X);
Result=none
)
).
%%%%%%%%%%%%%%%%%%%%%%%%
% show values
%%%%%%%%%%%%%%%%%%%%%%%%
skolemize(T1,T2):-
copy_term(T1,T2),
numbervars(T2,0,_).
intervals_merge_interval(all,X1,X2,interval(X1,X2)).
intervals_merge_interval(none,_,_,none).
intervals_merge_interval(above(X),Y1,Y2,Result) :-
number(X),
intervals_merge_above(interval(Y1,Y2),X,Result).
intervals_merge_interval(below(X),Y1,Y2,Result) :-
number(X),
intervals_merge_below(interval(Y1,Y2),X,Result).
intervals_merge_interval(interval(X1,X2),Y1,Y2,Result) :-
number(X1),
number(X2),
(
X1<Y1
->
intervals_merge_interval_intern(X1,X2,Y1,Y2,Result);
intervals_merge_interval_intern(Y1,Y2,X1,X2,Result)
).
intervals_merge_interval_intern(_X1,X2,Y1,Y2,Result) :-
(
Y1=<X2
->
(
Y2=<X2
->
Result=interval(Y1,Y2);
Result=interval(Y1,X2)
);
Result=none
).
learning_flags :-
format('~n',[]),
print_sep_line,
format('learning flags: use set_learning_flag(Flag,Option) to change, learning_flag(Flag,Option) to view~n',[]),
print_sep_line,
print_param(description,value,flag,option),
print_sep_line,
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
learning_flag(output_directory,Output_Directory),
print_long_param('Where to store results',Output_Directory,'output_directory','path'),
select_all([],List,List).
select_all([H|T],List,Remainder) :-
once(select(H,List,TMP)),
select_all(T,TMP,Remainder).
learning_flag(query_directory,Query_Directory),
print_long_param('Where to store BDD files',Query_Directory,'query_directory','path'),
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
learning_flag(verbosity_level,Verbosity_Level),
print_param('How much output shall be given (0=nothing,5=all)',Verbosity_Level,'verbosity_level','0,1,..,5'),
print_sep_line,
learning_flag(reuse_initialized_bdds,Reuse_Initialized_Bdds),
print_param('Reuse BDDs from previous runs',Reuse_Initialized_Bdds,'reuse_initialized_bdds','true/false'),
learning_flag(rebuild_bdds,Rebuild_BDDs),
print_param('Rebuild BDDs every nth iteration (0=never)',Rebuild_BDDs,'rebuild_bdds','Integer>=0'),
learning_flag(check_duplicate_bdds,Check_Duplicate_BDDs),
print_param('Store intermediate results in hash table',Check_Duplicate_BDDs,'check_duplicate_bdds','true/false'),
learning_flag(init_method,Init_Method),
skolemize(Init_Method,Init_Method_SK),
print_long_param('ProbLog predicate to search proofs',Init_Method_SK,'init_method','(+Query,-P,+BDDFile,+ProbFile,+Call)'),
learning_flag(probability_initializer,Prob_Initializer),
skolemize(Prob_Initializer,Prob_Initializer_SK),
print_long_param('Predicate to initialize probabilities',Prob_Initializer_SK,'probability_initializer','(+FactID,-P,+Call)'),
print_sep_line,
intervals_disjoin(X,P,In,Out) :-
disjoin_intern(X,P,In),
select_all(In,P,Out).
intervals_disjoin(X,P,In) :-
disjoin_intern(X,P,In).
disjoin_intern(below(X),P,In) :-
findall((interval(A,B),Tail),(member((interval(A,B),Tail),P),B=<X),Tmp),
(
(member((below(Y),Tail),P),Y=<X)
->
In=[(below(Y),Tail)|Tmp];
In=Tmp
).
disjoin_intern(above(X),P,In) :-
findall((interval(A,B),Tail),(member((interval(A,B),Tail),P),A>=X),Tmp),
(
(member((above(Y),Tail),P),Y>=X)
->
In=[(above(Y),Tail)|Tmp];
In=Tmp
).
disjoin_intern(interval(X,Y),P,In) :-
findall((interval(A,B),Tail),(member((interval(A,B),Tail),P),A>=X,B=<Y),In).
learning_flag(log_frequency,Log_Frequency),
print_param('log results every nth iteration',Log_Frequency,'log_frequency','integer>0'),
learning_flag(alpha,Alpha),
print_param('weight of negative examples (auto=n_p/n_n)',Alpha,'alpha','number or "auto"'),
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% partitions a list of intervals into disjoined intervals
% together with their prefix
%
%
% ?- intervals_partition([below(10),above(5)],X).
% X = [(below(5.0),[]),
% (interval(5.0,10.0),[below(5.0)]),
% (above(10.0),[interval(5.0,10.0),below(5.0)])]
%
%
% intervals_partition(+List,-List)
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
learning_flag(sigmoid_slope,Slope),
print_param('slope of sigmoid function',Slope,'slope','number>0'),
intervals_partition([],[]).
intervals_partition([X|T],[(below(A), [])|T2]) :-
once(extract_points([X|T],[],[A|PT])),
to_interval(PT,A,[below(A)],T2).
print_sep_line,
learning_flag(learning_rate,Learning_Rate),
print_param('Default Learning rate (If line_search=false)',Learning_Rate,'learning_rate','0<Number or "examples"'),
learning_flag(line_search,Line_Search),
print_param('Use line search to estimate learning rate',Line_Search,'line_search','true/false'),
learning_flag(line_search_tau,Line_Search_Tau),
print_param('Tau value for line search',Line_Search_Tau,'line_search_tau','0<Number<1'),
learning_flag(line_search_tolerance,Line_Search_Tolerance),
print_param('Tolerance value for line search',Line_Search_Tolerance,'line_search_tolerance','0<Number'),
learning_flag(line_search_interval,Line_Search_Interval),
print_param('Interval for line search',Line_Search_Interval,'line_search_interval','(a,b) an interval with 0<=a<b'),
learning_flag(line_search_never_stop,Line_Search_Never_Stop),
print_param('Make tiny step if line search returns 0',Line_Search_Never_Stop,'line_search_never_stop','true/false'),
print_sep_line,
format('~n',[]),
flush_output.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% extracts from list of intervals all relevant constants
%
% ?- intervals:extract_points([below(10),above(5)],[],L).
% L = [5.0,10.0] ?
%
% extract_points(+List, +List, -List)
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
extract_points([],X,Y) :-
sort(X,Y).
extract_points([below(A)|T],X,Y) :-
A2 is float(A),
extract_points(T,[A2|X],Y).
extract_points([above(A)|T],X,Y) :-
A2 is float(A),
extract_points(T,[A2|X],Y).
extract_points([interval(A,B)|T],X,Y) :-
A2 is float(A),
B2 is float(B),
extract_points(T,[A2,B2|X],Y).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% transforms a sorted list of constants into a list of
% intervals together with their prefixes
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
to_interval([],A,Tail,[(above(A),Tail)]).
to_interval([B|T],A,Tail,[(interval(A,B),Tail)|T2]) :-
to_interval(T,B,[interval(A,B)|Tail],T2).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% encodes an interval as an atom
%
% ?- intervals_encode(below(42),X).
% X = lm1000h42
% ?- intervals_encode(above(23),X).
% X = l23h1000
% ?- intervals_encode(interval(-2.3,4.2),X).
% X = lm2d3h4d2 ?
%
% intervals_encode(+Interval,-Atom)
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
intervals_encode(below(X),Atom) :-
(
X < -1000
->
X2 is 2*X;
X2 is -1000
),
intervals_encode(interval(X2,X),Atom).
intervals_encode(above(X),Atom) :-
(
X > 1000
->
X2 is 2*X;
X2 is 1000
),
intervals_encode(interval(X,X2),Atom).
intervals_encode(interval(Low,High),Atom) :-
once(my_number_atom(Low,LowA)),
once(my_number_atom(High,HighA)),
atomic_concat([l,LowA,h,HighA],Atom).
my_number_atom(Number,Atom) :-
% make float
NumberF is Number+0.0,
number_codes(NumberF,XC),
reverse(XC,A),
remove_prefix_zeros(A,B),
remove_prefix_dot(B,C),
fix_special_cases(C,D),
reverse(D,DC),
replace_special_characters(DC,DC_Final),
atom_codes(Atom,DC_Final).
remove_prefix_zeros([],[]).
remove_prefix_zeros([X|T],Result) :-
(
X==48 % 48 = '0'
->
remove_prefix_zeros(T,Result);
Result=[X|T]
).
remove_prefix_dot([],[]).
remove_prefix_dot([X|T],Result) :-
(
X==46 % 46 = '.'
->
Result=T;
Result=[X|T]
).
fix_special_cases([],[48]).
fix_special_cases([H|T],Result) :-
(
[H|T] == [48,45] % ='0-'
->
Result=[48];
Result=[H|T]
).
replace_special_characters([],[]).
replace_special_characters([H|T],[H2|T2]) :-
(
H==45 % '-'
->
H2=109; % 'm'
(
H==46
->
H2=100; % 'd'
H2=H
)
),
replace_special_characters(T,T2).

View File

@ -2,18 +2,17 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2009-06-17 22:22:00 +0200 (Mi, 17 Jun 2009) $
% $Revision: 1550 $
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% Copyright 2009 Katholieke Universiteit Leuven
%
% Authors: Luc De Raedt, Bernd Gutmann, Angelika Kimmig,
% Vitor Santos Costa
%
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Bernd Gutmann
%
@ -216,7 +215,9 @@
logger_start_timer/1,
logger_stop_timer/1,
logger_write_data/0,
logger_write_header/0]).
logger_write_header/0,
logger_variable_is_set/1,
logger_add_to_variable/2]).
:- use_module(library(system),[datime/1,mktime/2]).
:- use_module(library(lists),[append/3,member/2]).
@ -369,6 +370,18 @@ logger_variable_is_set(Name) :-
bb_get(Key,X),
X \= null.
logger_add_to_variable(Name,Value) :-
(
logger_variable_is_set(Name)
->
(
logger_get_variable(Name,OldValue),
NewValue is OldValue+Value,
logger_set_variable_again(Name,NewValue)
);
logger_set_variable(Name,Value)
).
%========================================================================
%= Get the value of the variable name. If the value is not yet set or
%= if the variable does not exists, an error will be displayed and the

View File

@ -0,0 +1,666 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Theofrastos Mantadelis, Dimitar Sht. Shterionov
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
% ensure that installation of your Modified Version does not prevent the
% user installing or running the Standard Version. In addition, the
% modified Version must bear a name that is different from the name of
% the Standard Version. (c) allow anyone who receives a copy of the
% Modified Version to make the Source form of the Modified Version
% available to others under (i) the Original License or (ii) a license
% that permits the licensee to freely copy, modify and redistribute the
% Modified Version using the same licensing terms that apply to the copy
% that the licensee received, and requires that the Source form of the
% Modified Version, and of any works derived from it, be made freely
% available in that license fees are prohibited but Distributor Fees are
% allowed.
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
% valid at the time of your distribution. If these instructions, at any
% time while you are carrying out such distribution, become invalid, you
% must provide new instructions on demand or cease further
% distribution. If you provide valid instructions or cease distribution
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
% Package. Distributor Fees are permitted, and licensing fees for other
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
% include the Package, and Distribute the result without restriction,
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
% considered parts of the Package itself, and are not subject to the
% terms of this license.
%
% General Provisions
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
% patent claims licensable by the Copyright Holder that are necessarily
% infringed by the Package. If you institute patent litigation
% (including a cross-claim or counterclaim) against any party alleging
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(mc_DNF_sampling, [problog_dnf_sampling/3]).
:- ensure_loaded(library(lists)).
:- ensure_loaded(variables).
:- use_module(sampling, _, [problog_random/1,
problog_convergence_check/6]).
:- use_module(flags, _, [problog_define_flag/5,
problog_flag/2]).
:- use_module(os, _, [convert_filename_to_working_path/2]).
:- ensure_loaded(hash_table).
:- problog_define_flag(search_method, problog_flag_validate_in_list([linear, binary]), 'search method for picking proof', binary, monte_carlo_sampling_dnf).
:- problog_define_flag(represent_world, problog_flag_validate_in_list([list, record, array, hash_table]), 'structure that represents sampled world', array, monte_carlo_sampling_dnf).
:- problog_var_define(dnf_sampling_time, times, time, messages('DNF Sampling', ':', ' ms')).
:- problog_var_define(probability_lower, result, untyped, messages('Lower probability bound', ' = ', '')).
:- problog_var_define(probability_upper, result, untyped, messages('Upper probability bound', ' = ', '')).
% problog_independed(T, P):-
% tries:trie_traverse_first(T, FirstRef), !,
% problog_independed(FirstRef, P, 0.0, _, 0).
% problog_independed(_T, 0.0).
problog_independed(T, P, ProofCNT):-
tries:trie_traverse_first(T, FirstRef), !,
problog_independed(FirstRef, P, 0.0, ProofCNT, 0).
problog_independed(_T, 0.0, 0).
%%% this should be generalized to handle nested tries
problog_independed([], P, P, ProofCNT, ProofCNT).
problog_independed(ProofRef, P, A, ProofCNT, Index):-
tries:trie_get_entry(ProofRef, Proof),
calculate_prob_proof(Proof, Pproof),
calculate_prob_proof(Proof, Pproof),
NA is A + Pproof,
NIndex is Index + 1,
recordz(problog_mc_dnf, proof(Index, ProofRef, Pproof, NA), _),
(tries:trie_traverse_next(ProofRef, NxtProofRef) ->
NextProofRef = NxtProofRef
;
NextProofRef = []
),
problog_independed(NextProofRef, P, NA, ProofCNT, NIndex).
%%% this should be generalized to handle nested tries
calculate_prob_proof([true], 1.0):-!.
calculate_prob_proof(Proof, P):-
calculate_curr_prob(Proof, 0.0, L),
P is exp(L).
calculate_curr_prob([], Acc, Acc).
calculate_curr_prob([ID|Rest], AccCurrProb, CurrProb):-
get_log_prob_not_check(ID, IDProb),
AccCurrProb1 is AccCurrProb + IDProb,
calculate_curr_prob(Rest, AccCurrProb1, CurrProb).
%%%% this should be generalized and go to problog_fact module
get_log_prob_not_check(not(ID), IDProb):-
!, problog:get_fact_probability(ID, Prob1),
Prob2 is 1 - Prob1, IDProb is log(Prob2).
get_log_prob_not_check(ID, IDProb):-
problog:get_fact_log_probability(ID, IDProb).
problog_mc_DNF(Trie, Delta, P):-
problog_flag(mc_batchsize, Samples),
problog_independed(Trie, Pind, ProofCNT),
(ProofCNT > 1 ->
problog_mc_DNF(Trie, Pind, ProofCNT, Delta, Samples, 0, SamplesSoFar, Naccepted, 0, _Epsilon),
P is Naccepted / SamplesSoFar * Pind
;
P is Pind,
problog_var_set(probability, P)
),
eraseall(problog_mc_dnf).
problog_mc_DNF(_Trie, Pind, _ProofCNT, Delta, Samples, SamplesSoFar, SamplesSoFar, Naccepted, Naccepted, Epsilon):-
SamplesSoFar > 0,
SamplesSoFar mod Samples =:= 0,
P is Naccepted / SamplesSoFar * Pind,
problog_timer_pause(dnf_sampling_time, T),
problog_timer_resume(dnf_sampling_time),
problog_convergence_check(T, P, SamplesSoFar, Delta, Epsilon, Converge),
(Converge = true; Converge = terminate), !,
problog_var_set(samples, SamplesSoFar),
problog_var_set(probability, P),
Pl is P - Epsilon,
Ph is P + Epsilon,
problog_var_set(probability_lower, Pl),
problog_var_set(probability_upper, Ph).
/*
problog_mc_DNF(_Trie, _Pind, _ProofCNT, _Delta, Samples, SamplesSoFar, _SamplesSoFar, _Naccepted, _Naccepted, _Epsilon):-
SamplesSoFar mod Samples =:= 0,
fail.*/
problog_mc_DNF(Trie, Pind, ProofCNT, Delta, Samples, SAcc, SamplesSoFar, Naccepted, NAcc, Epsilon):-
NSAcc is SAcc + 1,
problog_random(RND),
Thr is RND * Pind,
tries:trie_traverse_mode(backward),
(problog_flag(search_method, binary) ->
get_sample_proof_binary(CurRef, Thr, ProofCNT, L_true_pf, L_false_pf)
;
get_sample_proof_linear(CurRef, Thr, L_true_pf, L_false_pf)
),
(tries:trie_traverse_next(CurRef, NxtRef) ->
NextRef = NxtRef
;
NextRef = []
),
(check_sample_proofs(NextRef, L_true_pf, L_false_pf) ->
NNAcc is NAcc + 1
;
NNAcc is NAcc
),
(problog_flag(represent_world, record) ->
eraseall(problog_sample_world)
;
(problog_flag(represent_world, array) ->
close_static_array(problog_sample_world)
;
(problog_flag(represent_world, hash_table) ->
hash_table_delete(L_true_pf),
hash_table_delete(L_false_pf)
;
true
)
)
),
tries:trie_traverse_mode(forward),
problog_mc_DNF(Trie, Pind, ProofCNT, Delta, Samples, NSAcc, SamplesSoFar, Naccepted, NNAcc, Epsilon).
get_sample_proof_linear(Ref, Thr, L_true_pf, L_false_pf):-
recorded(problog_mc_dnf, proof(_Index, Ref, _Pproof, Ps), _),
Thr < Ps,
tries:trie_get_entry(Ref, Proof),
(problog_flag(represent_world, hash_table) ->
make_hash_tables(L_true_pf, L_false_pf),
add_proof_to_hash_world(Proof, L_true_pf, L_false_pf)
;
(problog_flag(represent_world, record) ->
add_proof_to_rec_world(Proof)
;
(problog_flag(represent_world, array) ->
nb_getval(probclause_counter, ProbFactCNT),
Size is ProbFactCNT + 1,
static_array(problog_sample_world, Size, int),
add_proof_to_array_world(Proof)
;
add_proof_to_list_world(Proof, L_true_pf, L_false_pf)
)
)
).
get_sample_proof_binary(Ref, Thr, ProofCNT, L_true_pf, L_false_pf):-
Last is ProofCNT - 1,
binary_search(Thr, 0, Last, Ref), !,
tries:trie_get_entry(Ref, Proof),
(problog_flag(represent_world, hash_table) ->
make_hash_tables(L_true_pf, L_false_pf),
add_proof_to_hash_world(Proof, L_true_pf, L_false_pf)
;
(problog_flag(represent_world, record) ->
add_proof_to_rec_world(Proof)
;
(problog_flag(represent_world, array) ->
nb_getval(probclause_counter, ProbFactCNT),
Size is ProbFactCNT + 1,
static_array(problog_sample_world, Size, int),
add_proof_to_array_world(Proof)
;
add_proof_to_list_world(Proof, L_true_pf, L_false_pf)
)
)
).
binary_search(Thr, From, To, Ref):-
1 is To - From, !,
recorded(problog_mc_dnf, proof(From, RefF, _Pproof, PsF), _),
(Thr > PsF ->
recorded(problog_mc_dnf, proof(To, Ref, _PproofTo, _Ps), _)
;
Ref = RefF
).
binary_search(_Thr, Index, Index, Ref):-
!, recorded(problog_mc_dnf, proof(Index, Ref, _Pproof, _Ps), _).
binary_search(Thr, From, To, Res):-
Look is From + integer((To - From + 1) / 2),
recorded(problog_mc_dnf, proof(Look, _Ref, _Pproof, Ps), _), !,
(Thr > Ps ->
NewFrom is Look + 1,
NewTo is To
;
NewFrom is From,
NewTo is Look
),
binary_search(Thr, NewFrom, NewTo, Res).
%%%%%%%%% This code can be improved and generalized %%%%%%%%%
check_sample_proofs([], _, _).
check_sample_proofs(CurRef, L_true_pf, L_false_pf):-
!, tries:trie_get_entry(CurRef, Proof),
(problog_flag(represent_world, hash_table) ->
check_proof_in_hash_world(Proof, L_true_pf, L_false_pf),
NL_true_pf = L_true_pf,
NL_false_pf = L_false_pf
;
(problog_flag(represent_world, record) ->
check_proof_in_rec_world(Proof),
NL_true_pf = L_true_pf,
NL_false_pf = L_false_pf
;
(problog_flag(represent_world, array) ->
check_proof_in_array_world(Proof),
NL_true_pf = L_true_pf,
NL_false_pf = L_false_pf
;
check_proof_in_list_world(Proof, L_true_pf, NL_true_pf, L_false_pf, NL_false_pf)
)
)
),
(tries:trie_traverse_next(CurRef, NxtRef) ->
NextRef = NxtRef
;
NextRef = []
),
check_sample_proofs(NextRef, NL_true_pf, NL_false_pf).
add_proof_to_array_world([]).
add_proof_to_array_world([not(H)|T]):-
!, update_array(problog_sample_world, H, -1), add_proof_to_array_world(T).
add_proof_to_array_world([H|T]):-
update_array(problog_sample_world, H, 1), add_proof_to_array_world(T).
check_proof_in_array_world([not(F)|_Rest]):-
array_element(problog_sample_world, F, 1), !.
check_proof_in_array_world([not(F)|Rest]):-
array_element(problog_sample_world, F, -1), !,
check_proof_in_array_world(Rest).
check_proof_in_array_world([not(F)|Rest]):-
!, problog_random(RND), Dice is RND,
problog:get_fact_probability(F, NumProbF),
(Dice =< NumProbF ->
update_array(problog_sample_world, F, 1)
;
update_array(problog_sample_world, F, -1),
check_proof_in_array_world(Rest)
).
check_proof_in_array_world([F|_Rest]):-
array_element(problog_sample_world, F, -1), !.
check_proof_in_array_world([F|Rest]):-
array_element(problog_sample_world, F, 1), !,
check_proof_in_array_world(Rest).
check_proof_in_array_world([F|Rest]):-
!, problog_random(RND), Dice is RND,
problog:get_fact_probability(F, NumProbF),
(Dice > NumProbF ->
update_array(problog_sample_world, F, -1)
;
update_array(problog_sample_world, F, 1),
check_proof_in_array_world(Rest)
).
add_proof_to_rec_world([]).
add_proof_to_rec_world([not(H)|T]):-
!, recordz(problog_sample_world, false_fact(H), _), add_proof_to_rec_world(T).
add_proof_to_rec_world([H|T]):-
recordz(problog_sample_world, true_fact(H), _), add_proof_to_rec_world(T).
check_proof_in_rec_world([not(F)|_Rest]):-
recorded(problog_sample_world, true_fact(F), _), !.
check_proof_in_rec_world([not(F)|Rest]):-
recorded(problog_sample_world, false_fact(F), _), !,
check_proof_in_rec_world(Rest).
check_proof_in_rec_world([not(F)|Rest]):-
!, problog_random(RND), Dice is RND,
problog:get_fact_probability(F, NumProbF),
(Dice =< NumProbF ->
recordz(problog_sample_world, true_fact(F), _)
;
recordz(problog_sample_world, false_fact(F), _),
check_proof_in_rec_world(Rest)
).
check_proof_in_rec_world([F|_Rest]):-
recorded(problog_sample_world, false_fact(F), _), !.
check_proof_in_rec_world([F|Rest]):-
recorded(problog_sample_world, true_fact(F), _), !,
check_proof_in_rec_world(Rest).
check_proof_in_rec_world([F|Rest]):-
!, problog_random(RND), Dice is RND,
problog:get_fact_probability(F, NumProbF),
(Dice > NumProbF ->
recordz(problog_sample_world, false_fact(F), _)
;
recordz(problog_sample_world, true_fact(F), _),
check_proof_in_rec_world(Rest)
).
make_hash_tables(TrueHashTable, FalseHashTable):-
nb_getval(probclause_counter, ProbFactCNT),
hash_table_init(ProbFactCNT, TrueHashTable),
hash_table_init(ProbFactCNT, FalseHashTable).
add_proof_to_hash_world([], _TrueHashTable, _FalseHashTable).
add_proof_to_hash_world([not(H)|T], TrueHashTable, FalseHashTable):-
!, problog_key_to_tuple(H, Tuple),
hash_table_lookup(FalseHashTable, Tuple, _),
add_proof_to_hash_world(T, TrueHashTable, FalseHashTable).
add_proof_to_hash_world([H|T], TrueHashTable, FalseHashTable):-
problog_key_to_tuple(H, Tuple),
hash_table_lookup(TrueHashTable, Tuple, _),
add_proof_to_hash_world(T, TrueHashTable, FalseHashTable).
check_proof_in_hash_world([not(F)|_Rest], TrueHashTable, _FalseHashTable):-
problog_key_to_tuple(F, Tuple),
hash_table_contains(TrueHashTable, Tuple, _), !.
check_proof_in_hash_world([not(F)|Rest], TrueHashTable, FalseHashTable):-
problog_key_to_tuple(F, Tuple),
hash_table_contains(FalseHashTable, Tuple, _), !,
check_proof_in_hash_world(Rest, TrueHashTable, FalseHashTable).
check_proof_in_hash_world([not(F)|Rest], TrueHashTable, FalseHashTable):-
!, problog_random(RND), Dice is RND,
problog:get_fact_probability(F, NumProbF),
problog_key_to_tuple(F, Tuple),
(Dice =< NumProbF ->
hash_table_lookup(TrueHashTable, Tuple, _)
;
hash_table_lookup(FalseHashTable, Tuple, _),
check_proof_in_hash_world(Rest, TrueHashTable, FalseHashTable)
).
check_proof_in_hash_world([F|_Rest], _TrueHashTable, FalseHashTable):-
problog_key_to_tuple(F, Tuple),
hash_table_contains(FalseHashTable, Tuple, _), !.
check_proof_in_hash_world([F|Rest], TrueHashTable, FalseHashTable):-
problog_key_to_tuple(F, Tuple),
hash_table_contains(TrueHashTable, Tuple, _), !,
check_proof_in_hash_world(Rest, TrueHashTable, FalseHashTable).
check_proof_in_hash_world([F|Rest], TrueHashTable, FalseHashTable):-
!, problog_random(RND), Dice is RND,
problog:get_fact_probability(F, NumProbF),
problog_key_to_tuple(F, Tuple),
(Dice > NumProbF ->
hash_table_lookup(FalseHashTable, Tuple, _)
;
hash_table_lookup(TrueHashTable, Tuple, _),
check_proof_in_hash_world(Rest, TrueHashTable, FalseHashTable)
).
add_proof_to_list_world([], [], []).
add_proof_to_list_world([not(H)|T], TrueList, [H|FalseList]):-
add_proof_to_list_world(T, TrueList, FalseList).
add_proof_to_list_world([H|T], [H|TrueList], FalseList):-
add_proof_to_list_world(T, TrueList, FalseList).
check_proof_in_list_world([not(F)|_Rest], TrueList, TrueList, FalseList, FalseList):-
memberchk(F, TrueList), !.
check_proof_in_list_world([not(F)|Rest], TrueList, NewTrueList, FalseList, NewFalseList):-
memberchk(F, FalseList), !,
check_proof_in_list_world(Rest, TrueList, NewTrueList, FalseList, NewFalseList).
check_proof_in_list_world([not(F)|Rest], TrueList, NewTrueList, FalseList, NewFalseList):-
!, problog_random(RND), Dice is RND,
problog:get_fact_probability(F, NumProbF),
(Dice =< NumProbF ->
NewTrueList = [F|TrueList],
NewFalseList = FalseList
;
check_proof_in_list_world(Rest, TrueList, NewTrueList, [F|FalseList], NewFalseList)
).
check_proof_in_list_world([F|_Rest], TrueList, TrueList, FalseList, FalseList):-
memberchk(F, FalseList), !.
check_proof_in_list_world([F|Rest], TrueList, NewTrueList, FalseList, NewFalseList):-
memberchk(F, TrueList), !,
check_proof_in_list_world(Rest, TrueList, NewTrueList, FalseList, NewFalseList).
check_proof_in_list_world([F|Rest], TrueList, NewTrueList, FalseList, NewFalseList):-
!, problog_random(RND), Dice is RND,
problog:get_fact_probability(F, NumProbF),
(Dice > NumProbF ->
NewTrueList = TrueList,
NewFalseList = [F|FalseList]
;
check_proof_in_list_world(Rest, [F|TrueList], NewTrueList, FalseList, NewFalseList)
).
problog_collect_trie(Goal, Threshold) :-
problog:init_problog_low(Threshold),
problog:problog_control(off, up),
problog:problog_control(on, exact),
problog_var_timer_start(sld_time),
problog:problog_call(Goal),
problog:add_solution,
fail.
problog_collect_trie(_, _) :-
problog:problog_control(off, exact),
problog_var_timer_stop(sld_time).
problog_dnf_sampling(Goal, Delta, P):-
% this should be generalized with general log file
problog_flag(mc_logfile, File1),
convert_filename_to_working_path(File1, File),
open(File, write, Log),
format(Log,'# goal: ~q~n#delta: ~w~n',[Goal, Delta]),
format(Log,'# samples prob low high time~2n',[]),
close(Log),
problog_collect_trie(Goal, 0.0),
nb_getval(problog_completed_proofs, Trie_Completed_Proofs),
problog_var_timer_start(dnf_sampling_time),
problog_mc_DNF(Trie_Completed_Proofs, Delta, P),
problog_var_timer_stop(dnf_sampling_time),
(problog_flag(verbose, true) ->
print:problog_statistics
;
true
),
ptree:delete_ptree(Trie_Completed_Proofs),
problog:clear_tabling.

View File

@ -0,0 +1,335 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Theofrastos Mantadelis, Bernd Gutmann
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
% ensure that installation of your Modified Version does not prevent the
% user installing or running the Standard Version. In addition, the
% modified Version must bear a name that is different from the name of
% the Standard Version. (c) allow anyone who receives a copy of the
% Modified Version to make the Source form of the Modified Version
% available to others under (i) the Original License or (ii) a license
% that permits the licensee to freely copy, modify and redistribute the
% Modified Version using the same licensing terms that apply to the copy
% that the licensee received, and requires that the Source form of the
% Modified Version, and of any works derived from it, be made freely
% available in that license fees are prohibited but Distributor Fees are
% allowed.
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
% valid at the time of your distribution. If these instructions, at any
% time while you are carrying out such distribution, become invalid, you
% must provide new instructions on demand or cease further
% distribution. If you provide valid instructions or cease distribution
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
% Package. Distributor Fees are permitted, and licensing fees for other
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
% include the Package, and Distribute the result without restriction,
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
% considered parts of the Package itself, and are not subject to the
% terms of this license.
%
% General Provisions
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
% patent claims licensable by the Copyright Holder that are necessarily
% infringed by the Package. If you institute patent litigation
% (including a cross-claim or counterclaim) against any party alleging
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%
% Collected OS depended instructions
%%%%%%%%
:- module(os, [set_problog_path/1,
problog_path/1,
convert_filename_to_working_path/2,
convert_filename_to_problog_path/2,
concat_path_with_filename/3,
empty_bdd_directory/1,
empty_output_directory/1,
calc_md5/2]).
% load library modules
:- ensure_loaded(library(system)).
% load our own modules
:- ensure_loaded(flags).
:- dynamic [problog_dir/1, problog_working_path/1].
set_problog_path(Path):-
retractall(problog_path(_)),
assert(problog_path(Path)).
convert_filename_to_working_path(File_Name, Path):-
problog_flag(dir, Dir),
concat_path_with_filename(Dir, File_Name, Path).
convert_filename_to_problog_path(File_Name, Path):-
problog_path(Dir),
concat_path_with_filename(Dir, File_Name, Path).
concat_path_with_filename(Path, File_Name, Result):-
nonvar(File_Name),
nonvar(Path),
% make sure, that there is no path delimiter at the end
prolog_file_name(Path,Path_Absolute),
(
yap_flag(windows, true)
->
Path_Seperator = '\\';
Path_Seperator = '/'
),
atomic_concat([Path_Absolute, Path_Seperator, File_Name], Result).
%========================================================================
%= store the current succes probabilities for training and test examples
%=
%========================================================================
empty_bdd_directory(Path) :-
ground(Path),
concat_path_with_filename(Path,'query_*',Files),
atomic_concat(['rm -f ',Files],Command),
(shell(Command) -> true; true).
%========================================================================
%= store the current succes probabilities for training and test examples
%=
%========================================================================
empty_output_directory(Path) :-
ground(Path),
concat_path_with_filename(Path,'log.dat',F1),
concat_path_with_filename(Path,'factprobs_*.pl',F2),
concat_path_with_filename(Path,'predictions_*.pl',F3),
atomic_concat(['rm -f ',F1, ' ', F2, ' ', F3],Command),
(shell(Command) -> true; true).
%========================================================================
%= Calculate the MD5 checksum of +Filename by calling md5sum
%= in case m5sum is not installed, try md5, otherwise fail
%= +Filename, -MD5
%========================================================================
calc_md5(Filename,MD5):-
catch(calc_md5_intern(Filename,'md5sum',MD5),_,fail),
!.
calc_md5(Filename,MD5):-
catch(calc_md5_intern(Filename,'md5',MD5),_,fail),
!.
calc_md5(Filename,MD5):-
throw(md5error(calc_md5(Filename,MD5))).
calc_md5_intern(Filename,Command,MD5) :-
( file_exists(Filename) -> true ; throw(md5_file(Filename)) ),
atomic_concat([Command,' "',Filename,'"'],Call),
% execute the md5 command
exec(Call,[null,pipe(S),null],_PID),
bb_put(calc_md5_temp,End-End), % use difference list
bb_put(calc_md5_temp2,0),
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
( % read 32 Bytes from stdout of process
repeat,
get0(S,C),
(
C== -1
->
(
close(S),
throw(md5error('premature end of output stream, please check os.yap calc_md5/2'))
);
true
),
bb_get(calc_md5_temp,List-[C|NewEnd]),
bb_put(calc_md5_temp,List-NewEnd),
bb_get(calc_md5_temp2,OldLength),
NewLength is OldLength+1,
bb_put(calc_md5_temp2,NewLength),
NewLength=32
),
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
!,
close(S),
bb_delete(calc_md5_temp, FinalList-[]),
bb_delete(calc_md5_temp2,_),
atom_codes(MD5,FinalList).

View File

@ -2,20 +2,19 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2009-06-17 22:22:00 +0200 (Mi, 17 Jun 2009) $
% $Revision: 1550 $
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% Copyright 2009 Katholieke Universiteit Leuven
%
% Authors: Luc De Raedt, Bernd Gutmann, Angelika Kimmig,
% Vitor Santos Costa
%
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Angelika Kimmig, Vitor Santos Costa
% Angelika Kimmig, Vitor Santos Costa, Theofrastos Mantadelis
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
@ -213,20 +212,216 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(print, [print_param/4,
print_sep_line/0,
print_inference/2]).
print_long_param/4,
print_sep_line/0,
print_sep_line_bold/0,
print_group_line/1,
print_group_line_bold/1,
print_inference/2,
problog_statistics/0,
show_inference/0,
problog_flags/0,
problog_flags/1,
problog_help/0]).
print_param(Keyword,Value,Function,Legal) :-
format(user,'~w~55+~q~15+~w~30+~w~25+~n',[Keyword,Value,Function,Legal]).
print_sep_line :-
sep_line(125).
sep_line(0) :-
!,
format('~n',[]).
sep_line(N) :-
format('-',[]),
NN is N-1,
sep_line(NN).
% load library modules
:- ensure_loaded(library(lists)).
% load our own modules
:- ensure_loaded(flags).
:- ensure_loaded(variables).
% size, line_char, line_char_bold
problog_pane_properties(125, 45, 61).
problog_pane_split_inference([65,60], [w,w]).
problog_pane_split_stat([40,3,1,1], ['t~w',w,q,w]).
problog_pane_split_param([55,30,20,20], [w,w,w,q]).
print_inference(Call,Description) :-
format(user,'~w~65+~w~60+~n',[Call,Description]).
problog_pane_split_inference(Columns, Style),
print_column(Columns, Style, [Call,Description]).
% format(user,'~w~65+~w~60+~n',[Call,Description]).
print_param(Keyword,Value,Function,Legal) :-
problog_pane_split_param(Columns, Style),
print_column(Columns, Style, [Keyword,Value,Function,Legal]).
% format(user,'~w~55+~w~29+~w~25+~q~25+~n',[Keyword,Value,Function,Legal]).
print_long_param(Keyword,Value,Function,Legal) :-
format(user,'~w~55+~q~25+~w~20+~w~25+~n',[Keyword,Value,'','']),
format(user,'~w~55+~w~25+~w~20+~w~25+~n',['','',Function,Legal]).
print_stat(StatName, Seperator, StatValue, StatUnit) :-
problog_pane_split_stat(Columns, Style),
print_column(Columns, Style, [StatName, Seperator, StatValue, StatUnit]).
print_sep_line :-
problog_pane_properties(Size, LineChar, _LineCharBold),
format(user,"~*c~n", [Size, LineChar]).
print_sep_line_bold :-
problog_pane_properties(Size, _LineChar, LineCharBold),
format(user,"~*c~n", [Size, LineCharBold]).
print_group_line(Group) :-
atom_length(Group, L),
problog_pane_properties(Size, LineChar, _LineCharBold),
Rest is Size - 5 - L,
format(user,"~*c ~w ~*c~n", [3, LineChar, Group, Rest, LineChar]).
print_group_line_bold(Group) :-
atom_length(Group, L),
problog_pane_properties(Size, _LineChar, LineCharBold),
Rest is Size - 5 - L,
format(user,"~*c ~w ~*c~n", [3, LineCharBold, Group, Rest, LineCharBold]).
print_column(Columns, Style, Messages):-
make_column_format(Columns, Style, Format),
format(user, Format, Messages).
make_column_format(Columns, Style, Format):-
make_column_format(Columns, Style, PreFormat, ''),
atomic_concat(PreFormat, '~n', Format).
make_column_format([], [], Format, Format).
make_column_format([HC|TC], [HS|TS], Format, Acc):-
atomic_concat([Acc,'~', HS,'~',HC,'+'], NAcc),
make_column_format(TC, TS, Format, NAcc).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% This is the help part of problog %
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
problog_help :-
format('~2nProbLog inference currently offers the following inference methods:~n',[]),
show_inference,
problog:problog_path(PD),
format('~nProblog directory: ~q~n',[PD]),
format('~nThe following global parameters are available:~n',[]),
problog_flags,
print_sep_line,
format('~n use problog_help/0 to display this information~n',[]),
format('~n use problog_flags/0 to display current parameter values~n',[]),
format('~n use problog_flags/1 to display current parameter values of a group~2n',[]),
print_sep_line,
nl,
flush_output.
show_inference :-
format('~n',[]),
print_sep_line,
print_inference(call,description),
print_sep_line,
print_inference('problog_delta(+Query,+Delta,-Low,-High,-Status)','approximation with interval width Delta (IJCAI07)'),
print_inference('problog_threshold(+Query,+Threshold,-Low,-High,-Status)','bounds based on single probability threshold'),
print_inference('problog_low(+Query,+Threshold,-Low,-Status)','lower bound based on single probability threshold'),
print_inference('problog_kbest(+Query,+K,-Low,-Status)','lower bound based on K most likely proofs'),
print_inference('problog_max(+Query,-Prob,-FactsUsed)','explanation probability (ECML07)'),
print_inference('problog_exact(+Query,-Prob,-Status)','exact probability'),
print_inference('problog_montecarlo(+Query,+Delta,-Prob)','program sampling with 95\%-confidence-interval-width Delta'),
print_inference('problog_dnf_sampling(+Query,+Delta,-Prob)','DNF sampling with 95\%-confidence-interval-width Delta'),
print_sep_line.
%%%%%%%%%%%%%%% This is the flag part towards screen %%%%%%%%%%%%%%%%%%%%
% Currently does not print default values to gain space
problog_flags(Group):-
problog_defined_flag_group(Group),
print_group_line(Group),
print_param(description, domain, flag, value),
print_sep_line,
( % iterate over all flags in this group
problog_defined_flag(Flag, Group, _Default, LValues, Desc),
problog_flag(Flag, Value),
(is_list(LValues) ->
atomic_concat(LValues, Values)
;
Values = LValues
),
print_param(Desc, Values, Flag, Value),
fail
; % go to next flag
true
),
print_sep_line.
problog_flags:-
format('~n',[]),
print_sep_line_bold,
format('problog flags: use set_problog_flag(Flag,Option) to change, problog_flag(Flag,Option) to view~n',[]),
print_sep_line_bold,
format('~n',[]),
( % iterate over all groups
problog_flags(_),
format('~n',[]),
fail; % go to next group
true
),
format('~n',[]).
%%%%%%%%%%%%%%% This is statistics part towards screen %%%%%%%%%%%%%%%%%%%
problog_statistics:-
nb_setval(problog_statistics, false),
problog_var_group(Group),
findall(Stat/Result, (
problog_var_defined(Stat, Group, _, _),
problog_var_is_set(Stat),
problog_var_get(Stat, Result)
), GroupStats),
\+ GroupStats == [],
nb_setval(problog_statistics, true),
print_group_line(Group),
forall(member(Stat/Result, GroupStats), (
problog_var_defined(Stat, Group, _, messages(MsgBefore, Seperator, MsgAfter)),
print_stat(MsgBefore, Seperator, Result, MsgAfter)
)),
fail.
problog_statistics:-
(nb_getval(problog_statistics, true)->
print_sep_line
;
true
),
nb_delete(problog_statistics).
% namee(A, Name):-
% atomic(A), !,
% name(A, Name).
% namee(L, Name):-
% is_list(L), !,
% namee(L, Name, []).
% namee(A, Name):-
% A =.. L,
% namee(L, Name, []).
% namee([], Name, Name).
% namee([H|T], Name, Acc):-
% namee(H, N),
% append(Acc, N, NAcc),
% namee(T, Name, NAcc).
% print_sep_line :-
% sep_line(125).
% sep_line(0) :-
% !,
% format('~n',[]).
% sep_line(N) :-
% format('-',[]),
% NN is N-1,
% sep_line(NN).
% print_sep_line_bold :-
% sep_line_bold(125).
% sep_line_bold(0) :-
% !,
% format('~n',[]).
% sep_line_bold(N) :-
% format('=',[]),
% NN is N-1,
% sep_line_bold(NN).

View File

@ -0,0 +1,269 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Theofrastos Mantadelis
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
% ensure that installation of your Modified Version does not prevent the
% user installing or running the Standard Version. In addition, the
% modified Version must bear a name that is different from the name of
% the Standard Version. (c) allow anyone who receives a copy of the
% Modified Version to make the Source form of the Modified Version
% available to others under (i) the Original License or (ii) a license
% that permits the licensee to freely copy, modify and redistribute the
% Modified Version using the same licensing terms that apply to the copy
% that the licensee received, and requires that the Source form of the
% Modified Version, and of any works derived from it, be made freely
% available in that license fees are prohibited but Distributor Fees are
% allowed.
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
% valid at the time of your distribution. If these instructions, at any
% time while you are carrying out such distribution, become invalid, you
% must provide new instructions on demand or cease further
% distribution. If you provide valid instructions or cease distribution
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
% Package. Distributor Fees are permitted, and licensing fees for other
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
% include the Package, and Distribute the result without restriction,
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
% considered parts of the Package itself, and are not subject to the
% terms of this license.
%
% General Provisions
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
% patent claims licensable by the Copyright Holder that are necessarily
% infringed by the Package. If you institute patent litigation
% (including a cross-claim or counterclaim) against any party alleging
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(sampling, [problog_random/1,
problog_convergence_check/6]).
:- use_module(flags, _, [problog_define_flag/5,
problog_flag/2]).
:- use_module(os, _, [convert_filename_to_working_path/2]).
:- ensure_loaded(library(random)).
:- problog_define_flag(mc_batchsize, problog_flag_validate_posint, 'number of samples before update in montecarlo', 1000, monte_carlo_sampling).
:- problog_define_flag(min_mc_samples, problog_flag_validate_nonegint, 'minimum number of samples before to converge', 0, monte_carlo_sampling).
:- problog_define_flag(max_mc_samples, problog_flag_validate_nonegint, 'maximum number of samples waiting to converge', 1000000, monte_carlo_sampling).
:- problog_define_flag(randomizer, problog_flag_validate_in_list([repeatable, nonrepeatable]), 'whether the random numbers are repeatable or not', repeatable, monte_carlo_sampling).
problog_convergence_check(Time, P, SamplesSoFar, Delta, Epsilon, Converged):-
Epsilon is 2.0 * sqrt(P * abs(1.0 - P) / SamplesSoFar),
(problog_flag(verbose, true) ->
Pl is P - Epsilon,
Ph is P + Epsilon,
Diff is 2.0 * Epsilon,
(problog_flag(verbose,true) ->
format(user, '~n~w samples over ~q ms~nestimated probability ~w~n95 percent confidence interval [~w,~w]~n', [SamplesSoFar, Time, P, Pl, Ph])
;
true
),
% this should be generalized with log file system
problog_flag(mc_logfile, File1),
convert_filename_to_working_path(File1, File),
open(File, append, Log),
format(Log,'~w ~8f ~8f ~8f ~8f ~3f~n',[SamplesSoFar,P,Pl,Ph,Diff,Time]),
close(Log)
;
true
),
(Delta > 2.0 * Epsilon ->
problog_flag(min_mc_samples, MinSamples),
(MinSamples =< SamplesSoFar ->
Converged = true
;
Converged = continue
)
;
problog_flag(max_mc_samples, MaxSamples),
(MaxSamples =< SamplesSoFar ->
Converged = terminate
;
Converged = false
)
).
problog_random(Random):-
(problog_flag(randomizer, repeatable) ->
random(Random)
;
Random is random
).

View File

@ -0,0 +1,515 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Theofrastos Mantadelis
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
% ensure that installation of your Modified Version does not prevent the
% user installing or running the Standard Version. In addition, the
% modified Version must bear a name that is different from the name of
% the Standard Version. (c) allow anyone who receives a copy of the
% Modified Version to make the Source form of the Modified Version
% available to others under (i) the Original License or (ii) a license
% that permits the licensee to freely copy, modify and redistribute the
% Modified Version using the same licensing terms that apply to the copy
% that the licensee received, and requires that the Source form of the
% Modified Version, and of any works derived from it, be made freely
% available in that license fees are prohibited but Distributor Fees are
% allowed.
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
% valid at the time of your distribution. If these instructions, at any
% time while you are carrying out such distribution, become invalid, you
% must provide new instructions on demand or cease further
% distribution. If you provide valid instructions or cease distribution
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
% Package. Distributor Fees are permitted, and licensing fees for other
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
% include the Package, and Distribute the result without restriction,
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
% considered parts of the Package itself, and are not subject to the
% terms of this license.
%
% General Provisions
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
% patent claims licensable by the Copyright Holder that are necessarily
% infringed by the Package. If you institute patent litigation
% (including a cross-claim or counterclaim) against any party alleging
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Problog Tabling: use Yap tabling for monte carlo
% use probabilistic semantics tabling for exact
% rest methods not benefited from tabling yet
%
% Look at: CICLOPS 2009 Mantadelis Theofrastos & Gerda Janssens
% SRL 2009 Angelika Kimming & Vitor
%
% Currently: Exact handles ground goals only and loops
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(tabling, [problog_table/1,
problog_tabled/1,
problog_neg/1,
init_tabling/0,
clear_tabling/0,
retain_tabling/0,
clear_retained_tables/0,
problog_chktabled/2,
problog_abolish_table/1,
problog_abolish_all_tables/0,
problog_tabling_negated_synonym/2,
problog_tabling_get_negated_from_pred/2,
problog_tabling_get_negated_from_id/2,
op(1150, fx, problog_table)]).
:- ensure_loaded(library(lists)).
:- use_module(extlists, _, [open_end_memberchk/2,
open_end_add/3,
open_end_add_unique/3,
open_end_close_end/2]).
:- use_module(flags, _, [problog_define_flag/4, problog_flag/2]).
:- use_module(ptree, _, [init_ptree/1,
delete_ptree/1,
merge_ptree/2,
empty_ptree/1]).
:- op( 1150, fx, problog_table ).
:- meta_predicate problog_table(:).
:- meta_predicate problog_neg(:).
:- dynamic problog_tabled/1, has_synonyms/0, problog_tabling_retain/1.
:- problog_define_flag(max_depth, problog_flag_validate_integer, 'maximum proof depth', -1).
:- problog_define_flag(retain_tables, problog_flag_validate_boolean, 'retain tables after query', false).
init_tabling :-
nb_setval(problog_current_depth, 0),
nb_setval(problog_suspended_tries, []),
nb_setval(problog_current_ptree, problog_completed_proofs),
nb_setval(problog_nested_tries, false),
nb_setval(problog_tabling_next_index, 1).
clear_tabling:-
nb_setval(problog_suspended_tries, []),
nb_setval(problog_current_ptree, 1),
nb_setval(problog_nested_tries, false),
nb_setval(problog_tabling_next_index, 1),
forall(problog_chktabled(_, Trie),
(problog_tabling_retain(Trie) ->
true
;
delete_ptree(Trie)
)
),
eraseall(problog_table), !.
clear_tabling.
retain_tabling:-
forall(problog_chktabled(_, Trie), assert(problog_tabling_retain(Trie))).
clear_retained_tables:-
forall(problog_tabling_retain(Trie), delete_ptree(Trie)),
retractall(problog_tabling_retain(_)).
problog_chktabled(Index, Trie):-
recorded(problog_table, store(_, Index, Trie, _, _), _).
problog_table_next_index(Index):-
nb_getval(problog_tabling_next_index, Index),
NIndex is Index + 1,
nb_setval(problog_tabling_next_index, NIndex).
makeargs(0, []):-!.
makeargs(N, [_Arg|L]):-
N > 0,
NN is N - 1,
makeargs(NN, L).
problog_table(M:P) :- !,
problog_table(P, M).
problog_table(P) :-
prolog_load_context(module, M),
problog_table(P, M).
problog_table(M:P, _) :-
problog_table(P, M).
problog_table((P1, P2), M) :-
problog_table(P1, M),
problog_table(P2, M).
problog_table(Name/Arity, Module) :-
makeargs(Arity, Args),
Head =.. [Name|Args],
not(predicate_property(Module:Head, dynamic)), !,
throw(error('problog_table: Problog tabling currently requires the predicate to be declared dynamic and compiles it to static.')).
problog_table(Name/Arity, Module) :-
makeargs(Arity, Args),
Head =.. [Name|Args],
atom_concat(['problog_', Name, '_original'], OriginalName),
atom_concat(['problog_', Name, '_mctabled'], MCName),
atom_concat(['problog_', Name, '_tabled'], ExactName),
% Monte carlo tabling
table(Module:MCName/Arity),
assert(problog_tabled(Module:Name/Arity)),
findall(_,(
OriginalPred =.. [OriginalName|Args],
MCPred =.. [MCName|Args],
retract(Module:(Head:-Body)),
assert_static(Module:(OriginalPred:-Body)),
assert_static(Module:(MCPred:-Body))
),_),
OriginalPred =.. [OriginalName|Args],
MCPred =.. [MCName|Args],
ExactPred =.. [ExactName|Args],
assert(Module:(
Head:-
(problog:problog_control(check, exact) ->
ExactPred
; problog:problog_control(check, mc) ->
MCPred
;
OriginalPred
)
)),
% Exact method tabling
assert_static((
Module:ExactPred :-
(ground(ExactPred) ->
nb_setval(problog_nested_tries, true),
get_negated_synonym_state(OriginalPred, State),
(State = false ->
true
;
(recorded(problog_table, store(OriginalPred, Hash, HashTrie, SuspTrie, Finished), Ref)->
(Finished = false ->
b_getval(problog_suspended_tries, Susp),
b_setval(problog_suspended_tries, [Hash|Susp])
;
Finished
),
b_getval(problog_current_proof, IDs),
not(open_end_memberchk(not(t(Hash)), IDs)),
open_end_add_unique(t(Hash), IDs, NIDs),
b_setval(problog_current_proof, NIDs)
;
b_getval(problog_current_proof, OIDs),
b_getval(problog_current_ptree, CurrentControlTrie),
b_getval(CurrentControlTrie, OCurTrie),
init_ptree(HashTrie),
init_ptree(SuspTrie),
b_setval(problog_current_proof, []),
b_setval(CurrentControlTrie, HashTrie),
problog_table_next_index(Hash),
recordz(problog_table, store(OriginalPred, Hash, HashTrie, SuspTrie, false), Ref),
problog_flag(max_depth, MaxDepth),
(MaxDepth > 0 ->
nb_getval(problog_current_depth, CurDepth)
;
CurDepth is MaxDepth - 1
),
(CurDepth < MaxDepth ->
NewDepth is CurDepth + 1,
b_setval(problog_current_depth, NewDepth),
findall(_, (
Module:OriginalPred,
b_getval(problog_suspended_tries, Susp),
(memberchk(Hash, Susp) ->
b_setval(CurrentControlTrie, SuspTrie) % maybe necessary to remove hash from susp
;
true
),
problog:add_solution
), _) % eager goal proofing (easier to expand for non-ground version)
;
/* (empty_ptree(HashTrie) ->
erase(Ref),
fail
;
true
)*/
true
),
erase(Ref),
(empty_ptree(HashTrie) ->
recordz(problog_table, store(OriginalPred, Hash, HashTrie, SuspTrie, fail), _NRef),
delete_ptree(SuspTrie),
fail % no justification exists
;
recordz(problog_table, store(OriginalPred, Hash, HashTrie, SuspTrie, true), _NRef),
merge_ptree(HashTrie, SuspTrie),
delete_ptree(SuspTrie)
),
b_setval(CurrentControlTrie, OCurTrie),
not(open_end_memberchk(not(t(Hash)), OIDs)),
open_end_add_unique(t(Hash), OIDs, NOIDs),
b_setval(problog_current_proof, NOIDs)
)
)
;
% writeln(non_ground),
Module:OriginalPred
)
)).
problog_abolish_all_tables:-
abolish_all_tables.
problog_abolish_table(M:P/A):-
atom_concat(['problog_', P, '_mctabled'], MCName),
abolish_table(M:MCName/A).
% supports exact, monte-carlo, requires expansion of tabling for rest methods
problog_neg(M:G):-
problog:problog_control(check, exact),
functor(G, Name, Arity),
not(problog_tabled(M:Name/Arity)),
not(problog:problog_predicate(Name, Arity)),
throw(problog_neg_error('Error: goal must be dynamic and tabled', M:G)).
problog_neg(M:G):-
% exact inference
problog:problog_control(check, exact),
b_getval(problog_current_proof, IDs),
b_setval(problog_current_proof, []),
M:G,
b_getval(problog_current_proof, L),
open_end_close_end(L, [Trie]),
not(open_end_memberchk(Trie, IDs)),
open_end_add_unique(not(Trie), IDs, NIDs),
b_setval(problog_current_proof, NIDs).
problog_neg(M:G):-
% monte carlo sampling
problog:problog_control(check, mc),
not(M:G).
% This predicate assigns a synonym for negation that means: NotName = problog_neg(Name)
problog_tabling_negated_synonym(Name, NotName):-
recorded(problog_table_synonyms, negated(Name, NotName), _), !.
problog_tabling_negated_synonym(Name, NotName):-
retractall(has_synonyms),
assert(has_synonyms),
recordz(problog_table_synonyms, negated(Name, NotName), _).
problog_tabling_get_negated_from_pred(Pred, Ref):-
tabling:has_synonyms,
Pred =.. [Name0|Args],
atomic_concat(problog_, Name1, Name0),
atomic_concat(Name, '_original', Name1),
(recorded(problog_table_synonyms, negated(Name, NotName1), _);
recorded(problog_table_synonyms, negated(NotName1, Name), _)),
atomic_concat([problog_, NotName1, '_original'], NotName),
NegPred =.. [NotName|Args],
recorded(problog_table, store(NegPred, _, _, _, _), Ref), !.
problog_tabling_get_negated_from_id(ID, Ref):-
tabling:has_synonyms,
recorded(problog_table, store(Pred, ID, _, _, _), _),
Pred =.. [Name0|Args],
atomic_concat(problog_, Name1, Name0),
atomic_concat(Name, '_original', Name1),
(recorded(problog_table_synonyms, negated(Name, NotName1), _);
recorded(problog_table_synonyms, negated(NotName1, Name), _)),
atomic_concat([problog_, NotName1, '_original'], NotName),
NegPred =.. [NotName|Args],
recorded(problog_table, store(NegPred, _, _, _, _), Ref), !.
get_negated_synonym_state(Pred, Fin):-
tabling:has_synonyms,
Pred =.. [Name0|Args],
atomic_concat(problog_, Name1, Name0),
atomic_concat(Name, '_original', Name1),
(recorded(problog_table_synonyms, negated(Name, NotName1), _);
recorded(problog_table_synonyms, negated(NotName1, Name), _)),
atomic_concat([problog_, NotName1, '_original'], NotName),
NegPred =.. [NotName|Args],
recorded(problog_table, store(NegPred, _, _, _, Fin), _), !.
get_negated_synonym_state(_, true).
/*
get_negated_synonym_id(ID, NegID):-
tabling:has_synonyms,
recorded(problog_table, store(Pred, ID, _, _, _), _),
Pred =.. [Name0|Args],
atomic_concat(problog_, Name1, Name0),
atomic_concat(Name, '_original', Name1),
(recorded(problog_table_synonyms, negated(Name, NotName1), _);
recorded(problog_table_synonyms, negated(NotName1, Name), _)),
atomic_concat([problog_, NotName1, '_original'], NotName),
NegPred =.. [NotName|Args],
recorded(problog_table, store(NegPred, NegID, _, _, _), _).
*/

View File

@ -0,0 +1,272 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Bernd Gutmann
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
% ensure that installation of your Modified Version does not prevent the
% user installing or running the Standard Version. In addition, the
% modified Version must bear a name that is different from the name of
% the Standard Version. (c) allow anyone who receives a copy of the
% Modified Version to make the Source form of the Modified Version
% available to others under (i) the Original License or (ii) a license
% that permits the licensee to freely copy, modify and redistribute the
% Modified Version using the same licensing terms that apply to the copy
% that the licensee received, and requires that the Source form of the
% Modified Version, and of any works derived from it, be made freely
% available in that license fees are prohibited but Distributor Fees are
% allowed.
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
% valid at the time of your distribution. If these instructions, at any
% time while you are carrying out such distribution, become invalid, you
% must provide new instructions on demand or cease further
% distribution. If you provide valid instructions or cease distribution
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
% Package. Distributor Fees are permitted, and licensing fees for other
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
% include the Package, and Distribute the result without restriction,
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
% considered parts of the Package itself, and are not subject to the
% terms of this license.
%
% General Provisions
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
% patent claims licensable by the Copyright Holder that are necessarily
% infringed by the Package. If you institute patent litigation
% (including a cross-claim or counterclaim) against any party alleging
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(timer,[timer_start/1, % +ID
timer_stop/2, % +ID,-Duration
timer_pause/1, % +ID
timer_pause/2, % +ID
timer_resume/1]). % +ID
:- yap_flag(unknown,error).
:- style_check(single_var).
:- dynamic timer/2.
:- dynamic timer_paused/2.
timer_start(Name) :-
(
timer(Name,_)
->
throw(timer_already_started(timer_start(Name)));
statistics(walltime,[StartTime,_]),
assert(timer(Name,StartTime))
).
timer_stop(Name,Duration) :-
(
retract(timer(Name,StartTime))
->
statistics(walltime,[StopTime,_]),
Duration is StopTime-StartTime;
throw(timer_not_started(timer_stop(Name,Duration)))
).
timer_pause(Name) :-
(
retract(timer(Name,StartTime))
->
statistics(walltime,[StopTime,_]),
Duration is StopTime-StartTime,
assert(timer_paused(Name,Duration));
throw(timer_not_started(timer_pause(Name)))
).
timer_pause(Name, Duration) :-
(
retract(timer(Name,StartTime))
->
statistics(walltime,[StopTime,_]),
Duration is StopTime-StartTime,
assert(timer_paused(Name,Duration));
throw(timer_not_started(timer_pause(Name)))
).
timer_resume(Name):-
(
retract(timer_paused(Name,Duration))
->
statistics(walltime,[ResumeTime,_]),
CorrectedStartTime is ResumeTime-Duration,
assert(timer(Name,CorrectedStartTime));
throw(timer_not_paused(timer_resume(Name)))
).

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,425 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Theofrastos Mantadelis
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
% ensure that installation of your Modified Version does not prevent the
% user installing or running the Standard Version. In addition, the
% modified Version must bear a name that is different from the name of
% the Standard Version. (c) allow anyone who receives a copy of the
% Modified Version to make the Source form of the Modified Version
% available to others under (i) the Original License or (ii) a license
% that permits the licensee to freely copy, modify and redistribute the
% Modified Version using the same licensing terms that apply to the copy
% that the licensee received, and requires that the Source form of the
% Modified Version, and of any works derived from it, be made freely
% available in that license fees are prohibited but Distributor Fees are
% allowed.
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
% valid at the time of your distribution. If these instructions, at any
% time while you are carrying out such distribution, become invalid, you
% must provide new instructions on demand or cease further
% distribution. If you provide valid instructions or cease distribution
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
% Package. Distributor Fees are permitted, and licensing fees for other
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
% include the Package, and Distribute the result without restriction,
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
% considered parts of the Package itself, and are not subject to the
% terms of this license.
%
% General Provisions
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
% patent claims licensable by the Copyright Holder that are necessarily
% infringed by the Package. If you institute patent litigation
% (including a cross-claim or counterclaim) against any party alleging
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(variable_elimination, [trie_check_for_and_cluster/1, trie_replace_and_cluster/2, clean_up/0, variable_elimination_stats/3]).
:- ensure_loaded(library(lists)).
:- ensure_loaded(library(tries)).
:- use_module('flags', _, [problog_define_flag/5]).
:- nb_setval(prob_fact_count, 0).
:- problog_define_flag(variable_elimination, problog_flag_validate_boolean, 'enable variable elimination', false, variable_elimination).
bit_encode(L, ON):-
bit_encode(L, ON, 0).
bit_encode([], ON, ON):-!.
bit_encode([PF|T], ON, Acc):-
(recorded(variable_elimination, prob_fact(PF, ID), _) ->
true
;
nb_getval(prob_fact_count, ID),
NID is ID + 1,
nb_setval(prob_fact_count, NID),
recordz(variable_elimination, prob_fact(PF, ID), _)
),
NAcc is Acc \/ (1 << ID),
bit_encode(T, ON, NAcc).
bit_decode(ON, L):-
bit_decode(ON, 0, L).
bit_decode(_, ID, []):-
nb_getval(prob_fact_count, ID), !.
bit_decode(ON, ID, [PF|L]):-
0 < ON /\ (1 << ID),
recorded(variable_elimination, prob_fact(PF, ID), _),
NID is ID + 1,
bit_decode(ON, NID, L).
bit_decode(ON, ID, L):-
NID is ID + 1,
bit_decode(ON, NID, L).
update_table(T, ON, NT):-
update_table(T, ON, NT, 0).
update_table([], _ON, [], _).
update_table([H|T], ON, [NH|NT], Row):-
0 is ON /\ (1 << Row), !,
NH is H /\ \ ON, % this is an optional improvement
NRow is Row + 1,
update_table(T, ON, NT, NRow).
update_table([H|T], ON, [NH|NT], Row):-
NH is H /\ ON,
NRow is Row + 1,
update_table(T, ON, NT, NRow).
make_mask(FromBit, ToBit, Mask):-
Mask is (1 << (ToBit + 1) - 1) - (1 << FromBit - 1).
make_table(_, 0, []):-!.
make_table(ON, T, [ON|L]):-
NT is T - 1,
make_table(ON, NT, L).
modify_table(L, OT, NT):-
nb_getval(prob_fact_count, OLS),
bit_encode(L, ON),
nb_getval(prob_fact_count, NLS),
update_table(OT, ON, L1),
D is NLS - OLS,
make_mask(OLS, NLS, M),
NON is M /\ ON,
make_table(NON, D, L2),
append(L1, L2, NT).
examin(T):-
examin(T, 0).
examin([], _Row).
examin([H|T], Row):-
N is 1 << Row,
0 is H /\ (N - 1),
0 < H - N, !,
bit_decode(H, L),
calc_prob_AND_cluster(L, P),
make_prob_fact(L, P, ID),
recordz(variable_elimination, and_cluster(L, ID), _),
NRow is Row + 1,
examin(T, NRow).
examin([_H|T], Row):-
NRow is Row + 1,
examin(T, NRow).
trie_check_for_and_cluster(T):-
tries:trie_traverse_first(T, E), !,
trie_check_for_and_cluster(E, []).
trie_check_for_and_cluster(_T).
trie_check_for_and_cluster(E, T):-
tries:trie_traverse_next(E, N), !,
tries:trie_get_entry(E, L),
modify_table(L, T, NT),
trie_check_for_and_cluster(N, NT).
trie_check_for_and_cluster(E, T):-
tries:trie_get_entry(E, L),
modify_table(L, T, NT),
examin(NT), !.
trie_replace_and_cluster(To, Tn):-
tries:trie_open(Tn),
trie_replace_and_cluster_do(To, Tn).
trie_replace_and_cluster_do(To, Tn):-
trie_traverse(To, E),
trie_get_entry(E, L),
findall(Cluster/VarName, recorded(variable_elimination, and_cluster(Cluster, VarName), _), Clusters),
foreach(Clusters, NewL, L),
trie_put_entry(Tn, NewL, _),
fail.
trie_replace_and_cluster_do(_To, _Tn).
foreach([], L, L).
foreach([Cluster/VarName|Rest], L, Acc):-
check_replace_cluster(Cluster, VarName, Acc, NL),
foreach(Rest, L, NL).
check_replace_cluster(Cluster, _VarName, L, L):-
nocluster(Cluster, L), !.
check_replace_cluster(Cluster, VarName, L, NewL):-
replace_cluster(Cluster, VarName, L, NewL).
replace_cluster(Cluster, VarName, L, Res):-
first_cluster_element(L, Cluster, First),
replace(L, First, VarName, NL),
delete(Cluster, First, RestCluster),
eliminate_list(RestCluster, NL, Res),
!.
replace_cluster(Cluster, VarName, _L, _Res):-
throw(error(Cluster, VarName)).
replace_cluster2(Cluster, VarName, L, Res):-
eliminate_list(Cluster, L, NL),
append(NL, [VarName], Res),
!.
replace_cluster2(Cluster, VarName, _L, _Res):-
throw(error(Cluster, VarName)).
replace_cluster3(Cluster, VarName, L, Res):-
last_cluster_element(L, Cluster, Last),
replace(L, Last, VarName, NL),
delete(Cluster, Last, RestCluster),
eliminate_list(RestCluster, NL, Res),
!.
replace_cluster3(Cluster, VarName, _L, _Res):-
throw(error(Cluster, VarName)).
first_cluster_element([], _, _).
first_cluster_element([H|_T], Cluster, H):-
memberchk(H, Cluster), !.
first_cluster_element([_H|T], Cluster, R):-
first_cluster_element(T, Cluster, R).
last_cluster_element(L, Cluster, R):-
reverse(L, RL),
first_cluster_element(RL, Cluster, R).
nocluster([], _).
nocluster([H|T], L):-
not(memberchk(H, L)),
nocluster(T, L).
eliminate_list([], L, L).
eliminate_list([H|T], L, Res):-
memberchk(H, L),
delete(L, H, NL),
eliminate_list(T, NL, Res).
replace([], _, _, []).
replace([H|T], H, NH, [NH|NT]):-
replace(T, H, NH, NT).
replace([H|T], R, NR, [H|NT]):-
\+ H == R,
replace(T, R, NR, NT).
clean_up:-
eraseall(variable_elimination),
nb_setval(prob_fact_count, 0).
variable_elimination_stats(Clusters, OrigPF, CompPF):-
nb_getval(prob_fact_count, OrigPF),
findall(L, (recorded(variable_elimination, and_cluster(Cluster, _), _), length(Cluster, L)), LL),
sum_list(LL, EliminatedPF),
length(LL, Clusters),
CompPF is OrigPF - EliminatedPF + Clusters.
calc_prob_AND_cluster(L, P):-
multiply_list(L, P, 1.0).
multiply_list([], P, P).
multiply_list([H|T], Pr, A):-
problog:get_fact_probability(H, P),
number(P),
NA is A * P,
multiply_list(T, Pr, NA).
make_prob_fact(L, P, ID):-
(clause(problog:problog_var_elimination(ID, L, _), true) ->
true
;
problog:probclause_id(ID),
assert_static(problog:prob_for_id(ID, P, _)),
(clause(problog:problog_predicate(var_elimination, 1), true) ->
true
;
assert(problog:problog_predicate(var_elimination, 1))
),
assert(problog:problog_var_elimination(ID, L, P))
).

View File

@ -0,0 +1,402 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% $Date: 2010-08-24 15:23:06 +0200 (Tue, 24 Aug 2010) $
% $Revision: 4672 $
%
% This file is part of ProbLog
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
% Copyright 2008, 2009, 2010
% Katholieke Universiteit Leuven
%
% Main authors of this file:
% Bernd Gutmann, Theofrastos Mantadelis
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
% ensure that installation of your Modified Version does not prevent the
% user installing or running the Standard Version. In addition, the
% modified Version must bear a name that is different from the name of
% the Standard Version. (c) allow anyone who receives a copy of the
% Modified Version to make the Source form of the Modified Version
% available to others under (i) the Original License or (ii) a license
% that permits the licensee to freely copy, modify and redistribute the
% Modified Version using the same licensing terms that apply to the copy
% that the licensee received, and requires that the Source form of the
% Modified Version, and of any works derived from it, be made freely
% available in that license fees are prohibited but Distributor Fees are
% allowed.
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
% valid at the time of your distribution. If these instructions, at any
% time while you are carrying out such distribution, become invalid, you
% must provide new instructions on demand or cease further
% distribution. If you provide valid instructions or cease distribution
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
% Package. Distributor Fees are permitted, and licensing fees for other
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
% include the Package, and Distribute the result without restriction,
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
% considered parts of the Package itself, and are not subject to the
% terms of this license.
%
% General Provisions
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
% patent claims licensable by the Copyright Holder that are necessarily
% infringed by the Package. If you institute patent litigation
% (including a cross-claim or counterclaim) against any party alleging
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
% PARTICULAR PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT
% PERMITTED BY YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT
% HOLDER OR CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT,
% INCIDENTAL, OR CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE
% OF THE PACKAGE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Statistics for ProbLog
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(variables, [problog_var_set/2,
problog_var_set_once/2,
problog_var_get/2,
problog_var_is_set/1,
problog_var_defined/4,
problog_var_defined/1,
problog_var_define/4,
problog_var_define/3,
problog_var_clear/1,
problog_var_clear_all/0,
problog_var_group/1,
problog_timer_start/1,
problog_timer_stop/2,
problog_timer_pause/1,
problog_timer_pause/2,
problog_timer_resume/1,
problog_time_out/4,
problog_var_timer_start/1,
problog_var_timer_resume/1,
problog_var_timer_pause/1,
problog_var_timer_stop/1,
problog_var_timer_timeout/1,
problog_var_time_out/4]).
:- yap_flag(unknown,error).
:- style_check(single_var).
problog_var_set(Variable, Value):-
ground(Variable), nonvar(Value),
(recorded(problog_variables, stored(Variable, _Value), Ref) ->
erase(Ref)
;
true
),
recordz(problog_variables, stored(Variable, Value), _Ref).
problog_var_set_once(Variable, Value):-
ground(Variable), nonvar(Value),
(recorded(problog_variables, stored(Variable, _Value), __Ref) ->
throw(problog_variable_already_set(problog_var_set_once(Variable, Value)))
;
recordz(problog_variables, stored(Variable, Value), _Ref)
).
problog_var_get(Variable, Value):-
((ground(Variable),recorded(problog_variables, stored(Variable, Value), _Ref)) ->
true
;
throw(problog_variable_not_set(problog_var_get(Variable, Value)))
).
problog_var_is_set(Variable):-
nonvar(Variable),
recorded(problog_variables, stored(Variable, _Value), _Ref).
problog_var_defined(Variable):-
problog_var_defined(Variable, _Group, _Type, _Messages).
problog_var_defined(Variable, Group, Type, Messages):-
recorded(problog_variables, defined(Variable, Group, Type, Messages), _Ref).
problog_var_defined(Variable, default, untyped, messages(Variable, ':', '')):-
recorded(problog_variables, stored(Variable, _Value), _Ref),
\+ recorded(problog_variables, defined(Variable, _Group, _Type, _Messages), _).
problog_var_define(Variable, Group, Type):-
problog_var_define(Variable, Group, Type, messages(Variable, ':', '')).
problog_var_define(Variable, Group, Type, Messages):-
recorded(problog_variables, defined(Variable, _Group, _Type, _Messages), _Ref),
throw(problog_variable_already_defined(problog_var_define(Variable, Group, Type, Messages))).
problog_var_define(Variable, Group, Type, Messages):-
recordz(problog_variables, defined(Variable, Group, Type, Messages), _Ref),
(recorded(problog_variables, group(Group), _) ->
true
;
recordz(problog_variables, group(Group), __Ref)
).
problog_var_clear(Variable):-
recorded(problog_variables, stored(Variable, _), Ref),
erase(Ref).
problog_var_clear_all:-
recorded(problog_variables, stored(_, _), Ref),
erase(Ref),
fail.
problog_var_clear_all.
problog_var_group(Group):-
recorded(problog_variables, group(Group), _).
problog_var_group(default).
%%% Migrated code from timers %%%
%
% This is more or less duplicate code now with timers.
% We should decide if it stays here or it is a seperate module.
%
% modfications from module timers: works with records, stop stops a paused timer
% should start resume a paused timer? Then no need for predicate resume...
%
problog_timer_start(Name) :-
(recorded(problog_timer, timer(Name, _), _) ->
throw(problog_timer_already_started(problog_timer_start(Name)));
statistics(walltime, [StartTime, _]),
recordz(problog_timer, timer(Name, StartTime), _)
).
problog_timer_stop(Name, Duration) :-
recorded(problog_timer, timer(Name, StartTime), Ref),
erase(Ref), !,
statistics(walltime, [StopTime, _]),
Duration is StopTime - StartTime.
problog_timer_stop(Name, Duration) :-
(recorded(problog_timer, timer_paused(Name, Duration), Ref) ->
erase(Ref)
;
throw(problog_timer_not_started(problog_timer_stop(Name, Duration)))
).
problog_timer_pause(Name) :-
(recorded(problog_timer, timer(Name, StartTime), Ref) ->
erase(Ref),
statistics(walltime, [StopTime, _]),
Duration is StopTime - StartTime,
recordz(problog_timer, timer_paused(Name, Duration), _)
;
throw(problog_timer_not_started(problog_timer_pause(Name)))
).
problog_timer_pause(Name, Duration) :-
(recorded(problog_timer, timer(Name, StartTime), Ref) ->
erase(Ref),
statistics(walltime, [StopTime, _]),
Duration is StopTime - StartTime,
recordz(problog_timer, timer_paused(Name, Duration), _)
;
throw(problog_timer_not_started(problog_timer_pause(Name)))
).
problog_timer_resume(Name):-
(recorded(problog_timer, timer_paused(Name, Duration), Ref) ->
erase(Ref),
statistics(walltime, [ResumeTime, _]),
CorrectedStartTime is ResumeTime - Duration,
recordz(problog_timer, timer(Name, CorrectedStartTime), _)
;
throw(problog_timer_not_paused(problog_timer_resume(Name)))
).
%%% Syntactic sugar to make timer based variables %%%
problog_var_timer_start(Variable):-
problog_timer_start(Variable).
problog_var_timer_resume(Variable):-
problog_timer_resume(Variable).
problog_var_timer_pause(Variable):-
problog_timer_pause(Variable, Duration),
problog_var_set(Variable, Duration).
problog_var_timer_stop(Variable):-
problog_timer_stop(Variable, Duration),
problog_var_set(Variable, Duration).
problog_var_timer_timeout(Variable):-
problog_timer_stop(Variable, _Duration),
problog_var_set(Variable, timeout).
%%% This is possible for future use %%%
:- use_module(library(timeout)).
:- meta_predicate problog_var_time_out(:,_,_,_), problog_time_out(:,_,_,_).
%
% Problems with nesting, use with care
% always succeeds returns Success = true/fail, Time = Msec taken/timeout
%
problog_var_time_out(M:Goal, TimeOut, Success, Variable):-
problog_time_out(M:Goal, TimeOut, Success, Time),
problog_var_set(Variable, Time).
problog_time_out(M:Goal, TimeOut, Success, Time):-
MSecs is TimeOut * 1000,
problog_timer_start(time_measure),
(time_out(M:Goal, MSecs, Result) ->
problog_timer_stop(time_measure, Duration),
(Result == success ->
Success = true,
Time = Duration
;
Success = fail,
Time = Result
)
;
Success = fail,
problog_timer_stop(time_measure, Time)
).