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