bug fices

This commit is contained in:
Vítor Santos Costa
2016-01-03 02:06:09 +00:00
parent 7a7354fb2b
commit 661f33ac7e
133 changed files with 6000 additions and 9890 deletions

View File

@@ -21,6 +21,7 @@
:- use_module(library(atts)).
:- use_module(library(bhash)).
:- use_module(library(lists)).
@@ -33,7 +34,7 @@
:- attribute key/1, dist/2, evidence/1.
:- use_module('clpbn/ve',
:- use_module(clpbn/ve,
[ve/3,
check_if_ve_done/1,
init_ve_solver/4,
@@ -198,7 +199,7 @@ clpbn_flag(parameter_softening,Before,After) :- !,
retract(parameter_softening(Before)),
assert(parameter_softening(After)).
clpbn_flag(use_factors,Before,After) :- !,
clpbn_flag(use_parfactors,Before,After) :- !,
retract(use_parfactors(Before)),
assert(use_parfactors(After)).

View File

@@ -248,7 +248,7 @@ This option allows exporting the current model to the href{http://graphmod.ics.u
+ export_graphviz
This option allows exporting the factor graph's structure into a format that can be parsed by href{http://www.graphviz.org/}{Graphviz}.
This option allows exporting the factor graph's structure into a format that xocan be parsed by href{http://www.graphviz.org/}{Graphviz}.
+ Values: `true` or `false` (default).
+ Affects: `hve`, `bp`, and `cbp`.
@@ -362,7 +362,7 @@ The options that are available with the `set_pfl_flag/2` predicate can be used i
->
% we're using factor language
% set appropriate flag
set_pfl_flag(use_factors,on)
set_pfl_flag(use_parfactors,on)
;
% we're within clp(bn), no need to do anything
true
@@ -504,7 +504,11 @@ new_skolem(Sk, D) :-
functor(Sk, N, A),
functor(NSk, N, A),
% [f,t] is special for evidence
( D = [f,t] -> assert((evidence(NSk, 1) :- user:NSk)) ; true ),
( D = [f,t] ->
dynamic(N/A),
assert((evidence(NSk, 1) :- user:NSk))
;
true ),
interface_predicate(NSk),
assert(skolem(NSk, D)).

View File

@@ -75,7 +75,8 @@ grounder_compute_reachable_atoms(A,ID,Success) :-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
( % go over all proofs for A in interpretation ID
tabled_meta_interpreter(A,ID),
tabled_meta_interpreter(A,ID),
writeln(A),
bb_put(dep_proven,true),
fail; % go to next proof
@@ -100,6 +101,8 @@ grounder_compute_reachable_atoms(A,ID,Success) :-
%========================================================================
tabled_meta_interpreter(X,ID) :-
writeln(ID:X), fail.
tabled_meta_interpreter((X,Y),ID) :-
!,
tabled_meta_interpreter(X,ID),
@@ -143,9 +146,9 @@ tabled_meta_interpreter(Atom,ID) :-
% we can ignore probabilistic facts and only look for myclauses
% since in ProbLog the requirement is that non-ground facts have to be
% ground at query time
current_predicate(user:myclause/3),
user:myclause(ID,Atom,Body),
writeln(Atom:Body),
tabled_meta_interpreter(Body,ID),

View File

@@ -228,8 +228,9 @@
:- initialization((
bb_put(logger_filename,'out.dat'),
bb_put(logger_delimiter,';'),
bb_put(logger_variables,[])
)).
bb_put(logger_variables,[])
)).
%========================================================================
%= Defines a new variable, possible types are: int, float and time

View File

@@ -53,7 +53,7 @@ myclause(calls(Person), (person(Person),alarm,hears_alarm(Person))).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%% Training examples %
%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%l
example(1).
example(2).
@@ -64,4 +64,3 @@ known(1,alarm,true).
%%%% Example 2
known(2,earthquake,false).
known(2,calls(mary),true).

View File

@@ -10,71 +10,71 @@
% http://dtai.cs.kuleuven.be/problog
%
% ProbLog was developed at Katholieke Universiteit Leuven
%
%
% Copyright 2009
% Angelika Kimmig, Vitor Santos Costa, Bernd Gutmann
%
%
% Main author of this file:
% Bernd Gutmann
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Artistic License 2.0
%
%
% Copyright (c) 2000-2006, The Perl Foundation.
%
%
% Everyone is permitted to copy and distribute verbatim copies of this
% license document, but changing it is not allowed. Preamble
%
%
% This license establishes the terms under which a given free software
% Package may be copied, modified, distributed, and/or
% redistributed. The intent is that the Copyright Holder maintains some
% artistic control over the development of that Package while still
% keeping the Package available as open source and free software.
%
%
% You are always permitted to make arrangements wholly outside of this
% license directly with the Copyright Holder of a given Package. If the
% terms of this license do not permit the full use that you propose to
% make of the Package, you should contact the Copyright Holder and seek
% a different licensing arrangement. Definitions
%
%
% "Copyright Holder" means the individual(s) or organization(s) named in
% the copyright notice for the entire Package.
%
%
% "Contributor" means any party that has contributed code or other
% material to the Package, in accordance with the Copyright Holder's
% procedures.
%
%
% "You" and "your" means any person who would like to copy, distribute,
% or modify the Package.
%
%
% "Package" means the collection of files distributed by the Copyright
% Holder, and derivatives of that collection and/or of those files. A
% given Package may consist of either the Standard Version, or a
% Modified Version.
%
%
% "Distribute" means providing a copy of the Package or making it
% accessible to anyone else, or in the case of a company or
% organization, to others outside of your company or organization.
%
%
% "Distributor Fee" means any fee that you charge for Distributing this
% Package or providing support for this Package to another party. It
% does not mean licensing fees.
%
%
% "Standard Version" refers to the Package if it has not been modified,
% or has been modified only in ways explicitly requested by the
% Copyright Holder.
%
%
% "Modified Version" means the Package, if it has been changed, and such
% changes were not explicitly requested by the Copyright Holder.
%
%
% "Original License" means this Artistic License as Distributed with the
% Standard Version of the Package, in its current version or as it may
% be modified by The Perl Foundation in the future.
%
%
% "Source" form means the source code, documentation source, and
% configuration files for the Package.
%
%
% "Compiled" form means the compiled bytecode, object code, binary, or
% any other form resulting from mechanical transformation or translation
% of the Source form.
@@ -82,34 +82,34 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Permission for Use and Modification Without Distribution
%
%
% (1) You are permitted to use the Standard Version and create and use
% Modified Versions for any purpose without restriction, provided that
% you do not Distribute the Modified Version.
%
% Permissions for Redistribution of the Standard Version
%
%
% (2) You may Distribute verbatim copies of the Source form of the
% Standard Version of this Package in any medium without restriction,
% either gratis or for a Distributor Fee, provided that you duplicate
% all of the original copyright notices and associated disclaimers. At
% your discretion, such verbatim copies may or may not include a
% Compiled form of the Package.
%
%
% (3) You may apply any bug fixes, portability changes, and other
% modifications made available from the Copyright Holder. The resulting
% Package will still be considered the Standard Version, and as such
% will be subject to the Original License.
%
% Distribution of Modified Versions of the Package as Source
%
%
% (4) You may Distribute your Modified Version as Source (either gratis
% or for a Distributor Fee, and with or without a Compiled form of the
% Modified Version) provided that you clearly document how it differs
% from the Standard Version, including, but not limited to, documenting
% any non-standard features, executables, or modules, and provided that
% you do at least ONE of the following:
%
%
% (a) make the Modified Version available to the Copyright Holder of the
% Standard Version, under the Original License, so that the Copyright
% Holder may include your modifications in the Standard Version. (b)
@@ -128,7 +128,7 @@
%
% Distribution of Compiled Forms of the Standard Version or
% Modified Versions without the Source
%
%
% (5) You may Distribute Compiled forms of the Standard Version without
% the Source, provided that you include complete instructions on how to
% get the Source of the Standard Version. Such instructions must be
@@ -139,13 +139,13 @@
% within thirty days after you become aware that the instructions are
% invalid, then you do not forfeit any of your rights under this
% license.
%
%
% (6) You may Distribute a Modified Version in Compiled form without the
% Source, provided that you comply with Section 4 with respect to the
% Source of the Modified Version.
%
% Aggregating or Linking the Package
%
%
% (7) You may aggregate the Package (either the Standard Version or
% Modified Version) with other packages and Distribute the resulting
% aggregation provided that you do not charge a licensing fee for the
@@ -153,7 +153,7 @@
% components in the aggregation are permitted. The terms of this license
% apply to the use and Distribution of the Standard or Modified Versions
% as included in the aggregation.
%
%
% (8) You are permitted to link Modified and Standard Versions with
% other works, to embed the Package in a larger work of your own, or to
% build stand-alone binary or bytecode versions of applications that
@@ -161,7 +161,7 @@
% provided the result does not expose a direct interface to the Package.
%
% Items That are Not Considered Part of a Modified Version
%
%
% (9) Works (including, but not limited to, modules and scripts) that
% merely extend or make use of the Package, do not, by themselves, cause
% the Package to be a Modified Version. In addition, such works are not
@@ -169,21 +169,21 @@
% terms of this license.
%
% General Provisions
%
%
% (10) Any use, modification, and distribution of the Standard or
% Modified Versions is governed by this Artistic License. By using,
% modifying or distributing the Package, you accept this license. Do not
% use, modify, or distribute the Package, if you do not accept this
% license.
%
%
% (11) If your Modified Version has been derived from a Modified Version
% made by someone other than you, you are nevertheless required to
% ensure that your Modified Version complies with the requirements of
% this license.
%
%
% (12) This license does not grant you the right to use any trademark,
% service mark, tradename, or logo of the Copyright Holder.
%
%
% (13) This license includes the non-exclusive, worldwide,
% free-of-charge patent license to make, have made, use, offer to sell,
% sell, import and otherwise transfer the Package with respect to any
@@ -193,7 +193,7 @@
% that the Package constitutes direct or contributory patent
% infringement, then this Artistic License to you shall terminate on the
% date that such litigation is filed.
%
%
% (14) Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT
% HOLDER AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED
% WARRANTIES. THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
@@ -312,7 +312,7 @@ print_ad_intern(_::Fact,[],Mass,Handle) :-
P2 is 1.0 - Mass,
format(Handle,'~f :: ~q',[P2,Fact]).
print_ad_intern_one(_::Fact,_::AuxFact,Mass,NewMass,Handle) :-
% ask problog to get the fact_id
% ask problog to get the fact_id
once(probabilistic_fact(_,AuxFact,FactID)),
% look in our table for the probability
array_element(factprob,FactID,P),
@@ -342,7 +342,7 @@ do_learning_intern(0,_) :-
do_learning_intern(Iterations,Epsilon) :-
Iterations>0,
logger_start_timer(duration),
current_iteration(CurrentIteration),
!,
retractall(current_iteration(_)),
@@ -350,7 +350,7 @@ do_learning_intern(Iterations,Epsilon) :-
NextIteration is CurrentIteration+1,
assertz(current_iteration(NextIteration)),
EndIteration is CurrentIteration+Iterations-1,
format_learning(1,'~nIteration ~d of ~d~n',[CurrentIteration,EndIteration]),
logger_set_variable(iteration,CurrentIteration),
@@ -358,7 +358,7 @@ do_learning_intern(Iterations,Epsilon) :-
once(llh_testset),
once(ground_truth_difference),
once(ground_truth_difference),
once(em_one_iteration),
problog_flag(log_frequency,Log_Frequency),
@@ -381,11 +381,11 @@ do_learning_intern(Iterations,Epsilon) :-
LLH_Diff is abs(Last_LLH-Current_LLH)
); (
logger_get_variable(llh_training_set,Current_LLH),
assertz(last_llh(Current_LLH)),
assertz(last_llh(Current_LLH)),
LLH_Diff is Epsilon+1
)
),
logger_stop_timer(duration),
logger_write_data,
RemainingIterations is Iterations-1,
@@ -424,12 +424,12 @@ init_learning :-
check_theory,
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Delete the stuff from the previous run
% Delete the stuff from the previous run
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
problog_flag(reuse_initialized_bdds,Re_Use_Flag),
(
Re_Use_Flag==false
->
@@ -438,7 +438,7 @@ init_learning :-
),
empty_output_directory,
logger_write_header,
format_learning(1,'Initializing everything~n',[]),
@@ -471,7 +471,7 @@ init_learning :-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% build BDD script for every example
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
once(init_queries),
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -492,7 +492,7 @@ init_learning :-
%========================================================================
%= This predicate checks some aspects of the data given by the user.
%= You know folks: Garbage in, garbage out.
%=
%=
%========================================================================
check_theory :-
(
@@ -510,7 +510,7 @@ check_theory :-
);
true
),
(
(current_predicate(user:example/1),user:example(_))
->
@@ -584,7 +584,7 @@ check_theory :-
%=
%========================================================================
initialize_fact_probabilities :-
initialize_fact_probabilities :-
problog:probclause_id(N),
static_array(factprob,N,float),
@@ -658,7 +658,7 @@ init_queries :-
assertz(test_set_cluster_list(Test_Set_Cluster_List)).
%========================================================================
%=
%=
%========================================================================
init_one_query(QueryID,_Query_Type) :-
@@ -689,10 +689,8 @@ create_test_query_cluster_list(L2) :-
calc_all_md5(AllCluster,AllCluster2),
findall(a(QueryID1,ClusterID1,Len),(bagof(a(QueryID,ClusterID),member(a(QueryID,ClusterID,_MD5),AllCluster2),L),nth1(1,L,a(QueryID1,ClusterID1)),length(L,Len)),L2),
!,
length(AllCluster,Len1),
length(L2,Len2),
(
Len1>0
->
@@ -717,25 +715,22 @@ create_training_query_cluster_list(L2) :-
), AllCluster),
calc_all_md5(AllCluster,AllCluster2),
findall(a(QueryID1,ClusterID1,Len),
(
bagof(a(QueryID,ClusterID),member(a(QueryID,ClusterID,_MD5),AllCluster2),L),
nth1(1,L,a(QueryID1,ClusterID1)),
length(L,Len)
),L2),
length(AllCluster,Len1),
length(L2,Len2),
Reduction is Len2/Len1,
format_learning(3,' ~d cluster after splitting, ~d unique cluster ==> reduction factor of ~4f~n',[Len1,Len2,Reduction]).
%========================================================================
%=
%=
%========================================================================
reset_learning :-
@@ -751,7 +746,7 @@ reset_learning :-
close_static_array(factprob),
close_static_array(factprob_temp),
close_static_array(factusage),
close_static_array(known_count_true_training),
close_static_array(known_count_false_training),
close_static_array(known_count_true_test),
@@ -760,14 +755,14 @@ reset_learning :-
reset_completion,
empty_bdd_directory,
empty_output_directory,
logger_reset_all_variables
);
true
).
%========================================================================
%= calculate the LLH on the test set and set the variable
%= calculate the LLH on the test set and set the variable
%= in the logger module
%========================================================================
@@ -863,7 +858,7 @@ write_probabilities_file :-
forall(get_fact_probability(ID,_),
(
array_element(factprob,ID,Prob),
(
non_ground_fact(ID)
->
@@ -885,17 +880,17 @@ write_probabilities_file :-
update_query(QueryID,ClusterID ,Method,Command,PID,Output_File_Name) :-
current_iteration(Iteration),
create_bdd_input_file_name(Iteration,Input_File_Name),
create_bdd_output_file_name(QueryID,ClusterID,Iteration,Output_File_Name),
create_bdd_file_name(QueryID,ClusterID,BDD_File_Name),
convert_filename_to_problog_path('problogbdd_lfi',Absolute_Name),
atomic_concat([Absolute_Name,
' -i "', Input_File_Name, '"',
' -l "', BDD_File_Name, '"',
' -m ', Method,
' -m ', Method,
' -id ', QueryID],Command),
open( Output_File_Name, write, Stream ),
exec(Command,[std, Stream ,std],PID),
@@ -914,7 +909,7 @@ update_query_wait(QueryID,_ClusterID,Count,Symbol,Command,PID,OutputFilename,BDD
);
true
),
once(my_load_allinone(OutputFilename,QueryID,Count,BDD_Probability)),
problog_flag(retain_bdd_output,Retain_BDD_Output),
@@ -1019,7 +1014,7 @@ em_one_iteration :-
KK_Sum is KK_True+KK_False,
KK_Sum>0,
% add counts
add_to_array_element(factprob_temp,FactID,KK_True,_NewValue),
add_to_array_element(factusage,FactID,KK_Sum,_NewCount),
@@ -1038,7 +1033,7 @@ em_one_iteration :-
LProb is Part1 + KK_False*log(1-P);
LProb is Part1
),
bb_get(dummy,Old),
New is Old+LProb,
bb_put(dummy,New),
@@ -1056,7 +1051,7 @@ em_one_iteration :-
evaluate_bdds(AllCluster,Handle,Parallel_Processes,'e','.',LLH_From_True_BDDs,LLH),
logger_set_variable(llh_training_set,LLH),
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% stop calculate new values
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -1065,7 +1060,7 @@ em_one_iteration :-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% start copy new values
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
problog_flag(pc_numerator,Pseudo_Counts_Numerator),
problog_flag(pc_denominator,Pseudo_Counts_Denominator),
@@ -1098,7 +1093,7 @@ em_one_iteration :-
%= S : symbol to print after a process finished
%= OldLLH : accumulator for LLH
%= LLH : resulting LLH
%=
%=
%= evaluate_bdds(+L,+H,+P,+T,+S,+OldLLH,-LLH)
%========================================================================
@@ -1107,7 +1102,7 @@ evaluate_bdds([H|T],Handle,Parallel_Processes,Type,Symbol,OldLLH,LLH) :-
once(slice_n([H|T],Parallel_Processes,ForNow,Later)),
logger_start_timer(bdd_evaluation),
once(evaluate_bdds_start(ForNow,Type,ForNow_Jobs)),
once(evaluate_bdds_stop(ForNow_Jobs,Handle,Symbol,OldLLH,NewLLH)),
once(evaluate_bdds_stop(ForNow_Jobs,Handle,Symbol,OldLLH,NewLLH)),
logger_stop_timer(bdd_evaluation),
evaluate_bdds(Later,Handle,Parallel_Processes,Type,Symbol,NewLLH,LLH).
@@ -1142,7 +1137,7 @@ init_flags :-
problog_define_flag(output_directory, problog_flag_validate_directory, 'directory for logfiles etc', Output_Folder,learning_general,flags:learning_output_dir_handler),
problog_define_flag(retain_bdd_output,problog_flag_validate_boolean,'Keep output files from BDD tool',false,learning_general),
problog_define_flag(log_frequency, problog_flag_validate_posint, 'log results every nth iteration', 1, learning_general),
problog_define_flag(reuse_initialized_bdds,problog_flag_validate_boolean, 'Reuse BDDs from previous runs',false, learning_general),
problog_define_flag(reuse_initialized_bdds,problog_flag_validate_boolean, 'Reuse BDDs from previous runs',false, learning_general),
problog_define_flag(pc_numerator,problog_flag_validate_in_interval_right_open([0.0,+inf]),'Add X to numerator (Pseudocounts)',0.0,learning_general),
problog_define_flag(pc_denominator,problog_flag_validate_in_interval_right_open([0.0,+inf]),'Add X to denominator (Pseudocounts)',0.0,learning_general),
problog_define_flag(parallel_processes,problog_flag_validate_posint,'Number of parallel BDD processes',8,learning_general),
@@ -1156,7 +1151,7 @@ init_logger :-
logger_define_variable(llh_training_set,float),
logger_define_variable(llh_test_set,float),
logger_define_variable(bdd_evaluation,time),
logger_define_variable(ground_truth_diff,float),
@@ -1186,6 +1181,3 @@ init_logger :-
%:- initialization(do_learning(100) ).

View File

@@ -35,12 +35,12 @@ IF (CUDD_FOUND)
${CUDD_INCLUDE_DIR}
${CMAKE_CURRENT_BINARY_DIR}
)
check_include_files( util.h HAVE_UTIL_H )
check_include_files( cudd/util.h HAVE_CUDD_UTIL_H )
check_include_files( cudd.h HAVE_CUDD_H )
check_include_files( "stdio.h;cudd/cudd.h" HAVE_CUDD_CUDD_H )
check_include_files( cuddInt.h HAVE_CUDDINT_H )
check_include_files( cuddInt.h HAVE_CUDDINT_H )
check_include_files( "stdio.h;cudd/cudd.h;cudd/cuddInt.h" HAVE_CUDD_CUDDINT_H )
configure_file ("${PROJECT_SOURCE_DIR}/cudd_config.h.cmake"
@@ -63,6 +63,7 @@ IF (CUDD_FOUND)
add_subdirectory(simplecudd)
add_subdirectory(simplecudd_lfi)
set(YAP_SYSTEM_OPTIONS "cudd " ${YAP_SYSTEM_OPTIONS} PARENT_SCOPE)
install(TARGETS cudd
LIBRARY DESTINATION ${dlls}
@@ -72,7 +73,7 @@ IF (CUDD_FOUND)
INSTALL(FILES ddnnf.yap DESTINATION ${libpl})
INSTALL(FILES simpbool.yap DESTINATION ${libpl})
INSTALL(FILES trie_sp.yap DESTINATION ${libpl})
ENDIF (CUDD_FOUND)
SET (CUDD_FOUND_EXPORT ${CUDD_FOUND} PARENT_SCOPE)

View File

@@ -2,7 +2,7 @@
/* Define to 1 if you have the <cuddInt.h> header file. */
#ifndef HAVE_CUDDINT_H
#define HAVE_CUDDINT_H
/* #undef HAVE_CUDDINT_H */
#endif
/* Define to 1 if you have the <cudd/cuddInt.h> header file. */
@@ -15,9 +15,9 @@
#define HAVE_CUDD_CUDD_H 1
#endif
/* Define to 1 if you have the <cudd.h> header file. */
/*Define to 1 if you have the <cudd.h> header file. */
#ifndef HAVE_CUDD_H
#define HAVE_CUDD_H
/* #undef HAVE_CUDD_H */
#endif
/* Define to 1 if you have the <cudd/util.h> header file. */

View File

@@ -254,7 +254,7 @@ int CharIn(const char c, const char *in) {
/* string handling */
int patternmatch(char *pattern, char *thestr) {
int patternmatch(const char *pattern, const char *thestr) {
int i, j = -1, pl = strlen(pattern), sl = strlen(thestr);
for(i = 0; i < pl; i++) {
if (pattern[i] == '*') {

View File

@@ -200,5 +200,5 @@ int IsRealNumber(char *c);
int IsNumber(const char *c);
char * freadstr(FILE *fd, const char *separators);
int CharIn(const char c, const char *in);
int patternmatch(char *pattern, char *thestr);
int patternmatch(const char *pattern, const char *thestr);

View File

@@ -241,7 +241,7 @@ double CalcExpectedCountsUp(extmanager * MyManager, DdNode *Current, char *query
double CalcExpectedCountsDown(extmanager * MyManager, DdNode *Current, char *query_id);
double CalcExpectedCounts(extmanager * MyManager, DdNode *Current, char *query_id, int calcdown_needed);
int patterncalculated(char *pattern, extmanager MyManager, int loc);
char * extractpattern(char *thestr);
char * extractpattern(const char *thestr);
int main(int argc, char **arg) {
extmanager MyManager;
@@ -476,7 +476,7 @@ int main(int argc, char **arg) {
free(MyManager.varmap.dynvalue);
}
for (i = 0; i < MyManager.varmap.varcnt; i++)
free(MyManager.varmap.vars[i]);
free((const char *)MyManager.varmap.vars[i]);
free(MyManager.varmap.vars);
}
if (params.error != NULL) free(params.error);
@@ -1168,7 +1168,7 @@ gradientpair CalcGradient(extmanager MyManager, DdNode *Current, int TargetVar,
return tvalue;
}
char * extractpattern(char *thestr) {
char * extractpattern(const char *thestr) {
char *p;
int i = 0, sl = strlen(thestr);
while((thestr[i] != '_') && (i < sl)) i++;

View File

@@ -370,7 +370,7 @@ int CheckFileVersion(const char *version) {
return -1;
}
int simpleBDDtoDot(DdManager *manager, DdNode *bdd, char *filename) {
int simpleBDDtoDot(DdManager *manager, DdNode *bdd, const char *filename) {
DdNode *f[1];
int ret;
FILE *fd;
@@ -385,8 +385,8 @@ int simpleBDDtoDot(DdManager *manager, DdNode *bdd, char *filename) {
return ret;
}
int simpleNamedBDDtoDot(DdManager *manager, const namedvars varmap, DdNode *bdd,
char *filename) {
int simpleNamedBDDtoDot(DdManager *manager, namedvars varmap, DdNode *bdd,
const char *filename) {
DdNode *f[1];
int ret;
FILE *fd;
@@ -435,7 +435,7 @@ void SaveExpand(DdManager *manager, namedvars varmap, hisqueue *Nodes,
DdNode *Current, FILE *outputfile) {
DdNode *h, *l;
hisnode *Found;
char *curnode;
const char *curnode;
int inode;
if (Current != HIGH(manager) && Current != LOW(manager)) {
if ((Found = GetNode(Nodes, varmap.varstart, Current)) == NULL) {
@@ -917,7 +917,7 @@ namedvars InitNamedVars(int varcnt, int varstart) {
int i;
temp.varcnt = varcnt;
temp.varstart = varstart;
temp.vars = (char **)malloc(sizeof(char *) * varcnt);
temp.vars = (const char **)malloc(sizeof(char *) * varcnt);
temp.loaded = (int *)malloc(sizeof(int) * varcnt);
temp.dvalue = (double *)malloc(sizeof(double) * varcnt);
temp.ivalue = (int *)malloc(sizeof(int) * varcnt);
@@ -934,7 +934,7 @@ namedvars InitNamedVars(int varcnt, int varstart) {
void EnlargeNamedVars(namedvars *varmap, int newvarcnt) {
int i;
varmap->vars = (char **)realloc(varmap->vars, sizeof(char *) * newvarcnt);
varmap->vars = (const char **)realloc(varmap->vars, sizeof(const char *) * newvarcnt);
varmap->loaded = (int *)realloc(varmap->loaded, sizeof(int) * newvarcnt);
varmap->dvalue =
(double *)realloc(varmap->dvalue, sizeof(double) * newvarcnt);
@@ -954,7 +954,7 @@ void EnlargeNamedVars(namedvars *varmap, int newvarcnt) {
int AddNamedVarAt(namedvars varmap, const char *varname, int index) {
if (varmap.varcnt > index) {
varmap.vars[index] = (char *)malloc(sizeof(char) * (strlen(varname) + 1));
strcpy(varmap.vars[index], varname);
strcpy(varmap.vars[index], (char *)varname);
return index;
}
return -1;
@@ -1010,7 +1010,7 @@ int GetNamedVarIndex(const namedvars varmap, const char *varname) {
return -1 * varmap.varcnt;
}
char *GetNodeVarName(DdManager *manager, namedvars varmap, DdNode *node) {
const char *GetNodeVarName(DdManager *manager, namedvars varmap, DdNode *node) {
if (node == NULL)
return NULL;
if (node == HIGH(manager))
@@ -1020,7 +1020,7 @@ char *GetNodeVarName(DdManager *manager, namedvars varmap, DdNode *node) {
return varmap.vars[GetIndex(node) - varmap.varstart];
}
char *GetNodeVarNameDisp(DdManager *manager, namedvars varmap, DdNode *node) {
const char *GetNodeVarNameDisp(DdManager *manager, namedvars varmap, DdNode *node) {
if (HIGH(manager) == node)
return "TRUE";
if (LOW(manager) == node)

View File

@@ -249,7 +249,7 @@ typedef struct _bddfileheader {
typedef struct _namedvars {
int varcnt;
int varstart;
char **vars;
const char ** vars;
int *loaded;
double *dvalue;
int *ivalue;
@@ -317,8 +317,8 @@ void SetNamedVarValuesAt(namedvars varmap, int index, double dvalue, int ivalue,
int SetNamedVarValues(namedvars varmap, const char *varname, double dvalue, int ivalue, void *dynvalue);
int GetNamedVarIndex(const namedvars varmap, const char *varname);
int RepairVarcnt(namedvars *varmap);
char* GetNodeVarName(DdManager *manager, namedvars varmap, DdNode *node);
char* GetNodeVarNameDisp(DdManager *manager, namedvars varmap, DdNode *node);
const char* GetNodeVarName(DdManager *manager, namedvars varmap, DdNode *node);
const char* GetNodeVarNameDisp(DdManager *manager, namedvars varmap, DdNode *node);
int all_loaded(namedvars varmap, int disp);
int all_loaded_for_deterministic_variables(namedvars varmap, int disp);
@@ -351,6 +351,6 @@ void ExpandNodes(hisqueue *Nodes, int index, int nodenum);
/* Export */
int simpleBDDtoDot(DdManager *manager, DdNode *bdd, char *filename);
int simpleNamedBDDtoDot(DdManager *manager, namedvars varmap, DdNode *bdd, char *filename);
int simpleBDDtoDot(DdManager *manager, DdNode *bdd, const char *filename);
int simpleNamedBDDtoDot(DdManager *manager, namedvars varmap, DdNode *bdd, const char *filename);

View File

@@ -22,7 +22,6 @@
:-set_clpbn_flag(bnt_model,propositional).
/* start of list of parameters that can be set by the user with
set(Parameter,Value) */
setting(epsilon_parsing,0.00001).

View File

@@ -56,6 +56,8 @@ if (Java_Development_FOUND)
set_target_properties(jplYap PROPERTIES
OUTPUT_NAME jpl )
set(YAP_SYSTEM_OPTIONS "jpl " ${YAP_SYSTEM_OPTIONS} PARENT_SCOPE)
install(TARGETS jplYap
LIBRARY DESTINATION ${dlls}
)

View File

@@ -81,14 +81,14 @@
jpl_set_element/2
]).
:- expects_dialect(swi).
%:- expects_dialect(swi).
:- use_module(library(lists)).
:- use_module(library(apply)).
:- use_module(library(shlib)).
% suppress debugging this library
:- set_prolog_flag(generate_debug_info, false).
%:- set_prolog_flag(generate_debug_info, false).
%------------------------------------------------------------------------------

View File

@@ -81,8 +81,6 @@
jpl_set_element/2
]).
:- expects_dialect(swi).
:- use_module(library(lists)).
:- use_module(library(apply)).
:- use_module(library(shlib)).
@@ -157,6 +155,8 @@ jpl_tidy_iref_type_cache( Iref) :-
%
% finally, an attempt will be made to unify Result with the returned result
:- stop_low_level_trace.
jpl_call(X, Mspec, Params, R) :-
( jpl_object_to_type(X, Type) % the usual case (goal fails safely if X is var or rubbish)
-> Obj = X,

View File

@@ -1,79 +0,0 @@
/* MYDDAS */
#ifdef USE_MYDDAS
/* myddas_initialization.c */
MYDDAS_GLOBAL myddas_init_initialize_myddas(void);
MYDDAS_UTIL_CONNECTION myddas_init_initialize_connection(void *,void *,MYDDAS_API,MYDDAS_UTIL_CONNECTION);
MYDDAS_UTIL_PREDICATE myddas_init_initialize_predicate(char *, int, char *,MYDDAS_UTIL_PREDICATE);
#ifdef MYDDAS_STATS
/* myddas_statistics.c */
MYDDAS_GLOBAL myddas_stats_initialize_global_stats(MYDDAS_GLOBAL);
MYDDAS_STATS_STRUCT myddas_stats_initialize_connection_stats(void);
void myddas_stats_delete_stats_list(MYDDAS_STATS_STRUCT);
#endif /* MYDDAS_STATS */
#ifdef MYDDAS_MYSQL
/* myddas_util.c */
void myddas_util_table_write(MYSQL_RES *);
#endif
MYDDAS_API myddas_util_connection_type(void *);
MYDDAS_UTIL_CONNECTION myddas_util_add_connection(void *,void *,MYDDAS_API);
MYDDAS_UTIL_CONNECTION myddas_util_search_connection(void *);
void myddas_util_delete_connection(void *);
MYDDAS_UTIL_CONNECTION myddas_util_add_predicate(char * ,Int , char *,void *);
MYDDAS_UTIL_PREDICATE myddas_util_search_predicate(char * ,Int , char *);
void myddas_util_delete_predicate(MYDDAS_UTIL_PREDICATE);
/* Get's the number of queries to save */
UInt myddas_util_get_total_multi_queries_number(MYDDAS_UTIL_CONNECTION);
void myddas_util_set_total_multi_queries_number(MYDDAS_UTIL_CONNECTION,UInt);
#ifdef MYDDAS_ODBC
/* Return enviromment identifier*/
SQLHENV myddas_util_get_odbc_enviromment(SQLHDBC);
#endif
void * myddas_util_get_list_pred(MYDDAS_UTIL_CONNECTION);
void * myddas_util_get_pred_next(void *);
char * myddas_util_get_pred_module(void *);
char * myddas_util_get_pred_name(void *);
MyddasInt myddas_util_get_pred_arity(void *);
//DELETE THIS WHEN DB_STATS IS COMPLETED
MyddasInt get_myddas_top(void);
#ifdef DEBUG
void check_int(void);
#endif
#endif /* MYDDAS_MYSQL || MYDDAS_ODBC */
/* myddas_mysql.c */
#if defined MYDDAS_MYSQL
void Yap_InitMYDDAS_MySQLPreds(void);
void Yap_InitBackMYDDAS_MySQLPreds(void);
#endif
/* myddas_odbc.c */
#if defined MYDDAS_ODBC
void Yap_InitMYDDAS_ODBCPreds(void);
void Yap_InitBackMYDDAS_ODBCPreds(void);
#endif
/* myddas_odbc.c */
#if defined MYDDAS_SQLITE3
void Yap_InitMYDDAS_SQLITE3Preds(void);
void Yap_InitBackMYDDAS_SQLITE3Preds(void);
#endif
/* Myddas_shared.c */
#if defined USE_MYDDAS
void Yap_MYDDAS_delete_all_myddas_structs(void);
void Yap_InitMYDDAS_SharedPreds(void);
void Yap_InitBackMYDDAS_SharedPreds(void);
#endif
/* myddas_top_level.c */
#if defined MYDDAS_TOP_LEVEL && defined MYDDAS_MYSQL //&& defined HAVE_LIBREADLINE
void Yap_InitMYDDAS_TopLevelPreds(void);
#endif

View File

@@ -13,7 +13,7 @@ set( MYDDAS_SOURCES
myddas_shared.c
myddas_statistics.c
myddas_top_level.c
myddas_wkb2prolog.c )
)
set( MYDDAS_HEADERS
myddas.h
@@ -21,8 +21,7 @@ set( MYDDAS_HEADERS
myddas_statistics_structs.h
myddas_structs.h
myddas_top_level.c
myddas_types.h
myddas_wkb2prolog.c )
myddas_types.h )
set( MYDDAS_UTIL_SOURCES
myddas_util.c

View File

@@ -3,44 +3,46 @@
#ifdef USE_MYDDAS
/* myddas_initialization.c */
MYDDAS_GLOBAL myddas_init_initialize_myddas(void);
MYDDAS_UTIL_CONNECTION myddas_init_initialize_connection(void *,void *,MYDDAS_API,MYDDAS_UTIL_CONNECTION);
MYDDAS_UTIL_PREDICATE myddas_init_initialize_predicate(const char *, int, const char *,MYDDAS_UTIL_PREDICATE);
MYDDAS_GLOBAL myddas_init_initialize_myddas(void);
MYDDAS_UTIL_CONNECTION
myddas_init_initialize_connection(void *, void *, MYDDAS_API,
MYDDAS_UTIL_CONNECTION);
MYDDAS_UTIL_PREDICATE myddas_init_initialize_predicate(const char *, int,
const char *,
MYDDAS_UTIL_PREDICATE);
#ifdef MYDDAS_STATS
/* myddas_statistics.c */
MYDDAS_GLOBAL myddas_stats_initialize_global_stats(MYDDAS_GLOBAL);
MYDDAS_STATS_STRUCT myddas_stats_initialize_connection_stats(void);
void myddas_stats_delete_stats_list(MYDDAS_STATS_STRUCT);
MYDDAS_GLOBAL myddas_stats_initialize_global_stats(MYDDAS_GLOBAL);
MYDDAS_STATS_STRUCT myddas_stats_initialize_connection_stats(void);
void myddas_stats_delete_stats_list(MYDDAS_STATS_STRUCT);
#endif /* MYDDAS_STATS */
#ifdef MYDDAS_MYSQL
/* myddas_util.c */
void myddas_util_table_write(MYSQL_RES *);
void myddas_util_table_write(MYSQL_RES *);
#endif
Short myddas_util_connection_type(void *);
MYDDAS_UTIL_CONNECTION myddas_util_add_connection(void *,void *,MYDDAS_API);
MYDDAS_UTIL_CONNECTION myddas_util_search_connection(void *con);
MYDDAS_UTIL_CONNECTION myddas_util_add_connection(void *, void *, MYDDAS_API);
MYDDAS_UTIL_CONNECTION myddas_util_search_connection(void *);
void myddas_util_delete_connection(void *);
MYDDAS_UTIL_CONNECTION myddas_util_add_predicate(const char * ,Int , const char *,void *);
MYDDAS_UTIL_PREDICATE myddas_util_search_predicate(const char * ,Int , const char *);
void myddas_util_delete_predicate(MYDDAS_UTIL_PREDICATE);
void myddas_util_delete_connection(void *);
MYDDAS_UTIL_CONNECTION myddas_util_add_predicate(const char *, Int,
const char *, void *);
MYDDAS_UTIL_PREDICATE myddas_util_search_predicate(const char *, Int,
const char *);
void myddas_util_delete_predicate(MYDDAS_UTIL_PREDICATE);
/* Get's the number of queries to save */
UInt myddas_util_get_total_multi_queries_number(MYDDAS_UTIL_CONNECTION);
void myddas_util_set_total_multi_queries_number(MYDDAS_UTIL_CONNECTION,UInt);
#ifdef MYDDAS_ODBC
/* Return enviromment identifier*/
SQLHENV myddas_util_get_odbc_enviromment(SQLHDBC);
#endif
UInt myddas_util_get_total_multi_queries_number(MYDDAS_UTIL_CONNECTION);
void myddas_util_set_total_multi_queries_number(MYDDAS_UTIL_CONNECTION, UInt);
void * myddas_util_get_list_pred(MYDDAS_UTIL_CONNECTION);
void * myddas_util_get_pred_next(void *);
const char * myddas_util_get_pred_module(void *);
const char * myddas_util_get_pred_name(void *);
MyddasInt myddas_util_get_pred_arity(void *);
//DELETE THIS WHEN DB_STATS IS COMPLETED
MyddasInt get_myddas_top(void);
void *myddas_util_get_list_pred(MYDDAS_UTIL_CONNECTION);
void *myddas_util_get_pred_next(void *);
const char *myddas_util_get_pred_module(void *);
const char *myddas_util_get_pred_name(void *);
MyddasInt myddas_util_get_pred_arity(void *);
// DELETE THIS WHEN DB_STATS IS COMPLETED
MyddasInt get_myddas_top(void);
#ifdef DEBUG
void check_int(void);
@@ -50,30 +52,31 @@ void check_int(void);
/* myddas_mysql.c */
#if defined MYDDAS_MYSQL
void Yap_InitMYDDAS_MySQLPreds(void);
void Yap_InitBackMYDDAS_MySQLPreds(void);
void Yap_InitMYDDAS_MySQLPreds(void);
void Yap_InitBackMYDDAS_MySQLPreds(void);
#endif
/* myddas_odbc.c */
#if defined MYDDAS_ODBC
void Yap_InitMYDDAS_ODBCPreds(void);
void Yap_InitBackMYDDAS_ODBCPreds(void);
void Yap_InitMYDDAS_ODBCPreds(void);
void Yap_InitBackMYDDAS_ODBCPreds(void);
#endif
/* myddas_odbc.c */
#if defined MYDDAS_SQLITE3
void Yap_InitMYDDAS_SQLITE3Preds(void);
void Yap_InitBackMYDDAS_SQLITE3Preds(void);
void Yap_InitMYDDAS_SQLITE3Preds(void);
void Yap_InitBackMYDDAS_SQLITE3Preds(void);
#endif
/* Myddas_shared.c */
#if defined USE_MYDDAS
void Yap_MYDDAS_delete_all_myddas_structs(void);
void Yap_InitMYDDAS_SharedPreds(void);
void Yap_InitBackMYDDAS_SharedPreds(void);
void Yap_MYDDAS_delete_all_myddas_structs(void);
void Yap_InitMYDDAS_SharedPreds(void);
void Yap_InitBackMYDDAS_SharedPreds(void);
#endif
/* myddas_top_level.c */
#if defined MYDDAS_TOP_LEVEL && defined MYDDAS_MYSQL //&& defined HAVE_LIBREADLINE
void Yap_InitMYDDAS_TopLevelPreds(void);
#if defined MYDDAS_TOP_LEVEL && \
defined MYDDAS_MYSQL //&& defined HAVE_LIBREADLINE
void Yap_InitMYDDAS_TopLevelPreds(void);
#endif

View File

@@ -11,32 +11,34 @@
#endif
MYDDAS_GLOBAL
myddas_init_initialize_myddas(void){
myddas_init_initialize_myddas(void) {
MYDDAS_GLOBAL global = NULL;
/* We cannot call MYDDAS_MALLOC were because the global
register isn't yet initialized */
global = (MYDDAS_GLOBAL) malloc (sizeof(struct myddas_global));
global = (MYDDAS_GLOBAL)malloc(sizeof(struct myddas_global));
#ifdef DEBUGX
printf ("MALLOC %p %s %d\n",global,__FILE__,__LINE__);
printf("MALLOC %p %s %d\n", global, __FILE__, __LINE__);
#endif
global->myddas_top_connections = NULL;
#ifdef MYDDAS_TOP_LEVEL
global->myddas_top_level_connection = NULL;
#endif
#ifdef MYDDAS_STATS
global->myddas_statistics = (MYDDAS_GLOBAL_STATS) malloc (sizeof(struct myddas_global_stats));
global->myddas_statistics =
(MYDDAS_GLOBAL_STATS)malloc(sizeof(struct myddas_global_stats));
#ifdef DEBUG
printf ("MALLOC %p %s %d\n",global->myddas_statistics,__FILE__,__LINE__);
printf("MALLOC %p %s %d\n", global->myddas_statistics, __FILE__, __LINE__);
#endif
global->myddas_statistics->stats = NULL;
#endif
#ifdef DEBUG
/* We first malloc for this struct and the stats struct */
/* We first malloc for this struct and the stats struct */
#ifdef MYDDAS_STATS
global->malloc_called = 2;
global->memory_allocated = sizeof(struct myddas_global) + sizeof(struct myddas_global_stats);
global->memory_allocated =
sizeof(struct myddas_global) + sizeof(struct myddas_global_stats);
#else
global->malloc_called = 1;
global->memory_allocated = sizeof(struct myddas_global);
@@ -50,34 +52,32 @@ myddas_init_initialize_myddas(void){
/* Inserts the new node on the front of the list */
MYDDAS_UTIL_CONNECTION
myddas_init_initialize_connection(void *conn,void *enviromment,
MYDDAS_API api,
MYDDAS_UTIL_CONNECTION next){
myddas_init_initialize_connection(void *conn, void *enviromment, MYDDAS_API api,
MYDDAS_UTIL_CONNECTION next) {
CACHE_REGS
MYDDAS_UTIL_CONNECTION new = NULL;
MYDDAS_MALLOC(new,struct myddas_list_connection);
MYDDAS_MALLOC(new, struct myddas_list_connection);
if (new == NULL)
{
return NULL;
}
if (new == NULL) {
return NULL;
}
new->api = api;
new->predicates=NULL;
new->connection=conn;
new->odbc_enviromment=enviromment;
new->predicates = NULL;
new->connection = conn;
new->odbc_enviromment = enviromment;
/* It saves n queries, doing at once n+1 queries */
new->total_number_queries=0; //Default
new->actual_number_queries=0;
new->total_number_queries = 0; // Default
new->actual_number_queries = 0;
new->queries = NULL;
/* List integrity */
new->next=next;
new->previous=NULL;
new->next = next;
new->previous = NULL;
/* If there's already at least one node
on the list */
if (next != NULL)
next->previous=new;
next->previous = new;
#ifdef MYDDAS_STATS
new->stats = NULL;
@@ -88,26 +88,26 @@ myddas_init_initialize_connection(void *conn,void *enviromment,
MYDDAS_UTIL_PREDICATE
myddas_init_initialize_predicate(const char *pred_name, int pred_arity,
const char *pred_module, MYDDAS_UTIL_PREDICATE next){
const char *pred_module,
MYDDAS_UTIL_PREDICATE next) {
CACHE_REGS
MYDDAS_UTIL_PREDICATE new = NULL;
MYDDAS_MALLOC(new,struct myddas_list_preds);
MYDDAS_MALLOC(new, struct myddas_list_preds);
if (new == NULL)
{
return NULL;
}
new->pred_name=pred_name;
new->pred_arity=pred_arity;
new->pred_module=pred_module;
if (new == NULL) {
return NULL;
}
new->pred_name = pred_name;
new->pred_arity = pred_arity;
new->pred_module = pred_module;
/* List integrity */
new->next=next;
new->previous=NULL;
new->next = next;
new->previous = NULL;
/* If there's already at least one node
on the list */
if (next != NULL)
next->previous=new;
next->previous = new;
return new;
}

View File

@@ -706,9 +706,6 @@ void
init_myddas(void)
{
CACHE_REGS
#if defined MYDDAS_MYSQL
Yap_InitBackMYDDAS_MySQLPreds();
#endif
#if defined MYDDAS_ODBC
Yap_InitBackMYDDAS_ODBCPreds();
#endif
@@ -733,21 +730,6 @@ init_myddas(void)
#if defined MYDDAS_TOP_LEVEL && defined MYDDAS_MYSQL // && defined HAVE_LIBREADLINE
Yap_InitMYDDAS_TopLevelPreds();
#endif
#ifdef MYDDAS_MYSQL_INIT
if (yap_init->myddas) {
Yap_PutValue(AtomMyddasGoal,MkIntegerTerm(yap_init->myddas));
/* Mandatory Fields */
Yap_PutValue(AtomMyddasUser,MkAtomTerm(Yap_LookupAtom(yap_init->myddas_user)));
Yap_PutValue(AtomMyddasDB,MkAtomTerm(Yap_LookupAtom(yap_init->myddas_db)));
/* Non-Mandatory Fields */
if (yap_init->myddas_pass != NULL)
Yap_PutValue(AtomMyddasPass,MkAtomTerm(Yap_LookupAtom(yap_init->myddas_pass)));
if (yap_init->myddas_host != NULL)
Yap_PutValue(AtomMyddasHost,MkAtomTerm(Yap_LookupAtom(yap_init->myddas_host)));
}
#endif
#if USE_MYDDAS
#define stringify(X) _stringify(X)
#define _stringify(X) #X

View File

@@ -12,374 +12,265 @@
#include <mysql/mysql.h>
#endif /*MYDDAS_MYSQL*/
#include "myddas.h"
#include "myddas_util.h"
#ifdef MYDDAS_MYSQL
/* Auxilary function to table_write*/
static void
n_print(Int , char );
#endif
/* Type: MYSQL->1 ODBC->2*/
Short
myddas_util_connection_type(void *con){
MYDDAS_UTIL_CONNECTION con_node =
myddas_util_search_connection(con);
Short myddas_util_connection_type(void *con) {
MYDDAS_UTIL_CONNECTION con_node = myddas_util_search_connection(con);
if (con_node == NULL)
return 0;
return con_node->api;
// if (con_node->odbc_enviromment != NULL) /* ODBC */
// if (con_node->odbc_enviromment != NULL) /* ODBC */
// return 2;
//else
// else
// return 1;
}
MYDDAS_UTIL_PREDICATE
myddas_util_search_predicate(const char *pred_name, Int pred_arity,
const char *pred_module){
const char *pred_module) {
CACHE_REGS
MYDDAS_UTIL_PREDICATE pred=NULL;
MYDDAS_UTIL_CONNECTION top = Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections;
MYDDAS_UTIL_PREDICATE pred = NULL;
MYDDAS_UTIL_CONNECTION top =
Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections;
for (;top!=NULL;top=top->next)
{
if ((pred=myddas_util_find_predicate(pred_name,pred_arity,pred_module,top->predicates)))
return pred;
}
for (; top != NULL; top = top->next) {
if ((pred = myddas_util_find_predicate(pred_name, pred_arity, pred_module,
top->predicates)))
return pred;
}
return NULL;
}
/* When using this function, we must guarante that this predicate
it's unique */
MYDDAS_UTIL_CONNECTION
MYDDAS_UTIL_CONNECTION
myddas_util_add_predicate(const char *pred_name, Int pred_arity,
const char *pred_module, void *con){
MYDDAS_UTIL_CONNECTION node_con =
myddas_util_search_connection(con);
MYDDAS_UTIL_PREDICATE new =
myddas_init_initialize_predicate(pred_name,pred_arity,pred_module,node_con->predicates);
if (new == NULL)
{
myddas_util_error_message("Could not initialize predicate node",__LINE__,__FILE__);
return NULL;
}
node_con->predicates=new;
return node_con;
}
const char *pred_module, void *con) {
void
myddas_util_delete_predicate(MYDDAS_UTIL_PREDICATE to_delete){
MYDDAS_UTIL_CONNECTION node_con = myddas_util_search_connection(con);
MYDDAS_UTIL_PREDICATE new = myddas_init_initialize_predicate(
pred_name, pred_arity, pred_module, node_con->predicates);
if (new == NULL) {
myddas_util_error_message("Could not initialize predicate node", __LINE__,
__FILE__);
return NULL;
}
node_con->predicates = new;
return node_con;
}
void myddas_util_delete_predicate(MYDDAS_UTIL_PREDICATE to_delete) {
CACHE_REGS
if (to_delete->next != NULL)
to_delete->next->previous = to_delete->previous;
if (to_delete->previous != NULL)
to_delete->previous->next = to_delete->next;
else //First predicate of the predicate list
{
MYDDAS_UTIL_CONNECTION con_node = Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections;
for(;con_node != NULL; con_node = con_node->next)
if (con_node->predicates == to_delete)
break;
con_node->predicates = to_delete->next;
}
MYDDAS_FREE(to_delete,struct myddas_list_preds);
else // First predicate of the predicate list
{
MYDDAS_UTIL_CONNECTION con_node =
Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections;
for (; con_node != NULL; con_node = con_node->next)
if (con_node->predicates == to_delete)
break;
con_node->predicates = to_delete->next;
}
MYDDAS_FREE(to_delete, struct myddas_list_preds);
}
void
myddas_util_delete_connection(void *conn){
void myddas_util_delete_connection(void *conn) {
CACHE_REGS
MYDDAS_UTIL_CONNECTION to_delete = myddas_util_search_connection(conn);
if (to_delete == NULL)
if (to_delete == NULL)
return;
else
{
/* Removes the predicates list */
myddas_util_delete_predicate_list(to_delete->predicates);
else {
/* Removes the predicates list */
myddas_util_delete_predicate_list(to_delete->predicates);
#ifdef MYDDAS_STATS
/* Removes the stats list */
myddas_stats_delete_stats_list(to_delete->stats);
/* Removes the stats list */
myddas_stats_delete_stats_list(to_delete->stats);
#endif
/* List Integrety */
/* Is the last element of the list */
if ((to_delete->next) != NULL)
to_delete->next->previous = to_delete->previous;
/* Is the first element of the list */
if (to_delete == (Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections))
Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections = to_delete->next;
else
to_delete->previous->next=to_delete->next;
MYDDAS_FREE(to_delete,struct myddas_list_connection);
return;
}
/* List Integrety */
/* Is the last element of the list */
if ((to_delete->next) != NULL)
to_delete->next->previous = to_delete->previous;
/* Is the first element of the list */
if (to_delete == (Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections))
Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections = to_delete->next;
else
to_delete->previous->next = to_delete->next;
MYDDAS_FREE(to_delete, struct myddas_list_connection);
return;
}
}
MYDDAS_UTIL_CONNECTION
myddas_util_search_connection(void *conn){
MYDDAS_UTIL_CONNECTION
myddas_util_search_connection(void *conn) {
CACHE_REGS
MYDDAS_UTIL_CONNECTION list = Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections;
MYDDAS_UTIL_CONNECTION list =
Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections;
#ifdef MYDDAS_STATS
if (conn == 0) { /* We want all the statistics */
return list;
}
#endif
for (;list!=NULL;list=list->next)
for (; list != NULL; list = list->next)
if (list->connection == conn)
return list;
return NULL;
}
MYDDAS_UTIL_CONNECTION
myddas_util_add_connection(void *conn, void *enviromment, MYDDAS_API api){
CACHE_REGS
MYDDAS_UTIL_CONNECTION node=NULL;
MYDDAS_UTIL_CONNECTION temp=NULL;
if ((node = myddas_util_search_connection(conn)) != NULL)
{
return node;
}
//put the new connection node on the top of the list
temp = myddas_init_initialize_connection(conn,enviromment,api,Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections);
if (temp == NULL)
{
MYDDAS_UTIL_CONNECTION
myddas_util_add_connection(void *conn, void *enviromment, MYDDAS_API api) {
CACHE_REGS
MYDDAS_UTIL_CONNECTION node = NULL;
MYDDAS_UTIL_CONNECTION temp = NULL;
if ((node = myddas_util_search_connection(conn)) != NULL) {
return node;
}
// put the new connection node on the top of the list
temp = myddas_init_initialize_connection(
conn, enviromment, api,
Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections);
if (temp == NULL) {
#ifdef DEBUG
myddas_util_error_message("Could not initialize connection node",__LINE__,__FILE__);
#endif
return NULL;
}
myddas_util_error_message("Could not initialize connection node", __LINE__,
__FILE__);
#endif
return NULL;
}
Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections = temp;
return Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections;
}
#ifdef MYDDAS_ODBC
/* This function searches the MYDDAS list for odbc connections
If there isn't any, it returns NULL. This is a nice way to know
if there is any odbc connections left on the list*/
SQLHENV
myddas_util_get_odbc_enviromment(SQLHDBC connection){
CACHE_REGS
MYDDAS_UTIL_CONNECTION top = Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections;
for (;top != NULL;top=top->next)
if (top->connection == ((void *)connection))
return top->odbc_enviromment;
return NULL;
}
#endif
UInt
myddas_util_get_total_multi_queries_number(MYDDAS_UTIL_CONNECTION con){
UInt myddas_util_get_total_multi_queries_number(MYDDAS_UTIL_CONNECTION con) {
return con->total_number_queries;
}
void
myddas_util_set_total_multi_queries_number(MYDDAS_UTIL_CONNECTION con,
UInt number){
void myddas_util_set_total_multi_queries_number(MYDDAS_UTIL_CONNECTION con,
UInt number) {
con->total_number_queries = number;
}
#ifdef MYDDAS_MYSQL
/* Auxilary function to table_write*/
static void
n_print(Int n, char c)
{
for(;n>0;n--) printf("%c",c);
static void n_print(Int n, char c) {
for (; n > 0; n--)
printf("%c", c);
}
#endif
void myddas_util_error_message(char *message ,Int line,char *file){
void myddas_util_error_message(char *message, Int line, char *file) {
#ifdef DEBUG
printf ("ERROR: %s at line %d in file %s\n",message,(int)line,file);
printf("ERROR: %s at line %d in file %s\n", message, (int)line, file);
#else
printf ("ERROR: %s\n",message);
printf("ERROR: %s\n", message);
#endif
}
MYDDAS_UTIL_PREDICATE
myddas_util_find_predicate(const char *pred_name, Int pred_arity,
const char *pred_module, MYDDAS_UTIL_PREDICATE list){
const char *pred_module,
MYDDAS_UTIL_PREDICATE list) {
for(;list != NULL ; list = list->next)
if (pred_arity == list->pred_arity &&
!strcmp(pred_name,list->pred_name) &&
!strcmp(pred_module,list->pred_module))
for (; list != NULL; list = list->next)
if (pred_arity == list->pred_arity && !strcmp(pred_name, list->pred_name) &&
!strcmp(pred_module, list->pred_module))
return list;
return NULL;
}
void
myddas_util_delete_predicate_list(MYDDAS_UTIL_PREDICATE preds_list){
void myddas_util_delete_predicate_list(MYDDAS_UTIL_PREDICATE preds_list) {
CACHE_REGS
MYDDAS_UTIL_PREDICATE to_delete = NULL;
for (;preds_list != NULL;)
{
to_delete = preds_list;
preds_list = preds_list->next;
MYDDAS_FREE(to_delete,struct myddas_list_preds);
}
for (; preds_list != NULL;) {
to_delete = preds_list;
preds_list = preds_list->next;
MYDDAS_FREE(to_delete, struct myddas_list_preds);
}
return;
}
#ifdef MYDDAS_MYSQL
void
myddas_util_table_write(MYSQL_RES *res_set){
MYSQL_ROW row;
MYSQL_FIELD *fields;
Int i,f;
if (mysql_num_rows(res_set) == 0)
{
printf ("Empty Set\n");
return;
}
f = mysql_num_fields(res_set);
fields = mysql_fetch_field(res_set);
for(i=0;i<f;i++)
{
printf("+");
if (strlen(fields[i].name)>fields[i].max_length) fields[i].max_length=strlen(fields[i].name);
n_print(fields[i].max_length+2,'-');
}
printf("+\n");
for(i=0;i<f;i++)
{
printf("|");
printf(" %s ",fields[i].name);
n_print(fields[i].max_length - strlen(fields[i].name),' ');
}
printf("|\n");
for(i=0;i<f;i++)
{
printf("+");
n_print(fields[i].max_length+2,'-');
}
printf("+\n");
while ((row = mysql_fetch_row(res_set)) != NULL)
{
for(i=0;i<f;i++)
{
printf("|");
if (row[i] != NULL)
{
printf(" %s ",row[i]);
n_print(fields[i].max_length - strlen(row[i]),' ');
}
else
{
printf(" NULL ");
n_print(fields[i].max_length - 4,' ');
}
}
printf("|\n");
}
for(i=0;i<f;i++)
{
printf("+");
n_print(fields[i].max_length+2,'-');
}
printf("+\n");
}
#endif
//DELETE THIS WHEN DB_STATS IS COMPLETED
MyddasInt
get_myddas_top( void ){
// DELETE THIS WHEN DB_STATS IS COMPLETED
MyddasInt get_myddas_top(void) {
CACHE_REGS
if (Yap_REGS.MYDDAS_GLOBAL_POINTER == NULL)
return 0;
return (Int)Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections;
}
void *
myddas_util_get_pred_next(void *pointer){
MYDDAS_UTIL_PREDICATE temp = (MYDDAS_UTIL_PREDICATE) pointer;
return (void *) (temp->next);
void *myddas_util_get_pred_next(void *pointer) {
MYDDAS_UTIL_PREDICATE temp = (MYDDAS_UTIL_PREDICATE)pointer;
return (void *)(temp->next);
}
MyddasInt
myddas_util_get_pred_arity(void *pointer){
MYDDAS_UTIL_PREDICATE temp = (MYDDAS_UTIL_PREDICATE) pointer;
MyddasInt myddas_util_get_pred_arity(void *pointer) {
MYDDAS_UTIL_PREDICATE temp = (MYDDAS_UTIL_PREDICATE)pointer;
return temp->pred_arity;
}
const char *
myddas_util_get_pred_name(void *pointer){
MYDDAS_UTIL_PREDICATE temp = (MYDDAS_UTIL_PREDICATE) pointer;
const char *myddas_util_get_pred_name(void *pointer) {
MYDDAS_UTIL_PREDICATE temp = (MYDDAS_UTIL_PREDICATE)pointer;
return temp->pred_name;
}
const char *
myddas_util_get_pred_module(void *pointer){
MYDDAS_UTIL_PREDICATE temp = (MYDDAS_UTIL_PREDICATE) pointer;
const char *myddas_util_get_pred_module(void *pointer) {
MYDDAS_UTIL_PREDICATE temp = (MYDDAS_UTIL_PREDICATE)pointer;
return temp->pred_module;
}
void *
myddas_util_get_list_pred(MYDDAS_UTIL_CONNECTION node){
void *myddas_util_get_list_pred(MYDDAS_UTIL_CONNECTION node) {
return (void *)(node->predicates);
}
#ifdef DEBUG
void check_int( void ){
void check_int(void) {
CACHE_REGS
MYDDAS_UTIL_PREDICATE pred = NULL;
MYDDAS_UTIL_CONNECTION top = Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections;
for ( ; top!=NULL ; top=top->next)
{
printf ("***************\n");
printf ("===== top =====\n");
printf ("======= %p =====\n",top);
printf ("CONN: = %p =====\n",top->connection);
printf ("ENV : = %p =====\n",top->odbc_enviromment);
printf ("PRED: = %p =====\n",top->predicates);
printf ("======= %p =====\n",top->previous);
printf ("======= %p =====\n",top->next);
if (top->predicates != NULL)
{
printf ("\t******\n");
printf ("\t===== PREDICATES =====\n");
for (pred = top->predicates ; pred != NULL ; pred = pred->next)
{
printf ("\t--------------\n");
printf ("\t===== %p =====\n",pred);
printf ("\t===== %s =====\n",pred->pred_name);
printf ("\t===== %d =====\n",pred->pred_arity);
printf ("\t===== %s =====\n",pred->pred_module);
printf ("\t===== %p =====\n",pred->previous);
printf ("\t===== %p =====\n",pred->next);
}
}
MYDDAS_UTIL_CONNECTION top =
Yap_REGS.MYDDAS_GLOBAL_POINTER->myddas_top_connections;
for (; top != NULL; top = top->next) {
printf("***************\n");
printf("===== top =====\n");
printf("======= %p =====\n", top);
printf("CONN: = %p =====\n", top->connection);
printf("ENV : = %p =====\n", top->odbc_enviromment);
printf("PRED: = %p =====\n", top->predicates);
printf("======= %p =====\n", top->previous);
printf("======= %p =====\n", top->next);
if (top->predicates != NULL) {
printf("\t******\n");
printf("\t===== PREDICATES =====\n");
for (pred = top->predicates; pred != NULL; pred = pred->next) {
printf("\t--------------\n");
printf("\t===== %p =====\n", pred);
printf("\t===== %s =====\n", pred->pred_name);
printf("\t===== %d =====\n", pred->pred_arity);
printf("\t===== %s =====\n", pred->pred_module);
printf("\t===== %p =====\n", pred->previous);
printf("\t===== %p =====\n", pred->next);
}
}
}
return;
}
#endif

View File

@@ -1,32 +1,14 @@
#include "myddas_structs.h"
void myddas_util_error_message(char *message ,Int line,char *file);
void myddas_util_error_message(char *message, Int line, char *file);
/* Search for the predicate in the given predicate list*/
MYDDAS_UTIL_CONNECTION myddas_util_search_connection(void *conn);
UInt myddas_util_get_total_multi_queries_number(MYDDAS_UTIL_CONNECTION con);
MYDDAS_UTIL_CONNECTION
myddas_init_initialize_connection(void *conn,void *enviromment,
MYDDAS_API api,
MYDDAS_UTIL_CONNECTION next);
void myddas_util_set_total_multi_queries_number(MYDDAS_UTIL_CONNECTION con,
UInt number);
MYDDAS_UTIL_CONNECTION
myddas_util_add_connection(void *conn, void *enviromment, MYDDAS_API api);
MYDDAS_UTIL_PREDICATE
myddas_init_initialize_predicate(const char *pred_name, int pred_arity,
const char *pred_module, MYDDAS_UTIL_PREDICATE next);
MYDDAS_UTIL_PREDICATE
myddas_util_find_predicate(const char *pred_name, Int pred_arity,
const char *pred_module, MYDDAS_UTIL_PREDICATE list);
UInt
myddas_util_get_total_multi_queries_number(MYDDAS_UTIL_CONNECTION con);
void
myddas_util_set_total_multi_queries_number(MYDDAS_UTIL_CONNECTION con, UInt number);
//void myddas_util_table_write(MYSQL_RES *res_set);
void *myddas_util_get_pred_next(void *pointer);
@@ -34,8 +16,30 @@ MyddasInt myddas_util_get_pred_arity(void *pointer);
const char *myddas_util_get_pred_name(void *pointer);
void myddas_util_delete_predicate(MYDDAS_UTIL_PREDICATE to_delete);
const char *myddas_util_get_pred_module(void *pointer);
void *myddas_util_get_list_pred(MYDDAS_UTIL_CONNECTION node);
void myddas_util_delete_predicate_list(MYDDAS_UTIL_PREDICATE preds_list);
MYDDAS_UTIL_CONNECTION myddas_util_search_connection(void *con);
MYDDAS_UTIL_PREDICATE myddas_util_find_predicate(const char *pred_name,
Int pred_arity,
const char *pred_module,
MYDDAS_UTIL_PREDICATE list);
MYDDAS_UTIL_CONNECTION myddas_util_add_connection(void *conn, void *enviromment,
MYDDAS_API api);
void myddas_util_delete_connection(void *conn);
MYDDAS_UTIL_PREDICATE
myddas_init_initialize_predicate(const char *pred_name, int pred_arity,
const char *pred_module,
MYDDAS_UTIL_PREDICATE next);
MYDDAS_UTIL_CONNECTION
myddas_init_initialize_connection(void *conn, void *enviromment, MYDDAS_API api,
MYDDAS_UTIL_CONNECTION next);

View File

@@ -1,6 +1,21 @@
#include <string.h>
p#include <string.h>
#include <stdlib.h>
#include "Yap.h"
#include "cut_c.h"
MYDDAS_UTIL_CONNECTION
myddas_init_initialize_connection(void *conn, void *enviromment, MYDDAS_API api,
MYDDAS_UTIL_CONNECTION next);
MYDDAS_UTIL_CONNECTION
myddas_util_add_connection(void *conn, void *enviromment, MYDDAS_API api);
MYDDAS_UTIL_PREDICATE
myddas_init_initialize_predicate(const char *pred_name, int pred_arity,
const char *pred_module,
MYDDAS_UTIL_PREDICATE next);
MYDDAS_UTIL_PREDICATE
myddas_util_find_predicate(const char *pred_name, Int pred_arity,
const char *pred_module, MYDDAS_UTIL_PREDICATE list);

View File

@@ -1,25 +0,0 @@
#ifndef MYDDAS_WKB_H_
#define MYDDAS_WKB_H_
typedef char byte;
typedef unsigned int uint32;
#define WKBXDR 0
#define WKBNDR 1
#define WKBMINTYPE 1
#define WKBPOINT 1
#define WKBLINESTRING 2
#define WKBPOLYGON 3
#define WKBMULTIPOINT 4
#define WKBMULTILINESTRING 5
#define WKBMULTIPOLYGON 6
#define WKBGEOMETRYCOLLECTION 7
#define WKBMAXTYPE 7
#define WKBGEOMETRY 0
#endif /* MYDDAS_WKB_H_ */

View File

@@ -1,382 +0,0 @@
#if defined MYDDAS_MYSQL
#include <stdio.h>
#include <stdlib.h>
#include "Yap.h"
#include <netinet/in.h>
#include "myddas_wkb.h"
#include "myddas_wkb2prolog.h"
static void readswap4(uint32 *buf);
static void readswap8(double *buf);
static byte get_hostbyteorder(void);
static byte get_inbyteorder(void);
static uint32 get_wkbType(void);
static Term get_point(char *functor USES_REGS);
static Term get_linestring(char *functor);
static Term get_polygon(char *functor);
static Term get_geometry(uint32 type);
static int swaporder;
static byte inbyteorder, hostbyteorder;
static byte *cursor;
Term wkb2prolog(char *wkb) {
uint32 type;
cursor = wkb;
/*ignore the SRID 4 bytes*/
cursor += 4;
/*byteorder*/
hostbyteorder = get_hostbyteorder();
inbyteorder = get_inbyteorder();
swaporder = 0;
if ( hostbyteorder != inbyteorder )
swaporder = 1;
type = get_wkbType();
return get_geometry(type);
}
static byte get_hostbyteorder(void){
uint16_t host = 5;
uint16_t net;
net = htons(host);
if ( net == host )
return(WKBXDR);
else
return(WKBNDR);
}
static byte get_inbyteorder(void){
byte b = cursor[0];
if (b != WKBNDR && b != WKBXDR) {
fprintf(stderr, "Unknown byteorder: %d\n",b);
exit(0);
}
cursor++;
return(b);
}
static uint32 get_wkbType(void){
uint32 u;
/* read the type */
readswap4(&u);
if (u > WKBMAXTYPE || u < WKBMINTYPE) {
fprintf(stderr, "Unknown type: %d\n",u);
exit(0);
}
return(u);
}
static void readswap4(uint32 *buf){
((byte *) buf)[0] = cursor[0];
((byte *) buf)[1] = cursor[1];
((byte *) buf)[2] = cursor[2];
((byte *) buf)[3] = cursor[3];
if ( swaporder ) {
if ( inbyteorder == WKBXDR ) {
*buf = (uint32)ntohl((u_long)*buf);
} else {
byte u[4];
u[0] = ((byte *) buf)[3];
u[1] = ((byte *) buf)[2];
u[2] = ((byte *) buf)[1];
u[3] = ((byte *) buf)[0];
((byte *) buf)[0] = u[0];
((byte *) buf)[1] = u[1];
((byte *) buf)[2] = u[2];
((byte *) buf)[3] = u[3];
}
}
cursor += 4;
}
static void readswap8(double *buf) {
((byte *) buf)[0] = cursor[0];
((byte *) buf)[1] = cursor[1];
((byte *) buf)[2] = cursor[2];
((byte *) buf)[3] = cursor[3];
((byte *) buf)[4] = cursor[4];
((byte *) buf)[5] = cursor[5];
((byte *) buf)[6] = cursor[6];
((byte *) buf)[7] = cursor[7];
if ( swaporder ) {
if ( inbyteorder == WKBXDR ) {
u_long u[2];
u[0] = ((u_long *) buf)[0];
u[1] = ((u_long *) buf)[1];
((u_long *) buf)[1] = ntohl(u[0]);
((u_long *) buf)[0] = ntohl(u[1]);
} else {
byte u[8];
u[0] = ((byte *) buf)[7];
u[1] = ((byte *) buf)[6];
u[2] = ((byte *) buf)[5];
u[3] = ((byte *) buf)[4];
u[4] = ((byte *) buf)[3];
u[5] = ((byte *) buf)[2];
u[6] = ((byte *) buf)[1];
u[7] = ((byte *) buf)[0];
((byte *) buf)[0] = u[0];
((byte *) buf)[1] = u[1];
((byte *) buf)[2] = u[2];
((byte *) buf)[3] = u[3];
((byte *) buf)[4] = u[4];
((byte *) buf)[5] = u[5];
((byte *) buf)[6] = u[6];
((byte *) buf)[7] = u[7];
}
}
cursor += 8;
}
static Term get_point(char *func USES_REGS){
Term args[2];
Functor functor;
double d;
if(func == NULL)
/*functor "," => (_,_)*/
functor = Yap_MkFunctor(Yap_LookupAtom(","), 2);
else
functor = Yap_MkFunctor(Yap_LookupAtom(func), 2);
/* read the X */
readswap8(&d);
args[0] = MkFloatTerm(d);
/* read the Y */
readswap8(&d);
args[1] = MkFloatTerm(d);
return Yap_MkApplTerm(functor, 2, args);
}
static Term get_linestring(char *func){
CACHE_REGS
Term *c_list;
Term list;
Functor functor;
uint32 n;
int i;
/* read the number of vertices */
readswap4(&n);
/* space for arguments */
c_list = (Term *) calloc(sizeof(Term),n);
for ( i = 0; i < n; i++) {
c_list[i] = get_point(NULL PASS_REGS);
}
list = MkAtomTerm(Yap_LookupAtom("[]"));
for (i = n - 1; i >= 0; i--) {
list = MkPairTerm(c_list[i],list);
}
if(func == NULL)
return list;
else{
functor = Yap_MkFunctor(Yap_LookupAtom(func), 1);
return Yap_MkApplTerm(functor, 1, &list);
}
}
static Term get_polygon(char *func){
CACHE_REGS
uint32 r;
int i;
Functor functor;
Term *c_list;
Term list;
/* read the number of rings */
readswap4(&r);
/* space for rings */
c_list = (Term *) calloc(sizeof(Term),r);
for ( i = 0; i < r; i++ ) {
c_list[i] = get_linestring(NULL);
}
list = MkAtomTerm(Yap_LookupAtom("[]"));
for (i = r - 1; i >= 0; i--) {
list = MkPairTerm(c_list[i],list);
}
if(func == NULL)
return list;
else{
functor = Yap_MkFunctor(Yap_LookupAtom("polygon"), 1);
return Yap_MkApplTerm(functor, 1, &list);
}
}
static Term get_geometry(uint32 type){
CACHE_REGS
switch(type) {
case WKBPOINT:
return get_point("point" PASS_REGS);
case WKBLINESTRING:
return get_linestring("linestring");
case WKBPOLYGON:
return get_polygon("polygon");
case WKBMULTIPOINT:
{
uint32 n;
int i;
Functor functor;
Term *c_list;
Term list;
/* read the number of points */
readswap4(&n);
/* space for points */
c_list = (Term *) calloc(sizeof(Term),n);
for ( i = 0; i < n; i++ ) {
/* read (and ignore) the byteorder and type */
get_inbyteorder();
get_wkbType();
c_list[i] = get_point(NULL PASS_REGS);
}
list = MkAtomTerm(Yap_LookupAtom("[]"));
for (i = n - 1; i >= 0; i--) {
list = MkPairTerm(c_list[i],list);
}
functor = Yap_MkFunctor(Yap_LookupAtom("multipoint"), 1);
return Yap_MkApplTerm(functor, 1, &list);
}
case WKBMULTILINESTRING:
{
uint32 n;
int i;
Functor functor;
Term *c_list;
Term list;
/* read the number of polygons */
readswap4(&n);
/* space for polygons*/
c_list = (Term *) calloc(sizeof(Term),n);
for ( i = 0; i < n; i++ ) {
/* read (and ignore) the byteorder and type */
get_inbyteorder();
get_wkbType();
c_list[i] = get_linestring(NULL);
}
list = MkAtomTerm(Yap_LookupAtom("[]"));
for (i = n - 1; i >= 0; i--) {
list = MkPairTerm(c_list[i],list);
}
functor = Yap_MkFunctor(Yap_LookupAtom("multilinestring"), 1);
return Yap_MkApplTerm(functor, 1, &list);
}
case WKBMULTIPOLYGON:
{
uint32 n;
int i;
Functor functor;
Term *c_list;
Term list;
/* read the number of polygons */
readswap4(&n);
/* space for polygons*/
c_list = (Term *) calloc(sizeof(Term),n);
for ( i = 0; i < n; i++ ) {
/* read (and ignore) the byteorder and type */
get_inbyteorder();
get_wkbType();
c_list[i] = get_polygon(NULL);
}
list = MkAtomTerm(Yap_LookupAtom("[]"));
for (i = n - 1; i >= 0; i--) {
list = MkPairTerm(c_list[i],list);
}
functor = Yap_MkFunctor(Yap_LookupAtom("multipolygon"), 1);
return Yap_MkApplTerm(functor, 1, &list);
}
case WKBGEOMETRYCOLLECTION:
{
uint32 n;
int i;
Functor functor;
Term *c_list;
Term list;
/* read the number of geometries */
readswap4(&n);
/* space for geometries*/
c_list = (Term *) calloc(sizeof(Term),n);
for ( i = 0; i < n; i++ ) {
get_inbyteorder();
c_list[i] = get_geometry(get_wkbType());
}
list = MkAtomTerm(Yap_LookupAtom("[]"));
for (i = n - 1; i >= 0; i--) {
list = MkPairTerm(c_list[i],list);
}
functor = Yap_MkFunctor(Yap_LookupAtom("geometrycollection"), 1);
return Yap_MkApplTerm(functor, 1, &list);
}
}
return MkAtomTerm(Yap_LookupAtom("[]"));
}
#endif /*MYDDAS_MYSQL*/

View File

@@ -1,6 +0,0 @@
#ifndef MYDDAS_WKB2PROLOG_H_
# define MYDDAS_WKB2PROLOG_H_
Term wkb2prolog(char *wkb) ;
#endif /* !MYDDAS_WKB2PROLOG_H_ */

View File

@@ -1,7 +1,10 @@
set( YAPMYSQL_SOURCES
myddas_mysql.c
)
myddas_util.c
myddas_util.c
myddas_wkb2prolog.c
)
set(SO_MAJOR 1)
set(SO_MINOR 0)
@@ -19,12 +22,8 @@ macro_log_feature (MYSQL_FOUND "MySQL"
# MYSQL_FOUND - True if MySQL found.
add_definitions (-DMYDDAS_MYSQL=1)
add_library (Yapmysql SHARED ${YAPMYSQL_SOURCES})
target_link_libraries(Yapmysql myddas libYap)
target_link_libraries(Yapmysql ${MYSQL_LIBRARIES} libYap)
include_directories (${MYSQL_INCLUDE_DIR} ..)
else()
add_definitions (-DMYDDAS_MYSQL=0)
endif (MYSQL_FOUND)
set_target_properties (Yapmysql PROPERTIES
POSITION_INDEPENDENT_CODE ON
VERSION "${SO_MAJOR}.${SO_MINOR}.${SO_PATCH}"
@@ -36,6 +35,10 @@ set_target_properties (Yapmysql PROPERTIES
LIBRARY DESTINATION ${libdir}
)
else()
add_definitions (-DMYDDAS_MYSQL=0)
endif (MYSQL_FOUND)
cmake_dependent_option (USE_MYDDAS_top_level
"enable the MYDDAS top-level (REPL) support for MySQL" OFF
'USE_MYDDAS AND MYSQL_FOUND' OFF)

View File

@@ -25,6 +25,7 @@
#include "Yatom.h"
#include "cut_c.h"
#include "myddas_structs.h"
#include "myddas_util.h"
#ifdef MYDDAS_STATS
#include "myddas_statistics.h"
#endif

View File

@@ -15,87 +15,75 @@
* *
*************************************************************************/
#include "Yap.h"
#include <string.h>
#include <stdlib.h>
#include <mysql/mysql.h>
#include <myddas_util.h>
#ifdef MYDDAS_MYSQL
/* Auxilary function to table_write*/
static void n_print(Int, char);
#endif
/* Auxilary function to table_write*/
static void
n_print(Int , char );
/* Auxilary function to table_write*/
static void
n_print(Int n, char c)
{
for(;n>0;n--) printf("%c",c);
static void n_print(Int n, char c) {
for (; n > 0; n--)
printf("%c", c);
}
void
myddas_util_table_write(MYSQL_RES *res_set){
void myddas_util_table_write(MYSQL_RES *res_set) {
MYSQL_ROW row;
MYSQL_FIELD *fields;
Int i,f;
Int i, f;
if (mysql_num_rows(res_set) == 0)
{
printf ("Empty Set\n");
return;
}
if (mysql_num_rows(res_set) == 0) {
printf("Empty Set\n");
return;
}
f = mysql_num_fields(res_set);
fields = mysql_fetch_field(res_set);
for(i=0;i<f;i++)
{
for (i = 0; i < f; i++) {
printf("+");
if (strlen(fields[i].name)>fields[i].max_length) fields[i].max_length=strlen(fields[i].name);
n_print(fields[i].max_length+2,'-');
if (strlen(fields[i].name) > fields[i].max_length)
fields[i].max_length = strlen(fields[i].name);
n_print(fields[i].max_length + 2, '-');
}
printf("+\n");
for(i=0;i<f;i++)
{
for (i = 0; i < f; i++) {
printf("|");
printf(" %s ",fields[i].name);
n_print(fields[i].max_length - strlen(fields[i].name),' ');
}
printf(" %s ", fields[i].name);
n_print(fields[i].max_length - strlen(fields[i].name), ' ');
}
printf("|\n");
for(i=0;i<f;i++)
{
for (i = 0; i < f; i++) {
printf("+");
n_print(fields[i].max_length+2,'-');
n_print(fields[i].max_length + 2, '-');
}
printf("+\n");
while ((row = mysql_fetch_row(res_set)) != NULL)
{
for(i=0;i<f;i++)
{
printf("|");
if (row[i] != NULL)
{
printf(" %s ",row[i]);
n_print(fields[i].max_length - strlen(row[i]),' ');
}
else
{
printf(" NULL ");
n_print(fields[i].max_length - 4,' ');
}
}
printf("|\n");
}
for(i=0;i<f;i++)
{
printf("+");
n_print(fields[i].max_length+2,'-');
while ((row = mysql_fetch_row(res_set)) != NULL) {
for (i = 0; i < f; i++) {
printf("|");
if (row[i] != NULL) {
printf(" %s ", row[i]);
n_print(fields[i].max_length - strlen(row[i]), ' ');
} else {
printf(" NULL ");
n_print(fields[i].max_length - 4, ' ');
}
}
printf("|\n");
}
for (i = 0; i < f; i++) {
printf("+");
n_print(fields[i].max_length + 2, '-');
}
printf("+\n");
}

File diff suppressed because it is too large Load Diff

View File

@@ -806,6 +806,8 @@
]).
#ifdef MYDDAS_MYSQL
:- load_foreign_files([], [], init_mysql).
:- use_module(myddas_mysql,[
db_my_result_set/1,
db_datalog_describe/1,

View File

@@ -21,16 +21,16 @@ if (POSTGRES_FOUND)
add_definitions (-DMYDDAS_POSTGRES=1)
target_link_libraries(Yappostgres libYap ${POSTGRES_LIBRARIES})
include_directories (${POSTGRES_INCLUDE_DIRECTORIES} ..)
else()
add_definitions (-DMYDDAS_POSTGRES=0)
endif (POSTGRES_FOUND)
set_target_properties (Yappostgres PROPERTIES
POSITION_INDEPENDENT_CODE ON
VERSION "${SO_MAJOR}.${SO_MINOR}.${SO_PATCH}"
SOVERSION ${SO_MAJOR}
set_target_properties (Yappostgres PROPERTIES
POSITION_INDEPENDENT_CODE ON
VERSION "${SO_MAJOR}.${SO_MINOR}.${SO_PATCH}"
SOVERSION ${SO_MAJOR}
)
install(TARGETS Yappostgres
LIBRARY DESTINATION ${libdir}
)
else()
add_definitions (-DMYDDAS_POSTGRES=0)
endif (POSTGRES_FOUND)

View File

@@ -3,7 +3,6 @@ set( YAPSQLITE3_SOURCES
myddas_sqlite3.c
)
add_library (Yapsqlite3 SHARED ${YAPSQLITE3_SOURCES})
macro_optional_find_package(SQLITE3 ON)
macro_log_feature (SQLITE3_FOUND "Sqlite3"
@@ -14,19 +13,19 @@ if (SQLITE3_FOUND)
# SQLITE3_INCLUDE_DIRECTORIES, where to find sql.h
# SQLITE3_LIBRARIES, the libraries to link against to use SQLITE3
# SQLITE3_FOUND. If false, you cannot build anything that requires Sqlite3.
add_definitions (target PUBLIC YapMyddasUtils Yapsqlite3 MYDDAS_SQLITE3=1)
add_library (Yapsqlite3 SHARED ${YAPSQLITE3_SOURCES})
add_definitions (-DMYDDAS_SQLITE3=1)
target_link_libraries(Yapsqlite3 ${SQLITE3_LIBRARIES} libYap)
include_directories (${SQLITE3_INCLUDE_DIRECTORIES} ..)
include_directories (${SQLITE3_INCLUDE_DIRECTORIES} .. )
endif (SQLITE3_FOUND)
set_target_properties (Yapsqlite3 PROPERTIES
set_target_properties (Yapsqlite3 PROPERTIES
POSITION_INDEPENDENT_CODE ON
VERSION "${SO_MAJOR}.${SO_MINOR}.${SO_PATCH}"
SOVERSION ${SO_MAJOR}
)
)
install(TARGETS Yapsqlite3
LIBRARY DESTINATION ${libdir}
)
endif (SQLITE3_FOUND)

File diff suppressed because it is too large Load Diff