1:- module(bddem,[
    2  init_em/1,init_ex/2,init/1,end_em/1,end_ex/1,end/1,
    3  one/2,zero/2,and/4,or/4,bdd_not/3,
    4  ret_prob/3,equality/4,add_var/4,
    5  add_abd_var/4,ret_abd_prob/4,
    6  add_query_var/4,ret_map_prob/4,
    7  onec/2,zeroc/2,andc/4,andcnf/4,bdd_notc/3,
    8  orc/3,
    9  ret_probc/3,equalityc/4,
   10  or_list/3,
   11  or_listc/3,
   12  make_query_var/3,create_dot/3,create_dot_string/3,
   13  em/9,rand_seed/1,
   14  gamma_sample/3,
   15  gauss_sample/3,
   16  uniform_sample/1,
   17  dirichlet_sample/2,
   18  symmetric_dirichlet_sample/3,
   19  discrete_sample/2,
   20  initial_values/2,
   21  add_decision_var/3,
   22  probability_dd/3,
   23  add_prod/4,
   24  add_sum/4,
   25  ret_strategy/4,
   26  % compute_best_strategy/5,
   27  debug_cudd_var/2
   28  ]).

bddem

Module for manipulating Binary Decision Diagrams.

It contains programs for building BDDs, for computing probabilities and for performing Expectation Maximization.

author
- Fabrizio Riguzzi
license
- Artistic License 2.0 https://opensource.org/licenses/Artistic-2.0
   40:-use_foreign_library(foreign(bddem),install).
 init_em(--Context:int) is det
Initializes a data structure for performing parameter learning. It returns an integer in Context that is a pointer to a context data structure for performing the EM algorithm. /
 end_em(++Context:int) is det
Terminates the context data structure for performing parameter learning. Context is a pointer to a context data structure for performing the EM algorithm. Context must have been returned by a call to init_em/1. It frees the memory occupied by Context. /
 init_ex(++Context:int, --Environment:int) is det
Initializes an enviroment data structure for storing a BDD. Context is an integer that is a pointer to a context data structure created using init_em/1. Returns an integer Environment that is a pointer to a data structure for storing a single BDD to be used for the EM algorithm. /
 end_ex(++Environment:int) is det
Terminates the evnironment data structure for storing a BDD. Environment is a pointer to a data structure returned by init_ex/2. It frees the memory occupied by the BDD. /
 init(--Environment:int) is det
Initializes a data structure for storing a single BDD. Returns an integer Environment that is a pointer to a data structure for storing a single BDD to be used for inference only (no learning). /
 end(++Environment:int) is det
Terminates the environment data structure for storing a single BDD. Environment is a pointer to a data structure returned by a call to init/1. /
 one(++Environment:int, --One:int) is det
Returns in One a pointer to a BDD belonging to environment Environment representing the one Boolean function. /
 zero(++Environment:int, --Zero:int) is det
Returns in Zero a pointer to a BDD belonging to environment Environment representing the zero Boolean function. /
 and(++Environment:int, ++A:int, ++B:int, --AandB:int) is det
Returns in AandB a pointer to a BDD belonging to environment Environment representing the conjunction of BDDs A and B. /
 or(++Environment:int, ++A:int, ++B:int, --AorB:int) is det
Returns in AorB a pointer to a BDD belonging to environment Environment representing the disjunction of BDDs A and B. /
 ret_prob(++Environment:int, ++BDD:int, -Probability:float) is det
Returns the Probability of BDD belonging to environment Environment. /
 ret_map_prob(++Environment:int, ++BDD:int, -Probability:float, -MAPState:list) is det
Returns the MAP state MPAState of BDD and its Probability. BDD belongs to environment Environment. /
 ret_abd_prob(++Environment:int, ++BDD:int, -Probability:float, -Explanation:list) is det
Returns the abductive Explanation of BDD and its Probability. BDD belongs to environment Environment. /
 ret_mpe_prob(++Environment:int, ++BDD:int, -Probability:float, -MPEState:list) is det
