1/* Copyright (C) 2024 Boris Vassilev <boris.vassilev@gmail.com>
    2
    3This program is free software: you can redistribute it and/or modify
    4it under the terms of the GNU General Public License as published by
    5the Free Software Foundation, either version 3 of the License, or
    6(at your option) any later version.
    7
    8This program is distributed in the hope that it will be useful,
    9but WITHOUT ANY WARRANTY; without even the implied warranty of
   10MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   11GNU General Public License for more details.
   12
   13You should have received a copy of the GNU General Public License
   14along with this program.  If not, see <https://www.gnu.org/licenses/>.
   15*/
   16:- module(sqlite, [
   17            sqlite_version/1,
   18            sqlite_open/3,
   19            sqlite_close/1,
   20            sqlite_prepare/3,
   21            sqlite_bind/2,
   22            sqlite_reset/1,
   23            sqlite_sql/2,
   24            sqlite_expanded_sql/2,
   25            sqlite_column_names/2,
   26            sqlite_finalize/1,
   27            sqlite_eval/1,
   28            sqlite_eval/2,
   29            sqlite_eval/4 ]).

Prolog bindings for SQLite

This module provides partial access to the C-language interface of SQLite.

It exposes the database connection object sqlite3 and the prepared statement object sqlite3_stmt, along with some of the essential functions using these objects. Please refer to the SQLite documentation and the implementation in c/swiplite.c when using this library. To make it easier to find the relevant docs, I have tried to consistently provide links.

Most of the predicates in this module are as close as possible in naming and semantics to the corresponding functions in the C interface. One exception is sqlite_bind/2, which converts values from Prolog terms to corresponding SQLite column datatype. Similarly, sqlite_eval/1, sqlite_eval/2, and sqlite_eval/4 wrap the necessary calls to sqlite3_step() and convert the results of SELECT queries to Prolog terms.

The database connection and prepared statement objects are represented in SWI-Prolog as blobs. They are garbage collected, but finalizing a statement or closing a database connection (and, alternatively, not doing it) have reprecussions, especially for long-running programs. The code in this library uses exclusively the *_v2 versions of the SQLite C interface. In particular:

> The sqlite3_close_v2() interface > is intended for use with host languages that are garbage > collected, and where the order in which destructors are called is > arbitrary. */

   69:- use_foreign_library(foreign(swiplite)).   70:- use_module(library(dcg/basics)).   71
   72:- multifile prolog:error_message//1.   73
   74prolog:error_message(sqlite_error(Caller, Code, Str, Message)) -->
   75    [ '[~s] (~d) ~s - ~s'-[Caller, Code, Str, Message] ].
   76prolog:error_message(swiplite_error(Caller, Message)) -->
   77    [ '[~s] ~s'-[Caller, Message] ].
 sqlite_version(-Version:atom) is det
Unify Version with the version of SQLite currently in use */
   83sqlite_version(V) :-
   84    setup_call_cleanup(sqlite_open('', DB, [memory(true)]),
   85        setup_call_cleanup(sqlite_prepare(DB, "select sqlite_version()", S),
   86            sqlite_eval(S, row(V0)),
   87            sqlite_finalize(S)),
   88        sqlite_close(DB)),
   89    atom_string(V, V0).
   90
   91:- predicate_options(sqlite_open/3, 3,
   92        [ mode(oneof([read,write,create])),
   93          memory(boolean),
   94          threaded(oneof([single,multi,serialized]))
   95        ]).
 sqlite_open(++File:text, -Connection:blob, ++Options:list) is semidet
Open Connection to the database in File using Options

The options are used to set the flags argument in the call to sqlite3_open_v2(). The following options are recognized:

mode Mode
Determines how the database is opened:
ValueCorresponding flags
read (default)SQLITE_OPEN_READONLY
writeSQLITE_OPEN_READWRITE
createSQLITE_OPEN_READWRITE | SQLITE_OPEN_CREATE
memory(Bool)
Open as an in-memory database:
ValueCorresponding flags
false (default)(empty)
trueSQLITE_OPEN_MEMORY
threaded(Threaded)
Threading mode for this database connection:
ValueCorresponding flags
single (default)(empty)
multiSQLITE_OPEN_NOMUTEX
serialized=SQLITE_OPEN_FULLMUTEX
Arguments:
File- Relative path to the database file. Interpreted as UTF-8 string.
Connection- A blob with the database connection.
Options- A list of options
See also
- sqlite3_open_v2()
- Using SQLite in multi-threaded applications
To be done
- Support all available SQLITE_OPEN_* flags. */
 sqlite_close(++Connection:blob) is det
