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 odbc_cancel_thread/1, 58 59 odbc_current_table/2, 60 odbc_current_table/3, 61 odbc_table_column/3, 62 odbc_table_column/4, 63 odbc_type/3, 64 odbc_data_source/2, 65
66 odbc_table_primary_key/3, 67 odbc_table_foreign_key/5, 68
69 odbc_set_option/1, 70 odbc_statistics/1, 71 odbc_debug/1 72 ]). 73:- autoload(library(lists),[member/2]). 74
75:- use_foreign_library(foreign(odbc4pl)). 76
80
81odbc_current_connection(Conn, DSN) :-
82 odbc_current_connections(Conn, DSN, Pairs),
83 member(Conn-DSN, Pairs).
84
98
99odbc_driver_connect(DriverString, Connection, Options) :-
100 odbc_connect(-, Connection, [driver_string(DriverString)|Options]).
101
105
106odbc_query(Connection, SQL, Row) :-
107 odbc_query(Connection, SQL, Row, []).
108
112
113odbc_query(Connection, SQL) :-
114 odbc_query(Connection, SQL, Row),
115 !,
116 ( Row = affected(_)
117 -> true
118 ; print_message(warning, odbc(unexpected_result(Row)))
119 ).
120
121odbc_execute(Statement, Parameters) :-
122 odbc_execute(Statement, Parameters, Row),
123 !,
124 ( Row = affected(_)
125 -> true
126 ; print_message(warning, odbc(unexpected_result(Row)))
127 ).
128
129odbc_prepare(Connection, SQL, Parameters, Statement) :-
130 odbc_prepare(Connection, SQL, Parameters, Statement, []).
131
132 135
139
140odbc_current_table(Connection, Table) :-
141 odbc_tables(Connection, row(_Qualifier, _Owner, Table, 'TABLE', _Comment)).
142
143odbc_current_table(Connection, Table, Facet) :-
144 odbc_tables(Connection, Tuple),
145 arg(3, Tuple, Table),
146 table_facet(Facet, Connection, Tuple).
147
148table_facet(qualifier(Qualifier), _, Tuple) :- arg(1, Tuple, Qualifier).
149table_facet(owner(Owner), _, Tuple) :- arg(2, Tuple, Owner).
150table_facet(type(Type), _, Tuple) :- arg(4, Tuple, Type).
151table_facet(comment(Comment), _, Tuple) :- arg(5, Tuple, Comment).
152table_facet(arity(Arity), Connection, Tuple) :-
153 arg(3, Tuple, Table),
154 findall(C, odbc_table_column(Connection, Table, C), Cs),
155 length(Cs, Arity).
156
161
162odbc_table_column(Connection, Table, Column) :-
163 table_column(Connection, Table, Column, _Tuple).
164
165table_column(Connection, Table, Column, Tuple) :-
166 ( var(Table)
167 -> odbc_current_table(Connection, Table)
168 ; true
169 ),
170 ( ground(Column) 171 -> odbc_column(Connection, Table, Tuple),
172 arg(4, Tuple, Column), !
173 ; odbc_column(Connection, Table, Tuple),
174 arg(4, Tuple, Column)
175 ).
176
178
179odbc_table_column(Connection, Table, Column, Facet) :-
180 table_column(Connection, Table, Column, Tuple),
181 column_facet(Facet, Tuple).
182
183column_facet(table_qualifier(Q), T) :- arg(1, T, Q).
184column_facet(table_owner(Q), T) :- arg(2, T, Q).
185column_facet(table_name(Q), T) :- arg(3, T, Q).
187column_facet(data_type(Q), T) :- arg(5, T, Q).
188column_facet(type_name(Q), T) :- arg(6, T, Q).
189column_facet(precision(Q), T) :- non_null_arg(7, T, Q).
190column_facet(length(Q), T) :- non_null_arg(8, T, Q).
191column_facet(scale(Q), T) :- non_null_arg(9, T, Q).
192column_facet(radix(Q), T) :- non_null_arg(10, T, Q).
193column_facet(nullable(Q), T) :- non_null_arg(11, T, Q).
194column_facet(remarks(Q), T) :- non_null_arg(12, T, Q).
195column_facet(type(Type), T) :-
196 arg(6, T, TypeName),
197 sql_type(TypeName, T, Type).
198
203
204sql_type(dec, T, Type) :-
205 !,
206 sql_type(decimal, T, Type).
207sql_type(numeric, T, Type) :-
208 !,
209 sql_type(decimal, T, Type).
210sql_type(decimal, T, Type) :-
211 !,
212 column_facet(precision(Len), T),
213 ( column_facet(scale(D), T),
214 D \== 0
215 -> Type = decimal(Len, D)
216 ; Type = decimal(Len)
217 ).
218sql_type(char, T, char(Len)) :-
219 !,
220 column_facet(length(Len), T).
221sql_type(varchar, T, varchar(Len)) :-
222 !,
223 column_facet(length(Len), T).
224sql_type(TypeName, _T, Type) :-
225 downcase_atom(TypeName, Type).
226
228
229odbc_type(Connection, TypeSpec, Facet) :-
230 odbc_types(Connection, TypeSpec, Row),
231 type_facet(Facet, Row).
232
233type_facet(name(V), Row) :- arg(1, Row, V).
234type_facet(data_type(V), Row) :- arg(2, Row, V).
235type_facet(precision(V), Row) :- arg(3, Row, V).
236type_facet(literal_prefix(V), Row) :- non_null_arg(4, Row, V).
237type_facet(literal_suffix(V), Row) :- non_null_arg(5, Row, V).
238type_facet(create_params(V), Row) :- non_null_arg(6, Row, V).
239type_facet(nullable(V), Row) :- arg(7, Row, I), nullable_arg(I, V).
240type_facet(case_sensitive(V), Row) :- bool_arg(8, Row, V).
241type_facet(searchable(V), Row) :- arg(9, Row, I), searchable_arg(I, V).
242type_facet(unsigned(V), Row) :- bool_arg(10, Row, V).
243type_facet(money(V), Row) :- bool_arg(11, Row, V).
244type_facet(auto_increment(V), Row) :- bool_arg(12, Row, V).
245type_facet(local_name(V), Row) :- non_null_arg(13, Row, V).
246type_facet(minimum_scale(V), Row) :- non_null_arg(14, Row, V).
247type_facet(maximum_scale(V), Row) :- non_null_arg(15, Row, V).
248
249non_null_arg(Index, Row, V) :-
250 arg(Index, Row, V),
251 V \== '$null$'.
252bool_arg(Index, Row, V) :-
253 arg(Index, Row, I),
254 int_to_bool(I, V).
255
256int_to_bool(0, false).
257int_to_bool(1, true).
258
259nullable_arg(0, false).
260nullable_arg(1, true).
261nullable_arg(2, unknown).
262
263searchable_arg(0, false).
264searchable_arg(1, like_only).
265searchable_arg(2, all_except_like).
266searchable_arg(4, true).
267
268
272
273odbc_data_source(DSN, Description) :-
274 odbc_data_sources(List),
275 member(data_source(DSN, Description), List).
276
277 280
284
285odbc_table_primary_key(Connection, Table, Column) :-
286 ( var(Table)
287 -> odbc_current_table(Connection, Table)
288 ; true
289 ),
290 ( ground(Column) 291 -> odbc_primary_key(Connection, Table, Tuple),
292 arg(4, Tuple, Column), !
293 ; odbc_primary_key(Connection, Table, Tuple),
294 arg(4, Tuple, Column)
295 ).
296
300
301odbc_table_foreign_key(Connection, PkTable, PkColumn, FkTable, FkColumn) :-
302 odbc_foreign_key(Connection, PkTable, FkTable, Tuple),
303 ( var(PkTable) -> arg(3, Tuple, PkTable) ; true ),
304 arg(4, Tuple, PkColumn),
305 ( var(FkTable) -> arg(7, Tuple, FkTable) ; true ),
306 arg(8, Tuple, FkColumn).
307
308
309 312
313odbc_statistics(Key) :-
314 statistics_key(Key),
315 '$odbc_statistics'(Key).
316
317statistics_key(statements(_Created, _Freed)).
318
319
320 323
324:- multifile
325 prolog:message/3. 326
327prolog:message(error(odbc(ODBCCode, _NativeCode, Comment), _)) -->
328 [ 'ODBC: State ~w: ~w'-[ODBCCode, Comment] ].
329prolog:message(error(context_error(Obj, Error, What), _)) -->
330 [ 'Context error: ~w ~w: '-[What, Obj] ],
331 context(Error).
332
333prolog:message(odbc(ODBCCode, _NativeCode, Comment)) -->
334 [ 'ODBC: State ~w: ~w'-[ODBCCode, Comment] ].
335prolog:message(odbc(unexpected_result(Row))) -->
336 [ 'ODBC: Unexpected result-row: ~p'-[Row] ].
337
338context(in_use) -->
339 [ 'object is in use' ]