1:- module( prosqlite,
    2          [ sqlite_connect/2,           % +FileName, -Conn
    3            sqlite_connect/3,           % +FileName, -Conn, +Opts
    4            sqlite_disconnect/1,        % +Conn
    5            sqlite_disconnect/2,        % +Conn, +Opts
    6            sqlite_current_connection/1,% -Conn
    7            sqlite_query/2,             % +SQL, -Row
    8            sqlite_query/3,             % +Conn, +SQL, -Row
    9            sqlite_format_query/3,      % +Conn, +SQL, -Row
   10            sqlite_current_table/2,     % +Conn, -Table
   11            sqlite_current_table/3,     % +Conn, ?Table, -Facet
   12            sqlite_table_column/3,      % +Conn, ?Table, ?Column
   13            sqlite_table_column/4,      % +Conn, ?Table, ?Column, -Facet
   14            sqlite_table_count/3,       % +Conn, +Table, -Count
   15            sqlite_default_connection/1,% -Conn
   16            sqlite_date_sql_atom/2,     % ?Date, ?SqlAtom
   17            sqlite_pragma/3,            % ?Date, ?SqlAtom
   18            sqlite_version/2,           % -Version, -Date
   19            sqlite_binary_version/2,    % -Version, -Date
   20            sqlite_library_version/1,   % -Version
   21            sqlite_library_version/2,   % +Alias, -Version
   22            sqlite_library_c_version/1, % -Version
   23            sqlite_build_version/1,     % -Version
   24            sqlite_citation/2           % -Atom, Bibterm
   25          ] ).   26
   27:- use_module(library(lists)).  % append/3, member/2, memberchk/2.
   28:- use_module(library(apply)).  % maplist/2,3.
   29:- use_module(library(debug)).   30
   31:- at_halt(sqlite_disconnect).   32
   33:- use_module(library(shlib)).   34:- use_foreign_library(foreign(prosqlite)).   35
   36:- dynamic(sqlite_connection/3).   37:- dynamic(sqlite_db:sqlite_asserted/4).

proSQLite: a Prolog interface to the SQLite database system.

This library follows the design and borrows code from the ODBC library of SWI-Prolog http://www.swi-prolog.org/pldoc/packasqlite_connectge/odbc.html .

The SQLite system is a powerful zero-configuration management systme that interacts with single-file databases that are cross-platform compatible binaries.

ProSQLite provides three layers of interaction with SQLite databases. At the lower level is the querying via SQL statements. A second layer allows the interogation of the database dictionary, and the final level facilitates the viewing of database tables as predicates. See the publication pointed to by sqlite_citation/2, for further details. If you use prosqlite in your research, please consider citing this publication.

The library has been developed and tested on SWI 6.3.2 and latest version was tested on 9.3.9.

The easiest way to install on SWI is via the package manager. Simply do:

     ?- pack_install(prosqlite).

You will also need the sqlite3{.so,.dll} in your path. If you have difficulties in MS platforms try dropping sqlite3.dll in installed prosqlite/lib/x86_64/ directory (or prosqlite/lib/i386-win32 if you are on 32 bits). Alternative place it in SWI's bin/ directory.

There are good/full examples in the sources, directory examples/. For instance test by :

     ?- [predicated].
     ?- predicated.

As of v2.0 errors and null values are better supported:

% assuming db is open in SQLiteBrowser, with unsaved changes:

?- sqlite_query(db1, "update ex_t set exid=99 where exf3='v13';", AffC ).

ERROR: Unhandled exception: SQLite code: 5, with short message: database is locked


?- ex_t(A,B,C), write(A:B:C), nl, fail.
1:v12:v13
2: : $null$
3: $null$ : w
false.

?- ex_t(A,B,'$null$')
|    .
exf3- $null$
A = 2,
B = '' ;

There is a sister package, db_facts (also installable via the manager). Db_facts, allow interaction with the underlying database via Prolog terms, That library can also be used as a common compatibility layer for the ODBC and proSQLite libraries of SWI-Prolog, as it works on both type of connections.

ProSQLite is debug/1 aware: call debug(sqlite) to see what is sent to the sqlite engine.

There are MS wins DLLs included in the sources and recent version of the SWI package manager will install these properly.

Predicates on Versions

There is a battery of predicates about versions. Some of these can be used to debug issues between compiled and loaded versions of SQLite, although we never had any issues and seems they have good backward compatibility.

Predicates

Thanks

Thanks to Samer Abdallah for 2 fixes. One on mapping blobs to strings and second for handling UTF text correctly.

Thanks to Christian Gimenez for suggesting replacing sqlite3_close() with sqlite3_close_(). The former returns the unhandled SQLITE_BUSY if there unfinalzed statements. _v2 is designed for garbage collected languages, see http://sqlite.org/c3ref/close.html.

Thanks to Wolfram Diestel for spotting a bug in opening 2 dbs with distinct aliases.

Thanks to Steve Moyle for contributing safe_column_names/2 (Nov 2016).

Thanks to John B Thiel (JBThiel) for opening a number of issues which led to v2.0.

History

