New ProbLog Distribution Version - all

This commit is contained in:
Theofrastos Mantadelis
2010-08-26 14:44:10 +02:00
parent a35f51b9d0
commit 0c83231d0e
16 changed files with 2889 additions and 1030 deletions

View File

@@ -1,21 +1,23 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% ProbLog program describing a probabilistic graph
% (running example from ProbLog presentations)
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- use_module(library(problog)).
:- use_module('../problog').
%%%%
% background knowledge
%%%%
%%%%
% definition of acyclic path using list of visited nodes
path(X,Y) :- path(X,Y,[X],_).
path(X,X,A,A).
path(X,Y,A,R) :-
X\==Y,
edge(X,Z),
absent(Z,A),
path(X,Y,A,R) :-
X\==Y,
edge(X,Z),
absent(Z,A),
path(Z,Y,[Z|A],R).
% using directed edges in both directions
@@ -42,7 +44,7 @@ absent(X,[Y|Z]):-X \= Y, absent(X,Z).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% example queries about path(1,4)
%
%%% explanation probability (and facts involved)
%%% explanation probability (and facts involved)
% ?- problog_max(path(1,4),Prob,FactsUsed).
% FactsUsed = [dir_edge(1,2),dir_edge(2,3),dir_edge(3,4)],
% Prob = 0.432 ?
@@ -63,7 +65,7 @@ absent(X,[Y|Z]):-X \= Y, absent(X,Z).
% ?- problog_montecarlo(path(1,4),0.01,Prob).
% Prob = 0.537525 ?
% yes
%%% upper and lower bound using iterative deepening, final interval width 0.01
%%% upper and lower bound using iterative deepening, final interval width 0.01
% ?- problog_delta(path(1,4),0.01,Bound_low,Bound_up,Status).
% Bound_low = 0.5354096,
% Bound_up = 0.53864,
@@ -82,5 +84,5 @@ absent(X,[Y|Z]):-X \= Y, absent(X,Z).
% Bound_low = 0.432,
% Status = ok ?
% yes
%
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

View File

@@ -0,0 +1,67 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% ProbLog program describing a probabilistic graph using tabling
% (running example from ProbLog presentations)
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- use_module('../problog').
% New trie method ensures Probibilistic Cycle Handling needed for tabling that handles loops
:- set_problog_flag(use_db_trie, true).
:- set_problog_flag(use_old_trie, false).
%%%%
% background knowledge
%%%%
% definition of acyclic path using list of visited nodes
% to table a predicate you first need to define it as a dynamic one
:- dynamic path/2.
path(X,X).
path(X,Y) :-
X\==Y,
edge(X,Z),
path(Z,Y).
:- problog_table path/2.
% after all predicate definitions have appeared you need to state that the predicate will be tabled
% using directed edges in both directions
edge(X,Y) :- dir_edge(Y,X).
edge(X,Y) :- dir_edge(X,Y).
%%%%
% probabilistic facts
%%%%
0.9::dir_edge(1,2).
0.8::dir_edge(2,3).
0.6::dir_edge(3,4).
0.7::dir_edge(1,6).
0.5::dir_edge(2,6).
0.4::dir_edge(6,5).
0.7::dir_edge(5,3).
0.2::dir_edge(5,4).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% example queries about tabled path(1,4) useable only with problog_exact, problog_montecarlo currently
%
%%% success probability
% ?- problog_exact(path(1,4),Prob,Status).
% Prob = 0.53864,
% Status = ok ?
% yes
%%% approximation using monte carlo, to reach 95%-confidence interval width 0.01
% ?- problog_montecarlo(path(1,4),0.01,Prob).
% Prob = 0.537525 ?
% yes
%%% success probability of negation
% ?- problog_exact(problog_neg(path(1,4)),Prob,Status).
% Prob = 0.46136,
% Status = ok ?
% yes
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

View File

@@ -1,3 +1,5 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% ProbLog program describing a probabilistic graph
% (running example from ProbLog presentations)
@@ -10,7 +12,7 @@
% will run 20 iterations of learning with default settings
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- use_module(library(problog_learning)).
:- use_module('../problog_learning').
%%%%
% background knowledge

View File

