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