author
- Nicos Angelopoulos
- Sander Canisius
version
- 1.0, 2014/12/24
- 1.1, 2016/10/9 changed to sqlite3_close() and fixed alias bug
- 1.2, 2016/11/22 added safe_column_names/2
- 1.4, 2018/3/18 fixed blobs support (see examples/two.pl), and logic for already opened file
- 1.6, 2020/5/29 recompiled for SWI 8.2
- 1.7, 2022/4/30 print message if new db file cannot be created
- 1.8, 2022/5/29 fixed major bug of deleting existing files introduced in 1.7 + minor doc + aarch64-linux binary
- 2.0 2024/8/15 better error propagation & nulls, keywords as fields, library + c + build versions, disconnect remove_predicates option
See also
- Sander Canisius, Nicos Angelopoulos and Lodewyk Wessels. proSQLite: Prolog file based databases via an SQLite interface. In the proceedings of Practical Aspects of Declarative languages (PADL 2013), (2013, Rome, Italy).
- Sander Canisius, Nicos Angelopoulos and Lodewyk Wessels. Exploring file based databases via an SQLite interface. In the ICLP Workshop on Logic-based methods in Programming Environments, p. 2-9, (2012, Budapest, Hungary).
- http://stoics.org.uk/~nicos/pbs/padl2013-prosqlite.pdf
- http://stoics.org.uk/~nicos/sware/prosqlite
- http://stoics.org.uk/~nicos/sware/db_facts
- http://www.sqlite.org/
- files in examples/ directory
- also available as a SWI pack http://www.swi-prolog.org/pack/list
license
- MIT
To be done
- set pragmas

*/

  163/* defaults and start ups */
  164arity_flag_values( [arity,unary,both,palette] ).
  165
  166%-Section interface predicates
  167%
 sqlite_version(-Version, -Date)
The current version and its publication date.

Version is a Mj:Mn:Fx term and date is a date(Y,M,D) term.

 ? sqlite_version(V, D).
 V = 2:0:0,
 D = date(2024, 8, 15).
author
- nicos angelopoulos
  183sqlite_version(2:0:0, date(2024,8,15)).
 sqlite_binary_version(-Version, -Date)
The current version and date of publication for the proSQLite c-code.

This is provided as the c code is not changed as often as the prolog part of the pack. These changes require re-compiling the binaries of the pack distribution.

?- sqlite_binary_version(V,D).
V = 1:3:0,
D = date(2018, 3, 17).

?- sqlite_version(V1,D1).
V1 = 1:8:2,
D1 = date(2024, 7, 6).
author
- nicos angelopoulos
version
- 0:2 24.08.03

*/

  206sqlite_binary_version( Ver, Date ) :-
  207     c_sqlite_version( Ver, Date ).
 sqlite_library_c_version(-LibCVers)
Get the vesion of the SQLite version via the C-interface.
?- sqlite_library_c_version(V).
V = '3.45.1'.
author
- nicos angelopoulos
version
- 0.1, 2024/8/14

*/

  222sqlite_library_c_version( Cersion ) :-
  223     c_library_version( Cersion ).
 sqlite_build_version(-LibCVers)
Get the version of the SQLITE against which the prosqlite binaries where compiled.

The Atom is bound to the SQLITE_VERSION macro from the SQLite sources at compile time.

?- sqlite_build_version(LibCV).
LibCV = '3.45.1'.

?- sqlite_library_c_version(V).
V = '3.45.1'.

?- sqlite_connect('/tmp/testo.sqlite', testo, exists(false)).
true.

?- sqlite_library_version(V).
V = '3.45.1'.

?- sqlite_disconnect.
ERROR: Unknown procedure: sqlite_disconnect/0
ERROR:     However, there are definitions for:
ERROR:         prosqlite:sqlite_disconnect/1
ERROR:         prosqlite:sqlite_disconnect/2
false.

?- sqlite_disconnect_all.
ERROR: Unknown procedure: sqlite_disconnect_all/0 (DWIM could not correct goal)
^  Exception: (4) setup_call_cleanup('$toplevel':notrace(call_repl_loop_hook(begin, 0)), '$toplevel':'$query_loop'(0), '$toplevel':notrace(call_repl_loop_hook(end, 0))) ? Unknown option (h for help)
^  Exception: (4) setup_call_cleanup('$toplevel':notrace(call_repl_loop_hook(begin, 0)), '$toplevel':'$query_loop'(0), '$toplevel':notrace(call_repl_loop_hook(end, 0))) ? Unknown option (h for help)
^  Exception: (4) setup_call_cleanup('$toplevel':notrace(call_repl_loop_hook(begin, 0)), '$toplevel':'$query_loop'(0), '$toplevel':notrace(call_repl_loop_hook(end, 0))) ? abort
% Execution Aborted
?- sqlite_disconnet(testo).
Correct to: "sqlite_disconnect(testo)"? yes
true.
author
- nicos angelopoulos
version
- 0.1, 2024/8/14

*/

  267sqlite_build_version( Bersion ) :-
  268     c_library_version( Bersion ).
 sqlite_library_version(-LibVers)
 sqlite_library_version(+Alias, -LibVers)
Get the version of the underlying sqlite library. Either uses Alias or default connection (which should exist).

This version uses the query interface so it expects a default connection to have been established.

?- sqlite_library_version(V).
false.

?- sqlite_connect('/tmp/testo.sqlite', testo, exists(false)).

?- sqlite_library_version(V).
V = '3.37.2'.

?- sqlite_disconnect(testo).
author
- nicos angelopoulos
version
- 0.1, 2024/8/3
See also
- sqlite_library_c_version/1
- sqlite_build_version/1

*/

  295sqlite_library_version( V ) :-
  296     sqlite_query( 'SELECT sqlite_version()', Row ),
  297     Row = row(V),
  298     % first draft was like below, but changed to chime with sqlite_library_c_version/1 and sqlite_build/1
  299     % Row = row(Atm),
  300     % atomic_list_concat([Mj,Mn,Fx],'.',Atm),
  301     % maplist( atom_number, [Mj,Mn,Fx], [Nj,Nn,Nx] ),
  302     % V = Nj:Nn:Nx,
  303     !.
  304sqlite_library_version( Alias, V ) :-
  305     sqlite_query( Alias, 'SELECT sqlite_version()', Row ),
  306     Row = row(V).
 sqlite_citation(-Atom, -Bibterm)
