Go to the first, previous, next, last section, table of contents.


Prolog to SQL translator

Author(s): C. Draxler. Adapted by M. Hermenegildo and I. Caballero.

Version: 1.5#118 (2000/4/19, 18:13:43 CEST)

Version of last change: 0.9#96 (1999/5/21, 19:53:48 MEST)

This library performs translation of Prolog queries into SQL. The code is an adaptation for Ciao of the Prolog to SQL compiler written by Christoph Draxler, CIS Centre for Information and Speech Processing, Ludwig-Maximilians-University Munich, draxler@cis.uni-muenchen.de, Version 1.1. Many thanks to Christoph for allowing us to include this adaptation of his code with Ciao.

The translator needs to know the correspondence between Prolog predicates and the SQL tables in the database. To this end this module exports two multifile predicates, relation/3 and attribute/4. See the description of these predicates for details on how such correspondance is specified.

The main entry points to the translator are pl2sqlstring/3 and pl2sqlterm/3. Details on the types of queries allowed can be found in the description of these predicates.

Example: the following program would print out a term representing the SQL query corresponding to the given Prolog query:

:- use_module(library('persdb_sql/pl2sql')).
:- use_module(library(strings)).

:- multifile [relation/3,attribute/4].
:- data [relation/3,attribute/4].

relation(product,3,'PRODUCT').
attribute(1,'PRODUCT','ID',int).
attribute(2,'PRODUCT','QUANTITY',int).
attribute(3,'PRODUCT','NAME',string).

main :- 
     pl2sqlstring( f(L,K), 
          ((product(L,N,a); product(L,N,b)),
           \+ product(2,3,b), 
           L + 2 > avg(Y, Z^product(Z,Y,a)),
           K is N + max(X, product(X,2,b))
           ), T),
     write_string(T).
     
%%     printqueries(T).

Note: while the translator can be used directly in programs, it is more convenient to use a higher-level abstraction: persistent predicates (implemented in the persdb library). The notion of persistent predicates provides a completely transparent interface between Prolog and relational databases. When using this library, the Prolog to SQL translation is called automatically as needed.

Usage and interface (pl2sql)

Documentation on exports (pl2sql)

PREDICATE: pl2sqlstring/3:

Usage: pl2sqlstring(+ProjectionTerm,+DatabaseGoal,-(SQLQueryString))

REGTYPE: querybody/1:

DBGoal is a goal meant to be executed in the external database. It can be a complex term containing conjunctions, disjunctions, and negations, of:

The binding of variables follows Prolog rules:

Database arithmetic expressions may contain:

In addition, variables can be existentially quantified using ^/2 (in a similar way to how it is done in setof/3).

Note that it is assumed that the arithmetic operators in Prolog and SQL are the same, i.e., + is addition in Prolog and in SQL, etc.

Usage: querybody(DBGoal)

REGTYPE: projterm/1:

DBProjTerm is a term onto which the result of a database query code is (in a similar way to the first argument of setof/3)).

A ProjectionTerm must meet the following restrictions:

Usage: projterm(DBProjTerm)

REGTYPE: sqlstring/1:
sqlstring(S) :-
        string(S).

Usage: sqlstring(S)

PREDICATE: pl2sqlterm/3:

Usage: pl2sqlterm(+ProjectionTerm,+DatabaseGoal,-(SQLQueryTerm))

PREDICATE: printqueries/1:

Usage: printqueries(SQLTermList)

PREDICATE: sqlterm2string/2:

Usage: sqlterm2string(+Queries,-(QueryString))

(UNDOC_REEXPORT): sqltype/1:

Imported from sqltypes (see the corresponding documentation for details).

Documentation on multifiles (pl2sql)

PREDICATE: relation/3:

The predicate is multifile.

The predicate is of type data.

Usage: relation(PredName,Arity,TableName)

PREDICATE: attribute/4:

The predicate is multifile.

The predicate is of type data.

Usage: attribute(ANumber,TblName,AName,AType)

Documentation on internals (pl2sql)

PREDICATE: query_generation/3:

Usage: query_generation(+ListOfConjunctions,+ProjectionTerm,-(ListOfQueries))

PREDICATE: translate_conjunction/5:

Usage: translate_conjunction(Conjunction,SQLFrom,SQLWhere,Dict,NewDict)

PREDICATE: translate_goal/5:

Usage: translate_goal(Goal,SQLFrom,SQLWhere,Dict,NewDict)

PREDICATE: translate_arithmetic_function/5:

Usage: translate_arithmetic_function(Result,Expression,SQLWhere,Dict,NewDict)

PREDICATE: translate_comparison/5:

Usage: translate_comparison(LeftArg,RightArg,CompOp,Dict,SQLComparison)

PREDICATE: aggregate_function/3:

Usage: aggregate_function(AggregateFunctionTerm,Dict,AggregateFunctionQuery)

PREDICATE: comparison/2:

Usage: comparison(PrologOperator,SQLOperator)

PREDICATE: negated_comparison/2:

Usage: negated_comparison(PrologOperator,SQLOperator)

PREDICATE: arithmetic_functor/2:

Usage: arithmetic_functor(PrologFunctor,SQLFunction)

PREDICATE: aggregate_functor/2:

Usage: aggregate_functor(PrologFunctor,SQLFunction)

Known bugs and planned improvements (pl2sql)


Go to the first, previous, next, last section, table of contents.