Returns the MPE state MPEState of BDD and its Probability. BDD belongs to environment Environment. /
 bdd_not(++Environment:int, ++A:int, --NotA:int) is det
Returns in NotA a pointer to a BDD belonging to environment Environment representing the negation of BDD A. /
 equality(++Environment:int, ++Variable:int, ++Value:int, --BDD:int) is det
Returns in BDD the BDD belonging to environment Environment that represents the equation Variable=Value. /
 em(++Context:int, ++RuleInfo:list, ++ListOfBDDs:list, ++EA:float, ++ER:float, ++Iterations:int, -LL:float, -Parameters:list, -ExampleProbabilities:list) is det
NumberOfHeads is a list of terms, one for each rule. Each term is either an integer, indicating the number of head atoms in the rule, or a list [N] where N is the number of head atoms. In the first case, the parameters of the rule are tunable, in the latter they are fixed.

Performs EM learning. Takes as input the Context, information on the rules, a list of BDDs each representing one example, the minimum absolute difference EA and relative difference ER between the log likelihood of examples in two different iterations and the maximum number of iterations Iterations. RuleInfo is a list of elements, one for each rule, with are either

 add_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable in Environment with NumberOHeads values and probability distribution ProbabilityDistribution. /
 add_abd_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new abducible random variable in Environment with NumberOHeads values and probability distribution ProbabilityDistribution. /
 add_query_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable to be queried in MAP inference with NumberOHeads values and probability distribution ProbabilityDistribution. The variable belongs to Environment. /
 make_query_var(++Environment:int, +Variable:int, --BDD:int) is det
Makes Variable belonging to Environment a query random variable for MAP inference. Returns in BDD the diagram of the formula encoding the required constraints among the Boolean random variable that represent Variable. /
 create_dot_string(++Env:int, ++BDD:int, -Dot:string) is det
The predicate returns the BDD in dot format. /
 create_dot(++Env:int, ++BDD:int, ++File:string) is det
The predicate writes the BDD in dot format to to file FileName. /
 rand_seed(+Seed:int) is det
The pseudo-random number generator is initialized using the argument passed as Seed. It calls the C function srand. /
 orc(++A:couple, ++B:couple, --AorB:couple) is det
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively Returns in AorB a couple (Environment, BDDAorB) where BDDAorB is pointer to a BDD belonging to environment Environment representing the disjunction of BDDs BDDA and BDDB. /
  253orc((Env,A),(_,B),(Env,C)):-
  254  or(Env,A,B,C).
 onec(++Environment:int, --One:couple) is det
Returns in One a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment representing the one Boolean function /
  262onec(Env,(Env,One)):-
  263  one(Env,One).
 zeroc(++Environment:int, --Zero:couple) is det
