bdd stuff
This commit is contained in:
parent
26b3cb5bb7
commit
252a2b7868
@ -72,7 +72,7 @@
|
||||
|
||||
:- use_module( library(bdd) ).
|
||||
|
||||
:- dynamic extension/4, init/2, frame/2.
|
||||
:- dynamic extension/4, init/2, frame/2, exclusive/0.
|
||||
|
||||
user:term_expansion(Term,Clauses) :-
|
||||
Term = ( Spec :- Body),
|
||||
@ -92,49 +92,65 @@ find_name( [_|UnsortedCurrentNames] , V, Name) :-
|
||||
expand( Skel, Names, GoalVars, Body, Tests, Out) :-
|
||||
Skel =.. [N|As], %
|
||||
%pick(Vs, As, Os),
|
||||
trace,
|
||||
append(As, GoalVars, Os),
|
||||
Head =.. [N|Os],
|
||||
maplist(original_name(GoalVars), Names, Ts),
|
||||
LinkGoal =.. [access|Ts],
|
||||
trace,
|
||||
formula( Tests, Fs, Dic),
|
||||
bdd_new(Fs , BDD),
|
||||
bdd_print( BDD, '/Users/vsc/bdd.dot', Names), bdd_tree(BDD, Tree),
|
||||
ptree(Tree, Names, Dic),
|
||||
rb_visit(Dic, Map),
|
||||
maplist( swap_f, Map, VNames),
|
||||
% bdd_reorder(BDD, exact);
|
||||
File = '/home/vsc/bdd0.dot',
|
||||
bdd_print( BDD, File, VNames),
|
||||
bdd_tree(BDD, Tree),
|
||||
ptree(Tree, Names, '/home/vsc/bdd.dot', Dic),
|
||||
% portray_clause((Head:-GExtBody)),
|
||||
unnumbervars((Head:- LinkGoal,Body), Out).
|
||||
|
||||
ptree( bdd(_,L,_Vs) , Names, Dic) :-
|
||||
swap_f(Key-V, Key=V).
|
||||
|
||||
ptree( bdd(Root,L,_Vs) , Names, File, Dic) :-
|
||||
% term_variables(L, LVs),
|
||||
% Vs =.. [_|LVs],
|
||||
% trace,
|
||||
maplist( bindv,Names),
|
||||
rb_visit(Dic, Pairs),
|
||||
maplist( bindv,Pairs),
|
||||
open('bdd.dot', write, S) ,
|
||||
absolute_file_name( File, [], AbsFile ),
|
||||
open(AbsFile, write, S) ,
|
||||
format(S,'digraph "DD" {
|
||||
size = "7.5,10"
|
||||
center = true;~n', []),
|
||||
format(S,' "~w" [label = "~w"];~n', [1, Root]),
|
||||
maplist( print_node(S), L),
|
||||
format(S, '}~n', []),
|
||||
close(S),
|
||||
fail.
|
||||
ptree(_, _, _).
|
||||
|
||||
bindv( X = '$VAR'(X) ).
|
||||
bindv( X - '$VAR'(X) ).
|
||||
bindv( X = '$VAR'(X) ) :- !.
|
||||
bindv( X - '$VAR'(X) ) :- !.
|
||||
bindv(_).
|
||||
|
||||
print_node(S,pp( Val, Name, Left, Right )) :-
|
||||
%writeln(Name),
|
||||
simplify(Name, N),
|
||||
format(S,' "~w" [label = "~w"];~n', [Val, N]),
|
||||
format(S,' "~w" -> "~w";~n', [Val, Right]),
|
||||
format(S,' "~w" -> "~w" [style = dashed];~n', [Val, Left]).
|
||||
format(S,' "~w" -> "~w" [arrowType="none" color="red"] ;~n', [Val, Left]),
|
||||
format(S,' "~w" -> "~w" [style = dashed arrowType="none"];~n', [Val, Right]).
|
||||
print_node(S,pn( Val, Name, Left, Right )) :-
|
||||
simplify(Name, N),
|
||||
%writeln(Name),
|
||||
format(S,' "~w" [label = "~w"];~n', [Val, N]),
|
||||
format(S,' "~w" -> "~w";~n', [Val, Right]),
|
||||
format(S,' "~w" -> "~w" [style = dashed];~n', [Val, Left]).
|
||||
format(S,' "~w" -> "~w" [arrowType="none" color="red"];~n', [Val,Left]),
|
||||
( Right == 1 ->
|
||||
format(S,' "~w" -> "0" [dir=none style = dotted];~n', [Val])
|
||||
;
|
||||
format(S,' "~w" -> "~w" [style = dotted type="odot"];~n', [Val, Right])
|
||||
).
|
||||
|
||||
simplify(V,V) :- var(V),!.
|
||||
simplify('$VAR'(X),Y) :- !, simplify(X,Y).
|
||||
simplify(c^(X),Y) :- !, simplify(X,Y).
|
||||
simplify(G, X:M) :- G=.. [X,N], !, simplify(N,M).
|
||||
@ -427,16 +443,16 @@ ensure((X in D)) :-
|
||||
|
||||
formula( Axioms, FormulaE, Dic) :-
|
||||
rb_new( Dic0 ),
|
||||
partition( is_init, Axioms, _Inits, OGoals),
|
||||
partition( is_frame, OGoals, _Frames, Goals),
|
||||
partition( is_frame, Axioms, _, Goals),
|
||||
foldl2( eq, Goals, Formula, Dic0, Dic, [], Extras),
|
||||
append(Formula, Extras, FormulaL),
|
||||
maplist(writeln,FormulaL),
|
||||
list2prod( FormulaL, FormulaE).
|
||||
|
||||
is_init( A ?= B ) :- assert(init(A, B)).
|
||||
|
||||
is_frame( A =:= B ) :- assert( frame(A, B)).
|
||||
is_frame( level(N, [H|L]) ) :- !, maplist( assertn(level, N), [H|L] ).
|
||||
is_frame( level(N, L ) ) :- assert( level( N, L) ).
|
||||
|
||||
assertn(level, N, L) :- assert( level( N, L) ).
|
||||
|
||||
list2prod( [], true).
|
||||
list2prod( [F], F).
|
||||
@ -444,6 +460,9 @@ list2prod( [F1,F2|Fs], F1*NF) :-
|
||||
list2prod( [F2|Fs], NF).
|
||||
|
||||
%eq(G,_,_,_,_,_) :- writeln(a:G), fail.
|
||||
eq(1, 1, Dic, Dic, I, I) :- !.
|
||||
eq(X, VX, Dic0, Dic, I0, I) :- var(X), !,
|
||||
add(X, VX, Dic0, Dic, I0, I).
|
||||
eq(X == Exp, (-TA + TY)*(-TY + TA), Dic0, Dic, I0, I) :- !,
|
||||
eq(X, TA, Dic0, Dic1, I0, I1),
|
||||
eq(Exp, TY, Dic1, Dic, I1, I).
|
||||
@ -471,22 +490,39 @@ eq((X xor Y), (TX xor TY), Dic0, Dic, I0, I) :- !,
|
||||
eq( X, TX, Dic0, Dic1, I0, I1),
|
||||
eq( Y, TY, Dic1, Dic, I1, I).
|
||||
|
||||
eq(X in D, TAX + (-TAX * (EDX+ (-EDX + Ds ))) , Dic0, Dic, I0, I) :- !,
|
||||
eq( t_atom(X), TAX, Dic0, Dic1, I0, I1),
|
||||
add( err(dom(X,D)), EDX, Dic1, Dic2, I1, I2),
|
||||
add(X, VX, Dic2, Dic3, I2, I3)
|
||||
t_domain( D, VX, Ds, Dic3, Dic, I3, I).
|
||||
eq((X in D), Disj , Dic0, Dic, I0, I) :- !,
|
||||
%trace,
|
||||
add(X, VX, Dic0, Dic1, I0, I1),
|
||||
append( D, [err], _Domain),
|
||||
foldl2(add, D, DVs, Dic1, Dic, I1, I),
|
||||
%foldl(add_xors(DVs), DVs, I2, I),
|
||||
foldl(xor(VX, DVs), DVs, 0, Disj).
|
||||
|
||||
eq(G, NG, Dic0, Dic, I0, I) :-
|
||||
add( G, NG, Dic0, Dic, I0, I).
|
||||
|
||||
t_domain( [D], VX, VD = VX, Dic0, Dic, I0, I) :- !,
|
||||
add(D, VD, Dic0, Dic, I0, I).
|
||||
t_domain( [D1|D2s], (VX==VX=D)* + D2S, _, Dic0, Dic, I0, I) :-
|
||||
add( X=D1, VDX, Dic0, Dic1, I0, I1),
|
||||
add( X, VX, Dic0, Dic1, I0, I1),
|
||||
maplist(diff(XD1), D2s, Dic1, Dic, I1, I),
|
||||
t_domain(D2S, X, ).
|
||||
add_xors(L, V, I0, I) :-
|
||||
foldl(add_xor(V), L, I0, I).
|
||||
|
||||
add_xor(V, V0, I, I) :- V == V0, !.
|
||||
add_xor(V, V0, I, [(V-V0)|I]).
|
||||
|
||||
xor( VX, DV0s, DV , Disj0, Disj0+Conj) :- !,
|
||||
foldl( add_all2(VX, DV), DV0s, 1,Conj).
|
||||
|
||||
add_all2(VX, G, GD, C, C*(VX=G)
|
||||
) :- G == GD, ! .
|
||||
add_all2(VX, _, G, C, C*(-(VX=G))).
|
||||
|
||||
list2prod(X, P, X *P).
|
||||
list2sum(X, P, X +P).
|
||||
|
||||
t_domain0( [D], DX, Dic0, Dic, I0, I) :- !,
|
||||
eq(D , DX , Dic0, Dic, I0, I).
|
||||
t_domain0( [D1|D2s], (DX1+ (-DX1*D2Xs)), Dic0, Dic, I0, I) :-
|
||||
eq(D1, DX1, Dic0, Dic1, I0, I1),
|
||||
t_domain0(D2s, D2Xs, Dic1, Dic, I1, I).
|
||||
|
||||
|
||||
diff(XD, DO, Dic0, Dic, [-XD*VDO+ (XD * -VDO)|I0], I) :-
|
||||
new(DO, VDO, Dic0, Dic, I0, I).
|
||||
@ -500,6 +536,7 @@ add( AG, V, Dic0, Dic, I0, IF) :-
|
||||
add( AG, V, Dic0, Dic, I, I) :-
|
||||
rb_insert( Dic0, AG, V, Dic).
|
||||
|
||||
simp_key(G , G) :- var(G), !.
|
||||
simp_key(_^_:error(_^G) , G) :- !.
|
||||
simp_key(_^_:G , G) :- !.
|
||||
simp_key('$VAR'(S):A, SAG) :-
|
||||
|
@ -32,6 +32,7 @@ The following predicates construct a BDD:
|
||||
bdd_print/3,
|
||||
bdd_to_probability_sum_product/2,
|
||||
bdd_to_probability_sum_product/3,
|
||||
bdd_reorder/2,
|
||||
bdd_close/1,
|
||||
mtbdd_close/1]).
|
||||
|
||||
@ -338,6 +339,14 @@ bdd_close(cudd(M,_,_Vars, _)) :-
|
||||
bdd_close(add(M,_,_Vars, _)) :-
|
||||
cudd_die(M).
|
||||
|
||||
/** @pred bdd_close( _BDDHandle_)
|
||||
|
||||
close the BDD and release any resources it holds.
|
||||
|
||||
*/
|
||||
bdd_reorder(cudd(M,Top,_Vars, _), How) :-
|
||||
cudd_reorder(M, Top,How).
|
||||
|
||||
/** @pred bdd_size(+ _BDDHandle_, - _Size_)
|
||||
|
||||
Unify _Size_ with the number of nodes in _BDDHandle_.
|
||||
@ -356,19 +365,23 @@ Output bdd _BDDHandle_ as a dot file to _File_.
|
||||
|
||||
*/
|
||||
bdd_print(cudd(M,Top,_Vars, _), File) :-
|
||||
cudd_print(M, Top, File).
|
||||
absolute_file_name(File, AFile, []),
|
||||
cudd_print(M, Top, AFile).
|
||||
bdd_print(add(M,Top,_Vars, _), File) :-
|
||||
cudd_print(M, Top, File).
|
||||
absolute_file_name(File, AFile, []),
|
||||
cudd_print(M, Top, AFile).
|
||||
|
||||
bdd_print(cudd(M,Top, Vars, _), File, Names) :-
|
||||
Vars =.. [_|LVars],
|
||||
%trace,
|
||||
maplist( fetch_name(Names), LVars, Ss),
|
||||
cudd_print(M, Top, File, Ss).
|
||||
absolute_file_name(File, AFile, []),
|
||||
cudd_print(M, Top, AFile, Ss).
|
||||
bdd_print(add(M,Top, Vars, _), File, Names) :-
|
||||
Vars =.. [_|LVars],
|
||||
maplist( fetch_name(Names), LVars, Ss),
|
||||
cudd_print(M, Top, File, Ss).
|
||||
absolute_file_name(File, AFile, []),
|
||||
cudd_print(M, Top, AFile, Ss).
|
||||
|
||||
fetch_name([S=V1|_], V2, SN) :- V1 == V2, !,
|
||||
( atom(S) -> SN = S ; format(atom(SN), '~w', [S]) ).
|
||||
|
@ -632,6 +632,13 @@ get_vars(YAP_Term t3)
|
||||
return YAP_ArityOfFunctor(YAP_FunctorOfTerm(t3));
|
||||
}
|
||||
|
||||
static YAP_Bool
|
||||
p_cudd_reorder(void)
|
||||
{
|
||||
DdManager *manager = (DdManager *)YAP_IntOfTerm(YAP_ARG1);
|
||||
return Cudd_ReduceHeap( manager, CUDD_REORDER_EXACT, 1);
|
||||
}
|
||||
|
||||
static YAP_Bool
|
||||
p_cudd_to_term(void)
|
||||
{
|
||||
@ -870,10 +877,12 @@ p_cudd_print_with_names(void)
|
||||
DdManager *manager = (DdManager *)YAP_IntOfTerm(YAP_ARG1);
|
||||
DdNode *n0 = (DdNode *)YAP_IntOfTerm(YAP_ARG2);
|
||||
const char *s = YAP_AtomName(YAP_AtomOfTerm(YAP_ARG3));
|
||||
const char **namesp;
|
||||
char **namesp;
|
||||
YAP_Term names = YAP_ARG4;
|
||||
FILE *f;
|
||||
YAP_Int len;
|
||||
YAP_Int i = 0;
|
||||
|
||||
if (!strcmp(s, "user_output")) f = stdout;
|
||||
else if (!strcmp(s, "user_error")) f = stderr;
|
||||
else if (!strcmp(s, "user")) f = stdout;
|
||||
@ -883,18 +892,34 @@ p_cudd_print_with_names(void)
|
||||
if ((namesp = malloc(sizeof(const char *)*len)) == NULL)
|
||||
return FALSE;
|
||||
while (YAP_IsPairTerm(names)) {
|
||||
YAP_Int i = 0;
|
||||
YAP_Term hd = YAP_HeadOfTerm( names);
|
||||
char * s = YAP_AtomName(YAP_AtomOfTerm(hd));
|
||||
const char *ns = malloc(strlen(s)+1);
|
||||
const char *f;
|
||||
|
||||
if (YAP_IsAtomTerm(hd)) {
|
||||
const char * s = YAP_AtomName(YAP_AtomOfTerm(hd));
|
||||
char *ns = malloc(strlen(s)+1);
|
||||
strncpy(ns, s, strlen(s)+1);
|
||||
namesp[i++] = ns;
|
||||
names = YAP_TailOfTerm( names);
|
||||
f = ns;
|
||||
} else {
|
||||
size_t sz =256;
|
||||
char *s = malloc(sz+256);
|
||||
while( !YAP_WriteBuffer(hd, s, sz-1, 0) ) {
|
||||
sz+=1024;
|
||||
s = realloc(s, sz);
|
||||
}
|
||||
Cudd_DumpDot(manager, 1, &n0, (char **)namesp, NULL, f);
|
||||
free( namesp );
|
||||
f = s;
|
||||
}
|
||||
names = YAP_TailOfTerm( names);
|
||||
namesp[i++] = f;
|
||||
}
|
||||
Cudd_DumpDot(manager, 1, &n0, namesp, NULL, f);
|
||||
if (f != stdout && f != stderr)
|
||||
fclose(f);
|
||||
while (i > 0) {
|
||||
i--;
|
||||
free(namesp[i]);
|
||||
}
|
||||
free( namesp );
|
||||
return TRUE;
|
||||
}
|
||||
|
||||
@ -943,6 +968,7 @@ init_cudd(void)
|
||||
FunctorCudd = YAP_MkFunctor(YAP_LookupAtom("cudd"), 1);
|
||||
TermMinusOne = YAP_MkIntTerm(-1);
|
||||
TermPlusOne = YAP_MkIntTerm(+1);
|
||||
TermZero = YAP_MkIntTerm(0);
|
||||
TermFalse = YAP_MkAtomTerm(YAP_LookupAtom("false"));
|
||||
TermTrue = YAP_MkAtomTerm(YAP_LookupAtom("true"));
|
||||
YAP_UserCPredicate("term_to_cudd", p_term_to_cudd, 3);
|
||||
@ -954,6 +980,7 @@ init_cudd(void)
|
||||
YAP_UserCPredicate("cudd_to_probability_sum_product", p_cudd_to_p, 4);
|
||||
YAP_UserCPredicate("cudd_size", p_cudd_size, 3);
|
||||
YAP_UserCPredicate("cudd_die", p_cudd_die, 1);
|
||||
YAP_UserCPredicate("cudd_reorder", p_cudd_reorder, 2);
|
||||
YAP_UserCPredicate("cudd_release_node", p_cudd_release_node, 2);
|
||||
YAP_UserCPredicate("cudd_print", p_cudd_print, 3);
|
||||
YAP_UserCPredicate("cudd_print", p_cudd_print_with_names, 4);
|
||||
|
@ -57,31 +57,36 @@ MYDDAS_SOURCES= \
|
||||
myddas_wkb2prolog.c
|
||||
|
||||
MYDDAS_PROLOG= \
|
||||
$(srcdir)/pl/myddas.ypp \
|
||||
$(srcdir)/pl/myddas_assert_predicates.ypp \
|
||||
$(srcdir)/pl/myddas_mysql.ypp \
|
||||
$(srcdir)/pl/myddas_sqlite3.ypp \
|
||||
$(srcdir)/pl/myddas_top_level.ypp \
|
||||
$(srcdir)/pl/myddas_errors.ypp \
|
||||
$(srcdir)/pl/myddas_postgres.ypp \
|
||||
$(srcdir)/pl/myddas_prolog2sql.ypp \
|
||||
$(srcdir)/pl/myddas_util_predicates.ypp \
|
||||
$(srcdir)/pl/myddas_prolog2sql_optimizer.ypp
|
||||
myddas.ypp \
|
||||
myddas_assert_predicates.ypp \
|
||||
myddas_mysql.ypp \
|
||||
myddas_sqlite3.ypp \
|
||||
myddas_top_level.ypp \
|
||||
myddas_errors.ypp \
|
||||
myddas_postgres.ypp \
|
||||
myddas_prolog2sql.ypp \
|
||||
myddas_util_predicates.ypp \
|
||||
myddas_prolog2sql_optimizer.ypp
|
||||
|
||||
|
||||
OBJS= $(MYDDAS_SOURCES:.c=.o)
|
||||
MYDDAS_YAP= $(MYDDAS_PROLOG:.ypp=.yap)
|
||||
SOBJS= myddas.@SO@
|
||||
|
||||
|
||||
#in some systems we just create a single object, in others we need to
|
||||
# create a libray
|
||||
|
||||
all: $(SOBJS)
|
||||
all: $(SOBJS) $(MYDDAS_YAP)
|
||||
|
||||
.PRECIOUS: %.o
|
||||
.PRECIOUS: %.o %.yap
|
||||
|
||||
%.o: $(srcdir)/%.c
|
||||
$(CC) -c $(CFLAGS) $< -o $@
|
||||
|
||||
%.yap: $(srcdir)/pl/%.ypp
|
||||
cpp $(YAP_EXTRAS) -P -E -w $< -o $@
|
||||
|
||||
@DO_SECOND_LD@%.@SO@: $(OBJS)
|
||||
@DO_SECOND_LD@ @SHLIB_LD@ $(LDFLAGS) -o $@ $(OBJS) @EXTRA_LIBS_FOR_DLLS@ @MYDDAS_LIBS@
|
||||
|
||||
@ -97,7 +102,7 @@ install_myddas:
|
||||
mkdir -p $(DESTDIR)$(SHAREDIR); \
|
||||
for p in $(MYDDAS_PROLOG); \
|
||||
do name=`basename $$p .ypp`; echo $$name;\
|
||||
cpp $(YAP_EXTRAS) -P -E -w $$p > $(DESTDIR)$(SHAREDIR)/$$name.yap; \
|
||||
$(INSTALL_DATA) $$name.yap $(DESTDIR)$(SHAREDIR); \
|
||||
done; \
|
||||
fi
|
||||
|
||||
|
@ -15,7 +15,7 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
#if USE_MYDDAS
|
||||
#if 1 //USE_MYDDAS
|
||||
|
||||
:- load_foreign_files([myddas], [], init_myddas).
|
||||
|
||||
@ -157,7 +157,7 @@ we were using Datalog.
|
||||
|
||||
The system includes four main blocks that are put together through the
|
||||
MYDDAS interface: the Yap Prolog compiler, the MySQL database system, an
|
||||
ODBC layer and a Prolog to SQL compiler. Current effort is put on the
|
||||
ODBC level and a Prolog to SQL compiler. Current effort is put on the
|
||||
MySQL interface rather than on the ODBC interface. If you want to use
|
||||
the full power of the MYDDAS interface we recommend you to use a MySQL
|
||||
database. Other databases, such as Oracle, PostGres or Microsoft SQL
|
||||
@ -872,6 +872,7 @@ You can see the available SQL Modes at the MySQL homepage at
|
||||
|
||||
#if MYDDAS_DECLARATIONS
|
||||
:- db_open(Protocol) extra_arguments
|
||||
connection=Connection,
|
||||
db=Db,
|
||||
port=Port,
|
||||
socket=Socket,
|
||||
@ -888,30 +889,21 @@ data:odbc=ODBC_DSN
|
||||
/* specify conditions */
|
||||
such_that
|
||||
|
||||
/** implicit, types are conditioned on start
|
||||
|
||||
atom(Db),
|
||||
positive_or_zero_integer(Port),
|
||||
atom(Socket),
|
||||
atom(User),
|
||||
atom(Password),
|
||||
file(File),
|
||||
atom(ODBC_DSN),
|
||||
internet_host(Host), */
|
||||
/** implicit, types are conditioned on start */
|
||||
|
||||
/* general theory, type hierarchy
|
||||
atom(X) ==> nonvar(X),
|
||||
\+ atom(X) * nonvar(X) ==> error(atom, X),
|
||||
var(X) ==> error(var, X),
|
||||
|
||||
internet_host(X) <=> atom(X),
|
||||
internet_host(X) ==> atom(X),
|
||||
|
||||
integer(X) ==> nonvar(X),
|
||||
\+ integer(X) * nonvar(X) ==> error(integer, X),
|
||||
var(X) ==> error(var, X)
|
||||
|
||||
positive_or_zero_integer(X) ==> integer(X),
|
||||
positive_or_zero_integer(X) ==> positive_or_zero(X)
|
||||
positive_or_zero_integer(X) ==> positive_or_zero(X),
|
||||
|
||||
positive_or_zero(X) ==> number(X),
|
||||
|
||||
@ -921,129 +913,181 @@ float(X) ==> number(X),
|
||||
rational(X) => number(X),
|
||||
number(X) ==> nonvar(X),
|
||||
\+ number(X) * nonvar(X) ==> error(number, X),
|
||||
var(X) ==> error(var, X),
|
||||
*/
|
||||
|
||||
/************
|
||||
this unfolds to
|
||||
P == ( (Protocol = mysql) + Protocol = powstgres + Protocol = odbc + Protocol = sqlite3 ),
|
||||
P == ( (Protocol = mysql) + Protocol = postgres + Protocol = odbc + Protocol = sqlite3 ),
|
||||
|
||||
Protocol = mysql ==> \+ Protocol = postgres,
|
||||
Protocol = mysql ==> \+ Protocol = odbc,
|
||||
Protocol = mysql ==> \+ Protocol = sqlite3,
|
||||
Protocol = postgres ==> \+ Protocol = mysql,
|
||||
|
||||
% P(X,D)
|
||||
% P(X,D) %
|
||||
P ==> atom(Protocol),
|
||||
atom(X) * not P ==> error(domain, X, D),
|
||||
*/
|
||||
|
||||
/* problem specific axioms */
|
||||
Connection?=myddas,
|
||||
Host ?= localhost,
|
||||
User ?= '',
|
||||
Password ?= '',
|
||||
top,
|
||||
|
||||
%( TOP :- mysql + postgres + odbc + sqlite3 ),
|
||||
|
||||
t_atom(X) =:= atom(X) \/ t_var(X) \/ type_err(atom(X)),
|
||||
t_var(X) =:= err(var(X)),
|
||||
t_integer(X) =:= integer(X) \/ t_var(X) \/ err(integer(X)),
|
||||
i_atom(X) =:= atom(X) \/ i_var(X) \/ t(atom(X)),
|
||||
i_var(X) =:= i(var(X)),
|
||||
i_integer(X) =:= integer(X) \/ i_var(X) \/ err(integer(X)),
|
||||
/* t_atom(X) =:= one_of([atom(X) , err(inst(X)) , err(type(atom,X))]),
|
||||
t_integer(X) =:= one_of([atom(X) , err(inst(X)) , err(type(integer,X))]),
|
||||
internet_host(X) =:= ( internet_host(X) ==> i_atom(X) ),
|
||||
positive_or_zero_integer(X) =:= ( positive_or_zero_integer(X) ==> t_integer(X) ),
|
||||
err(X) =:= ( err(X) ==> error ),
|
||||
*/
|
||||
%//list( X ) =:= ( nil(X) + ( X = cons( A, Y ) * L ) ) ),
|
||||
|
||||
%//list( Protocol ) .
|
||||
|
||||
( list( X ) =:= ( nil(X) + ( X = cons( A, Y ) * L ) ) ),
|
||||
%level( 1, [odbc, mysql, c_postgres_my_connect, c_sqlite3_connect, error]),
|
||||
%level( 2, c^_ )
|
||||
/* c^c_db_odbc_connect(ODBC_DSN,User,Password,Handle) ==
|
||||
odbc,
|
||||
|
||||
list( Protocol ) .
|
||||
c^c_db_my_connect(Host,User,Password,Db,Port,Socket,Handle) ==
|
||||
c_db_my_connect,
|
||||
|
||||
/*
|
||||
((Protocol = odbc) :-
|
||||
c^c_db_odbc_connect(ODBCEntry,User,Password,Handle) ),
|
||||
c^c_c_postgres_connect_connect(Host/Db/Port/Socket,User,Password, Handle) ==
|
||||
c_postgres_connect,
|
||||
|
||||
((Protocol = mysql) :-
|
||||
c^c_db_my_connect(Host,User,Password,Db,Port,Socket,Handle)),
|
||||
|
||||
((Protocol = postgres) :- c^c_postgres_connect(Host/Db/Port/Socket,User,Password, Handle)),
|
||||
|
||||
((Protocol = sqlite3) :-
|
||||
c^c_sqlite3_connect(File,User,Password,Handle),
|
||||
t_atom(File), i_atom(User)),
|
||||
|
||||
Protocol in [ mysql, postgres, odbc, sqlite3 ],
|
||||
|
||||
(- (c^c_sqlite3_connect(File,User,Password,Handle)) :- (c ^fail) ).
|
||||
|
||||
/*
|
||||
( c^c_db_my_connect(Host,User,Password,Db,Port,Socket,Handle) ==
|
||||
-(Protocol = odbc)*
|
||||
(Protocol = mysql) *
|
||||
-(Protocol = sqlite3)*
|
||||
-(Protocol = postgres) ),
|
||||
|
||||
|
||||
% t_internet_host(Host),
|
||||
% i_atom(User) *
|
||||
% i_atom(Password) *
|
||||
% i_positive_or_zero_integer(Port) *
|
||||
% i_atom(Db) *
|
||||
% i_atom(Socket)
|
||||
|
||||
( c^c_db_odbc_connect(ODBCEntry,User,Password,Handle) ==
|
||||
(Protocol = odbc)*
|
||||
-(Protocol = mysql) *
|
||||
-(Protocol = sqlite3)*
|
||||
-(Protocol = postgres) ),
|
||||
|
||||
|
||||
|
||||
( c^c_postgres_connect(Host/Db/Port/Socket,User,Password, Handle) ==
|
||||
-(Protocol = odbc)*
|
||||
-(Protocol = mysql) *
|
||||
-(Protocol = sqlite3)*
|
||||
(Protocol = posgrtgres) ),
|
||||
|
||||
% t_internet_host(Host)*
|
||||
% i_atom(User) *
|
||||
% i_atom(Password) *
|
||||
% i_positive_or_zero_integer(Port) *
|
||||
% i_atom(Db) *
|
||||
% i_atom(Socket) *
|
||||
|
||||
% 0 is default port and Var to be NULL, the default socket
|
||||
(c^c_sqlite3_connect(File,User,Password,Handle)
|
||||
==
|
||||
-(Protocol = odbc)*
|
||||
-(Protocol = mysql) *
|
||||
(Protocol = sqlite3)*
|
||||
-(Protocol = postgres)).
|
||||
%(Protocol = sqlite3),
|
||||
% t_file( File ) *
|
||||
%
|
||||
% i_atom(User) *
|
||||
% i_atom(Password).
|
||||
/*
|
||||
integer(Handle) ==
|
||||
c^c_db_my_connect(Host,User,Password,Db,Port,Socket,Handle) +
|
||||
c^c_db_odbc_connect(ODBCEntry,User,Password,Handle) +
|
||||
c^c_postgres_connect(Host/Db/Port/Socket,User,Password, Handle) +
|
||||
c^c_sqlite3_connect(File,User,Password,Handle).
|
||||
c^c_c_sqlite3_connect_connect(File,User,Password,Handle) ==
|
||||
c_sqlite3_connect,
|
||||
*/
|
||||
|
||||
% Connection == i_atom( Connection ),
|
||||
|
||||
%c_db_odbc_connect + - c_db_odbc_connect,
|
||||
%c_db_my_connect + - c_db_my_connect,
|
||||
%c_postgres_connect + - c_postgres_connect,
|
||||
%c_sqlite3_connect + - c_sqlite3_connect,
|
||||
|
||||
(protocol_odbc) + - (protocol_odbc),
|
||||
(protocol_mysql) + - (protocol_mysql),
|
||||
(protocol_postgres) + - (protocol_postgres),
|
||||
(protocol_sqlite3) + - (protocol_sqlite3),
|
||||
|
||||
file( File ) + - file( File ),
|
||||
atom( ODBC_DSN ) + - atom( ODBC_DSN ),
|
||||
i_atom( Db ) + - i_atom( Db ),
|
||||
i_atom( User ) + - i_atom( Password ),
|
||||
i_atom( Connection ) + - i_atom( Connection ),
|
||||
positive_or_zero_integer(Port) + - positive_or_zero_integer(Port),
|
||||
internet_host(Host) + - internet_host(Host),
|
||||
i_atom( User ) + - i_atom( User ),
|
||||
i_atom( Password ) + - i_atom( Password ),
|
||||
|
||||
i_atom( Db ) ,
|
||||
|
||||
%c_db_my_connect + c_postgres_connect ==> positive_or_zero_integer(Port),
|
||||
|
||||
%c_db_my_connect + c_postgres_connect ==> internet_host( Host ) ,
|
||||
|
||||
(protocol_mysql) + (protocol_postgres) ==>positive_or_zero_integer(Port),
|
||||
|
||||
(protocol_mysql) + (protocol_postgres) ==> internet_host( Host ) ,
|
||||
|
||||
i_atom( User ),
|
||||
|
||||
i_atom( Password ),
|
||||
|
||||
i_atom( Connection),
|
||||
|
||||
% c_postgres_connect == (protocol_postgres),
|
||||
|
||||
% c_db_odbc_connect == (protocol_odbc),
|
||||
|
||||
%c_db_odbc_connect == atom( ODBC_DSN ),
|
||||
|
||||
(protocol_odbc) == atom( ODBC_DSN ),
|
||||
|
||||
(protocol_sqlite3) == file( File ),
|
||||
|
||||
% c_db_my_connect == (protocol_mysql),
|
||||
|
||||
% c_sqlite3_connect == (protocol_sqlite3),
|
||||
|
||||
bound(Handle),
|
||||
|
||||
bound(Handle) ==
|
||||
((protocol_odbc *
|
||||
( - (protocol_sqlite3) *
|
||||
( - (protocol_postgres)) *
|
||||
( - (protocol_mysql)) )
|
||||
+
|
||||
(( - (protocol_odbc)) ) *
|
||||
(protocol_sqlite3) *
|
||||
( - (protocol_postgres) ) *
|
||||
( - (protocol_mysql) ) )
|
||||
+
|
||||
( - (protocol_odbc) ) *
|
||||
( - (protocol_sqlite3) ) *
|
||||
(protocol_postgres) *
|
||||
( - (protocol_mysql) ) )
|
||||
+
|
||||
(( - (protocol_odbc) ) *
|
||||
( - (protocol_sqlite3) ) *
|
||||
( - (protocol_postgres) ) *
|
||||
( protocol_mysql )
|
||||
).
|
||||
|
||||
/* bound(Handle) ==
|
||||
((c_db_odbc_connect *
|
||||
- ( c_sqlite3_connect *
|
||||
- c_postgres_connect *
|
||||
- c_db_my_connect )
|
||||
+
|
||||
(-c_db_odbc_connect *
|
||||
c_sqlite3_connect *
|
||||
- c_postgres_connect *
|
||||
- c_db_my_connect )
|
||||
+
|
||||
(-c_db_odbc_connect *
|
||||
-c_sqlite3_connect *
|
||||
c_postgres_connect *
|
||||
- c_db_my_connect )
|
||||
+
|
||||
(-c_db_odbc_connect *
|
||||
-c_sqlite3_connect *
|
||||
- c_postgres_connect *
|
||||
c_db_my_connect )
|
||||
). */
|
||||
|
||||
/*
|
||||
c_db_c_db_odbc_connect_connect ==> c_db_odbc_connect,
|
||||
c_db_my_connect ==> c_db_connect,
|
||||
c_c_postgres_connect_connect ==> c_postgres_connect,
|
||||
c_sqlite3_connect ==> sqlite3.
|
||||
*/
|
||||
|
||||
%c_db_odbc_connect ==> i_atom( Password ) * i_atom( User ) *
|
||||
|
||||
|
||||
|
||||
% Connection?=myddas,
|
||||
% Host ?= localhost,
|
||||
% User ?= '',
|
||||
% Password ?= ''.
|
||||
/* one_of(
|
||||
[c^c_db_odbc_connect(ODBC_DSN,User,Password,Handle),
|
||||
c^c_db_(Host,User,Password,Db,Port,Socket,Handle),
|
||||
c^c_postgres_connect(Host/Db/Port/Socket,User,Password, Handle),
|
||||
c^c_sqlite3_connect(File,User,Password,Handle)])
|
||||
*/
|
||||
db_open(Protocol) :- true.
|
||||
|
||||
#else
|
||||
|
||||
db_close:-
|
||||
db_close(myddas).
|
||||
db_close(Connection):-
|
||||
'$error_checks'(db_close(Connection)),
|
||||
get_value(Connection,Con),
|
||||
'$abolish_all'(Con).
|
||||
db_close(Connection) :-
|
||||
'$error_checks'(db_close(Connection)),
|
||||
get_value(Connection,Con),
|
||||
db_open:-
|
||||
db_open(myddas).
|
||||
|
||||
db_open(Protocol) :-
|
||||
'$error_checks'(db_open(Protocol)),
|
||||
get_value(Protocol,Con),
|
||||
c_db_connection_type(Con,ConType),
|
||||
( ConType == mysql ->
|
||||
c_db_my_disconnect(Con)
|
||||
@ -1054,7 +1098,7 @@ c_db_connection_type(Con,ConType),
|
||||
;
|
||||
c_db_odbc_disconnect(Con)
|
||||
),
|
||||
set_value(Connection,[]). % "deletes" atom
|
||||
set_value(Protocol,[]). % "deletes" atom
|
||||
|
||||
#endif
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
@ -1067,13 +1111,13 @@ set_value(Connection,[]). % "deletes" atom
|
||||
%
|
||||
db_close:-
|
||||
db_close(myddas).
|
||||
db_close(Connection):-
|
||||
'$error_checks'(db_close(Connection)),
|
||||
get_value(Connection,Con),
|
||||
db_close(Protocol):-
|
||||
'$error_checks'(db_close(Protocol)),
|
||||
get_value(Protocol,Con),
|
||||
'$abolish_all'(Con).
|
||||
db_close(Connection) :-
|
||||
'$error_checks'(db_close(Connection)),
|
||||
get_value(Connection,Con),
|
||||
db_close(Protocol) :-
|
||||
'$error_checks'(db_close(Protocol)),
|
||||
get_value(Protocol,Con),
|
||||
c_db_connection_type(Con,ConType),
|
||||
( ConType == mysql ->
|
||||
c_db_my_disconnect(Con)
|
||||
@ -1084,7 +1128,7 @@ c_db_connection_type(Con,ConType),
|
||||
;
|
||||
c_db_odbc_disconnect(Con)
|
||||
),
|
||||
set_value(Connection,[]). % "deletes" atom
|
||||
set_value(Protocol,[]). % "deletes" atom
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
|
||||
@ -1135,14 +1179,14 @@ c_db_check_if_exists_pred(PredName,Arity,Module).
|
||||
db_stats(List):-
|
||||
db_stats(myddas,List).
|
||||
|
||||
db_stats(Connection,List):-
|
||||
'$error_checks'(db_stats(Connection,List)),
|
||||
db_stats(Protocol,List):-
|
||||
'$error_checks'(db_stats(Protocol,List)),
|
||||
NumberOfStats = 10,
|
||||
'$make_a_list'(NumberOfStats,ListX1),
|
||||
( var(Connection) ->
|
||||
( var(Protocol) ->
|
||||
c_db_stats(0,ListX1)
|
||||
;
|
||||
get_value(Connection,Conn),
|
||||
get_value(Protocol,Conn),
|
||||
c_db_stats(Conn,ListX1)
|
||||
),
|
||||
'$make_stats_list'(ListX1,List).
|
||||
@ -1168,8 +1212,8 @@ c_db_stats_time(Reference,Time).
|
||||
%
|
||||
|
||||
%compatibility
|
||||
db_sql_select(Connection,SQL,LA):-
|
||||
db_sql(Connection,SQL,LA).
|
||||
db_sql_select(Protocol,SQL,LA):-
|
||||
db_sql(Protocol,SQL,LA).
|
||||
|
||||
db_sql(SQL,LA):-
|
||||
db_sql(myddas,SQL,LA).
|
||||
|
@ -1 +1 @@
|
||||
Subproject commit b36fdac2281b7eef141095375d81456410dbcd2f
|
||||
Subproject commit 36f99e3c3c978fef25f899dc4fab1ffee334d73c
|
Reference in New Issue
Block a user