r9372: further uffi porting
[clsql.git] / db-oracle / oracle-sql.lisp
1 ;;;; -*- Mode: LISP; Syntax: ANSI-Common-Lisp; Base: 10 -*-
2 ;;;; *************************************************************************
3 ;;;; FILE IDENTIFICATION
4 ;;;;
5 ;;;; Name:          oracle-sql.lisp
6 ;;;;
7 ;;;; $Id$
8 ;;;;
9 ;;;; This file is part of CLSQL.
10 ;;;;
11 ;;;; CLSQL users are granted the rights to distribute and use this software
12 ;;;; as governed by the terms of the Lisp Lesser GNU Public License
13 ;;;; (http://opensource.franz.com/preamble.html), also known as the LLGPL.
14 ;;;; *************************************************************************
15
16 (in-package #:clsql-oracle)
17
18 (defmethod database-initialize-database-type
19     ((database-type (eql :oracle)))
20   t)
21
22 ;;;; KLUDGE: The original prototype of this code was implemented using
23 ;;;; lots of special variables holding MAKE-ALIEN values. When I was 
24 ;;;; first converting it to use WITH-ALIEN variables, I was confused
25 ;;;; about the behavior of MAKE-ALIEN and WITH-ALIEN; I thought that
26 ;;;; (MAKE-ALIEN TYPEFOO) returned the same type of object as is bound
27 ;;;; to the name BAR by (WITH-ALIEN ((BAR TYPEFOO)) ..). In fact the
28 ;;;; value returned by MAKE-ALIEN has an extra level of indirection
29 ;;;; relative to the value bound by WITH-ALIEN, i.e.  (DEREF
30 ;;;; (MAKE-ALIEN TYPEFOO)) has the same type as the value bound to the
31 ;;;; name BAR by (WITH-ALIEN ((BAR TYPEFOO)) ..). Laboring under my
32 ;;;; misunderstanding, I was unable to use ordinary scalars bound by
33 ;;;; WITH-ALIEN, and I ended up giving up and deciding to work around
34 ;;;; this apparent bug in CMUCL by using 1-element arrays instead.
35 ;;;; This "workaround" for my misunderstanding is obviously unnecessary
36 ;;;; and confusing, but still remains in the code. -- WHN 20000106
37
38
39 ;;;; arbitrary parameters, tunable for performance or other reasons
40
41 (uffi:def-foreign-type void-pointer (* :void))
42
43 (eval-when (:compile-toplevel :load-toplevel :execute)
44   (defconstant +errbuf-len+ 512
45     "the number of characters that we allocate for an error message buffer")
46   (defconstant +n-buf-rows+ 200
47     "the number of table rows that we buffer at once when reading a table.
48 CMUCL has a compiled-in limit on how much C data can be allocated
49 (through malloc() and friends) at any given time, typically 8 Mb.
50 Setting this constant to a moderate value should make it less
51 likely that we'll have to worry about the CMUCL limit."))
52
53
54 ;;; utilities for mucking around with C-level stuff
55
56 ;; Return the address of ALIEN-OBJECT (like the C operator "&").
57 ;;
58 ;; The INDICES argument is useful to give the ALIEN-OBJECT the
59 ;; expected number of zero indices, especially when we have a bunch of
60 ;; 1-element arrays running around due to the workaround for the CMUCL
61 ;; 18b WITH-ALIEN scalar bug.
62
63 (defmacro c-& (alien-object type)
64   `(uffi:pointer-address (uffi:deref-pointer ,alien-object ,type)))
65
66 ;; constants - from OCI?
67
68 (defconstant +var-not-in-list+       1007)
69 (defconstant +no-data-found+         1403)
70 (defconstant +null-value-returned+   1405)
71 (defconstant +field-truncated+       1406)
72
73 (eval-when (:compile-toplevel :load-toplevel :execute)
74   (defconstant SQLT-INT 3)
75   (defconstant SQLT-STR 5)
76   (defconstant SQLT-FLT 4)
77   (defconstant SQLT-DATE 12))
78
79 ;;; Note that despite the suggestive class name (and the way that the
80 ;;; *DEFAULT-DATABASE* variable holds an object of this class), a DB
81 ;;; object is not actually a database but is instead a connection to a
82 ;;; database. Thus, there's no obstacle to having any number of DB
83 ;;; objects referring to the same database.
84
85 (uffi:def-type pointer-pointer-void '(* (* :void)))
86
87 (defclass oracle-database (database)    ; was struct db
88   ((envhp
89     :reader envhp
90     :initarg :envhp
91     :type pointer-pointer-void
92     :documentation
93     "OCI environment handle")
94    (errhp
95     :reader errhp
96     :initarg :errhp
97     :type pointer-pointer-void
98     :documentation
99     "OCI error handle")
100    (svchp
101     :reader svchp
102     :initarg :svchp
103     :type pointer-pointer-void
104     :documentation
105     "OCI service context handle")
106    (data-source-name
107     :initarg :dsn
108     :initform nil
109     :documentation
110     "optional data source name (used only for debugging/printing)")
111    (user
112     :initarg :user
113     :reader user
114     :type string
115     :documentation
116     "the \"user\" value given when data source connection was made")
117    (date-format
118     :initarg :date-format
119     :reader date-format
120     :initform "YYYY-MM-DD HH24:MI:SS\"+00\"")
121    (date-format-length
122     :type number
123     :documentation
124     "Each database connection can be configured with its own date
125 output format.  In order to extract date strings from output buffers
126 holding multiple date strings in fixed-width fields, we need to know
127 the length of that format.")))
128
129
130 ;;; Handle the messy case of return code=+oci-error+, querying the
131 ;;; system for subcodes and reporting them as appropriate. ERRHP and
132 ;;; NULLS-OK are as in the OERR function.
133
134 (defun handle-oci-error (&key database nulls-ok)
135   (cond (database
136          (with-slots (errhp)
137              database
138            (uffi:with-foreign-objects ((errbuf (:array :unsigned-char #.+errbuf-len+))
139                                        (errcode :long))
140              (setf (uffi:deref-array errbuf '(:array :unsigned-char) 0) (code-char 0)) ; i.e. init to empty string
141              (setf (uffi:deref-pointer errcode :long) 0)
142              (oci-error-get (uffi:deref-pointer errhp '(* :void)) 1 "" (c-& errcode :unsigned-char) 
143                             (c-& errbuf :unsigned-char) +errbuf-len+ +oci-htype-error+)
144              (let ((subcode (uffi:deref-pointer errcode :long)))
145                (unless (and nulls-ok (= subcode +null-value-returned+))
146                  (error 'clsql-sql-error
147                         :database database
148                         :errno subcode
149                         :expression (uffi:convert-from-foreign-string errbuf)))))))
150         (nulls-ok
151          (error 'clsql-sql-error
152                 :database database
153                 :message "can't handle NULLS-OK without ERRHP"))
154         (t 
155          (error 'clsql-sql-error
156                 :database database
157                 :message "OCI Error (and no ERRHP available to find subcode)"))))
158
159 ;;; Require an OCI success code.
160 ;;;
161 ;;; (The ordinary OCI error reporting mechanisms uses a fair amount of
162 ;;; machinery (environments and other handles). In order to get to
163 ;;; where we can use these mechanisms, we have to be able to allocate
164 ;;; the machinery. The functions for allocating the machinery can
165 ;;; return errors (e.g. out of memory) but shouldn't. Wrapping this function
166 ;;; around function calls to such have-to-succeed functions enforces
167 ;;; this condition.)
168
169 (defun osucc (code)
170   (declare (type fixnum code))
171   (unless (= code +oci-success+)
172     (error 'dbi-error
173            :format-control "unexpected OCI failure, code=~S"
174            :format-arguments (list code))))
175
176
177 ;;; Enabling this can be handy for low-level debugging.
178 #+nil
179 (progn
180   (trace oci-initialize #+oci-8-1-5 oci-env-create oci-handle-alloc oci-logon
181          oci-error-get oci-stmt-prepare oci-stmt-execute
182          oci-param-get oci-logon oci-attr-get oci-define-by-pos oci-stmt-fetch)
183   (setf debug::*debug-print-length* nil))
184
185
186 ;;;; the OCI library, part V: converting from OCI representations to Lisp
187 ;;;; representations
188
189 ;; Return the INDEXth string of the OCI array, represented as Lisp
190 ;; SIMPLE-STRING. SIZE is the size of the fixed-width fields used by
191 ;; Oracle to store strings within the array.
192
193 ;; In the wild world of databases, trailing spaces aren't generally
194 ;; significant, since e.g. "LARRY " and "LARRY    " are the same string
195 ;; stored in different fixed-width fields. OCI drops trailing spaces
196 ;; for us in some cases but apparently not for fields of fixed
197 ;; character width, e.g.
198 ;;
199 ;;   (dbi:sql "create table employees (name char(15), job char(15), city
200 ;;            char(15), rate float)" :db orcl :types :auto)
201 ;; In order to map the "same string" property above onto Lisp equality,
202 ;; we drop trailing spaces in all cases:
203
204 (uffi:def-type string-pointer (* :unsigned-char))
205
206 (defun deref-oci-string (arrayptr string-index size)
207   (declare (type string-pointer arrayptr))
208   (declare (type (mod #.+n-buf-rows+) string-index))
209   (declare (type (and unsigned-byte fixnum) size))
210   (let* ((raw (uffi:convert-from-foreign-string 
211                (uffi:pointer-address (uffi:deref-array arrayptr '(:array :unsigned-char) (* string-index size)))))
212          (trimmed (string-trim " " raw)))
213     (if (equal trimmed "NULL") nil trimmed)))
214
215 ;; the OCI library, part Z: no-longer used logic to convert from
216 ;; Oracle's binary date representation to Common Lisp's native date
217 ;; representation
218
219 #+nil
220 (defvar +oci-date-bytes+ 7)
221
222 ;;; Return the INDEXth date in the OCI array, represented as
223 ;;; a Common Lisp "universal time" (i.e. seconds since 1900).
224
225 #+nil
226 (defun deref-oci-date (arrayptr index)
227   (oci-date->universal-time (uffi:pointer-address (uffi:deref-array arrayptr '(:array :unsigned-char)
228                                                     (* index +oci-date-bytes+)))))
229 #+nil
230 (defun oci-date->universal-time (oci-date)
231   (declare (type (alien (* :unsigned-char)) oci-date))
232   (flet (;; a character from OCI-DATE, interpreted as an unsigned byte
233          (ub (i)
234            (declare (type (mod #.+oci-date-bytes+) i))
235            (mod (uffi:deref-array oci-date string-pointer i) 256)))
236     (let* ((century (* (- (ub 0) 100) 100))
237            (year    (+ century (- (ub 1) 100)))
238            (month   (ub 2))
239            (day     (ub 3))
240            (hour    (1- (ub 4)))
241            (minute  (1- (ub 5)))
242            (second  (1- (ub 6))))
243       (encode-universal-time second minute hour day month year))))
244
245 ;; Return (VALUES ALL-TABLES COLUMN-NAMES), where ALL-TABLES is a
246 ;; table containing one row for each table available in DB, and
247 ;; COLUMN-NAMES is a list of header names for the columns in
248 ;; ALL-TABLES.
249 ;;
250 ;; The Allegro version also accepted a HSTMT argument.
251
252 ;(defmethod database-list-tables ((db oracle-database))
253 ;  (sql:query "select '',OWNER,TABLE_NAME,TABLE_TYPE,'' from all_catalog"))
254   
255
256 (defmethod list-all-user-database-tables ((db oracle-database))
257   (unless db
258     (setf db clsql:*default-database*))
259   (values (database-query "select TABLE_NAME from all_catalog
260                 where owner <> 'PUBLIC' and owner <> 'SYSTEM' and owner <> 'SYS'"
261                           db nil nil)))
262
263
264 (defmethod database-list-tables ((database oracle-database)
265                                  &key (system-tables nil) owner)
266   (if system-tables
267       (database-query "select table_name from all_catalog" database nil nil)
268     (database-query "select table_name from all_catalog where owner <> 'PUBLIC' and owner <> 'SYSTEM' and owner <> 'SYS'"
269                     database nil nil)))
270
271 ;; Return a list of all columns in TABLE.
272 ;;
273 ;; The Allegro version of this also returned a second value.
274
275 (defmethod list-all-table-columns (table (db oracle-database))
276   (declare (type string table))
277   (unless db
278     (setf db clsql:*default-database*))
279   (let* ((sql-stmt (concatenate
280                     'simple-string
281                     "select "
282                     "'',"
283                     "all_tables.OWNER,"
284                     "'',"
285                     "user_tab_columns.COLUMN_NAME,"
286                     "user_tab_columns.DATA_TYPE from user_tab_columns,"
287                     "all_tables where all_tables.table_name = '" table "'"
288                     " and user_tab_columns.table_name = '" table "'"))
289          (preresult (sql sql-stmt :db db :types :auto)))
290     ;; PRERESULT is like RESULT except that it has a name instead of
291     ;; type codes in the fifth column of each row. To fix this, we
292     ;; destructively modify PRERESULT.
293     (dolist (preresult-row preresult)
294       (setf (fifth preresult-row)
295             (if (find (fifth preresult-row)
296                       #("NUMBER" "DATE")
297                       :test #'string=)
298                 2 ; numeric
299                 1))) ; string
300     preresult))
301
302 (defmethod database-list-attributes (table (database oracle-database) &key owner)
303   (let* ((relname (etypecase table
304                     (clsql-sys::sql-ident
305                      (string-upcase
306                       (symbol-name (slot-value table 'clsql-sys::name))))
307                     (string table))))
308     (mapcar #'car
309             (database-query
310              (format nil
311                      "select user_tab_columns,column_name from user_tab_columns where user_tab_columns.table_name=~A"
312                      relname)
313              database nil nil))))
314
315
316
317 ;; Return one row of the table referred to by QC, represented as a
318 ;; list; or if there are no more rows, signal an error if EOF-ERRORP,
319 ;; or return EOF-VALUE otherwise.
320
321 ;; KLUDGE: This CASE statement is a strong sign that the code would be
322 ;; cleaner if CD were made into an abstract class, we made variant
323 ;; classes for CD-for-column-of-strings, CD-for-column-of-floats,
324 ;; etc., and defined virtual functions to handle operations like
325 ;; get-an-element-from-column. (For a small special purpose module
326 ;; like this, would arguably be overkill, so I'm not going to do it
327 ;; now, but if this code ends up getting more complicated in
328 ;; maintenance, it would become a really good idea.)
329
330 ;; Arguably this would be a good place to signal END-OF-FILE, but
331 ;; since the ANSI spec specifically says that END-OF-FILE means a
332 ;; STREAM which has no more data, and QC is not a STREAM, we signal
333 ;; DBI-ERROR instead.
334
335 (uffi:def-type short-pointer '(* :short))
336 (uffi:def-type double-pointer '(* :double))
337
338 ;;; the result of a database query: a cursor through a table
339 (defstruct (oracle-result-set (:print-function print-query-cursor)
340                               (:conc-name qc-)
341                               (:constructor %make-query-cursor))
342   (db (error "missing DB")              ; db conn. this table is associated with
343     :type db
344     :read-only t)
345   (stmthp (error "missing STMTHP")      ; the statement handle used to create
346 ;;  :type alien                 ; this table. owned by the QUERY-CURSOR
347     :read-only t)                       ; object, deallocated on CLOSE-QUERY
348   (cds) ;  (error "missing CDS")            ; column descriptors
349 ;    :type (simple-array cd 1)
350                                         ;    :read-only t)
351   (n-from-oci 
352    0                         ; buffered rows: number of rows recv'd
353    :type (integer 0 #.+n-buf-rows+))   ; from the database on the last read
354   (n-to-dbi
355    0                           ; number of buffered rows returned, i.e.
356    :type (integer 0 #.+n-buf-rows+))   ; the index, within the buffered rows,
357                                         ; of the next row which hasn't already
358                                         ; been returned
359   (total-n-from-oci
360    0                   ; total number of bytes recv'd from OCI
361    :type unsigned-byte)                ; in all reads
362   (oci-end-seen-p nil))                 ; Have we seen the end of OCI
363                                         ; data, i.e. OCI returning
364                                         ; less data than we requested?
365                                         ; OCI doesn't seem to like us
366                                         ; to try to read more data
367                                         ; from it after that..
368
369
370 (defun fetch-row (qc &optional (eof-errorp t) eof-value)
371   (declare (optimize (speed 3)))
372   (cond ((zerop (qc-n-from-oci qc))
373          (if eof-errorp
374              (error 'clsql-error :message
375                     (format nil "no more rows available in ~S" qc))
376            eof-value))
377         ((>= (qc-n-to-dbi qc)
378              (qc-n-from-oci qc))
379          (refill-qc-buffers qc)
380          (fetch-row qc nil eof-value))
381         (t
382          (let ((cds (qc-cds qc))
383                (reversed-result nil)
384                (irow (qc-n-to-dbi qc)))
385            (dotimes (icd (length cds))
386              (let* ((cd (aref cds icd))
387                     (b (foreign-resource-buffer (cd-buffer cd)))
388                     (value
389                      (let ((arb (foreign-resource-buffer (cd-indicators cd))))
390                        (declare (type short-pointer arb))
391                        (unless (= (uffi:deref-array arb :int irow) -1)
392                          (ecase (cd-oci-data-type cd)
393                            (#.SQLT-STR  (deref-oci-string b irow (cd-sizeof cd)))
394                            (#.SQLT-FLT  (uffi:deref-array b '(:array :double) irow))
395                            (#.SQLT-INT  (uffi:deref-array b '(:array :int) irow))
396                            (#.SQLT-DATE (deref-oci-string b irow (cd-sizeof cd))))))))
397                (push value reversed-result)))
398            (incf (qc-n-to-dbi qc))
399            (nreverse reversed-result)))))
400
401 (defun refill-qc-buffers (qc)
402   (with-slots (errhp)
403     (qc-db qc)
404     (setf (qc-n-to-dbi qc) 0)
405     (cond ((qc-oci-end-seen-p qc)
406            (setf (qc-n-from-oci qc) 0))
407           (t
408            (let ((oci-code (%oci-stmt-fetch (uffi:deref-pointer (qc-stmthp qc) void-pointer)
409                                            (uffi:deref-pointer errhp void-pointer)
410                                            +n-buf-rows+
411                                            +oci-fetch-next+ +oci-default+)))
412              (ecase oci-code
413                (#.+oci-success+ (values))
414                (#.+oci-no-data+ (setf (qc-oci-end-seen-p qc) t)
415                                 (values))
416                (#.+oci-error+ (handle-oci-error :database (qc-db qc)
417                                                 :nulls-ok t))))
418            (uffi:with-foreign-object (rowcount :long)
419              (oci-attr-get (uffi:deref-pointer (qc-stmthp qc) void-pointer) +oci-htype-stmt+
420                            (c-& rowcount :long) nil +oci-attr-row-count+ 
421                            (uffi:deref-pointer errhp void-pointer))
422              (setf (qc-n-from-oci qc)
423                    (- (uffi:deref-pointer rowcount :long) (qc-total-n-from-oci qc)))
424              (when (< (qc-n-from-oci qc) +n-buf-rows+)
425                (setf (qc-oci-end-seen-p qc) t))
426              (setf (qc-total-n-from-oci qc)
427                    (uffi:deref-pointer rowcount :long)))))
428     (values)))
429
430 ;; the guts of the SQL function
431 ;;
432 ;; (like the SQL function, but with the QUERY argument hardwired to T, so
433 ;; that the return value is always a cursor instead of a list)
434
435 ;; Is this a SELECT statement?  SELECT statements are handled
436 ;; specially by OCIStmtExecute().  (Non-SELECT statements absolutely
437 ;; require a nonzero iteration count, while the ordinary choice for a
438 ;; SELECT statement is a zero iteration count.
439
440 ;; SELECT statements are the only statements which return tables.  We
441 ;; don't free STMTHP in this case, but instead give it to the new
442 ;; QUERY-CURSOR, and the new QUERY-CURSOR becomes responsible for
443 ;; freeing the STMTHP when it is no longer needed.
444
445 (defun sql-stmt-exec (sql-stmt-string db &key types)
446   (with-slots (envhp svchp errhp)
447     db
448     (let ((stmthp (uffi:allocate-foreign-object (* :void))))
449       (uffi:with-foreign-object (stmttype :unsigned-short)
450         
451         (oci-handle-alloc (uffi:deref-pointer envhp void-pointer) (c-& stmthp void-pointer) +oci-htype-stmt+ 0 nil)
452         (oci-stmt-prepare (uffi:deref-pointer stmthp void-pointer) (uffi:deref-pointer errhp void-pointer)
453                           sql-stmt-string (length sql-stmt-string)
454                           +oci-ntv-syntax+ +oci-default+ :database db)
455         (oci-attr-get (uffi:deref-pointer stmthp void-pointer) +oci-htype-stmt+ 
456                       (c-& stmttype :unsigned-short) nil +oci-attr-stmt-type+ 
457                       (uffi:deref-pointer errhp void-pointer) :database db)
458         (let* ((select-p (= (uffi:deref-pointer stmttype :unsigned-short) 1)) 
459                (iters (if select-p 0 1)))
460           
461           (oci-stmt-execute (uffi:deref-pointer svchp void-pointer) (uffi:deref-pointer stmthp void-pointer)
462                             (uffi:deref-pointer errhp void-pointer)
463                             iters 0 nil nil +oci-default+ :database db)
464           (cond (select-p
465                  (make-query-cursor db stmthp types))
466                 (t
467                  (oci-handle-free (uffi:deref-pointer stmthp void-pointer) +oci-htype-stmt+)
468                  nil)))))))
469
470
471 ;; Return a QUERY-CURSOR representing the table returned from the OCI
472 ;; operation done through STMTHP.  TYPES is the argument of the same
473 ;; name from the external SQL function, controlling type conversion
474 ;; of the returned arguments.
475
476 (defun make-query-cursor (db stmthp types)
477   (let ((qc (%make-query-cursor :db db
478                                 :stmthp stmthp
479                                 :cds (make-query-cursor-cds db stmthp types))))
480     (refill-qc-buffers qc)
481     qc))
482
483
484 ;; the hairy part of MAKE-QUERY-CURSOR: Ask OCI for information
485 ;; about table columns, translate the information into a Lisp
486 ;; vector of column descriptors, and return it.
487
488 ;; Allegro defines several flavors of type conversion, but this
489 ;; implementation only supports the :AUTO flavor.
490
491 ;; A note of explanation: OCI's internal number format uses 21
492 ;; bytes (42 decimal digits). 2 separate (?) one-byte fields,
493 ;; scale and precision, are used to deduce the nature of these
494 ;; 21 bytes. See pp. 3-10, 3-26, and 6-13 of OCI documentation
495 ;; for more details.
496
497 ;; When calling OCI C code to handle the conversion, we have
498 ;; only two numeric types available to pass the return value:
499 ;; double-float and signed-long. It would be possible to
500 ;; bypass the OCI conversion functions and write Lisp code
501 ;; which reads the 21-byte field directly and decodes
502 ;; it. However this is left as an exercise for the reader. :-)
503
504 ;; The following table describes the mapping, based on the implicit
505 ;; assumption that C's "signed long" type is a 32-bit integer.
506 ;;
507 ;;   Internal Values                     SQL Type        C Return Type
508 ;;   ===============                     ========        =============
509 ;;   Precision > 0        SCALE = -127   FLOAT       --> double-float
510 ;;   Precision > 0 && <=9 SCALE = 0      INTEGER     --> signed-long
511 ;;   Precision = 0 || > 9 SCALE = 0      BIG INTEGER --> double-float
512 ;;   Precision > 0        SCALE > 0      DECIMAL     --> double-float
513
514 ;; (OCI uses 1-based indexing here.)
515
516 ;; KLUDGE: This should work for all other data types except those
517 ;; which don't actually fit in their fixed-width field (BLOBs and the
518 ;; like). As Winton says, we (Cadabra) don't need to worry much about
519 ;; those, since we can't reason with them, so we don't use them. But
520 ;; for a more general application it'd be good to have a more
521 ;; selective and rigorously correct test here for whether we can
522 ;; actually handle the given DEREF-DTYPE value. -- WHN 20000106
523
524 ;; Note: The OCI documentation doesn't seem to say whether the COLNAME
525 ;; value returned here is a newly-allocated copy which we're
526 ;; responsible for freeing, or a pointer into some system copy which
527 ;; will be freed when the system itself is shut down.  But judging
528 ;; from the way that the result is used in the cdemodsa.c example
529 ;; program, it looks like the latter: we should make our own copy of
530 ;; the value, but not try to free it.
531
532 ;; WORKAROUND: OCI seems to return ub2 values for the
533 ;; +oci-attr-data-size+ attribute even though its documentation claims
534 ;; that it returns a ub4, and even though the associated "sizep" value
535 ;; is 4, not 2.  In order to make the code here work reliably, without
536 ;; having to patch it later if OCI is ever fixed to match its
537 ;; documentation, we pre-zero COLSIZE before making the call into OCI.
538
539 ;; To exercise the weird OCI behavior (thereby blowing up the code
540 ;; below, beware!) try setting this value into COLSIZE, calling OCI,
541 ;; then looking at the value in COLSIZE.  (setf colsize #x12345678)
542 ;; debugging only
543             
544
545 (defun make-query-cursor-cds (database stmthp types)
546   (declare (optimize (speed 3))
547            (type oracle-database database)
548            (type pointer-pointer-void stmthp))
549   (with-slots (errhp)
550     database
551     (unless (eq types :auto)
552       (error "unsupported TYPES value"))
553     (uffi:with-foreign-objects ((dtype :unsigned-short)
554                            (parmdp (* :void))
555                            (precision :byte)
556                            (scale :byte)
557                            (colname (* :unsigned-char))
558                            (colnamelen :unsigned-long)
559                            (colsize :unsigned-long)
560                            (colsizesize :unsigned-long)
561                            (defnp (* :void)))
562       (let ((buffer nil)
563             (sizeof nil))
564         (do ((icolumn 0 (1+ icolumn))
565              (cds-as-reversed-list nil))
566             ((not (eql (oci-param-get (uffi:deref-pointer stmthp void-pointer) +oci-htype-stmt+
567                                       (uffi:deref-pointer errhp void-pointer)
568                                       (uffi:pointer-address parmdp)
569                                       (1+ icolumn) :database database)
570                        +oci-success+))
571              (coerce (reverse cds-as-reversed-list) 'simple-vector))
572           ;; Decode type of ICOLUMNth column into a type we're prepared to
573           ;; handle in Lisp.
574           (oci-attr-get parmdp +oci-dtype-param+ (uffi:pointer-address dtype)
575                         nil +oci-attr-data-type+ (uffi:deref-pointer errhp void-pointer))
576           (case dtype
577             (#.SQLT-DATE
578              (setf buffer (acquire-foreign-resource char (* 32 +n-buf-rows+)))
579              (setf sizeof 32 dtype #.SQLT-STR))
580             (2 ;; number
581              ;;(oci-attr-get parmdp +oci-dtype-param+
582              ;;(addr precision) nil +oci-attr-precision+
583              ;;(uffi:deref-pointer errhp))
584              (oci-attr-get parmdp +oci-dtype-param+
585                            (uffi:pointer-address scale) nil +oci-attr-scale+
586                            (uffi:deref-pointer errhp void-pointer))
587              (cond
588               ((zerop scale)
589                (setf buffer (acquire-foreign-resource signed +n-buf-rows+)
590                      sizeof 4                   ;; sizeof(int)
591                      dtype #.SQLT-INT))
592               (t
593                (setf buffer (acquire-foreign-resource double-float +n-buf-rows+)
594                      sizeof 8                   ;; sizeof(double)
595                      dtype #.SQLT-FLT))))          
596             (t  ; Default to SQL-STR
597              (setf colsize 0
598                    dtype #.SQLT-STR)
599              (oci-attr-get parmdp +oci-dtype-param+ (uffi:pointer-address colsize)
600                            (uffi:pointer-address colsizesize) +oci-attr-data-size+
601                            (uffi:deref-pointer errhp void-pointer))
602              (let ((colsize-including-null (1+ colsize)))
603                (setf buffer (acquire-foreign-resource char (* +n-buf-rows+ colsize-including-null)))
604                (setf sizeof colsize-including-null))))
605           (let ((retcodes (acquire-foreign-resource short +n-buf-rows+))
606                 (indicators (acquire-foreign-resource short +n-buf-rows+)))
607             (push (make-cd :name "col" ;(subseq colname 0 colnamelen)
608                            :sizeof sizeof
609                            :buffer buffer
610                            :oci-data-type dtype
611                            :retcodes retcodes
612                            :indicators indicators)
613                   cds-as-reversed-list)
614             (oci-define-by-pos (uffi:deref-pointer stmthp void-pointer)
615                                (uffi:pointer-address defnp)
616                                (uffi:deref-pointer errhp void-pointer)
617                                (1+ icolumn) ; OCI 1-based indexing again
618                                (foreign-resource-buffer buffer)
619                                sizeof
620                                dtype
621                                (foreign-resource-buffer indicators)
622                                nil
623                                (foreign-resource-buffer retcodes)
624                                +oci-default+)))))))
625
626 ;; Release the resources associated with a QUERY-CURSOR.
627
628 (defun close-query (qc)
629   (oci-handle-free (uffi:deref-pointer (qc-stmthp qc) void-pointer) +oci-htype-stmt+)
630   (let ((cds (qc-cds qc)))
631     (dotimes (i (length cds))
632       (release-cd-resources (aref cds i))))
633   (values))
634
635
636 ;; Release the resources associated with a column description.
637
638 (defun release-cd-resources (cd)
639   (free-foreign-resource (cd-buffer cd))
640   (free-foreign-resource (cd-retcodes cd))
641   (free-foreign-resource (cd-indicators cd))
642   (values))
643
644
645 (defmethod print-object ((db oracle-database) stream)
646   (print-unreadable-object (db stream :type t :identity t)
647     (format stream "\"/~a/~a\""
648             (slot-value db 'data-source-name)
649             (slot-value db 'user))))
650
651
652 (defmethod database-name-from-spec (connection-spec (database-type (eql :oracle)))
653   (check-connection-spec connection-spec database-type (user password dsn))
654   (destructuring-bind (user password dsn)
655       connection-spec
656     (declare (ignore password))
657     (concatenate 'string "/" dsn "/" user)))
658
659
660 (defmethod database-connect (connection-spec (database-type (eql :oracle)))
661   (check-connection-spec connection-spec database-type (user password dsn))
662   (destructuring-bind (data-source-name user password)
663       connection-spec
664     (let ((envhp (uffi:allocate-foreign-object (* :void)))
665           (errhp (uffi:allocate-foreign-object (* :void)))
666           (svchp (uffi:allocate-foreign-object (* :void)))
667           (srvhp (uffi:allocate-foreign-object (* :void))))
668       ;; Requests to allocate environments and handles should never
669       ;; fail in normal operation, and they're done too early to
670       ;; handle errors very gracefully (since they're part of the
671       ;; error-handling mechanism themselves) so we just assert they
672       ;; work.
673       (setf (uffi:deref-pointer envhp void-pointer) +null-void-pointer+)
674       #+oci-8-1-5
675       (progn
676         (oci-env-create (c-& envhp void-pointer) +oci-default+ nil nil nil nil 0 nil)
677         (oci-handle-alloc (uffi:deref-pointer envhp void-pointer) 
678                           (c-& errhp void-pointer) +oci-htype-error+ 0 nil))
679       #-oci-8-1-5
680       (progn
681         (oci-initialize +oci-object+ +null-void-pointer+ +null-void-pointer+ +null-void-pointer+ +null-void-pointer+)
682         (ignore-errors (oci-handle-alloc nil envhp +oci-htype-env+ 0 +null-void-pointer+)) ;no testing return
683         (oci-env-init envhp +oci-default+ 0 +null-void-pointer+)
684         (oci-handle-alloc (uffi:deref-pointer envhp void-pointer) errhp +oci-htype-error+ 0 +null-void-pointer+)
685         (oci-handle-alloc (uffi:deref-pointer envhp void-pointer) srvhp +oci-htype-server+ 0 +null-void-pointer+)
686         ;;(osucc (oci-server-attach srvhp errhp nil 0 +oci-default+))
687         (oci-handle-alloc (uffi:deref-pointer envhp void-pointer) svchp +oci-htype-svcctx+ 0 +null-void-pointer+)
688         ;; oci-handle-alloc((dvoid *)encvhp, (dvoid **)&stmthp, OCI_HTYPE_STMT, 0, 0);
689         #+nil
690         (oci-attr-set svchp +oci-htype-svcctx+ 
691                       srvhp 0 +oci-attr-server+ errhp)
692         )
693       #+nil
694       (format t "Logging in as user '~A' to database ~A~%"
695               user password data-source-name)
696       (oci-logon (uffi:deref-pointer envhp void-pointer) (uffi:deref-pointer errhp void-pointer) (c-& svchp void-pointer)
697                  (uffi:convert-to-cstring user) (length user)
698                  (uffi:convert-to-cstring password) (length password)
699                  (uffi:convert-to-cstring data-source-name) (length data-source-name))
700       (let ((db (make-instance 'oracle-database
701                                :name (database-name-from-spec connection-spec
702                                                               database-type)
703                                :envhp envhp
704                                :errhp errhp
705                                :db-type :oracle
706                                :svchp svchp
707                                :dsn data-source-name
708                                :user user)))
709         ;; :date-format-length (1+ (length date-format)))))
710         (clsql:execute-command
711          (format nil "alter session set NLS_DATE_FORMAT='~A'"
712                  (date-format db)) :database db)
713         db))))
714
715
716 ;; Close a database connection.
717
718 (defmethod database-disconnect ((database oracle-database))
719   (osucc (oci-logoff (uffi:deref-pointer (svchp database) void-pointer)
720                      (uffi:deref-pointer (errhp database) void-pointer)))
721   (osucc (oci-handle-free (uffi:deref-pointer (envhp database) void-pointer)
722                           +oci-htype-env+))
723   ;; Note: It's neither required nor allowed to explicitly deallocate the
724   ;; ERRHP handle here, since it's owned by the ENVHP deallocated above,
725   ;; and was therefore automatically deallocated at the same time.
726   t)
727
728 ;;; Do the database operation described in SQL-STMT-STRING on database
729 ;;; DB and, if the command is a SELECT, return a representation of the
730 ;;; resulting table. The representation of the table is controlled by the
731 ;;; QUERY argument:
732 ;;;   * If QUERY is NIL, the table is returned as a list of rows, with
733 ;;;     each row represented by a list.
734 ;;;   * If QUERY is non-NIL, the result is returned as a QUERY-CURSOR
735 ;;;     suitable for FETCH-ROW and CLOSE-QUERY
736 ;;; The TYPES argument controls the type conversion method used
737 ;;; to construct the table. The Allegro version supports several possible
738 ;;; values for this argument, but we only support :AUTO.
739
740 (defmethod database-query (query-expression (database oracle-database) result-types field-names)
741   (let ((cursor (sql-stmt-exec query-expression database :types :auto)))
742     (declare (type (or query-cursor null) cursor))
743     (if (null cursor) ; No table was returned.
744         (values)
745       (do ((reversed-result nil))
746           (nil)
747         (let* ((eof-value :eof)
748                (row (fetch-row cursor nil eof-value)))
749           (when (eq row eof-value)
750             (close-query cursor)
751             (return (nreverse reversed-result)))
752           (push row reversed-result))))))
753
754
755 (defmethod database-create-sequence
756   (sequence-name (database oracle-database))
757   (execute-command
758    (concatenate 'string "CREATE SEQUENCE "
759                 (sql-escape sequence-name))
760    :database database))
761
762 (defmethod database-drop-sequence
763   (sequence-name (database oracle-database))
764   (execute-command
765    (concatenate 'string "DROP SEQUENCE "
766                 (sql-escape sequence-name))
767    :database database))
768
769 (defmethod database-sequence-next (sequence-name (database oracle-database))
770   (caar
771    (query
772     (concatenate 'string "SELECT "
773                  (sql-escape sequence-name)
774                  ".NEXTVAL FROM dual"
775                  ) :database database)))
776
777
778 (defmethod database-execute-command
779   (sql-expression (database oracle-database))
780   (database-query sql-expression database nil nil)
781   ;; HACK HACK HACK
782   (database-query "commit" database nil nil)
783   t)
784
785
786 ;;; a column descriptor: metadata about the data in a table
787 (defstruct (cd (:constructor make-cd)
788                (:print-function print-cd))
789   ;; name of this column
790   (name (error "missing NAME") :type simple-string :read-only t)
791   ;; the size in bytes of a single element
792   (sizeof (error "missing SIZE") :type fixnum :read-only t)
793   ;; an array of +N-BUF-ROWS+ elements in C representation
794   (buffer (error "Missing BUFFER")
795           :type foreign-resource
796           :read-only t)
797   ;; an array of +N-BUF-ROWS+ OCI return codes in C representation.
798   ;; (There must be one return code for every element of every
799   ;; row in order to be able to represent nullness.)
800   (retcodes (error "Missing RETCODES")
801             :type foreign-resource
802             :read-only t)
803   (indicators (error "Missing INDICATORS")
804               :type foreign-resource
805               :read-only t)
806   ;; the OCI code for the data type of a single element
807   (oci-data-type (error "missing OCI-DATA-TYPE")
808                  :type fixnum
809                  :read-only t))
810
811
812 (defun print-cd (cd stream depth)
813   (declare (ignore depth))
814   (print-unreadable-object (cd stream :type t)
815     (format stream
816             ":NAME ~S :OCI-DATA-TYPE ~S :OCI-DATA-SIZE ~S"
817             (cd-name cd)
818             (cd-oci-data-type cd)
819             (cd-sizeof cd))))
820
821 (defun print-query-cursor (qc stream depth)
822   (declare (ignore depth))
823   (print-unreadable-object (qc stream :type t :identity t)
824     (prin1 (qc-db qc) stream)))
825
826
827 (defmethod database-query-result-set ((query-expression string)
828                                       (database oracle-database) 
829                                       &key full-set result-types)
830   )
831
832 (defmethod database-dump-result-set (result-set (database oracle-database))
833   )
834
835 (defmethod database-store-next-row (result-set (database oracle-database) list)
836   )
837
838 (defmethod clsql-sys::database-start-transaction ((database oracle-database))
839   (call-next-method))
840
841 ;;(with-slots (svchp errhp) database
842 ;;    (osucc (oci-trans-start (uffi:deref-pointer svchp)
843 ;;                          (uffi:deref-pointer errhp)
844 ;;                          60
845 ;;                          +oci-trans-new+)))
846 ;;  t)
847   
848
849 (defmethod clsql-sys::database-commit-transaction ((database oracle-database))
850   (call-next-method)
851   (with-slots (svchp errhp) database
852               (osucc (oci-trans-commit (uffi:deref-pointer svchp void-pointer)
853                                        (uffi:deref-pointer errhp void-pointer)
854                                        0)))
855   t)
856
857 (defmethod clsql-sys::database-abort-transaction ((database oracle-database))
858   (call-next-method)
859   (osucc (oci-trans-rollback (uffi:deref-pointer (svchp database) void-pointer)
860                            (uffi:deref-pointer (errhp database) void-pointer)
861                            0))
862   t)
863
864 (defparameter *constraint-types*
865   '(("NOT-NULL" . "NOT NULL")))
866
867 (defmethod database-output-sql ((str string) (database oracle-database))
868   (if (and (null (position #\' str))
869            (null (position #\\ str)))
870       (format nil "'~A'" str)
871     (let* ((l (length str))
872            (buf (make-string (+ l 3))))
873       (setf (aref buf 0) #\')
874       (do ((i 0 (incf i))
875            (j 1 (incf j)))
876           ((= i l) (setf (aref buf j) #\'))
877         (if (= j (- (length buf) 1))
878             (setf buf (adjust-array buf (+ (length buf) 1))))
879         (cond ((eql (aref str i) #\')
880                (setf (aref buf j) #\')
881                (incf j)))
882         (setf (aref buf j) (aref str i)))
883       buf)))
884
885