Author(s): D. Cabeza, M. Carro, I. Caballero, and M. Hermenegildo..
Version: 1.5#118 (2000/4/19, 18:13:43 CEST)
Version of last change: 1.3#53 (1999/9/15, 23:37:55 MEST)
This library provides a socket-based interface to SQL Databases, using the database mediator server ODBC interface developed by C. Taboch and I. Caballero. The interface currently works for databases running in Win95/NT machines via ODBC. This low-level interface was defined with two goals in mind:
In order to allow the flexibility mentioned above, a socket (TCP/IP) client-server architecture was chosen. The interface has two main components:
Example:
:- use_module(library('persdb_sql/db_client')).
:- use_module(library(format)).
:- use_module(library(lists)).
:- multifile issue_debug_messages/1.
:- data issue_debug_messages/1.
issue_debug_messages('db_client').
main0:- %% getting the tables existing in a database
odbc_connect('r2d5.dia.fi.upm.es':2020,Stream),
db_login(Stream,'DaletDemo',dalet_admin,dalet_admin,
%% db_login(Stream,'ASA 6.0 Sample',dba,sql,
dbconnection(Stream,DbHandle)),
%% db_get_tables(dbconnection(Stream,DbHandle),TablesList),
db_table_types(dbconnection(Stream,DbHandle),'Titles',AttList),
db_logoff(dbconnection(Stream,DbHandle)),
odbc_disconnect(Stream),
format("Results: ~w \n",AttList).
main1 :- %% accessing the whole table in one go
odbc_connect('r2d5.dia.fi.upm.es':2020,Stream),
db_login(Stream,'ASA 6.0 Sample',dba,sql,Conn),
db_eval_sql(Conn,"SELECT fname,lname,address from ""DBA"".customer
WHERE ((Id>100) AND (Id<105))",Term),
write(Term), nl,nl,nl,nl,nl,nl,nl,nl,nl,nl,nl,nl,nl,nl,nl,
functor(Term,X,_Y),
write(X),nl,
Term=..[_|L],
write('That is L'),nl,
write(L),nl,L=[M],length(M,N),write(N),
% db_eval_sql(Conn,"SELECT id,name,description,color from
% ""DBA"".product WHERE size='One size fits all'
% OR size='Large'",Term2),
% write(Term2), nl,
db_logoff(Conn),
odbc_disconnect(Stream).
main2:- %% accessing tuples one by one
odbc_connect('r2d5.dia.fi.upm.es':2020,Stream),
db_login(Stream,'ASA 6.0 Sample',dba,sql,Conn),
db_stmt_handle(Conn,
"SELECT fname,lname,address from ""DBA"".customer
WHERE ((Id>100) AND (Id<105))",QueryConn),
db_one_tuple(QueryConn,Answer),
format("First Tuple: ~w \n",Answer),
db_one_tuple(QueryConn,Answer2),
format("Second Tuple: ~w \n",Answer2),
db_logoff(Conn),
odbc_disconnect(Stream).
main3:- %% bringing tuples (one to one) from Literature Database
%% TO SEE : check it
odbc_connect('r2d5.dia.fi.upm.es':2020,Stream),
db_login(Stream,'Literature',dba,sql,Conn),
db_stmt_handle(Conn,"SELECT * FROM AUTHORS ORDER BY ID",QueryConn),
print_all_one_by_one(QueryConn),
db_logoff(Conn),
odbc_disconnect(Stream).
print_all_one_by_one(QueryConn):-
db_one_tuple(QueryConn,Answer),
Answer\=[],
!,
format(" ~w \n",Answer),
print_all_one_by_one(QueryConn).
print_all_one_by_one(_QueryConn):-
write(' Finished fetching query statement.'),
nl.
main4:- %% inserting a tuple into the Literature database
odbc_connect('r2d5.dia.fi.upm.es':2020,Stream),
db_login(Stream,'Literature',dba,sql,Conn),
db_stmt_handle(Conn,
"INSERT INTO AUTHORS values ('Martin Gaite',
'Carmen',10,'1910-7-10 00:00:00:000')",_QueryConn),
db_logoff(Conn),
odbc_disconnect(Stream).
main5:- %% creating a view
odbc_connect('r2d5.dia.fi.upm.es':2020,Stream),
db_login(Stream,'Literature',dba,sql,Conn),
db_stmt_handle(Conn,
"CREATE VIEW AntoniosDateOfBirth AS SELECT
LastName,Date_of_birth FROM
AUTHORS where FirstName='Antonio';",_QueryConn),
db_logoff(Conn),
odbc_disconnect(Stream).
main6:- %% printing the view
odbc_connect('r2d5.dia.fi.upm.es':2020,Stream),
db_login(Stream,'Literature',dba,sql,Conn),
db_eval_sql(Conn,"select * from AntoniosDateOfBirth",Term),
write(Term),
db_logoff(Conn),
odbc_disconnect(Stream).
main7:- %% dropping a view
odbc_connect('r2d5.dia.fi.upm.es':2020,Stream),
db_login(Stream,'Literature',dba,sql,Conn),
db_eval_sql(Conn,"DROP VIEW AntoniosDateOfBirth",Term),
write(Term),
db_logoff(Conn),
odbc_disconnect(Stream).
db_client):- use_module(library(db_client)).
odbc_connect/2,
db_login/5,
db_eval_sql/3,
db_stmt_handle/3,
db_one_tuple/2,
db_get_tables/2,
db_table_types/3,
db_logoff/1,
odbc_disconnect/1,
match_string/3.
socketname/1,
dbname/1,
user/1,
passwd/1,
dbconnection/1,
answertableterm/1,
tuple/1,
dbqueryconnection/1,
answertupleterm/1.
db_client)
Usage: odbc_connect(+DbAddress,-(Stream))
DbAddress, which should be the address of a
database mediator server. Stream is the identifier of the corresponding Prolog stream. It is simply a call to
connect_to_socket/3
+DbAddress is a structure describing a complete TCP/IP port address.
(db_client:socketname/1)
-(Stream) is an open stream.
(streams_basic:stream/1)
Usage: db_login(+Stream,+DbName,+User,+Passwd,-(DbConnection))
DbName with user User and password Passwd via connection Stream. DbConnection contains the identifier of the session, to be used in the calls to other predicates defining the interface. It fails and display an error message if the login is not succesfully completed.
+Stream is an open stream.
(streams_basic:stream/1)
+DbName is the identifier of an ODBC database.
(db_client:dbname/1)
+User is a user name in the ODBC database.
(db_client:user/1)
+Passwd is the password for the user name in the ODBC database.
(db_client:passwd/1)
-(DbConnection) a unique identifier of a database session connection.
(db_client:dbconnection/1)
socketname(IPAddress:PortNumber) :-
atm(IPAddress),
int(PortNumber).
Usage: socketname(IPP)
IPP is a structure describing a complete TCP/IP port address.
dbname(DBId) :-
atm(DBId).
Usage: dbname(DBId)
DBId is the identifier of an ODBC database.
user(User) :-
atm(User).
Usage: user(User)
User is a user name in the ODBC database.
passwd(Passwd) :-
atm(Passwd).
Usage: passwd(Passwd)
Passwd is the password for the user name in the ODBC database.
dbconnection(dbconnection(DbStream,DbHandle)) :-
stream(DbStream),
dbhandle(DbHandle).
Usage: dbconnection(H)
H a unique identifier of a database session connection.
Usage: db_eval_sql(+DbConnection,+Sentence,-(AnswerTableTerm))
Sentence in database session DbConnection. AnswerTableTerm is the response. If a wrong answer is obtained, AnswerTableTerm will indicate the error (see
answertableterm for details).
+DbConnection a unique identifier of a database session connection.
(db_client:dbconnection/1)
+Sentence is a string of SQL code.
(db_client:sqlstring/1)
-(AnswerTableTerm) is a response from the ODBC database interface.
(db_client:answertableterm/1)
Represents the types of responses that will be returned from the ODBC database interface. These can be a set of answer tuples, or the atom ok in case of a successful addition or deletion.
Usage: answertableterm(AT)
AT is a response from the ODBC database interface.
tuple(T) :-
list(T,atm).
Usage: tuple(T)
T is a tuple of values from the ODBC database interface.
Usage: db_stmt_handle(+DbConnection,+Sentence,-(DbQueryConnection))
Sentence in database session DbConnection. If Sentence is a succesfull selection, DbQueryConnection is a handle to the set of tuples produced by this selection. The individual members of this set can then be accessed via DbQueryConnection using the
db_one_tuple/2 predicate. If Sentence is not succesfull or is not a selection, DbQueryConnection will contain the answer received.
+DbConnection a unique identifier of a database session connection.
(db_client:dbconnection/1)
+Sentence is a string of SQL code.
(db_client:sqlstring/1)
-(DbQueryConnection) is a unique identifier of a query answer in a database session connection.
(db_client:dbqueryconnection/1)
dbqueryconnection(dbqueryconnection(DbStream,DbHandle,StmtHandle)) :-
stream(DbStream),
dbhandle(DbHandle),
stmthandle(StmtHandle).
Usage: dbqueryconnection(H)
H is a unique identifier of a query answer in a database session connection.
Usage: db_one_tuple(+DbQueryConnection,-(TupleTerm))
TupleTerm represents the last tuple read from handle DbQueryConnection. Will be an empty list if all the answers have already been read. It displays an error if any unformatted string is fetched.
+DbQueryConnection is a unique identifier of a query answer in a database session connection.
(db_client:dbqueryconnection/1)
-(TupleTerm) is a predicate containing a tuple.
(db_client:answertupleterm/1)
answertupleterm([]).
answertupleterm(tup(T)) :-
tuple(T).
Usage: answertupleterm(X)
X is a predicate containing a tuple.
Usage: db_get_tables(+DbConnection,-(Tables))
Tables contains the tables available in DbConnection.
+DbConnection a unique identifier of a database session connection.
(db_client:dbconnection/1)
-(Tables) is a list of atms.
(basic_props:list/2)
Usage: db_table_types(+DbConnection,+Table,-(AttrTypes))
AttrTypes are the attributes and types of Table in DbConnection.
+DbConnection a unique identifier of a database session connection.
(db_client:dbconnection/1)
+Table is an atom.
(basic_props:atm/1)
-(AttrTypes) is a list.
(basic_props:list/1)
Usage: db_logoff(+DbConnection)
DbConnection. It fails and display an error message if the login is not succesfully completed.
+DbConnection a unique identifier of a database session connection.
(db_client:dbconnection/1)
Usage: odbc_disconnect(+Stream)
No further documentation available for this predicate.
db_client)
dbhandle(H) :-
string(H).
Usage: dbhandle(H)
H is the internal database identifier (handle) of a database session.
stmthandle(H) :-
string(H).
Usage: stmthandle(H)
H is the internal statement identifier (handle) of a query answer in a database session connection.
db_client)Go to the first, previous, next, last section, table of contents.