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