@@ -0,0 +1,27 @@
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% ProbLog program describing an office window
%
% example for using hybrid ProbLog
%
% query ?- problog_exact(room_has_window, Prob, Status).
% Prob = 0.008527075,
% Status = ok ?
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- use_module('../problog').
width(gaussian(2,1)).
length(gaussian(9,3)).
0.8 :: office_has_window.
0.001 :: corridor_has_window.
in_office :- width(W),length(L), in_interval(W,2,4), in_interval(L,2,4).
in_corridor :- width(W),length(L), below(W,2.5), above(L,3).
room_has_window:-
in_office, office_has_window.
room_has_window:-
in_corridor,corridor_has_window.

View File

@@ -0,0 +1,114 @@
%%% -*- Mode: Prolog; -*-
% The viral marketing example consists of a social network of friend relations. You have to decide which persons to market. Sending marketing has a cost of 2, but might cause people to buy your product, giving you a profit of 5. When someone buys the product, it becomes more likely that his friends also buy the product.
:- use_module('../dtproblog').
% Decisions
? :: marketed(P) :- person(P).
% Utility attributes
buys(P) => 5 :- person(P).
marketed(P) => -2 :- person(P).
% Probabilistic facts
0.2 :: buy_from_marketing(_).
0.3 :: buy_from_trust(_,_).
% Background knowledge
person(bernd).
person(ingo).
person(theo).
person(angelika).
person(guy).
person(martijn).
person(laura).
person(kurt).
trusts(X,Y) :- trusts_directed(X,Y).
trusts(X,Y) :- trusts_directed(Y,X).
trusts_directed(bernd,ingo).
trusts_directed(ingo,theo).
trusts_directed(theo,angelika).
trusts_directed(bernd,martijn).
trusts_directed(ingo,martijn).
trusts_directed(martijn,guy).
trusts_directed(guy,theo).
trusts_directed(guy,angelika).
trusts_directed(laura,ingo).
trusts_directed(laura,theo).
trusts_directed(laura,guy).
trusts_directed(laura,martijn).
trusts_directed(kurt,bernd).
buys(X) :- buys(X,[X]).
buys(X, _) :-
marketed(X),
buy_from_marketing(X).
buys(X, Visited) :-
trusts(X,Y),
buy_from_trust(X,Y),
absent(Y,Visited),
buys(Y, [Y|Visited]).
absent(_,[]).
absent(X,[Y|Z]):-X \= Y, absent(X,Z).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% EXAMPLE USE::
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Find the globally optimal strategy.
%
% ?- dtproblog_solve(Strategy,ExpectedValue).
% ExpectedValue = 3.21097,
% Strategy = [marketed(martijn),marketed(guy),marketed(theo),marketed(ingo)]
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Compute the expected value for a given strategy.
%
% ?- dtproblog_ev([marketed(martijn),marketed(laura)],ExpectedValue).
% ExpectedValue = 2.35771065
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Find a locally optimal strategy.
%
% ?- set_problog_flag(optimization, local), dtproblog_solve(Strategy,ExpectedValue).
% ExpectedValue = 3.19528,
% Strategy = [marketed(martijn),marketed(laura),marketed(guy),marketed(ingo)]
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Find all ground utility facts in the theory.
%
% ?- dtproblog_utility_facts(Facts).
% Facts = [buys(bernd)=>5, buys(ingo)=>5, buys(theo)=>5, buys(angelika)=>5, buys(guy)=>5, buys(martijn)=>5, buys(laura)=>5, buys(kurt)=>5, marketed(bernd)=> -2, marketed(ingo)=> -2, marketed(theo)=> -2, marketed(angelika)=> -2, marketed(guy)=> -2, marketed(martijn)=> -2, marketed(laura)=> -2, marketed(kurt)=> -2]
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Find all ground decisions relevant to the utility attributes.
%
% ?- dtproblog_decisions(Decisions).
% Decisions = [marketed(angelika), marketed(theo), marketed(kurt), marketed(ingo), marketed(laura), marketed(martijn), marketed(guy), marketed(bernd)]
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Set the inference method to K-best to limit the complexity. This means that only the K most likely proofs for each utility attribute are considered as an underestimate of the probabilities and utilities. In the viral marketing example, this means that the probability that someone buys the product only depends on a limited number of other people in the social network, regardless of the size of the social network.
% Finding the globally optimal strategy under these simplifying assumptions yields a good but suboptimal strategy.
%
% ?- set_problog_flag(inference,20-best), dtproblog_solve(Strategy,ExpectedValue).
% ExpectedValue = 2.62531,
% Strategy = [marketed(martijn),marketed(guy),marketed(ingo),marketed(laura)]
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% The expected value returned in the previous example is an underestimate of the real expected value of the strategy found, which can be computed as
%
% ?- set_problog_flag(inference,exact), dtproblog_ev([marketed(martijn), marketed(guy), marketed(ingo), marketed(laura)], ExpectedValue).
% ExpectedValue = 3.1952798
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