Succeeds once for each publication related to this library. Atom is the atom representation suitable for printing while Bibterm is a bibtex(Type,Key,Pairs) term of the same publication. Produces all related publications on backtracking.
  312sqlite_citation( Atom, bibtex(Type,Key,Pairs) ) :-
  313     Atom = 'Sander Canisius, Nicos Angelopoulos and Lodewyk Wessels. proSQLite: Prolog file based databases via an SQLite interface.  In the proceedings of Practical Aspects of Declarative languages (PADL 2013), (2013, Rome, Italy).',
  314     Type = inproceedings,
  315     Key  = 'CanisiusS+2013',
  316     Pairs = [
  317          author = 'Sander Canisius and Nicos Angelopoulos and Lodewyk Wessels',
  318          title  = 'Exploring file based databases via an Sqlite interface',
  319          booktitle = 'In ICLP Workshop on Logic-based methods in Programming Environments (WLPE\'12)',
  320          year = 2012,
  321          pages= '2-9',
  322          month = 'September',
  323          address = 'Budapest, Hungary',
  324          url     = 'http://stoics.org.uk/~nicos/pbs/padl2013-prosqlite.pdf'
  325     ].
  326     
  327sqlite_citation( Atom, bibtex(Type,Key,Pairs) ) :-
  328     Atom = 'Exploring file based databases via an Sqlite interface. \n Canisius Sander, Nicos Angelopoulos and Lodewyk Wessels \n In the ICLP Workshop on Logic-based methods in Programming Environments (WLPE\'12),\n p.2-9, 2012. Budapest, Hungary.',
  329     Type = inproceedings,
  330     Key  = 'CanisiusS+2012',
  331     Pairs = [
  332          author = 'Sander Canisius and Nicos Angelopoulos and Lodewyk Wessels',
  333          title  = 'Exploring file based databases via an Sqlite interface',
  334          booktitle = 'In ICLP Workshop on Logic-based methods in Programming Environments (WLPE\'12)',
  335          year = 2012,
  336          pages= '2-9',
  337          month = 'September',
  338          address = 'Budapest, Hungary',
  339          url     = 'http://stoics.org.uk/~nicos/pbs/wlpe2012_sqlite.pdf'
  340     ].
 sqlite_connect(+File, ?Alias)
Open a connection to an sqlite File. If Alias is a variable, an opaque atom is generated and unified to it. The opened db connection to file can be accessed via Alias.
  sqlite_connect('uniprot.sqlite', uniprot).
  352sqlite_connect(File, Conn) :-
  353     sqlite_connect(File, Conn, []).
 sqlite_connect(+File, ?Connection, +Options)
Open a connection to an sqlite File. If Connection is unbound then if (a) alias(Alias) option is given, Connection is bound to Alias, else (b) an opaque atom is generated. If Connection is ground, the opened can be accessed with Connection as a handle.

Options is a single term or a list of terms from the following:

alias(Atom)
identify the connection as Alias (no default, interplays with Connection)
as_predicates(AsPred=false)
if true, create hook predicates that map each sqlite table to a prolog predicate. These are created in module user (see at_module()). The user should make sure the predicate is not previously defined.
at_module(AtMod=user)
the module at which the predicates will be asserted at (if as_predicates(true)) is also given)
arity(Arity=arity)
Arity denotes the arity of access clauses to be added in the prolog database that correspond to SQLite tables. The default is arity, which asserts a predicate matching the arity of the table. both adds two predicates, one matching the arity and a single argument one. The later can be interrogated with something like
?-  phones( [name=naku, telephone=T] ).

unary only adds the unary version, and palette adds a suite of predicates with arities from 1 to N, where N is the number of columns. These can be interrogated by :

?-  phones( name=Name ).
?-  phones( name=naku, telephone=T ).
?-  phones( [name=naku, telephone=T] ).

Predicated tables can be used to insert values to the database by virtue of all their columns are give ground values.

exists(Exists=true)
do not throw an error if file does not exist and Exists is false.
ext(Ext=sqlite)
database files are assumed to have an sqlite extension. To ovewrite this give a different Ext or '' for no extension.
table_as(Table, Pname, Arity)
map the table to predicate with name Pname. Arity should be defined for this representaition as per arity() option.
verbose(Verb=false)
Iff Verb==true print messages- currently about file used.

When unary predicates are defined the columns can be interrogated/accessed by list pairs of the form Column=Value. Column-Value and Column:Value are also recognised.

So for example, for table phones with columns Name, Address and Phone, prosqlite will add

     phones(_,_,_)
as a response to as_predicates, and
     phones(_)

if Arity is unary.

