34
35:- module(odbc,
36 [ odbc_connect/3, 37 odbc_driver_connect/3, 38 odbc_disconnect/1, 39 odbc_current_connection/2, 40 odbc_set_connection/2, 41 odbc_get_connection/2, 42 odbc_end_transaction/2, 43
44 odbc_query/4, 45 odbc_query/3, 46 odbc_query/2, 47
48 odbc_prepare/4, 49 odbc_prepare/5, 50 odbc_execute/2, 51 odbc_execute/3, 52 odbc_fetch/3, 53 odbc_next_result_set/1, 54 odbc_close_statement/1, 55 odbc_clone_statement/2, 56 odbc_free_statement/1, 57 58 odbc_current_table/2, 59 odbc_current_table/3, 60 odbc_table_column/3, 61 odbc_table_column/4, 62 odbc_type/3, 63 odbc_data_source/2, 64
65 odbc_table_primary_key/3, 66 odbc_table_foreign_key/5, 67
68 odbc_set_option/1, 69 odbc_statistics/1, 70 odbc_debug/1 71 ]). 72:- autoload(library(lists),[member/2]). 73
74:- use_foreign_library(foreign(odbc4pl)). 75
76:- if(current_predicate(odbc_cancel_thread/1)). 77:- export(odbc_cancel_thread/1). 78:- endif. 79
83
84odbc_current_connection(Conn, DSN) :-
85 odbc_current_connections(Conn, DSN, Pairs),
86 member(Conn-DSN, Pairs).
87
101
102odbc_driver_connect(DriverString, Connection, Options) :-
103 odbc_connect(-, Connection, [driver_string(DriverString)|Options]).
104
108
109odbc_query(Connection, SQL, Row) :-
110 odbc_query(Connection, SQL, Row, []).
111
115
116odbc_query(Connection, SQL) :-
117 odbc_query(Connection, SQL, Row),
118 !,
119 ( Row = affected(_)
120 -> true
121 ; print_message(warning, odbc(unexpected_result(Row)))
122 ).
123
124odbc_execute(Statement, Parameters) :-
125 odbc_execute(Statement, Parameters, Row),
126 !,
127 ( Row = affected(_)
128 -> true
129 ; print_message(warning, odbc(unexpected_result(Row)))
130 ).
131
132odbc_prepare(Connection, SQL, Parameters, Statement) :-
133 odbc_prepare(Connection, SQL, Parameters, Statement, []).
134
135 138
142
143odbc_current_table(Connection, Table) :-
144 odbc_tables(Connection, row(_Qualifier, _Owner, Table, 'TABLE', _Comment)).
145
146odbc_current_table(Connection, Table, Facet) :-
147 odbc_tables(Connection, Tuple),
148 arg(3, Tuple, Table),
149 table_facet(Facet, Connection, Tuple).
150
151table_facet(qualifier(Qualifier), _, Tuple) :- arg(1, Tuple, Qualifier).
152table_facet(owner(Owner), _, Tuple) :- arg(2, Tuple, Owner).
153table_facet(type(Type), _, Tuple) :- arg(4, Tuple, Type).
154table_facet(comment(Comment), _, Tuple) :- arg(5, Tuple, Comment).
155table_facet(arity(Arity), Connection, Tuple) :-
156 arg(3, Tuple, Table),
157 findall(C, odbc_table_column(Connection, Table, C), Cs),
158 length(Cs, Arity).
159
164
165odbc_table_column(Connection, Table, Column) :-
166 table_column(Connection, Table, Column, _Tuple).
167
168table_column(Connection, Table, Column, Tuple) :-
169 ( var(Table)
170 -> odbc_current_table(Connection, Table)
171 ; true
172 ),
173 ( ground(Column) 174 -> odbc_column(Connection, Table, Tuple),
175 arg(4, Tuple, Column), !
176 ; odbc_column(Connection, Table, Tuple),
177 arg(4, Tuple, Column)
178 ).
179
181
182odbc_table_column(Connection, Table, Column, Facet) :-
183 table_column(Connection, Table, Column, Tuple),
184 column_facet(Facet, Tuple).
185
186column_facet(table_qualifier(Q), T) :- arg(1, T, Q).
187column_facet(table_owner(Q), T) :- arg(2, T, Q).
188column_facet(table_name(Q), T) :- arg(3, T, Q).
190column_facet(data_type(Q), T) :- arg(5, T, Q).
191column_facet(type_name(Q), T) :- arg(6, T, Q).
192column_facet(precision(Q), T) :- non_null_arg(7, T, Q).
193column_facet(length(Q), T) :- non_null_arg(8, T, Q).
194column_facet(scale(Q), T) :- non_null_arg(9, T, Q).
195column_facet(radix(Q), T) :- non_null_arg(10, T, Q).
196column_facet(nullable(Q), T) :- non_null_arg(11, T, Q).
197column_facet(remarks(Q), T) :- non_null_arg(12, T, Q).
198column_facet(type(Type), T) :-
199 arg(6, T, TypeName),
200 sql_type(TypeName, T, Type).
201
206
207sql_type(dec, T, Type) :-
208 !,
209 sql_type(decimal, T, Type).
210sql_type(numeric, T, Type) :-
211 !,
212 sql_type(decimal, T, Type).
213sql_type(decimal, T, Type) :-
214 !,
215 column_facet(precision(Len), T),
216 ( column_facet(scale(D), T),
217 D \== 0
218 -> Type = decimal(Len, D)
219 ; Type = decimal(Len)
220 ).
221sql_type(char, T, char(Len)) :-
222 !,
223 column_facet(length(Len), T).
224sql_type(varchar, T, varchar(Len)) :-
225 !,
226 column_facet(length(Len), T).
227sql_type('TEXT', T, longvarchar(Len)) :-
228 !,
229 column_facet(length(Len), T).
230sql_type(TypeName, _T, Type) :-
231 downcase_atom(TypeName, Type).
232
234
235odbc_type(Connection, TypeSpec, Facet) :-
236 odbc_types(Connection, TypeSpec, Row),
237 type_facet(Facet, Row).
238
239type_facet(name(V), Row) :- arg(1, Row, V).
240type_facet(data_type(V), Row) :- arg(2, Row, V).
241type_facet(precision(V), Row) :- arg(3, Row, V).
242type_facet(literal_prefix(V), Row) :- non_null_arg(4, Row, V).
243type_facet(literal_suffix(V), Row) :- non_null_arg(5, Row, V).
244type_facet(create_params(V), Row) :- non_null_arg(6, Row, V).
245type_facet(nullable(V), Row) :- arg(7, Row, I), nullable_arg(I, V).
246type_facet(case_sensitive(V), Row) :- bool_arg(8, Row, V).
247type_facet(searchable(V), Row) :- arg(9, Row, I), searchable_arg(I, V).
248type_facet(unsigned(V), Row) :- bool_arg(10, Row, V).
249type_facet(money(V), Row) :- bool_arg(11, Row, V).
250type_facet(auto_increment(V), Row) :- bool_arg(12, Row, V).
251type_facet(local_name(V), Row) :- non_null_arg(13, Row, V).
252type_facet(minimum_scale(V), Row) :- non_null_arg(14, Row, V).
253type_facet(maximum_scale(V), Row) :- non_null_arg(15, Row, V).
254
255non_null_arg(Index, Row, V) :-
256 arg(Index, Row, V),
257 V \== '$null$'.
258bool_arg(Index, Row, V) :-
259 arg(Index, Row, I),
260 int_to_bool(I, V).
261
262int_to_bool(0, false).
263int_to_bool(1, true).
264
265nullable_arg(0, false).
266nullable_arg(1, true).
267nullable_arg(2, unknown).
268
269searchable_arg(0, false).
270searchable_arg(1, like_only).
271searchable_arg(2, all_except_like).
272searchable_arg(4, true).
273
274
278
279odbc_data_source(DSN, Description) :-
280 odbc_data_sources(List),
281 member(data_source(DSN, Description), List).
282
283 286
290
291odbc_table_primary_key(Connection, Table, Column) :-
292 ( var(Table)
293 -> odbc_current_table(Connection, Table)
294 ; true
295 ),
296 ( ground(Column) 297 -> odbc_primary_key(Connection, Table, Tuple),
298 arg(4, Tuple, Column), !
299 ; odbc_primary_key(Connection, Table, Tuple),
300 arg(4, Tuple, Column)
301 ).
302
306
307odbc_table_foreign_key(Connection, PkTable, PkColumn, FkTable, FkColumn) :-
308 odbc_foreign_key(Connection, PkTable, FkTable, Tuple),
309 ( var(PkTable) -> arg(3, Tuple, PkTable) ; true ),
310 arg(4, Tuple, PkColumn),
311 ( var(FkTable) -> arg(7, Tuple, FkTable) ; true ),
312 arg(8, Tuple, FkColumn).
313
314
315 318
319odbc_statistics(Key) :-
320 statistics_key(Key),
321 '$odbc_statistics'(Key).
322
323statistics_key(statements(_Created, _Freed)).
324
325
326 329
330:- multifile
331 prolog:message/3. 332
333prolog:message(error(odbc(ODBCCode, _NativeCode, Comment), _)) -->
334 [ 'ODBC: State ~w: ~w'-[ODBCCode, Comment] ].
335prolog:message(error(context_error(Obj, Error, What), _)) -->
336 [ 'Context error: ~w ~w: '-[What, Obj] ],
337 context(Error).
338
339prolog:message(odbc(ODBCCode, _NativeCode, Comment)) -->
340 [ 'ODBC: State ~w: ~w'-[ODBCCode, Comment] ].
341prolog:message(odbc(unexpected_result(Row))) -->
342 [ 'ODBC: Unexpected result-row: ~p'-[Row] ].
343
344context(in_use) -->
345 [ 'object is in use' ]