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