The latter can be interrogated by

     phones( ['Name'=naku','Phone'=Phone] ).

which will return the phone number(s) associated with individual named by naku.

author
- nicos angelopoulos
version
- 0.2 2018/03/17, fixed logic for existing connection to a file (existing alias is returned)
- 0.3 2022/04/30, add permissions error message, if new sqlite file cannot be created
See also
- examples/predicated.pl .
- pack(prosqlite/examples/two.pl)

*/

  441sqlite_connect(FileIn, Conn, OptIn) :-
  442     to_list( OptIn, Opts ),
  443     ( memberchk(ext(Ext),Opts) -> true; Ext=sqlite ),
  444     ( file_name_extension(_,Ext,FileIn) -> File=FileIn; file_name_extension(FileIn,Ext,File) ),
  445     sqlite_connect_1(File, Conn, Opts).
  446
  447sqlite_connect_1(File, _Conn, Opts) :-
  448     \+ exists_file(File),
  449     \+ memberchk(exists(false), Opts),
  450     !,
  451     open(File, read, _). % just so it throws a nice error
  452sqlite_connect_1(File1, Conn, Opts) :-
  453     sqlite_alias(Opts, Conn, Alias),
  454     \+ var(Alias),
  455     sqlite_connection(Alias,File2,_),
  456     !,
  457     ( File1==File2 -> 
  458          print_message( informational, sqlite(connection_already_open(Conn)) )
  459          ;
  460          sqlite_error( alias_in_use(Alias,File2) )
  461     ).
  462sqlite_connect_1(File, Alias, Opts) :-
  463     sqlite_alias(Opts, Conn, Alias),
  464     ( sqlite_connection(_Conn1,File,Alias1) ->
  465        Alias1 = Alias,
  466        ( (memberchk(verbose(Verb),Opts),Verb==true) -> 
  467                print_message( informational, sqlite(file_already_open(File,Alias1)) )
  468                ;
  469                true
  470        )
  471        ;
  472        ( (memberchk(verbose(Verb),Opts),Verb==true) -> 
  473            print_message( informational, sqlite(db_at(File)) )
  474            ;
  475            true
  476        ),
  477        % 22.04.30: adding the following 2 commands to get an informative error when file cannot be open for updating (report on github by korvo)
  478        open( File, append, TmpStream ),
  479        close( TmpStream ),
  480        c_sqlite_connect(File, Conn),
  481        asserta( sqlite_connection(Alias,File,Conn) ),
  482        ( sqlite_establish_predicates(Opts, Conn) ->
  483            true
  484            ;
  485            retractall( sqlite_connection(Alias,File,Conn) ),
  486            c_sqlite_disconnect(Conn),
  487            sqlite_error( predicated_creation_error(File,Alias) )
  488        )
  489    ).
  490
  491/*
  492sqlite_connect(File, Conn, Opts) :-
  493     c_sqlite_connect(File, Internal),
  494     !,
  495     assert( sqlite_connection(Conn,File,Internal) ). 
  496     */
  497
  498% this is currently private only for use with at_halt.
  499% 
  500sqlite_disconnect :-
  501     sqlite_connection(Alias,_,_),
  502     sqlite_disconnect( Alias, [] ),
  503     fail.
  504sqlite_disconnect.
 sqlite_disconnect(+Alias)
 sqlite_disconnect(+Alias, +Options)
Terminate the connection to an SQLite database file.

Options is a single term or a list of terms from the following:

remove_predicates(Rmv=abolish)
defines the method of removing predicates that are defined on tables of connection Alias. (That is, that as_predicates(true)|+ was used when created Alias connection.) Set to =|retractall to only retract predicated definitions, by default these are abolished. prolog_flag/2 key sqlite_remove_predicates can set a new default value.

Examples

   ?-
        sqlite_disconnect(uniprot).

?- sqlite_connect( kword, kwordo, as_predicates(true) ).
true.

?- kwordo(A,B,C).
A = 1,
B = f11,
C = f21 ;
A = 2,
B = f12,
C = groupaa ;
false.

?- sqlite_disconnect( kwordo ).
true.

?- kwordo(A,B,C).
ERROR: Unknown procedure: kwordo/3 (DWIM could not correct goal)
?- sqlite_connect( kword, kwordo, as_predicates(true) ).
true.

?- kwordo(A,B,C).
A = 1,
B = f11,
C = f21 ;
A = 2,
B = f12,
C = groupaa ;
false.

?- sqlite_disconnect( kwordo, remove_predicates(retractall) ).
true.

?- kwordo(A,B,C).
false.
author
- nicos angelopoulos
version
- 0:2 2024/08/03

*/

  565sqlite_disconnect( Alias ) :-
  566     sqlite_disconnect( Alias, [] ).
  567
  568sqlite_disconnect( Alias, OptIn ) :-
  569     once( sqlite_connection(Alias,_,Conn) ),
  570     !,
  571     debug( sqlite, 'Disconnecting from db with alias: ~w.', [Alias] ),
  572     findall( pam(Pname,Arity,Mod), sqlite_db:sqlite_asserted(Conn,Pname,Arity,Mod), PAs ),
  573     c_sqlite_disconnect( Conn ),
  574     retractall( sqlite_connection(Alias,_,Conn) ),
  575     to_list( OptIn, Opts ),
  576     sqlite_disconnect_predicates( Opts, Abo ),
  577     maplist( sqlite_clean_up_predicated_for(Abo,Conn), PAs ).
  578sqlite_disconnect( Alias, _ ) :-
  579     sqlite_fail( not_a_connection(Alias) ).
  580
  581sqlite_disconnect_predicates( Opts, Rmv ) :-
  582     memberchk( remove_predicates(Rmv), Opts ),
  583     !.
  584sqlite_disconnect_predicates( _Opts, Rmv ) :-
  585     current_prolog_flag( sqlite_remove_predicates, Rmv ),
  586     !.
  587sqlite_disconnect_predicates( _Opts, Rmv ) :-
  588     Rmv = abolish.
  589
  590sqlite_clean_up_predicated_for( Abo, Conn, Pam ) :-
  591     sqlite_clean_up_predicated_for_known( Abo, Conn, Pam ),
  592     !.
  593sqlite_clean_up_predicated_for( Abo, _Conn, _Pam ) :-
  594     throw( unknown_value(remove_predicates,Abo) ).
  595
  596sqlite_clean_up_predicated_for_known( retractall, Conn, pam(Pname,Arity,Mod) ) :-
  597     functor( Head, Pname, Arity ),
  598     retractall( Mod:Head ),
  599     retractall( sqlite_db:sqlite_asserted(Conn,Pname,Arity,Mod) ).
  600sqlite_clean_up_predicated_for_known( abolish, Conn, pam(Pname,Arity,Mod) ) :-
  601     abolish( Mod:Pname, Arity ),
  602     retractall( sqlite_db:sqlite_asserted(Conn,Pname,Arity,Mod) ).
 sqlite_current_connection(-Connection)
Return or interrogate the name of open connection handles.
  608sqlite_current_connection(Conn) :-
  609     sqlite_connection(Conn,_,_).
 sqlite_default_connection(-Connection)
Return or interrogate the name of the default connection. This is the last connection opened.
  616sqlite_default_connection(Alias) :-
  617     sqlite_connection(Alias,_,_),
  618     !.
 sqlite_query(+Sql, -Row)
Post an Sql query to default connection and get row result in Row.
  624sqlite_query(Sql, Row) :-
  625     sqlite_default_connection(Alias),
  626     sqlite_query(Alias, Sql, Row).
 sqlite_query(+Connection, +Sql, -Row)
Post an Sql query to Sqlite Connection and get row result in Row.
  632sqlite_query(Alias, Query, Row) :-
  633     sqlite_alias_connection(Alias, Connection),
  634     debug( sqlite, 'Alias: ~w, sending: ~a', [Alias,Query] ),
  635     c_sqlite_query(Connection, Query, Row).
 sqlite_format_query(+Connection, +FAs, -Row)
Post a format style Sql query to Sqlite Connection and get row result in Row. FAs is a - pair structure : Format-Arguments.
   sqlite_format_query(uniprot, 'PRAGMA table_info(~w)'-Table, row(_, Column, _, _, _, _))
  647sqlite_format_query(Alias, Format-Arguments, Row) :-
  648    format(atom(Query), Format, Arguments),
  649    sqlite_query(Alias, Query, Row).
 sqlite_current_table(+Connection, -Table)
Return or interrogate tables in the Sqlite database associated with Connection.
  655sqlite_current_table(Alias, Table) :-
  656    var( Table ),
  657    !,
  658    sqlite_query(Alias, 'SELECT name FROM sqlite_master WHERE type = "table"', row(Table)).
  659sqlite_current_table(Alias, Table) :-
  660    ground( Table ),
  661    sqlite_query(Alias, 'SELECT name FROM sqlite_master WHERE type = "table"', row(TableIn)),
  662    %13.10.26: have a look at the C code above to see if 'row(Table)' can work on the above line.
  663    Table = TableIn,
  664    !.
 sqlite_current_table(+Connection, ?Table, -Facet)
Facet is a property of Table found at Connection. Currently only arity(Arity) is delivered.
  670sqlite_current_table(Connection, Table, Facet ) :-
  671     sqlite_current_table(Connection, Table),
  672     sqlite_facet_table( Facet, Connection, Table ).
 sqlite_table_column(+Connection, ?Table, -Column)
Return or interrogate tables and columns in the Sqlite database associated with Connection.
  678sqlite_table_column( Alias, Table, Column ) :-
  679     set_table( Alias, Table ),
  680    sqlite_format_query(Alias, 'PRAGMA table_info(~w)'-Table, row(_, Column, _, _, _, _)).
 sqlite_table_column(+Connection, ?Table, ?Column, -Facet)
Facet is one of:
  691sqlite_table_column(Alias, Table, Column, Facet) :-
  692    set_table( Alias, Table ),
  693    sqlite_format_query(Alias, 'PRAGMA table_info(~w)'-Table, Row ),
  694    Row = row(_, Column, _, _, _, _),
  695    sqlite_pragma_info_facet( Row, Facet ).
  696
  697sqlite_pragma_info_facet( row(Nth0,_,_,_,_,_), position(Nth0) ).
  698sqlite_pragma_info_facet( row(_,_,Dtype,_,_,_), data_type(Dtype) ).
  699sqlite_pragma_info_facet( row(_,_,_,Null,_,_), nullable(Null) ).  % fixme, ensure same semantics as ODBC
  700sqlite_pragma_info_facet( row(_,_,_,_,Default,_), default(Default) ).
  701sqlite_pragma_info_facet( row(_,_,_,_,_,Key), primary_key(Key) ).
 sqlite_pragma(+Alias, +Pragma, -Row)
Interrogate SQLite Pragmas. Currently only reading is supported. Pragma can be an atom or a - separated pair, as in table_info-TableName.
     sqlite_pragma( phone_db, encoding, Row).
  711sqlite_pragma( Alias, Pragma-Par, Row ) :-
  712     !,
  713     atomic_list_concat( ['PRAGMA',Pragma,'(~w)'],' ', Query ), 
  714     sqlite_format_query( Alias, Query-Par, Row ).
  715sqlite_pragma( Alias, Pragma, Row ) :-
  716     atomic_list_concat( ['PRAGMA',Pragma],' ', Query ), 
  717     sqlite_query( Alias, Query, Row ).
  718
  719% pragmas_info( [...,encoding,...,secure_delete,synchronous,temp_store,writable_schema] ).
  720pragmas_comm( [shrink_memory] ).
  721
  722
  723set_table( Alias, Table ) :-
  724     ( var(Table) -> 
  725          sqlite_current_table(Alias, Table) 
  726          ;
  727          true
  728     ).
 sqlite_table_count(+Connection, +Table, -Count)
True if Count is the number of rows in Sqlite Connection associated Table.
  734sqlite_table_count(Alias, Table, Count) :-
  735     Sel = 'Select count (*) from ~w',
  736    sqlite_format_query(Alias, Sel-Table, row(Count)),
  737     !.
 sqlite_date_sql_atom(Date, Sql)
Convert between a Prolog date/3 term and an Sql atom. The conversion is bidirectional. */
  744sqlite_date_sql_atom( date(Y,M,D), Sql ) :-
  745     ground( Sql ), 
  746     !,
  747     atomic_list_concat( Consts, '/', Sql ),
  748     maplist( atom_number, Consts, [Y,M,D] ).
  749sqlite_date_sql_atom( date(Y,M,D), Sql ) :-
  750     atomic_list_concat( ['"',Y], Ya ),
  751     atomic_list_concat( [D,'"'], Da ),
  752     atomic_list_concat( [Ya,M,Da], '/', Sql ).
  753
  754
  755%-Section non-interface sqlite specific predicates
  756%
  757
  758sqlite_alias(Opts, _Conn, Alias) :-
  759     memberchk(alias(Alias), Opts),
  760     !.
  761sqlite_alias(_Opts, _Conn, Alias ) :-
  762     atomic( Alias ),
  763     !.
  764sqlite_alias(_Opts, Conn, Conn).
  765
  766sqlite_establish_predicates( Opts, Conn ) :-
  767     memberchk(as_predicates(true), Opts), 
  768     !,
  769     findall(T-C, sqlite_table_column(Conn,T,C), TCs ),
  770     findall( T, member(T-_,TCs), RepTs ),
  771     sort( RepTs, Ts ),
  772     findall( T-Cs, (member(T,Ts),findall(C,member(T-C,TCs),Cs)), TdCs ),
  773     ( memberchk(at_module(Mod), Opts) -> true; Mod = user ),
  774     arity_option( Opts, ArityF ),
  775     sqlite_establish_tables(TdCs, Conn, Mod, ArityF, Opts ).
  776sqlite_establish_predicates(_Opts, _Conn ).
  777
  778sqlite_establish_tables( [], _Conn, _Mod, _ArityF, _Opts ).
  779sqlite_establish_tables( [Table-Columns|T], Conn, Mod, ArityF, Opts ) :-
  780     ( memberchk(table_as(Table,Pname,TArityF), Opts) ->
  781          true
  782          ;
  783          Pname = Table, TArityF = ArityF
  784     ), 
  785     sqlite_establish_table(TArityF,Table,Pname,Columns,Conn,Mod),
  786          % Internal = 'Internal prosqlite error. Unable to establish table',
  787          % throw( Internal:TArityF/Table )  % handled furter up now
  788     sqlite_establish_tables( T, Conn, Mod, ArityF, Opts ).
  789
  790sqlite_establish_table( arity, Table, Pname, Columns, Conn, Mod ) :-
  791     length( Columns, Arity ),
  792     sqlite_establish_table_typed( Table, Pname, Columns, Conn, Mod, predicate, Arity ).
  793sqlite_establish_table( both, Table, Pname, Columns, Conn, Mod ) :-
  794     sqlite_establish_table_typed( Table, Pname, Columns, Conn, Mod, unary, 1 ),
  795     length( Columns, Arity ),
  796     sqlite_establish_table_typed( Table, Pname, Columns, Conn, Mod, predicate, Arity ).
  797sqlite_establish_table( unary, Table, Pname, Columns, Conn, Mod ) :-
  798     sqlite_establish_table_typed( Table, Pname, Columns, Conn, Mod, unary, 1 ).
  799sqlite_establish_table( palette, Table, Pname, Columns, Conn, Mod ) :-
  800     length( Columns, Arity ),
  801     % Shorter is Arity - 1,
  802     findall( _, ( between(1,Arity,I), 
  803                   sqlite_establish_table_typed(Table, Pname, Columns, Conn, Mod, palette, I)
  804                 ), _ ).
  805
  806sqlite_establish_table_typed( Table, Pname, Columns, Conn, Mod, ArityF, Arity ) :-
  807     functor( Head, Pname, Arity ),
  808     Head =..[Pname|Args],
  809     Body = prosqlite:sqlite_holds(Conn,Table,Arity,ArityF,Columns,Args),
  810     ( clause(Mod:Head,_Body) ->
  811          sqlite_fail( maps_to_existing_predicate(Pname,Arity) )
  812          ;
  813          true
  814     ),
  815     % retractall( Mod:Head ),   % fixme: double check this and test it works
  816     ( sqlite_db:sqlite_asserted(Conn1,Pname,Args,_Mod1) ->
  817          sqlite_fail( predicate_already_registered(Conn1,Pname,Arity) )
  818          ;
  819          Mod:assert((Head :- Body))
  820     ),
  821     assert( sqlite_db:sqlite_asserted(Conn,Pname,Arity,Mod) ).
  822     % assert((Head :- Body)),
  823
  824sqlite_holds( AliasOr, Name, _Arity, Type, Columns, Args ) :-
  825     sqlite_alias_connection( AliasOr, Conn ),
  826     pl_as_predicate_to_sql_ready_data( Type, Columns, Args, KnwnClmPrs, UnKnwnCs, UnKnwnAs ),
  827     safe_column_names(Columns, SafeColumns),
  828     safe_column_names(UnKnwnCs, SafeUnKnwnCs),
  829     sqlite_holds_unknown( SafeUnKnwnCs, UnKnwnAs, KnwnClmPrs, Name, SafeColumns, Conn ).
  830
  831/* fixme:
  832sqlite_holds_unknown( [], _UnKnwnAs, KnwnClmPrs, Name, Columns, Conn ) :-
  833     shall we throw an error if there is nothing to report and nothing to assert ?
  834     */
  835
  836sqlite_holds_unknown( UnKnwnCs, UnKnwnAs, KnwnClmPrs, Name, _Columns, Conn ) :-
  837     sql_clm_value_pairs_to_where(KnwnClmPrs, Where),
  838     atomic_list_concat( UnKnwnCs, ',', UnC ),
  839     atomic_list_concat( ['Select ',UnC,'From',Name,Where,';'], ' ', Sql ),
  840     Row =.. [row|UnKnwnAs],
  841     debug( sqlite, 'Conn: ~w, sending: ~a', [Conn,Sql] ),
  842     c_sqlite_query(Conn, Sql, Row).
  843
  844sqlite_alias_connection( Alias, Connection ) :-
  845     sqlite_connection( Alias,_,Connection ),
  846     !.
  847% allows access with either alias or connection :
  848sqlite_alias_connection( Connection, Connection ) :-
  849     sqlite_connection(_,_,Connection),
  850     !.
  851sqlite_alias_connection( Alias, _Connection ) :-
  852     sqlite_error( unknown_alias(Alias) ).
  853
  854% fixme: we should really use the db_facts code here.
  855pl_as_predicate_to_sql_ready_data( unary, Columns, [Args], KnwnClmPrs, UnKnwnCs, UnKnwnAs ) :-
  856     pl_look_for_args_to_un_known( Args, Columns, KnwnClmPrs, UnKnwnCs, UnKnwnAs ).
  857pl_as_predicate_to_sql_ready_data( palette, Columns, ArgsIn, KnwnClmPrs, UnKnwnCs, UnKnwnAs ) :-
  858     ( (ArgsIn=[Args],is_list(Args)) -> true; Args = ArgsIn ),
  859     pl_args_column_arg_ground_or_not_pairs(Args,Columns,KnwnClmPrs,UnKnwnCs,UnKnwnAs),
  860     ( maplist(var,Args) ->
  861          true % then a palette predicate has been called with full arity and all variables
  862          ;
  863          % maplist( look_for_pair,Args,_,_),
  864          findall( LFA, (member(LFA,Args),look_for_pair_silent(LFA,_,_)), [] )
  865          % then a palette predicate has been called with full arity and look_for_pair
  866     ),
  867     !.
  868pl_as_predicate_to_sql_ready_data( palette, Columns, ArgsIn, KnwnClmPrs, UnKnwnCs, UnKnwnAs ) :-
  869     ( (ArgsIn=[Args],is_list(Args)) -> true; Args = ArgsIn ),
  870     pl_look_for_args_to_un_known( Args, Columns, KnwnClmPrs, UnKnwnCs, UnKnwnAs ).
  871pl_as_predicate_to_sql_ready_data( predicate, Columns, Args, KnwnClmPrs, UnKnwnCs, UnKnwnAs ) :-
  872     pl_args_column_arg_ground_or_not_pairs( Args, Columns, KnwnClmPrs, UnKnwnCs, UnKnwnAs ).
  873
  874pl_args_column_arg_ground_or_not_pairs( [], [], [], [], [] ).
  875pl_args_column_arg_ground_or_not_pairs( [A|As], [C|Cs], Knwn, UnCs, UnAs ) :-
  876     ( ground(A) -> 
  877          Knwn = [C-A|TKnwn],
  878          TUnCs = UnCs,
  879          TUnAs = UnAs
  880          ;
  881          TKnwn = Knwn,
  882          UnCs = [C|TUnCs],
  883          UnAs = [A|TUnAs]
  884     ),
  885     pl_args_column_arg_ground_or_not_pairs( As, Cs, TKnwn, TUnCs, TUnAs ).
  886
  887pl_look_for_args_to_un_known( [], _Columns, [], [], [] ).
  888pl_look_for_args_to_un_known( [A|As], Columns, Knwn, UnKnwnCs, UnKnownAs ) :-
  889     look_for_pair( A, Clm, Val ),
  890     is_one_of_columns( Clm, Columns ),
  891     ( ground(Val) ->
  892          Knwn = [Clm-Val|TKnwn],
  893          TUnKnwnCs = UnKnwnCs,
  894          TUnKnownAs = UnKnownAs
  895          ;
  896          TKnwn = Knwn,
  897          UnKnwnCs = [Clm|TUnKnwnCs],
  898          UnKnownAs = [Val|TUnKnownAs]
  899     ),
  900     pl_look_for_args_to_un_known( As, Columns, TKnwn, TUnKnwnCs, TUnKnownAs ).
  901
  902is_one_of_columns( Clm, Columns ) :-
  903     memberchk( Clm, Columns ), 
  904     !.
  905is_one_of_columns( Clm, Columns ) :-
  906     sqlite_error( unknown_column(Clm,Columns) ).
  907
  908look_for_pair( Pair, K, V ) :-
  909     look_for_pair_silent( Pair, K, V ),
  910     !.
  911look_for_pair( Term, _A, _B ) :-
  912    % print_message(informational, pack(git_fetch(Dir))).
  913     sqlite_error( pair_representation(Term) ).
  914     % type_error( 'Binary compound with functor {=,-,:}', Term ). 
  915     % Type = 'Binary compound with functor {=,-,:}',
  916     % print_message( error, error(type_error(Type,Term)) ),
  917     % abort.
  918
  919look_for_pair_silent( A=B, A, B ).
  920look_for_pair_silent( A-B, A, B ).
  921look_for_pair_silent( A:B, A, B ).
  922
  923/* error messages */
  924
  925sqlite_error( Term ) :-
  926     Type = error,
  927     print_message( Type, sqlite(Term) ),
  928     abort.
  929
  930sqlite_fail( Term ) :-
  931     Type = informational,
  932     sqlite_fail( Type, Term ).
  933
  934sqlite_fail( Type, Term ) :-
  935     print_message( Type, sqlite(Term) ),
  936     fail.
  937
  938%-Section error handling.
  939
  940:- multifile prolog:message//1.  941
  942prolog:message(sqlite(Message)) -->
  943    message(Message).
  944prolog:message(sqlite_error(Code,Message)) -->
  945    message(sqlite_error(Code,Message)).
  946
  947message( sqlite_error(Code,Mess) ) -->
  948     ['SQLite code: ~d, with short message: ~w' - [Code,Mess] ].
  949message( pair_representation(Term) ) -->
  950     ['Wrong term type ~q in predicated table arguments. Expected binary with functor, {=,:,-}.' - [Term] ].
  951message( unknown_column(Clm,Columns) ) -->
  952     [ 'Unkown column, ~q expected one in ~q.' - [Clm,Columns] ].
  953message( unknown_alias(Alias) ) -->
  954     ['Not a known alias or connection:~q.' - Alias ].
  955message( wrong_arity_value(ArityF) ) -->
  956     { arity_flag_values( Arities ) },
  957     [ 'Unrecognised arity option value ~q, expected ~q.' - [ArityF,Arities] ].
  958message( predicated_creation_error(File,Alias) ) -->
  959     [ 'Closed connection ~q to file ~q due to failure in predicated table creation.' - [Alias,File] ].
  960message( connection_already_open(Conn) ) -->
  961     [ 'Connection already open ~q.'- [Conn] ].
  962message( alias_in_use(Conn,File) ) --> 
  963     [ 'Alias/connection ~q already in use for file ~q.'- [Conn,File] ].
  964message( not_a_connection(Alias) ) -->
  965     [ 'Not an open connection or known alias to a connection: ~q' - [Alias] ].
  966message( insufficient_columns(Goal,Op) ) -->
  967     [ 'Insufficient number of known column values in ~q for operation ~q.' - [Goal,Op] ].
  968message( predicate_already_registered(Conn,Pname,Arity) ) -->
  969     [ 'Predicate ~q already registered by connection ~q' - [Pname/Arity,Conn] ].
  970message( maps_to_existing_predicate(Pname,Arity) ) -->
  971     ['Predicated table maps to existing predicate ~q.' - [Pname/Arity] ].
  972message( file_already_open(File,Alias) ) -->
  973     ['File, ~q already open with alias ~q.' - [File,Alias] ].
  974message( db_at(File) ) -->
  975     ['Using database from file: ~q.' - [File] ].
  976message( asserting_non_ground(Goal) ) -->
  977     [ 'Asserting non ground term ~q.' - [Goal] ].
  978message( debug(Format,Args) ) -->
  979     [ 'Found Format (1st arg) ~q and Args (2nd arg) ~q.' - [Format,Args] ].
  980     
  981%-Section sqlite non-specific auxiliary predicates 
  982%
  983to_list(OptIn, Opts) :-
  984     is_list(OptIn),
  985     !,
  986     Opts = OptIn.
  987to_list(Opt, [Opt] ).
  988
  989dquote( Val, Quoted ) :-
  990     number( Val ), 
  991     !,
  992     Quoted = Val.
  993dquote( Val, Quoted ) :-
  994     atom( Val ),
  995     !,
  996     atomic_list_concat( ['"',Val,'"'], Quoted ).
  997dquote( Val, Quoted ) :-
  998     is_list( Val ),
  999     append( [0'"|Val], [0'"], QuotedCs ),
 1000     atom_codes( Quoted, QuotedCs ).
 1001
 1002sql_clm_value_pairs_to_where(Known, Where) :-
 1003     sql_clm_value_pairs_to_where_conjunction(Known, Conjunction),
 1004     sql_where_conjunction_to_where(Conjunction, Where).
 1005
 1006sql_where_conjunction_to_where('', '' ) :- !.
 1007sql_where_conjunction_to_where(Conjunction, Where ) :-
 1008     atom_concat( 'Where ', Conjunction, Where ).
 1009
 1010sql_clm_value_pairs_to_where_conjunction([], '').
 1011sql_clm_value_pairs_to_where_conjunction([K-V|T], Where) :-
 1012     sql_clm_value_pairs_to_where_conjunction(T, InWhere),
 1013     sql_clm_and_val_to_sql_equals_atom(K, V, KVAtm),
 1014     ( InWhere == '' -> 
 1015          Where = KVAtm
 1016          ;
 1017          atomic_list_concat([KVAtm, ' AND ', InWhere], Where)
 1018     ).
 1019
 1020sql_clm_and_val_to_sql_equals_atom(K, V, KVAtm) :-
 1021     ( number(V) -> 
 1022          atom_number(Vatm, V),
 1023          atom_concat('=',Vatm,EqV),
 1024          atomic_list_concat( ['[',K,']',EqV], '', KVAtm )
 1025          ;
 1026          ( V == '$null$' ->
 1027               atomic_list_concat( '[',K,'] IS NULL', KVAtm )
 1028               ;
 1029               atom_concat(V, '\'', VDsh),
 1030               atom_concat('=\'',VDsh,EqV),
 1031               atomic_list_concat( ['[',K,']',EqV], '', KVAtm )
 1032          )
 1033     ).
 1034
 1035sqlite_facet_table( arity(Arity), Connection, Table ) :-
 1036     findall( Column, sqlite_table_column(Connection, Table, Column), Columns ),
 1037     length( Columns, Arity ).
 1038
 1039arity_option( Opts, ArityF ) :-
 1040     memberchk( arity(ArityF), Opts ),
 1041     arity_flag_values( Arities ),
 1042     memberchk( ArityF, Arities ),
 1043     !.
 1044arity_option( Opts, ArityF ) :-
 1045     memberchk( arity(ArityF), Opts ),
 1046     !,
 1047     sqlite_fail( wrong_arity_value(ArityF) ).
 1048arity_option( _Opts, arity ). % default for this flag, although we should 
 1049                             % move all defaults to one location/list (fixme)
 1050
 1051kv_decompose( [], [], [] ).
 1052kv_decompose( [K-V|T], [K|Ks], [V|Vs] ) :-
 1053     kv_decompose( T, Ks, Vs ).
 safe_column_names(+Cols, -SafeCols) is det
author
- : Steve Moyle

+Cols is a list of column names stored in the sqlite db -SafeCols is the each element of the input is the atom wrapped in [].

sqlite (and possibly other RDBMSs) does not like columns with names including periods like:

'id.orig_h' They need to be refered to in the select statement as: [id.orig_h]

?- safe_column_names(['id.orig_h'], S). Correct to: "prosqlite:safe_column_names(['id.orig_h'],S)"? yes S = ['[id.orig_h]'].

 1074safe_column_names([], []).
 1075safe_column_names([Col | Cols], [SafeCol | SafeCols]) :-
 1076    safe_column_name(Col, SafeCol),
 1077    safe_column_names(Cols, SafeCols).
 1078
 1079safe_column_name(Col, SafeCol) :-
 1080        format(atom(SafeCol), '[~w]', [Col])