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