Close a Connection opened with sqlite_open/3
Arguments:
Connection- A database connection obtained with sqlite_open/3
See also
- sqlite3_close_v2() */
 sqlite_prepare(++Connection:blob, ++SQL:text, -Statement:blob) is semidet
Compile Statement from the text in SQL using the database in Connection

The UTF-8 encoded text in SQL is parsed up to the first nul, or up to the end of the first SQL statement. SQL parameters are initially all set to NULL. Anonymous variables are not allowed. If ?NNN parameters are used, they must be numbered starting from 1, without any gaps.

Arguments:
Connection- A database connection obtained with sqlite_open/3
SQL- The UTF8-encoded text of the SQL as an atom, string, or list of codes
See also
- sqlite_bind/2
- SQL statement parameters in SQLite
- sqlite3_bind_parameter_count()
To be done
- Do something with the rest of the text in SQL */
 sqlite_finalize(++Statement:blob) is det
Delete a prepared statement
Arguments:
Connection- A database connection obtained with sqlite_open/3
See also
- sqlite3_finalize() */
 sqlite_bind(++Statement:blob, ++Bind_values:bv) is det
Use Bind_values to set the variables in Statement

The term in Bind_values must be named "bv" (bind values). Use an empty list [] to set a variable to NULL.

?- sqlite_prepare(DB, "Select ?1, ?2", S),
   sqlite_bind(S, bv('a', [])),
   sqlite_expanded_sql(S, E).
E = "Select 'a', NULL".

Each term in the Bind_values argument is used to set the variable with the same index in the SQL statement; both start counting at 1.

In addition to using the empty list to represent SQL NULL:

Arguments:
Statement- A statement compiled with sqlite_prepare/3
Bind_values- A flat term with functor bv/<number of parameters>
Statement- A blob with the compiled statement
See also
- sqlite_prepare/3
- sqlite_sql/2
- sqlite_expanded_sql/2
- SQL statement parameters in SQLite
To be done
- Support more types */
 sqlite_reset(++Statement:blob) is det
Reset Statement
Arguments:
Statement- A statement compiled with sqlite_prepare/3
See also
- sqlite3_reset() */
 sqlite_sql(++Statement:blob, -SQL:atom) is det
Unify SQL with the UTF-8 text used to create the prepared statement
Arguments:
Statement- A statement compiled with sqlite_prepare/3
SQL- An atom with the original text of the statement
See also
- sqlite_prepare/3
- sqlite_bind/2
- sqlite3_sql() */
 sqlite_expanded_sql(++Statement:blob, -Expanded_SQL:string) is det
Retrieve the SQL statement with bind parameters expanded
Arguments:
Statement- A statement compiled with sqlite_prepare/3
Expanded_SQL- A string with the expanded statement
See also
- sqlite_prepare/3
- sqlite_bind/2
- sqlite3_expanded_sql() */
 sqlite_column_names(++Statement:blob, -Column_names:cols) is det
Retrieve the column names of a SELECT statement

For a SELECT statement, the result is a flat term cols(column_1, column_2, ...).

If the prepared statement does not have a result set with columns in it, Column_names is unified with cols().

Arguments:
Statement- A statement compiled with sqlite_prepare/3
Column_names- A flat term with functor cols/<number of columns>
See also
- sqlite3_column_name()
- sqlite3_column_count() */
 sqlite_eval(++Statement:blob) is semidet
Evaluate a statement that has no results

For example, CREATE or INSERT statements must be evaluated using sqlite_eval/1, while a SELECT needs either sqlite_eval/2 or sqlite_eval/4.

Statement is reset automatically upon success.

Arguments:
Statement- A statement compiled with sqlite_prepare/3 */
Errors
- swiplite_error When the statement has results
 sqlite_eval(++Statement:blob, Result:row) is semidet
Evaluate a SELECT statement with exactly one row in the result set

Statement is reset automatically upon success.

Arguments:
Statement- A SELECT statement compiled with sqlite_prepare/3
Result- A flat term with functor row/<number of columns> */
Errors
- swiplite_error When the statement does not have exactly one result row
 sqlite_eval(++Statement:blob, ?N:nonneg, -R:list(row), ?T) is semidet
Evaluate a statement to collect results in the difference list R-T.

When N is a free variable, fetch all rows of the result set and unify N with the number of rows.

Otherwise, fetch up to N result rows in R.

R and T form a difference list. When there are no more results in the result set, T is unified with the empty list [].

A statement evaluated with sqlite_eval/4 must be explictly reset using sqlite_reset/1 after all rows in the result set have been fetched. Until it is reset, consecutive calls will unify N with 0 and both R and T with the empty list [].

Arguments:
Statement- A SELECT statement compiled with sqlite_prepare/3
N- Number of rows
R- Rows of the result set
T- Tail of R
See also
- sqlite3_column_count() */