View File

@@ -0,0 +1,106 @@
%%% -*- Mode: Prolog; -*-
% The viral marketing example consists of a social network of friend relations. You have to decido which persons to market. Sending marketing has a cost of 2, but might cause people to buy your product, giving you a profit of 5. When someone buys the product, it becomes more likely that his friends also buy the product.
:- use_module('../dtproblog').
% Decisions
? :: marketed(P) :- person(P).
% Utility attributes
buys(P) => 5 :- person(P).
marketed(P) => -2 :- person(P).
% Probabilistic facts
0.2 :: buy_from_marketing(_).
0.3 :: buy_from_trust(_,_).
% Background knowledge
person(bernd).
person(ingo).
person(theo).
person(angelika).
person(guy).
person(martijn).
person(laura).
person(kurt).
trusts(X,Y) :- trusts_directed(X,Y).
trusts(X,Y) :- trusts_directed(Y,X).
trusts_directed(bernd,ingo).
trusts_directed(ingo,theo).
trusts_directed(theo,angelika).
trusts_directed(bernd,martijn).
trusts_directed(ingo,martijn).
trusts_directed(martijn,guy).
trusts_directed(guy,theo).
trusts_directed(guy,angelika).
trusts_directed(laura,ingo).
trusts_directed(laura,theo).
trusts_directed(laura,guy).
trusts_directed(laura,martijn).
trusts_directed(kurt,bernd).
% The buys predicate is tabled to speed up exact inference. K-best inference does not support tabled predicates.
% Add this before a tabled predicate.
:- dynamic buys/1.
buys(X) :-
marketed(X),
buy_from_marketing(X).
buys(X) :-
trusts(X,Y),
buy_from_trust(X,Y),
buys(Y).
% Add this after a tabled predicate.
:- problog_table buys/1.
:- set_problog_flag(use_db_trie, true).
:- set_problog_flag(use_old_trie, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% EXAMPLE USE::
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Find the globally optimal strategy.
%
% ?- dtproblog_solve(Strategy,ExpectedValue).
% ExpectedValue = 3.21097,
% Strategy = [marketed(martijn),marketed(guy),marketed(theo),marketed(ingo)]
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Compute the expected value for a given strategy.
%
% ?- dtproblog_ev([marketed(martijn),marketed(laura)],ExpectedValue).
% ExpectedValue = 2.35771065
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Find a locally optimal strategy.
%
% ?- set_problog_flag(optimization, local), dtproblog_solve(Strategy,ExpectedValue).
% ExpectedValue = 3.19528,
% Strategy = [marketed(martijn),marketed(laura),marketed(guy),marketed(ingo)]
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Find all ground utility facts in the theory.
%
% ?- dtproblog_utility_facts(Facts).
% Facts = [buys(bernd)=>5, buys(ingo)=>5, buys(theo)=>5, buys(angelika)=>5, buys(guy)=>5, buys(martijn)=>5, buys(laura)=>5, buys(kurt)=>5, marketed(bernd)=> -2, marketed(ingo)=> -2, marketed(theo)=> -2, marketed(angelika)=> -2, marketed(guy)=> -2, marketed(martijn)=> -2, marketed(laura)=> -2, marketed(kurt)=> -2]
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Find all ground decisions relevant to the utility attributes.
%
% ?- dtproblog_decisions(Decisions).
% Decisions = [marketed(angelika), marketed(theo), marketed(kurt), marketed(ingo), marketed(laura), marketed(martijn), marketed(guy), marketed(bernd)]
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% (K-best inference and optimization does not support tabled predicates. Please use the non-tabled viral marketing example.)
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%