New ProbLog Distribution Version - all
This commit is contained in:
parent
a35f51b9d0
commit
0c83231d0e
@ -1,9 +1,11 @@
|
||||
%%% -*- Mode: Prolog; -*-
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
% ProbLog program describing a probabilistic graph
|
||||
% (running example from ProbLog presentations)
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
:- use_module(library(problog)).
|
||||
:- use_module('../problog').
|
||||
|
||||
%%%%
|
||||
% background knowledge
|
||||
|
67
packages/ProbLog/problog_examples/graph_tabled.pl
Normal file
67
packages/ProbLog/problog_examples/graph_tabled.pl
Normal 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
|
||||
%
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
@ -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
|
||||
|
27
packages/ProbLog/problog_examples/office.pl
Normal file
27
packages/ProbLog/problog_examples/office.pl
Normal 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.
|
||||
|
114
packages/ProbLog/problog_examples/viralmarketing.pl
Normal file
114
packages/ProbLog/problog_examples/viralmarketing.pl
Normal 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
|
||||
%
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
106
packages/ProbLog/problog_examples/viralmarketing_tabled.pl
Normal file
106
packages/ProbLog/problog_examples/viralmarketing_tabled.pl
Normal 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.)
|
||||
%
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
@ -17,6 +17,10 @@ BINDIR = $(EROOTDIR)/bin
|
||||
LIBDIR=@libdir@
|
||||
YAPLIBDIR=@libdir@/Yap
|
||||
#
|
||||
# where YAP should look for architecture-independent Prolog libraries
|
||||
#
|
||||
SHAREDIR=$(ROOTDIR)/share
|
||||
#
|
||||
#
|
||||
CC=@CC@
|
||||
#
|
||||
@ -34,30 +38,25 @@ SO=@SO@
|
||||
CWD=$(PWD)
|
||||
#
|
||||
|
||||
CUDD = cudd-2.4.1
|
||||
DYNAMIC =
|
||||
CFLAGS = @CFLAGS@
|
||||
INCLUDE = @CUDD_CPPFLAGS@
|
||||
LINKFLAGS = -lm
|
||||
LINKLIBS = @CUDD_LDFLAGS@
|
||||
|
||||
default: Example ProbLogBDD
|
||||
default: problogbdd
|
||||
|
||||
Example: Example.o simplecudd.o general.o
|
||||
@echo Making Example...
|
||||
@echo Copyright T. Mantadelis and Katholieke Universiteit Leuven 2008
|
||||
$(CC) Example.o simplecudd.o general.o $(LINKLIBS) $(LINKFLAGS) -o Example
|
||||
|
||||
ProbLogBDD: ProblogBDD.o simplecudd.o general.o
|
||||
@echo Making ProblogBDD...
|
||||
@echo Copyright T. Mantadelis, A. Kimmig, B. Gutmann and Katholieke Universiteit Leuven 2008
|
||||
$(CC) ProblogBDD.o simplecudd.o general.o $(LINKLIBS) $(LINKFLAGS) -o ProblogBDD
|
||||
problogbdd: problogbdd.o simplecudd.o general.o problogmath.o
|
||||
@echo Making problogbdd...
|
||||
@echo Copyright Katholieke Universiteit Leuven 2008
|
||||
@echo Authors: T. Mantadelis, A. Kimmig, B. Gutmann, I. Thon, G. Van den Broeck
|
||||
$(CC) problogbdd.o simplecudd.o general.o problogmath.o $(LINKLIBS) $(LINKFLAGS) -o problogbdd
|
||||
|
||||
%.o : $(srcdir)/%.c
|
||||
$(CC) $(CFLAGS) $(INCLUDE) $(DYNAMIC) -c $<
|
||||
|
||||
clean:
|
||||
rm -f *.o ProblogBDD Example
|
||||
rm -f *.o problogbdd
|
||||
|
||||
install: default
|
||||
$(INSTALL_PROGRAM) ProblogBDD $(DESTDIR)$(YAPLIBDIR)
|
||||
$(INSTALL_PROGRAM) problogbdd $(DESTDIR)$(SHAREDIR)/Yap
|
||||
|
@ -1,718 +0,0 @@
|
||||
/******************************************************************************\
|
||||
* *
|
||||
* SimpleCUDD library (www.cs.kuleuven.be/~theo/tools/simplecudd.html) *
|
||||
* SimpleCUDD was developed at Katholieke Universiteit Leuven(www.kuleuven.be) *
|
||||
* *
|
||||
* Copyright Katholieke Universiteit Leuven 2008 *
|
||||
* *
|
||||
* Author: Theofrastos Mantadelis, Angelika Kimmig, Bernd Gutmann *
|
||||
* File: ProblogBDD.c *
|
||||
* *
|
||||
********************************************************************************
|
||||
* *
|
||||
* 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. *
|
||||
* *
|
||||
* The End *
|
||||
* *
|
||||
\******************************************************************************/
|
||||
|
||||
#include "simplecudd.h"
|
||||
#include <signal.h>
|
||||
|
||||
typedef struct _parameters {
|
||||
int loadfile;
|
||||
int savedfile;
|
||||
int exportfile;
|
||||
int inputfile;
|
||||
int debug;
|
||||
int errorcnt;
|
||||
int *error;
|
||||
int method;
|
||||
int queryid;
|
||||
int timeout;
|
||||
double sigmoid_slope;
|
||||
int online;
|
||||
int maxbufsize;
|
||||
char *ppid;
|
||||
} parameters;
|
||||
|
||||
typedef struct _gradientpair {
|
||||
double probability;
|
||||
double gradient;
|
||||
} gradientpair;
|
||||
|
||||
typedef struct _extmanager {
|
||||
DdManager *manager;
|
||||
DdNode *t, *f;
|
||||
hisqueue *his;
|
||||
namedvars varmap;
|
||||
} extmanager;
|
||||
|
||||
int argtype(const char *arg);
|
||||
void printhelp(int argc, char **arg);
|
||||
parameters loadparam(int argc, char **arg);
|
||||
parameters params;
|
||||
|
||||
void handler(int num);
|
||||
void pidhandler(int num);
|
||||
void termhandler(int num);
|
||||
|
||||
double sigmoid(double x, double slope);
|
||||
void myexpand(extmanager MyManager, DdNode *Current);
|
||||
double CalcProbability(extmanager MyManager, DdNode *Current);
|
||||
double CalcProbabilitySigmoid(extmanager MyManager, DdNode *Current);
|
||||
gradientpair CalcGradient(extmanager MyManager, DdNode *Current, int TargetVar, char *TargetPattern);
|
||||
int patterncalculated(char *pattern, extmanager MyManager, int loc);
|
||||
char * extractpattern(char *thestr);
|
||||
|
||||
int main(int argc, char **arg) {
|
||||
extmanager MyManager;
|
||||
DdNode *bdd;
|
||||
bddfileheader fileheader;
|
||||
int i, ivarcnt, code;
|
||||
gradientpair tvalue;
|
||||
double probability = -1.0;
|
||||
char *varpattern;
|
||||
varpattern = NULL;
|
||||
code = -1;
|
||||
params = loadparam(argc, arg);
|
||||
|
||||
if (params.errorcnt > 0) {
|
||||
printhelp(argc, arg);
|
||||
for (i = 0; i < params.errorcnt; i++) {
|
||||
fprintf(stderr, "Error: not known or error at parameter %s.\n", arg[params.error[i]]);
|
||||
}
|
||||
return -1;
|
||||
}
|
||||
|
||||
if (params.online == 0 && params.loadfile == -1) {
|
||||
printhelp(argc, arg);
|
||||
fprintf(stderr, "Error: you must specify a loading file.\n");
|
||||
return -1;
|
||||
}
|
||||
|
||||
if (params.method != 0 && arg[params.method][0] != 'g' && arg[params.method][0] != 'p' && arg[params.method][0] != 'o' && arg[params.method][0] != 'l') {
|
||||
printhelp(argc, arg);
|
||||
fprintf(stderr, "Error: you must choose a calculation method beetween [p]robability, [g]radient, [l]ine search, [o]nline.\n");
|
||||
return -1;
|
||||
}
|
||||
|
||||
if (params.method != 0 && (arg[params.method][0] == 'g' || arg[params.method][0] == 'p' || arg[params.method][0] == 'l') && params.inputfile == -1) {
|
||||
printhelp(argc, arg);
|
||||
fprintf(stderr, "Error: an input file is necessary for probability, gradient or line search calculation methods.\n");
|
||||
return -1;
|
||||
}
|
||||
|
||||
if (params.debug) DEBUGON;
|
||||
RAPIDLOADON;
|
||||
SETMAXBUFSIZE(params.maxbufsize);
|
||||
|
||||
signal(SIGINT, termhandler);
|
||||
if (params.ppid != NULL) {
|
||||
signal(SIGALRM, pidhandler);
|
||||
alarm(5);
|
||||
} else {
|
||||
signal(SIGALRM, handler);
|
||||
alarm(params.timeout);
|
||||
}
|
||||
if (params.online) {
|
||||
MyManager.manager = simpleBDDinit(0);
|
||||
MyManager.t = HIGH(MyManager.manager);
|
||||
MyManager.f = LOW(MyManager.manager);
|
||||
MyManager.varmap = InitNamedVars(1, 0);
|
||||
bdd = OnlineGenerateBDD(MyManager.manager, &MyManager.varmap);
|
||||
ivarcnt = GetVarCount(MyManager.manager);
|
||||
} else {
|
||||
fileheader = ReadFileHeader(arg[params.loadfile]);
|
||||
switch(fileheader.filetype) {
|
||||
case BDDFILE_SCRIPT:
|
||||
MyManager.manager = simpleBDDinit(fileheader.varcnt);
|
||||
MyManager.t = HIGH(MyManager.manager);
|
||||
MyManager.f = LOW(MyManager.manager);
|
||||
MyManager.varmap = InitNamedVars(fileheader.varcnt, fileheader.varstart);
|
||||
bdd = FileGenerateBDD(MyManager.manager, MyManager.varmap, fileheader);
|
||||
ivarcnt = fileheader.varcnt;
|
||||
break;
|
||||
case BDDFILE_NODEDUMP:
|
||||
MyManager.manager = simpleBDDinit(fileheader.varcnt);
|
||||
MyManager.t = HIGH(MyManager.manager);
|
||||
MyManager.f = LOW(MyManager.manager);
|
||||
MyManager.varmap = InitNamedVars(fileheader.varcnt, fileheader.varstart);
|
||||
bdd = LoadNodeDump(MyManager.manager, MyManager.varmap, fileheader.inputfile);
|
||||
ivarcnt = fileheader.varcnt;
|
||||
break;
|
||||
default:
|
||||
fprintf(stderr, "Error: not a valid file format to load.\n");
|
||||
return -1;
|
||||
break;
|
||||
}
|
||||
}
|
||||
alarm(0);
|
||||
|
||||
// problem specifics
|
||||
|
||||
if (bdd != NULL) {
|
||||
ivarcnt = RepairVarcnt(&MyManager.varmap);
|
||||
code = 0;
|
||||
if (params.inputfile != -1) {
|
||||
if (LoadVariableData(MyManager.varmap, arg[params.inputfile]) == -1) return -1;
|
||||
if (!all_loaded(MyManager.varmap, 1)) return -1;
|
||||
}
|
||||
MyManager.his = InitHistory(ivarcnt);
|
||||
if (params.method != 0) {
|
||||
switch(arg[params.method][0]) {
|
||||
case 'g':
|
||||
for (i = 0; i < MyManager.varmap.varcnt; i++) {
|
||||
if (MyManager.varmap.vars[i] != NULL) {
|
||||
varpattern = extractpattern(MyManager.varmap.vars[i]);
|
||||
if ((varpattern == NULL) || (!patterncalculated(varpattern, MyManager, i))) {
|
||||
tvalue = CalcGradient(MyManager, bdd, i + MyManager.varmap.varstart, varpattern);
|
||||
probability = tvalue.probability;
|
||||
double factor = sigmoid(MyManager.varmap.dvalue[i], params.sigmoid_slope) * (1 - sigmoid(MyManager.varmap.dvalue[i], params.sigmoid_slope)) * params.sigmoid_slope;
|
||||
if (varpattern == NULL) {
|
||||
printf("query_gradient(%s,%s,%1.12f).\n", arg[params.queryid], MyManager.varmap.vars[i], tvalue.gradient * factor);
|
||||
} else {
|
||||
varpattern[strlen(varpattern) - 2] = '\0';
|
||||
printf("query_gradient(%s,%s,%1.12f).\n", arg[params.queryid], varpattern, tvalue.gradient * factor);
|
||||
}
|
||||
ReInitHistory(MyManager.his, MyManager.varmap.varcnt);
|
||||
}
|
||||
if (varpattern != NULL) free(varpattern);
|
||||
} else {
|
||||
fprintf(stderr, "Error: no variable name given for parameter.\n");
|
||||
}
|
||||
}
|
||||
if (probability < 0.0) {
|
||||
// no nodes, so we have to calculate probability ourself
|
||||
tvalue = CalcGradient(MyManager, bdd, 0 + MyManager.varmap.varstart, NULL);
|
||||
probability = tvalue.probability;
|
||||
}
|
||||
printf("query_probability(%s,%1.12f).\n", arg[params.queryid], probability);
|
||||
break;
|
||||
case 'l':
|
||||
tvalue = CalcGradient(MyManager, bdd, 0 + MyManager.varmap.varstart, NULL);
|
||||
probability = tvalue.probability;
|
||||
printf("query_probability(%s,%1.12f).\n", arg[params.queryid], probability);
|
||||
break;
|
||||
case 'p':
|
||||
printf("probability(%1.12f).\n", CalcProbability(MyManager, bdd));
|
||||
break;
|
||||
case 'o':
|
||||
onlinetraverse(MyManager.manager, MyManager.varmap, MyManager.his, bdd);
|
||||
break;
|
||||
default:
|
||||
myexpand(MyManager, bdd);
|
||||
break;
|
||||
}
|
||||
} else {
|
||||
myexpand(MyManager, bdd);
|
||||
}
|
||||
if (params.savedfile > -1) SaveNodeDump(MyManager.manager, MyManager.varmap, bdd, arg[params.savedfile]);
|
||||
if (params.exportfile > -1) simpleNamedBDDtoDot(MyManager.manager, MyManager.varmap, bdd, arg[params.exportfile]);
|
||||
ReInitHistory(MyManager.his, MyManager.varmap.varcnt);
|
||||
free(MyManager.his);
|
||||
}
|
||||
if (MyManager.manager != NULL) {
|
||||
KillBDD(MyManager.manager);
|
||||
free(MyManager.varmap.dvalue);
|
||||
free(MyManager.varmap.ivalue);
|
||||
if (MyManager.varmap.dynvalue != NULL) {
|
||||
for(i = 0; i < MyManager.varmap.varcnt; i++)
|
||||
if (MyManager.varmap.dynvalue[i] != NULL) {
|
||||
free(MyManager.varmap.dynvalue[i]);
|
||||
}
|
||||
free(MyManager.varmap.dynvalue);
|
||||
}
|
||||
for (i = 0; i < MyManager.varmap.varcnt; i++)
|
||||
free(MyManager.varmap.vars[i]);
|
||||
free(MyManager.varmap.vars);
|
||||
}
|
||||
if (params.error != NULL) free(params.error);
|
||||
|
||||
return code;
|
||||
|
||||
}
|
||||
|
||||
/* Shell Parameters handling */
|
||||
|
||||
int argtype(const char *arg) {
|
||||
if (strcmp(arg, "-l") == 0 || strcmp(arg, "--load") == 0) return 0;
|
||||
if (strcmp(arg, "-e") == 0 || strcmp(arg, "--export") == 0) return 2;
|
||||
if (strcmp(arg, "-m") == 0 || strcmp(arg, "--method") == 0) return 3;
|
||||
if (strcmp(arg, "-i") == 0 || strcmp(arg, "--input") == 0) return 4;
|
||||
if (strcmp(arg, "-h") == 0 || strcmp(arg, "--help") == 0) return 5;
|
||||
if (strcmp(arg, "-d") == 0 || strcmp(arg, "--debug") == 0) return 6;
|
||||
if (strcmp(arg, "-id") == 0 || strcmp(arg, "--queryid") == 0) return 7;
|
||||
if (strcmp(arg, "-t") == 0 || strcmp(arg, "--timeout") == 0) return 8;
|
||||
if (strcmp(arg, "-sd") == 0 || strcmp(arg, "--savedump") == 0) return 9;
|
||||
if (strcmp(arg, "-sl") == 0 || strcmp(arg, "--slope") == 0) return 10;
|
||||
if (strcmp(arg, "-o") == 0 || strcmp(arg, "--online") == 0) return 11;
|
||||
if (strcmp(arg, "-bs") == 0 || strcmp(arg, "--bufsize") == 0) return 12;
|
||||
if (strcmp(arg, "-pid") == 0 || strcmp(arg, "--pid") == 0) return 13;
|
||||
return -1;
|
||||
}
|
||||
|
||||
void printhelp(int argc, char **arg) {
|
||||
fprintf(stderr, "\nUsage: %s -l [filename] -i [filename] -o (-s(d) [filename] -e [filename] -m [method] -id [queryid] -sl [double]) (-t [seconds] -d -h)\n", arg[0]);
|
||||
fprintf(stderr, "Generates and traverses a BDD\nMandatory parameters:\n");
|
||||
fprintf(stderr, "\t-l [filename]\t->\tfilename to load supports two formats:\n\t\t\t\t\t\t1. script with generation instructions\n\t\t\t\t\t\t2. node dump saved file\n");
|
||||
fprintf(stderr, "\t-i [filename]\t->\tfilename to input problem specifics (mandatory with file formats 1, 2)\n");
|
||||
fprintf(stderr, "\t-o\t\t->\tgenerates the BDD in online mode instead from a file can be used instead of -l\n");
|
||||
fprintf(stderr, "Optional parameters:\n");
|
||||
fprintf(stderr, "\t-sd [filename]\t->\tfilename to save generated BDD in node dump format (fast loading, traverse valid only)\n");
|
||||
fprintf(stderr, "\t-e [filename]\t->\tfilename to export generated BDD in dot format\n");
|
||||
fprintf(stderr, "\t-m [method]\t->\tthe calculation method to be used: none(default), [p]robability, [g]radient, [l]ine search, [o]nline\n");
|
||||
fprintf(stderr, "\t-id [queryid]\t->\tthe queries identity name (used by gradient) default: %s\n", arg[0]);
|
||||
fprintf(stderr, "\t-sl [double]\t->\tthe sigmoid slope (used by gradient) default: 1.0\n");
|
||||
fprintf(stderr, "Extra parameters:\n");
|
||||
fprintf(stderr, "\t-t [seconds]\t->\tthe seconds (int) for BDD generation timeout default 0 = no timeout\n");
|
||||
fprintf(stderr, "\t-pid [pid]\t->\ta process id (int) to check for termination default 0 = no process to check\n");
|
||||
fprintf(stderr, "\t-bs [bytes]\t->\tthe bytes (int) to use as a maximum buffer size to read files default 0 = no max\n");
|
||||
fprintf(stderr, "\t-d\t\t->\tRun in debug mode (gives extra messages in stderr)\n");
|
||||
fprintf(stderr, "\t-h\t\t->\tHelp (displays this message)\n\n");
|
||||
fprintf(stderr, "Example: %s -l testbdd -i input.txt -m g -id testbdd\n", arg[0]);
|
||||
}
|
||||
|
||||
parameters loadparam(int argc, char **arg) {
|
||||
int i;
|
||||
parameters params;
|
||||
params.loadfile = -1;
|
||||
params.savedfile = -1;
|
||||
params.exportfile = -1;
|
||||
params.method = 0;
|
||||
params.inputfile = -1;
|
||||
params.debug = 0;
|
||||
params.errorcnt = 0;
|
||||
params.queryid = 0;
|
||||
params.timeout = 0;
|
||||
params.sigmoid_slope = 1.0;
|
||||
params.online = 0;
|
||||
params.maxbufsize = 0;
|
||||
params.ppid = NULL;
|
||||
params.error = (int *) malloc(argc * sizeof(int));
|
||||
for (i = 1; i < argc; i++) {
|
||||
switch(argtype(arg[i])) {
|
||||
case 0:
|
||||
if (argc > i + 1) {
|
||||
i++;
|
||||
params.loadfile = i;
|
||||
} else {
|
||||
params.error[params.errorcnt] = i;
|
||||
params.errorcnt++;
|
||||
}
|
||||
break;
|
||||
case 2:
|
||||
if (argc > i + 1) {
|
||||
i++;
|
||||
params.exportfile = i;
|
||||
} else {
|
||||
params.error[params.errorcnt] = i;
|
||||
params.errorcnt++;
|
||||
}
|
||||
break;
|
||||
case 3:
|
||||
if (argc > i + 1) {
|
||||
i++;
|
||||
params.method = i;
|
||||
} else {
|
||||
params.error[params.errorcnt] = i;
|
||||
params.errorcnt++;
|
||||
}
|
||||
break;
|
||||
case 4:
|
||||
if (argc > i + 1) {
|
||||
i++;
|
||||
params.inputfile = i;
|
||||
} else {
|
||||
params.error[params.errorcnt] = i;
|
||||
params.errorcnt++;
|
||||
}
|
||||
break;
|
||||
case 5:
|
||||
printhelp(argc, arg);
|
||||
break;
|
||||
case 6:
|
||||
params.debug = 1;
|
||||
break;
|
||||
case 7:
|
||||
if (argc > i + 1) {
|
||||
i++;
|
||||
params.queryid = i;
|
||||
} else {
|
||||
params.error[params.errorcnt] = i;
|
||||
params.errorcnt++;
|
||||
}
|
||||
break;
|
||||
case 8:
|
||||
if ((argc > i + 1) && (IsPosNumber(arg[i + 1]))) {
|
||||
i++;
|
||||
params.timeout = atoi(arg[i]);
|
||||
} else {
|
||||
params.error[params.errorcnt] = i;
|
||||
params.errorcnt++;
|
||||
}
|
||||
break;
|
||||
case 9:
|
||||
if (argc > i + 1) {
|
||||
i++;
|
||||
params.savedfile = i;
|
||||
} else {
|
||||
params.error[params.errorcnt] = i;
|
||||
params.errorcnt++;
|
||||
}
|
||||
break;
|
||||
case 10:
|
||||
if ((argc > i + 1) && (IsRealNumber(arg[i + 1]))) {
|
||||
i++;
|
||||
params.sigmoid_slope = atof(arg[i]);
|
||||
} else {
|
||||
params.error[params.errorcnt] = i;
|
||||
params.errorcnt++;
|
||||
}
|
||||
break;
|
||||
case 11:
|
||||
params.online = 1;
|
||||
break;
|
||||
case 12:
|
||||
if ((argc > i + 1) && (IsPosNumber(arg[i + 1]))) {
|
||||
i++;
|
||||
params.maxbufsize = atoi(arg[i]);
|
||||
} else {
|
||||
params.error[params.errorcnt] = i;
|
||||
params.errorcnt++;
|
||||
}
|
||||
break;
|
||||
case 13:
|
||||
if ((argc > i + 1) && (IsPosNumber(arg[i + 1]))) {
|
||||
i++;
|
||||
params.ppid = (char *) malloc(sizeof(char) * (strlen(arg[i]) + 1));
|
||||
strcpy(params.ppid, arg[i]);
|
||||
} else {
|
||||
params.error[params.errorcnt] = i;
|
||||
params.errorcnt++;
|
||||
}
|
||||
break;
|
||||
default:
|
||||
params.error[params.errorcnt] = i;
|
||||
params.errorcnt++;
|
||||
break;
|
||||
}
|
||||
}
|
||||
return params;
|
||||
}
|
||||
|
||||
/* Error Handlers */
|
||||
|
||||
void handler(int num) {
|
||||
fprintf(stderr, "Error: Timeout %i exceeded.\n", params.timeout);
|
||||
exit(-1);
|
||||
}
|
||||
|
||||
void pidhandler(int num) {
|
||||
char *s;
|
||||
if (params.timeout > 0) {
|
||||
params.timeout -= 5;
|
||||
if (params.timeout <= 0) {
|
||||
fprintf(stderr, "Error: Timeout exceeded.\n");
|
||||
exit(-1);
|
||||
}
|
||||
}
|
||||
s = (char *) malloc(sizeof(char) * (19 + strlen(params.ppid)));
|
||||
strcpy(s, "ps "); strcat(s, params.ppid); strcat(s, " >/dev/null");
|
||||
if (system(s) != 0) exit(4);
|
||||
signal(SIGALRM, pidhandler);
|
||||
alarm(5);
|
||||
free(s);
|
||||
}
|
||||
|
||||
void termhandler(int num) {
|
||||
exit(3);
|
||||
}
|
||||
|
||||
/* General Functions */
|
||||
|
||||
double sigmoid(double x, double slope) {
|
||||
return 1 / (1 + exp(-x * slope));
|
||||
}
|
||||
|
||||
/* Debugging traverse function */
|
||||
|
||||
void myexpand(extmanager MyManager, DdNode *Current) {
|
||||
DdNode *h, *l;
|
||||
hisnode *Found;
|
||||
char *curnode;
|
||||
curnode = GetNodeVarNameDisp(MyManager.manager, MyManager.varmap, Current);
|
||||
printf("%s\n", curnode);
|
||||
if ((Current != MyManager.t) && (Current != MyManager.f) &&
|
||||
((Found = GetNode(MyManager.his, MyManager.varmap.varstart, Current)) == NULL)) {
|
||||
l = LowNodeOf(MyManager.manager, Current);
|
||||
h = HighNodeOf(MyManager.manager, Current);
|
||||
printf("l(%s)->", curnode);
|
||||
myexpand(MyManager, l);
|
||||
printf("h(%s)->", curnode);
|
||||
myexpand(MyManager, h);
|
||||
AddNode(MyManager.his, MyManager.varmap.varstart, Current, 0.0, 0, NULL);
|
||||
}
|
||||
}
|
||||
|
||||
/* Angelicas Algorithm */
|
||||
|
||||
double CalcProbability(extmanager MyManager, DdNode *Current) {
|
||||
DdNode *h, *l;
|
||||
hisnode *Found;
|
||||
char *curnode;
|
||||
double lvalue, hvalue, tvalue;
|
||||
if (params.debug) {
|
||||
curnode = GetNodeVarNameDisp(MyManager.manager, MyManager.varmap, Current);
|
||||
fprintf(stderr, "%s\n", curnode);
|
||||
}
|
||||
if (Current == MyManager.t) return 1.0;
|
||||
if (Current == MyManager.f) return 0.0;
|
||||
if ((Found = GetNode(MyManager.his, MyManager.varmap.varstart, Current)) != NULL) return Found->dvalue;
|
||||
l = LowNodeOf(MyManager.manager, Current);
|
||||
h = HighNodeOf(MyManager.manager, Current);
|
||||
if (params.debug) fprintf(stderr, "l(%s)->", curnode);
|
||||
lvalue = CalcProbability(MyManager, l);
|
||||
if (params.debug) fprintf(stderr, "h(%s)->", curnode);
|
||||
hvalue = CalcProbability(MyManager, h);
|
||||
tvalue = MyManager.varmap.dvalue[GetIndex(Current) - MyManager.varmap.varstart];
|
||||
tvalue = tvalue * hvalue + lvalue * (1.0 - tvalue);
|
||||
AddNode(MyManager.his, MyManager.varmap.varstart, Current, tvalue, 0, NULL);
|
||||
return tvalue;
|
||||
}
|
||||
|
||||
/* Bernds Algorithm */
|
||||
|
||||
gradientpair CalcGradient(extmanager MyManager, DdNode *Current, int TargetVar, char *TargetPattern) {
|
||||
DdNode *h, *l;
|
||||
hisnode *Found;
|
||||
char *curnode;
|
||||
gradientpair lvalue, hvalue, tvalue;
|
||||
double this_probability;
|
||||
double *gradient;
|
||||
if (params.debug) {
|
||||
curnode = GetNodeVarNameDisp(MyManager.manager, MyManager.varmap, Current);
|
||||
fprintf(stderr, "%s\n", curnode);
|
||||
}
|
||||
if (Current == MyManager.t) {
|
||||
tvalue.probability = 1.0;
|
||||
tvalue.gradient = 0.0;
|
||||
return tvalue;
|
||||
}
|
||||
if (Current == MyManager.f) {
|
||||
tvalue.probability = 0.0;
|
||||
tvalue.gradient = 0.0;
|
||||
return tvalue;
|
||||
}
|
||||
if ((Found = GetNode(MyManager.his, MyManager.varmap.varstart, Current)) != NULL) {
|
||||
tvalue.probability = Found->dvalue;
|
||||
tvalue.gradient = *((double *) Found->dynvalue);
|
||||
return tvalue;
|
||||
}
|
||||
l = LowNodeOf(MyManager.manager, Current);
|
||||
h = HighNodeOf(MyManager.manager, Current);
|
||||
if (params.debug) fprintf(stderr, "l(%s)->", curnode);
|
||||
lvalue = CalcGradient(MyManager, l, TargetVar, TargetPattern);
|
||||
if (params.debug) fprintf(stderr, "h(%s)->", curnode);
|
||||
hvalue = CalcGradient(MyManager, h, TargetVar, TargetPattern);
|
||||
this_probability = sigmoid(MyManager.varmap.dvalue[GetIndex(Current) - MyManager.varmap.varstart], params.sigmoid_slope);
|
||||
tvalue.probability = this_probability * hvalue.probability + (1 - this_probability) * lvalue.probability;
|
||||
tvalue.gradient = this_probability * hvalue.gradient + (1 - this_probability) * lvalue.gradient;
|
||||
if ((GetIndex(Current) == TargetVar) ||
|
||||
((TargetPattern != NULL) && patternmatch(TargetPattern, MyManager.varmap.vars[GetIndex(Current)]))) {
|
||||
tvalue.gradient += hvalue.probability - lvalue.probability;
|
||||
}
|
||||
gradient = (double *) malloc(sizeof(double));
|
||||
*gradient = tvalue.gradient;
|
||||
AddNode(MyManager.his, MyManager.varmap.varstart, Current, tvalue.probability, 0, gradient);
|
||||
return tvalue;
|
||||
}
|
||||
|
||||
char * extractpattern(char *thestr) {
|
||||
char *p;
|
||||
int i = 0, sl = strlen(thestr);
|
||||
while((thestr[i] != '_') && (i < sl)) i++;
|
||||
if (i == sl) return NULL;
|
||||
i++;
|
||||
p = (char *) malloc(sizeof(char) * (i + 2));
|
||||
strncpy(p, thestr, i);
|
||||
p[i] = '*';
|
||||
p[i + 1] = '\0';
|
||||
return p;
|
||||
}
|
||||
|
||||
int patterncalculated(char *pattern, extmanager MyManager, int loc) {
|
||||
int i;
|
||||
if (pattern == NULL) return 0;
|
||||
for (i = loc - 1; i > -1; i--)
|
||||
if (patternmatch(pattern, MyManager.varmap.vars[i])) return 1;
|
||||
return 0;
|
||||
}
|
@ -1,141 +0,0 @@
|
||||
:-use_module(library(system)).
|
||||
%:-use_module(library(clib)).
|
||||
|
||||
bdd_init(FDO, FDI, PID):-
|
||||
exec('/home/theo/BDDs/SimpleCUDD/Version4/Example -online', [pipe(FDO), pipe(FDI), std], PID).
|
||||
%process_create('/home/theo/BDDs/SimpleCUDD/Version3/Example', ['-online'], [stdin(pipe(FDI)), stdout(pipe(FDO)), process(PID)]).
|
||||
|
||||
bdd_commit(FDO, LINE):-
|
||||
write(FDO, LINE),
|
||||
write(FDO, '\n').
|
||||
|
||||
bdd_kill(FDO, FDI, PID, S):-
|
||||
bdd_commit(FDO, '@e'),
|
||||
wait(PID, S),
|
||||
%process_wait(PID, S),
|
||||
close(FDO),
|
||||
close(FDI).
|
||||
|
||||
bdd_line([], X, _, L):-
|
||||
atomic(X),
|
||||
X \= [],
|
||||
(bdd_curinter(N) ->
|
||||
retract(bdd_curinter(N))
|
||||
;
|
||||
N = 1
|
||||
),
|
||||
M is N + 1,
|
||||
assert(bdd_curinter(M)),
|
||||
atomic_concat(['L', N, '=', X], L).
|
||||
|
||||
bdd_line(L, X, O, NL):-
|
||||
atomic(X),
|
||||
X \= [],
|
||||
atom(L),
|
||||
L \= [],
|
||||
atomic_concat([L, O, X], NL).
|
||||
|
||||
bdd_line(L, [], _, L):-!.
|
||||
|
||||
bdd_line(L, [X|T], O, R):-
|
||||
bdd_line(L, X, O, NL),
|
||||
bdd_line(NL, T, O, R).
|
||||
|
||||
bdd_AND(L, X, NL):-
|
||||
bdd_line(L, X, '*', NL).
|
||||
bdd_OR(L, X, NL):-
|
||||
bdd_line(L, X, '+', NL).
|
||||
bdd_XOR(L, X, NL):-
|
||||
bdd_line(L, X, '#', NL).
|
||||
bdd_NAND(L, X, NL):-
|
||||
bdd_line(L, X, '~*', NL).
|
||||
bdd_NOR(L, X, NL):-
|
||||
bdd_line(L, X, '~+', NL).
|
||||
bdd_XNOR(L, X, NL):-
|
||||
bdd_line(L, X, '~#', NL).
|
||||
|
||||
bdd_not(X, NX):-
|
||||
atomic(X),
|
||||
atomic_concat(['~', X], NX).
|
||||
|
||||
bdd_laststep(L):-
|
||||
bdd_curinter(N),
|
||||
M is N - 1,
|
||||
atomic_concat(['L', M], L),
|
||||
!.
|
||||
|
||||
bdd_nextDFS(FDO):-
|
||||
bdd_commit(FDO, '@n').
|
||||
|
||||
bdd_nextBFS(FDO):-
|
||||
bdd_commit(FDO, '@n,BFS').
|
||||
|
||||
bdd_current(FDO, FDI, N, Qcnt):-
|
||||
bdd_commit(FDO, '@c'),
|
||||
read(FDI, F),
|
||||
assert(F),
|
||||
bdd_temp_value(N, Qcnt),
|
||||
retract(F).
|
||||
|
||||
bdd_highnodeof(FDO, FDI, H):-
|
||||
bdd_commit(FDO, '@h'),
|
||||
read(FDI, F),
|
||||
assert(F),
|
||||
bdd_temp_value(H),
|
||||
retract(F).
|
||||
|
||||
bdd_lownodeof(FDO, FDI, L):-
|
||||
bdd_commit(FDO, '@l'),
|
||||
read(FDI, F),
|
||||
assert(F),
|
||||
bdd_temp_value(L),
|
||||
retract(F).
|
||||
|
||||
bdd_nodevaluesof(FDO, FDI, N, V):-
|
||||
atomic_concat(['@v,', N], Q),
|
||||
bdd_commit(FDO, Q),
|
||||
read(FDI, F),
|
||||
assert(F),
|
||||
bdd_temp_value(V),
|
||||
retract(F).
|
||||
/*
|
||||
bdd_addnodetohis(FDO, N, [D, I, Dyn]):-
|
||||
atomic_concat(['@a,', N, ',', D, ',', I, ',', Dyn], Q),
|
||||
bdd_commit(FDO, Q).
|
||||
|
||||
bdd_getnodefromhis(FDO, FDI, N, V):-
|
||||
atomic_concat(['@g,', N], Q),
|
||||
bdd_commit(FDO, Q),
|
||||
read(FDI, F),
|
||||
assert(F),
|
||||
bdd_temp_value(V),
|
||||
retract(F).
|
||||
*/
|
||||
|
||||
runme:-
|
||||
bdd_init(FDO, FDI, PID),
|
||||
bdd_AND([], ['A', 'B', 'C', 'D', 'E'], L1),
|
||||
bdd_laststep(L1S),
|
||||
bdd_commit(FDO, L1),
|
||||
bdd_AND([], ['A', 'F', 'G', '~B'], L2),
|
||||
bdd_laststep(L2S),
|
||||
bdd_commit(FDO, L2),
|
||||
bdd_AND([], ['A', 'F', 'G', '~C'], L3),
|
||||
bdd_laststep(L3S),
|
||||
bdd_commit(FDO, L3),
|
||||
bdd_OR([], [L1S, L2S, L3S], L4),
|
||||
bdd_laststep(L4S),
|
||||
bdd_commit(FDO, L4),
|
||||
bdd_commit(FDO, L4S),
|
||||
|
||||
repeat,
|
||||
bdd_current(FDO, FDI, N, I),
|
||||
write(1),nl,
|
||||
bdd_nodevaluesof(FDO, FDI, N, V),
|
||||
write(N), write(' ('), write(V), write(')'), nl,
|
||||
bdd_next(FDO),
|
||||
I = 0, (N = 'TRUE' ; N = 'FALSE'),
|
||||
|
||||
bdd_kill(FDO, FDI, PID, S),
|
||||
write('BDD terminated with state: '), write(S), nl.
|
||||
|
@ -3,7 +3,7 @@
|
||||
* SimpleCUDD library (www.cs.kuleuven.be/~theo/tools/simplecudd.html) *
|
||||
* SimpleCUDD was developed at Katholieke Universiteit Leuven(www.kuleuven.be) *
|
||||
* *
|
||||
* Copyright Katholieke Universiteit Leuven 2008 *
|
||||
* Copyright Katholieke Universiteit Leuven 2008, 2009, 2010 *
|
||||
* *
|
||||
* Author: Theofrastos Mantadelis *
|
||||
* File: general.c *
|
||||
|
@ -3,7 +3,7 @@
|
||||
* SimpleCUDD library (www.cs.kuleuven.be/~theo/tools/simplecudd.html) *
|
||||
* SimpleCUDD was developed at Katholieke Universiteit Leuven(www.kuleuven.be) *
|
||||
* *
|
||||
* Copyright Katholieke Universiteit Leuven 2008 *
|
||||
* Copyright Katholieke Universiteit Leuven 2008, 2009, 2010 *
|
||||
* *
|
||||
* Author: Theofrastos Mantadelis *
|
||||
* File: general.h *
|
||||
|
1998
packages/ProbLog/simplecudd/problogbdd.c
Normal file
1998
packages/ProbLog/simplecudd/problogbdd.c
Normal file
File diff suppressed because it is too large
Load Diff
@ -3,10 +3,13 @@
|
||||
* SimpleCUDD library (www.cs.kuleuven.be/~theo/tools/simplecudd.html) *
|
||||
* SimpleCUDD was developed at Katholieke Universiteit Leuven(www.kuleuven.be) *
|
||||
* *
|
||||
* Copyright Katholieke Universiteit Leuven 2008 *
|
||||
* Copyright Katholieke Universiteit Leuven 2008, 2009, 2010 *
|
||||
* *
|
||||
* Author: Bernd Gutmann *
|
||||
* File: problogmath.c *
|
||||
* $Date:: 2010-08-25 15:23:30 +0200 (Wed, 25 Aug 2010) $ *
|
||||
* $Revision:: 4683 $ *
|
||||
* *
|
||||
* Author: Theofrastos Mantadelis *
|
||||
* File: Example.c *
|
||||
* *
|
||||
********************************************************************************
|
||||
* *
|
||||
@ -184,141 +187,168 @@
|
||||
* *
|
||||
\******************************************************************************/
|
||||
|
||||
#include "problogmath.h"
|
||||
|
||||
#include "simplecudd.h"
|
||||
|
||||
typedef struct _extmanager {
|
||||
DdManager *manager;
|
||||
DdNode *t, *f;
|
||||
hisqueue *his;
|
||||
namedvars varmap;
|
||||
} extmanager;
|
||||
double sigmoid(double x, double slope) {
|
||||
return 1.0 / (1.0 + exp(-x * slope));
|
||||
}
|
||||
|
||||
void DFS(extmanager MyManager, DdNode *Current);
|
||||
int compexpand(extmanager MyManager, DdNode *Current, extmanager MyManager2, DdNode *Current2);
|
||||
int bufstrcat(char *targetstr, int targetmem, const char *srcstr);
|
||||
void getalltruepaths(extmanager MyManager, DdNode *Current, const char *startpath, const char *prevvar);
|
||||
// This function calculates the accumulated density of the normal distribution
|
||||
// For details see G. Marsaglia, Evaluating the Normal Distribution, Journal of Statistical Software, 2004:11(4).
|
||||
double Phi(double x) {
|
||||
double s=x;
|
||||
double t=0.0;
|
||||
double b=x;
|
||||
double q=x*x;
|
||||
double i=1;
|
||||
|
||||
int main(int argc, char **arg) {
|
||||
extmanager MyManager;
|
||||
DdNode *bdd;
|
||||
bddfileheader fileheader;
|
||||
int code;
|
||||
char yn;
|
||||
code = -1;
|
||||
if (argc != 2) {
|
||||
fprintf(stderr, "\nUsage: %s [filename]\nGenerates and traverses a BDD from file\n", arg[0]);
|
||||
fprintf(stderr, "\nUsage: %s -online\nGenerates and traverses a BDD online mode\n", arg[0]);
|
||||
return code;
|
||||
// if the value is too small or too big, return
|
||||
// 0/1 to avoid long computations
|
||||
if (x < -10.0) {
|
||||
return 0.0;
|
||||
}
|
||||
RAPIDLOADON;
|
||||
if (strcmp("-online", arg[1]) == 0) {
|
||||
MyManager.manager = simpleBDDinit(0);
|
||||
MyManager.t = HIGH(MyManager.manager);
|
||||
MyManager.f = LOW(MyManager.manager);
|
||||
MyManager.varmap = InitNamedVars(1, 0);
|
||||
bdd = OnlineGenerateBDD(MyManager.manager, &MyManager.varmap);
|
||||
|
||||
if (x > 10.0) {
|
||||
return 1.0;
|
||||
}
|
||||
|
||||
// t is the value from last iteration
|
||||
// s is the value from the current iteration
|
||||
// iterate until they are equal
|
||||
while(fabs(s-t) >= DBL_MIN) {
|
||||
t=s;
|
||||
i+=2;
|
||||
b*=q/i;
|
||||
s+=b;
|
||||
}
|
||||
|
||||
return 0.5+s*exp(-0.5*q-0.91893853320467274178);
|
||||
}
|
||||
|
||||
// integrates the normal distribution over [low,high]
|
||||
double cumulative_normal(double low, double high, double mu, double sigma) {
|
||||
return Phi((high-mu)/sigma) - Phi((low-mu)/sigma);
|
||||
}
|
||||
|
||||
// integrates the normal distribution over [-oo,high]
|
||||
double cumulative_normal_upper(double high, double mu, double sigma) {
|
||||
return Phi((high-mu)/sigma);
|
||||
}
|
||||
|
||||
|
||||
// evaluates the density of the normal distribution
|
||||
double normal(double x, double mu,double sigma) {
|
||||
double inner=(x-mu)/sigma;
|
||||
double denom=sigma*sqrt(2*3.14159265358979323846);
|
||||
return exp(-inner*inner/2)/denom;
|
||||
}
|
||||
|
||||
double cumulative_normal_dmu(double low, double high,double mu,double sigma) {
|
||||
return normal(low,mu,sigma) - normal(high,mu,sigma);
|
||||
}
|
||||
|
||||
double cumulative_normal_upper_dmu(double high,double mu,double sigma) {
|
||||
return - normal(high,mu,sigma);
|
||||
}
|
||||
|
||||
|
||||
double cumulative_normal_dsigma(double low, double high,double mu,double sigma) {
|
||||
return (((mu-high)*normal(high,mu,sigma) - (mu-low)*normal(low,mu,sigma))/sigma);
|
||||
}
|
||||
|
||||
double cumulative_normal_upper_dsigma(double high,double mu,double sigma) {
|
||||
return (mu-high)*normal(high,mu,sigma);
|
||||
}
|
||||
|
||||
|
||||
// this function parses two strings "$a;$b" and "???_???l$ch$d" where $a-$d are (real) numbers
|
||||
// it is used to parse in the parameters of continues variables from the input file
|
||||
density_integral parse_density_integral_string(char *input, char *variablename) {
|
||||
density_integral result;
|
||||
int i;
|
||||
char garbage[64], s1[64],s2[64],s3[64],s4[64];
|
||||
|
||||
if(sscanf(input, "%64[^;];%64[^;]", s1,s2) != 2) {
|
||||
fprintf(stderr, "Error at parsing the string %s in the function parse_density_integral_string\n",input);
|
||||
fprintf(stderr, "The string should contain 2 fields seperated by ; characters.\n");
|
||||
exit(EXIT_FAILURE);
|
||||
}
|
||||
|
||||
if (IsRealNumber(s1)) {
|
||||
result.mu=atof(s1);
|
||||
} else {
|
||||
fileheader = ReadFileHeader(arg[1]);
|
||||
switch(fileheader.filetype) {
|
||||
case BDDFILE_SCRIPT:
|
||||
MyManager.manager = simpleBDDinit(fileheader.varcnt);
|
||||
MyManager.t = HIGH(MyManager.manager);
|
||||
MyManager.f = LOW(MyManager.manager);
|
||||
MyManager.varmap = InitNamedVars(fileheader.varcnt, fileheader.varstart);
|
||||
bdd = FileGenerateBDD(MyManager.manager, MyManager.varmap, fileheader);
|
||||
break;
|
||||
case BDDFILE_NODEDUMP:
|
||||
MyManager.manager = simpleBDDinit(fileheader.varcnt);
|
||||
MyManager.t = HIGH(MyManager.manager);
|
||||
MyManager.f = LOW(MyManager.manager);
|
||||
MyManager.varmap = InitNamedVars(fileheader.varcnt, fileheader.varstart);
|
||||
bdd = LoadNodeDump(MyManager.manager, MyManager.varmap, fileheader.inputfile);
|
||||
break;
|
||||
default:
|
||||
fprintf(stderr, "Error: not a valid file format to load.\n");
|
||||
return code;
|
||||
break;
|
||||
}
|
||||
}
|
||||
if (bdd != NULL) {
|
||||
printf("Do you want to load parameter values from testdata.txt [y]? "); yn = getchar(); getchar();
|
||||
if (yn == 'y') LoadVariableData(MyManager.varmap, "testdata.txt");
|
||||
code = 0;
|
||||
MyManager.his = InitHistory(GetVarCount(MyManager.manager));
|
||||
if (strcmp("-online", arg[1]) != 0) {
|
||||
DFS(MyManager, bdd);
|
||||
printf("Do you need an export [y]? "); yn = getchar(); getchar();
|
||||
if (yn == 'y') simpleNamedBDDtoDot(MyManager.manager, MyManager.varmap, bdd, "SimpleCUDDExport.dot");
|
||||
printf("Do you want a save [y]? "); yn = getchar(); getchar();
|
||||
if (yn == 'y') SaveNodeDump(MyManager.manager, MyManager.varmap, bdd, "SimpleCUDDSave.sav");
|
||||
printf("Do you want to see all true paths [y]? "); yn = getchar(); getchar();
|
||||
if (yn == 'y') {
|
||||
ReInitHistory(MyManager.his, GetVarCount(MyManager.manager));
|
||||
getalltruepaths(MyManager, bdd, "", "");
|
||||
fprintf(stderr, "Error at parsing the string %s in the function parse_density_integral_string\n",input);
|
||||
fprintf(stderr, "%s is not a number\n",s1);
|
||||
exit(EXIT_FAILURE);
|
||||
}
|
||||
|
||||
if (IsRealNumber(s2)) {
|
||||
result.log_sigma=atof(s2);
|
||||
} else {
|
||||
onlinetraverse(MyManager.manager, MyManager.varmap, MyManager.his, bdd);
|
||||
fprintf(stderr, "Error at parsing the string %s in the function parse_density_integral_string\n",input);
|
||||
fprintf(stderr, "%s is not a number\n",s2);
|
||||
exit(EXIT_FAILURE);
|
||||
}
|
||||
}
|
||||
if (MyManager.manager != NULL) KillBDD(MyManager.manager);
|
||||
return code;
|
||||
}
|
||||
|
||||
void DFS(extmanager MyManager, DdNode *Current) {
|
||||
DdNode *h, *l;
|
||||
hisnode *Found;
|
||||
char *curnode;
|
||||
curnode = GetNodeVarNameDisp(MyManager.manager, MyManager.varmap, Current);
|
||||
if (GetIndex(Current) < MyManager.varmap.varcnt) {
|
||||
printf("%s(%f,%i,%s)\n", curnode, MyManager.varmap.dvalue[GetIndex(Current)], MyManager.varmap.ivalue[GetIndex(Current)], (char *) MyManager.varmap.dynvalue[GetIndex(Current)]);
|
||||
/* if (result.sigma<=0) { */
|
||||
/* fprintf(stderr, "Error at parsing the string %s in the function parse_density_integral_string",input); */
|
||||
/* fprintf(stderr, "The value for sigma has to be larger than 0.\n"); */
|
||||
|
||||
/* exit(EXIT_FAILURE); */
|
||||
/* } */
|
||||
|
||||
if (sscanf(variablename,"%64[^lh]l%64[^lh]h%64[^lh]",garbage,s3,s4) != 3) {
|
||||
fprintf(stderr, "Error at parsing the string %s in the function parse_density_integral_string\n",variablename);
|
||||
fprintf(stderr, "The string should contain 2 fields seperated by ; characters.\n");
|
||||
exit(EXIT_FAILURE);
|
||||
}
|
||||
|
||||
// replace the d by . in s1 and s2
|
||||
for(i=0; s3[i]!='\0' ; i++) {
|
||||
if (s3[i]=='d') {
|
||||
s3[i]='.';
|
||||
}
|
||||
if (s3[i]=='m') {
|
||||
s3[i]='-';
|
||||
}
|
||||
}
|
||||
for(i=0; s4[i]!='\0' ; i++) {
|
||||
if (s4[i]=='d') {
|
||||
s4[i]='.';
|
||||
}
|
||||
if (s4[i]=='m') {
|
||||
s4[i]='-';
|
||||
}
|
||||
}
|
||||
|
||||
if (IsRealNumber(s3)) {
|
||||
result.low=atof(s3);
|
||||
} else {
|
||||
printf("%s\n", curnode);
|
||||
fprintf(stderr, "Error at parsing the string %s in the function parse_density_integral_string\n",input);
|
||||
fprintf(stderr, "%s is not a number\n",s1);
|
||||
exit(EXIT_FAILURE);
|
||||
}
|
||||
if ((Current != MyManager.t) && (Current != MyManager.f) &&
|
||||
((Found = GetNode(MyManager.his, MyManager.varmap.varstart, Current)) == NULL)) {
|
||||
l = LowNodeOf(MyManager.manager, Current);
|
||||
h = HighNodeOf(MyManager.manager, Current);
|
||||
printf("l(%s)->", curnode);
|
||||
DFS(MyManager, l);
|
||||
printf("h(%s)->", curnode);
|
||||
DFS(MyManager, h);
|
||||
AddNode(MyManager.his, MyManager.varmap.varstart, Current, 0.0, 0, NULL);
|
||||
}
|
||||
}
|
||||
|
||||
void getalltruepaths(extmanager MyManager, DdNode *Current, const char *startpath, const char *prevvar) {
|
||||
DdNode *h, *l;
|
||||
char *curnode, *curpath;
|
||||
int pathmaxsize = 1024;
|
||||
curpath = (char *) malloc(sizeof(char) * pathmaxsize);
|
||||
curpath[0] = '\0';
|
||||
pathmaxsize = bufstrcat(curpath, pathmaxsize, startpath);
|
||||
pathmaxsize = bufstrcat(curpath, pathmaxsize, prevvar);
|
||||
pathmaxsize = bufstrcat(curpath, pathmaxsize, "*");
|
||||
curnode = GetNodeVarNameDisp(MyManager.manager, MyManager.varmap, Current);
|
||||
if (Current == MyManager.t) {
|
||||
printf("%s\n", curpath);
|
||||
} else if (Current != MyManager.f) {
|
||||
h = HighNodeOf(MyManager.manager, Current);
|
||||
if (h != MyManager.f) {
|
||||
getalltruepaths(MyManager, h, curpath, curnode);
|
||||
if (IsRealNumber(s4)) {
|
||||
result.high=atof(s4);
|
||||
} else {
|
||||
fprintf(stderr, "Error ar parsing the string %s in the function parse_density_integral_string\n",input);
|
||||
fprintf(stderr, "%s is not a number\n",s1);
|
||||
exit(EXIT_FAILURE);
|
||||
}
|
||||
l = LowNodeOf(MyManager.manager, Current);
|
||||
if (l != MyManager.f) {
|
||||
pathmaxsize = bufstrcat(curpath, pathmaxsize, "~");
|
||||
getalltruepaths(MyManager, l, curpath, curnode);
|
||||
}
|
||||
}
|
||||
free(curpath);
|
||||
}
|
||||
|
||||
int bufstrcat(char *targetstr, int targetmem, const char *srcstr) {
|
||||
int strinc = strlen(srcstr), strsize = strlen(targetstr);
|
||||
while ((strsize + strinc) > (targetmem - 1)) {
|
||||
targetmem *= 2;
|
||||
targetstr = (char *) realloc(targetstr, sizeof(char) * targetmem);
|
||||
|
||||
if (result.low>result.high) {
|
||||
fprintf(stderr, "Error ar parsing the string %s in the function parse_density_integral_string\n",input);
|
||||
fprintf(stderr, "The value for low has to be larger than then value for high.\n");
|
||||
fprintf(stderr, " was [%f, %f]\n",result.low, result.high);
|
||||
fprintf(stderr, " input %s \n",input);
|
||||
fprintf(stderr, " variablename %s \n",variablename);
|
||||
|
||||
exit(EXIT_FAILURE);
|
||||
}
|
||||
strcat(targetstr, srcstr);
|
||||
return targetmem;
|
||||
|
||||
|
||||
return result;
|
||||
}
|
216
packages/ProbLog/simplecudd/problogmath.h
Normal file
216
packages/ProbLog/simplecudd/problogmath.h
Normal file
@ -0,0 +1,216 @@
|
||||
/******************************************************************************\
|
||||
* *
|
||||
* SimpleCUDD library (www.cs.kuleuven.be/~theo/tools/simplecudd.html) *
|
||||
* SimpleCUDD was developed at Katholieke Universiteit Leuven(www.kuleuven.be) *
|
||||
* *
|
||||
* Copyright Katholieke Universiteit Leuven 2008, 2009, 2010 *
|
||||
* *
|
||||
* Author: Bernd Gutmann *
|
||||
* File: problogmath.h *
|
||||
* $Date:: 2010-08-25 15:23:30 +0200 (Wed, 25 Aug 2010) $ *
|
||||
* $Revision:: 4683 $ *
|
||||
* *
|
||||
* *
|
||||
********************************************************************************
|
||||
* *
|
||||
* 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. *
|
||||
* *
|
||||
* The End *
|
||||
* *
|
||||
\******************************************************************************/
|
||||
|
||||
#include <math.h>
|
||||
#include <float.h>
|
||||
#include <stdio.h>
|
||||
#include <stdlib.h>
|
||||
#include <string.h>
|
||||
|
||||
typedef struct _density_integral {
|
||||
double low;
|
||||
double high;
|
||||
double mu;
|
||||
double log_sigma;
|
||||
} density_integral;
|
||||
|
||||
|
||||
|
||||
double sigmoid(double x, double slope);
|
||||
double Phi(double x);
|
||||
|
||||
double cumulative_normal(double low, double high, double sigma, double mu);
|
||||
double cumulative_normal_dmu(double low, double high,double mu,double sigma);
|
||||
double cumulative_normal_dsigma(double low, double high,double mu,double sigma);
|
||||
|
||||
double cumulative_normal_upper(double high, double mu, double sigma);
|
||||
double cumulative_normal_upper_dsigma(double high,double mu,double sigma);
|
||||
double cumulative_normal_upper_dmu(double high,double mu,double sigma);
|
||||
|
||||
density_integral parse_density_integral_string(char *input, char *variablename);
|
@ -3,7 +3,7 @@
|
||||
* SimpleCUDD library (www.cs.kuleuven.be/~theo/tools/simplecudd.html) *
|
||||
* SimpleCUDD was developed at Katholieke Universiteit Leuven(www.kuleuven.be) *
|
||||
* *
|
||||
* Copyright Katholieke Universiteit Leuven 2008 *
|
||||
* Copyright Katholieke Universiteit Leuven 2008, 2009, 2010 *
|
||||
* *
|
||||
* Author: Theofrastos Mantadelis *
|
||||
* File: simplecudd.c *
|
||||
@ -203,6 +203,16 @@ DdManager* simpleBDDinit(int varcnt) {
|
||||
return temp;
|
||||
}
|
||||
|
||||
DdManager* simpleBDDinitNoReOrder(int varcnt) {
|
||||
DdManager *temp;
|
||||
temp = Cudd_Init(varcnt, 0, CUDD_UNIQUE_SLOTS, CUDD_CACHE_SLOTS, 0);
|
||||
Cudd_AutodynDisable(temp);// Cudd_AutodynEnable(temp, CUDD_REORDER_NONE);
|
||||
Cudd_SetMaxCacheHard(temp, 1024*1024*1024);
|
||||
Cudd_SetLooseUpTo(temp, 1024*1024*512);
|
||||
if (_debug) Cudd_EnableReorderingReporting(temp);
|
||||
return temp;
|
||||
}
|
||||
|
||||
/* BDD tree travesrsing */
|
||||
|
||||
DdNode* HighNodeOf(DdManager *manager, DdNode *node) {
|
||||
@ -305,6 +315,7 @@ bddfileheader ReadFileHeader(char *filename) {
|
||||
case BDDFILE_SCRIPT:
|
||||
switch (temp.version) {
|
||||
case 1:
|
||||
case 2:
|
||||
fscanf(temp.inputfile, "%i\n", &temp.varcnt);
|
||||
fscanf(temp.inputfile, "%i\n", &temp.varstart);
|
||||
fscanf(temp.inputfile, "%i\n", &temp.intercnt);
|
||||
@ -583,6 +594,50 @@ void ExpandNodes(hisqueue *Nodes, int index, int nodenum) {
|
||||
Nodes[index].cnt = nodenum + 1;
|
||||
}
|
||||
|
||||
char** GetVariableOrder(char *filename, int varcnt) {
|
||||
FILE *data;
|
||||
char *dataread, buf, **varname;
|
||||
int icur = 0, maxbufsize = 10, index = -1;
|
||||
if ((data = fopen(filename, "r")) == NULL) {
|
||||
perror(filename);
|
||||
return NULL;
|
||||
}
|
||||
varname = (char **) malloc(sizeof(char *) * varcnt);
|
||||
dataread = (char *) malloc(sizeof(char) * maxbufsize);
|
||||
while(!feof(data)) {
|
||||
fread(&buf, 1, 1, data);
|
||||
if (buf == '\n') {
|
||||
dataread[icur] = '\0';
|
||||
icur = 0;
|
||||
buf = ' ';
|
||||
if (dataread[0] == '@') {
|
||||
index++;
|
||||
varname[index] = (char *) malloc(sizeof(char) * strlen(dataread));
|
||||
strcpy(varname[index], dataread + 1);
|
||||
}
|
||||
} else {
|
||||
dataread[icur] = buf;
|
||||
icur++;
|
||||
if (icur == _maxbufsize) {
|
||||
fprintf(stderr, "Error: Maximum buffer size(%i) exceeded.\n", _maxbufsize);
|
||||
fclose(data);
|
||||
free(varname);
|
||||
free(dataread);
|
||||
return NULL;
|
||||
}
|
||||
while (icur > maxbufsize - 1) {
|
||||
maxbufsize *= 2;
|
||||
dataread = (char *) realloc(dataread, sizeof(char) * maxbufsize);
|
||||
}
|
||||
}
|
||||
}
|
||||
fclose(data);
|
||||
free(dataread);
|
||||
for(icur=index+1; icur < varcnt; icur++)
|
||||
varname[icur] = NULL;
|
||||
return varname;
|
||||
}
|
||||
|
||||
int LoadVariableData(namedvars varmap, char *filename) {
|
||||
FILE *data;
|
||||
char *dataread, buf, *varname, *dynvalue;
|
||||
@ -596,14 +651,16 @@ int LoadVariableData(namedvars varmap, char *filename) {
|
||||
dataread = (char *) malloc(sizeof(char) * maxbufsize);
|
||||
while(!feof(data)) {
|
||||
fread(&buf, 1, 1, data);
|
||||
if (buf == '\n') {
|
||||
if ((buf == '\n') && icur == 0) {
|
||||
// ignore empty lines
|
||||
} else if (buf == '\n') {
|
||||
dataread[icur] = '\0';
|
||||
icur = 0;
|
||||
buf = ' ';
|
||||
if (dataread[0] == '@') {
|
||||
if (hasvar) {
|
||||
for (index = 0; index < varmap.varcnt; index++) {
|
||||
if (patternmatch(varname, varmap.vars[index])) {
|
||||
if ((varmap.vars[index] != NULL) && (patternmatch(varname, varmap.vars[index]))) {
|
||||
varmap.loaded[index] = 1;
|
||||
varmap.dvalue[index] = dvalue;
|
||||
varmap.ivalue[index] = ivalue;
|
||||
@ -679,7 +736,7 @@ int LoadVariableData(namedvars varmap, char *filename) {
|
||||
}
|
||||
if (hasvar) {
|
||||
for (index = 0; index < varmap.varcnt; index++) {
|
||||
if (patternmatch(varname, varmap.vars[index])) {
|
||||
if ((varmap.vars[index] != NULL) && (patternmatch(varname, varmap.vars[index]))) {
|
||||
varmap.loaded[index] = 1;
|
||||
varmap.dvalue[index] = dvalue;
|
||||
varmap.ivalue[index] = ivalue;
|
||||
@ -879,12 +936,56 @@ int all_loaded(namedvars varmap, int disp) {
|
||||
return res;
|
||||
}
|
||||
|
||||
int ImposeOrder(DdManager *manager, const namedvars varmap, char **map) {
|
||||
int order[varmap.varcnt], i, mappos, index = -1, ivar;
|
||||
for (i = 0; i < varmap.varcnt; i++) {
|
||||
if (map[i] != NULL) {
|
||||
order[i] = GetNamedVarIndex(varmap, map[i]);
|
||||
index = i;
|
||||
} else {
|
||||
order[i] = -1;
|
||||
}
|
||||
}
|
||||
index++;
|
||||
for (i = 0; i < varmap.varcnt; i++) {
|
||||
ivar = Cudd_ReadPerm(manager, i);
|
||||
mappos = get_var_pos_in_map(map, varmap.vars[ivar], varmap.varcnt);
|
||||
if (mappos == -1) {
|
||||
order[index] = ivar;
|
||||
index++;
|
||||
}
|
||||
}
|
||||
if (index != varmap.varcnt)
|
||||
fprintf(stderr, "Warning possible error in: Impose Order...\n");
|
||||
return Cudd_ShuffleHeap(manager, order);
|
||||
}
|
||||
|
||||
int get_var_pos_in_map(char **map, const char *var, int varcnt) {
|
||||
int i;
|
||||
for (i = 0; i < varcnt; i++) {
|
||||
if (map[i] == NULL) return -1;
|
||||
if (strcmp(map[i], var) == 0) return i;
|
||||
}
|
||||
return -1;
|
||||
}
|
||||
|
||||
/* Parser */
|
||||
|
||||
DdNode* FileGenerateBDD(DdManager *manager, namedvars varmap, bddfileheader fileheader) {
|
||||
return (FileGenerateBDDForest(manager, varmap, fileheader))[0];
|
||||
}
|
||||
|
||||
void unreference(DdManager *manager, DdNode ** intermediates, int count){
|
||||
// int i;
|
||||
// for(i = 0;i<count;i++){
|
||||
// if(intermediates[i] != NULL) Cudd_RecursiveDeref(manager,intermediates[i]);
|
||||
// }
|
||||
}
|
||||
|
||||
DdNode** FileGenerateBDDForest(DdManager *manager, namedvars varmap, bddfileheader fileheader) {
|
||||
int icomment, maxlinesize, icur, iline, curinter, iequal;
|
||||
DdNode *Line, **inter;
|
||||
char buf, *inputline, *filename;
|
||||
DdNode *Line, **inter, **result;
|
||||
char buf, *inputline, *filename, *subl;
|
||||
bddfileheader interfileheader;
|
||||
// Initialization of intermediate steps
|
||||
inter = (DdNode **) malloc(sizeof(DdNode *) * fileheader.intercnt);
|
||||
@ -921,15 +1022,19 @@ DdNode* FileGenerateBDD(DdManager *manager, namedvars varmap, bddfileheader file
|
||||
}
|
||||
curinter = getInterBDD(inputline);
|
||||
if (curinter == -1) {
|
||||
if (fileheader.version < 2) {
|
||||
if (inputline[0] == 'L' && IsPosNumber(inputline + 1)) {
|
||||
curinter = atoi(inputline + 1) - 1;
|
||||
if (curinter > -1 && curinter < fileheader.intercnt && inter[curinter] != NULL) {
|
||||
if (_debug) fprintf(stderr, "Returned: %s\n", inputline);
|
||||
fclose(fileheader.inputfile);
|
||||
Line = inter[curinter];
|
||||
result = (DdNode **) malloc(sizeof(DdNode *) * 1);
|
||||
result[0] = inter[curinter];
|
||||
Cudd_Ref(result[0]);
|
||||
unreference(manager, inter, fileheader.intercnt);
|
||||
free(inter);
|
||||
free(inputline);
|
||||
return Line;
|
||||
return result;
|
||||
} else {
|
||||
fprintf(stderr, "Error at line: %i. Return result asked doesn't exist.\n", iline);
|
||||
fclose(fileheader.inputfile);
|
||||
@ -944,6 +1049,49 @@ DdNode* FileGenerateBDD(DdManager *manager, namedvars varmap, bddfileheader file
|
||||
free(inputline);
|
||||
return NULL;
|
||||
}
|
||||
} else {
|
||||
// Support for forest
|
||||
result = (DdNode **) malloc(sizeof(DdNode *) * 10);
|
||||
maxlinesize = 10;
|
||||
iline = -1;
|
||||
for (subl = strtok(inputline, ","); subl != NULL; subl = strtok(NULL, ",")) {
|
||||
if (subl[0] == 'L' && IsPosNumber(subl + 1)) {
|
||||
curinter = atoi(subl + 1) - 1;
|
||||
if (curinter > -1 && curinter < fileheader.intercnt && inter[curinter] != NULL) {
|
||||
iline++;
|
||||
if (iline >= (maxlinesize - 1)) {
|
||||
maxlinesize *= 2;
|
||||
result = (DdNode **) realloc(result, sizeof(DdNode *) * maxlinesize);
|
||||
}
|
||||
Cudd_Ref(inter[curinter]);
|
||||
result[iline] = inter[curinter];
|
||||
} else {
|
||||
fprintf(stderr, "Error at line: %i. Return result asked(%s) doesn't exist.\n", iline, subl);
|
||||
fclose(fileheader.inputfile);
|
||||
free(inter);
|
||||
free(inputline);
|
||||
free(subl);
|
||||
return NULL;
|
||||
}
|
||||
} else {
|
||||
fprintf(stderr, "Error at line: %i. Invalid intermediate result format.\n", iline);
|
||||
fclose(fileheader.inputfile);
|
||||
free(inter);
|
||||
free(inputline);
|
||||
free(subl);
|
||||
return NULL;
|
||||
}
|
||||
}
|
||||
if (_debug) fprintf(stderr, "Returned: %s\n", inputline);
|
||||
fclose(fileheader.inputfile);
|
||||
unreference(manager, inter, fileheader.intercnt);
|
||||
free(inter);
|
||||
free(inputline);
|
||||
free(subl);
|
||||
iline++;
|
||||
result[iline] = NULL;
|
||||
return result;
|
||||
}
|
||||
} else if (curinter > -1 && curinter < fileheader.intercnt && inter[curinter] == NULL) {
|
||||
if (_debug) fprintf(stderr, "%i %s\n", curinter, inputline);
|
||||
filename = getFileName(inputline);
|
||||
@ -1050,7 +1198,7 @@ DdNode* LineParser(DdManager *manager, namedvars varmap, DdNode **inter, int max
|
||||
int istart, iend, ilength, i, symbol, ivar, inegvar, inegoper, iconst;
|
||||
long startAt, endAt;
|
||||
double secs;
|
||||
DdNode *bdd;
|
||||
DdNode *bdd, *temp;
|
||||
char *term, curoper;
|
||||
bdd = HIGH(manager);
|
||||
Cudd_Ref(bdd);
|
||||
@ -1092,6 +1240,10 @@ DdNode* LineParser(DdManager *manager, namedvars varmap, DdNode **inter, int max
|
||||
} else {
|
||||
iconst = 0;
|
||||
ivar = AddNamedVar(varmap, term + inegvar);
|
||||
/* if (ivar == -1) {
|
||||
EnlargeNamedVars(&varmap, varmap.varcnt + 1);
|
||||
ivar = AddNamedVar(varmap, term + inegvar);
|
||||
}*/
|
||||
if (ivar == -1) {
|
||||
fprintf(stderr, "Line Parser Error at line: %i. More BDD variables than the reserved term: %s.\n", iline, term);
|
||||
free(term);
|
||||
|
@ -3,7 +3,7 @@
|
||||
* SimpleCUDD library (www.cs.kuleuven.be/~theo/tools/simplecudd.html) *
|
||||
* SimpleCUDD was developed at Katholieke Universiteit Leuven(www.kuleuven.be) *
|
||||
* *
|
||||
* Copyright Katholieke Universiteit Leuven 2008 *
|
||||
* Copyright Katholieke Universiteit Leuven 2008, 2009, 2010 *
|
||||
* *
|
||||
* Author: Theofrastos Mantadelis *
|
||||
* File: simplecudd.h *
|
||||
@ -263,6 +263,7 @@ typedef struct _nodeline {
|
||||
/* Initialization */
|
||||
|
||||
DdManager* simpleBDDinit(int varcnt);
|
||||
DdManager* simpleBDDinitNoReOrder(int varcnt);
|
||||
|
||||
/* BDD Generation */
|
||||
|
||||
@ -274,6 +275,7 @@ DdNode* D_BDDXor(DdManager *manager, DdNode *bdd1, DdNode *bdd2);
|
||||
DdNode* D_BDDXnor(DdManager *manager, DdNode *bdd1, DdNode *bdd2);
|
||||
|
||||
DdNode* FileGenerateBDD(DdManager *manager, namedvars varmap, bddfileheader fileheader);
|
||||
DdNode** FileGenerateBDDForest(DdManager *manager, namedvars varmap, bddfileheader fileheader);
|
||||
DdNode* OnlineGenerateBDD(DdManager *manager, namedvars *varmap);
|
||||
DdNode* LineParser(DdManager *manager, namedvars varmap, DdNode **inter, int maxinter, char *function, int iline);
|
||||
DdNode* OnlineLineParser(DdManager *manager, namedvars *varmap, DdNode **inter, int maxinter, char *function, int iline);
|
||||
@ -281,10 +283,13 @@ DdNode* BDD_Operator(DdManager *manager, DdNode *bdd1, DdNode *bdd2, char Operat
|
||||
int getInterBDD(char *function);
|
||||
char* getFileName(const char *function);
|
||||
int GetParam(char *inputline, int iParam);
|
||||
char** GetVariableOrder(char *filename, int varcnt);
|
||||
int LoadVariableData(namedvars varmap, char *filename);
|
||||
|
||||
/* Named variables */
|
||||
|
||||
int ImposeOrder(DdManager *manager, const namedvars varmap, char **map);
|
||||
int get_var_pos_in_map(char **map, const char *var, int varcnt);
|
||||
namedvars InitNamedVars(int varcnt, int varstart);
|
||||
void EnlargeNamedVars(namedvars *varmap, int newvarcnt);
|
||||
int AddNamedVarAt(namedvars varmap, const char *varname, int index);
|
||||
|
Reference in New Issue
Block a user