Returns in Zero a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment representing the zero Boolean function /
  271zeroc(Env,(Env,Zero)):-
  272  zero(Env,Zero).
 andc(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment representing the conjunction of BDDs BDDA and BDDB. fails if BDDB represents the zero function /
  282andc(Env,(_,A),(_,B),(Env,C)):-
  283  (zero(Env,B)->
  284    fail
  285  ;
  286    and(Env,A,B,C)
  287  ).
 andcnf(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment representing the conjunction of BDDs BDDA and BDDB. /
  296andcnf(Env,(_,A),(_,B),(Env,C)):-
  297  and(Env,A,B,C).
 bdd_notc(++Environment:int, ++EBDD:couple, --NotEBDD:couple) is det
EBDD is a couple (Environment,A) Returns in NotEBDD a couple (Environment,NotA) where NotA is pointer to a BDD belonging to environment Environment representing the negation of BDD A /
  307bdd_notc(Env,(_,A),(Env,NA)):-
  308  bdd_not(Env,A,NA).
 equalityc(++Environment:int, ++Variable:int, ++Value:int, --EBDD:couple) is det
Returns in EBDD a couple (Environment,BDD) where BDD belongs to environment Environment and represents the equation Variable=Value. /
  316equalityc(Env,V,N,(Env,B)):-
  317  equality(Env,V,N,B).
 ret_probc(++Environment:int, ++EBDD:couple, -Probability:float) is det
EBDD is a couple (Environment,BDD) Returns the Probability of BDD belonging to environment Environment Uses /
  326ret_probc(Env,(_,BDD),P):-
  327  ret_prob(Env,BDD,P).
 initial_values(++Environment:int, ++Alpha:float) is det
Sets the type of parameter initialization for EM on Environment: if Alpha is 0.0, it uses a truncated Dirichlet process if Alpha is a float > 0.0, it uses a symmetric Dirichlet distribution with that value as parameter /
 or_list(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a pointer to a BDD belonging to environment Environment representing the disjunction of all the BDDs in ListOfBDDs /
  344or_list([H],_Env,H):-!.
  345
  346or_list([H|T],Env,B):-
  347  or_list1(T,Env,H,B).
  348
  349
  350or_list1([],_Env,B,B).
  351
  352or_list1([H|T],Env,B0,B1):-
  353  or(Env,B0,H,B2),
  354  or_list1(T,Env,B2,B1).
 or_listc(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a couple (Env,B) with B a pointer to a BDD belonging to environment Environment representing the disjunction of all the BDDs in ListOfBDDs (a list of couples (Env,BDD)) /
  364or_listc([H],_Env,H):-!.
  365
  366or_listc([H|T],Env,B):-
  367  or_listc1(T,Env,H,B).
  368
  369
  370or_listc1([],_Env,B,B).
  371
  372or_listc1([H|T],Env,B0,B1):-
  373  orc(B0,H,B2),
  374  or_listc1(T,Env,B2,B1).
 gamma_sample(++Shape:float, ++Scale:float, --Value:float) is det
Returns a Value sampled from a gamma distribution with parameters Shape and Scale /
 gauss_sample(++Mean:float, ++Variance:float, --Value:float) is det
Returns a Value sampled from a Gaussian distribution with parameters Mean and Variance /
 uniform_sample(--Value:float) is det
Returns a Value sampled from a uniform distribution in [0,1] /
 dirichlet_sample(++Alpha:list, --Value:list) is det
Returns a Value sampled from a Dirichlet distribution with parameters Alpha. Alpha and Value are lists of floating point numbers of the same length. /
 symmetric_dirichlet_sample(++Alpha:float, ++K:int, --Value:list) is det
Returns a Value sampled from a symmetric Dirichlet distribution with parameter Alpha. K is the number of dimensions of the result. /
 discrete_sample(++Theta:list, --Value:int) is det
Returns a Value sampled from a discrete distribution with parameters Theta. Theta is a list of floating point numbers in [0,1] that sum to 1. Value is in 0..(length(Theta)-1) /
 probability_dd(++Environment:int, ++BDD:int, --ADD:int) is det
Converts the BDD belonging to environment Environment into an ADD. */
 add_prod(++Environment:int, ++ADDIn:int, ++Utility:float, --ADDOut:int) is det
Multiplies the ADD belonging to environment Environment with the value Utility and stores the result in ADDOut. */
 add_sum(++Environment:int, ++ADD1:int, ++ADD2:int, --ADDOut:int) is det
Computes the sum of the two ADDs ADD1 ADD2 belonging to environment Environment. The result in saved in ADDOut. */
 ret_strategy(++Environment:int, ++ADD:int, --Decision:list, --Cost:int) is det
Computes the optimal strategy given a pointer to the ADD belonging to environment Environment. Decision is a list of selected facts, Cost is the total cost. */
 add_decision_var(++Environment:int, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new decision variable in Environment /
 debug_cudd_var(++Environment:int, -Variable:out) is det
Prints the debug information which is the result of the call of Cudd_ReadDead, Cudd_CheckZeroRef, Cudd_CheckKeys and Cudd_DebugCheck(env->mgr)); /