r9456: relax type for server-version
[clsql.git] / sql / sql.lisp
1 ;;;; -*- Mode: LISP; Syntax: ANSI-Common-Lisp; Base: 10 -*-
2 ;;;; *************************************************************************
3 ;;;;
4 ;;;; $Id$
5 ;;;;
6 ;;;; The CLSQL Functional Data Manipulation Language (FDML). 
7 ;;;;
8 ;;;; This file is part of CLSQL.
9 ;;;;
10 ;;;; CLSQL users are granted the rights to distribute and use this software
11 ;;;; as governed by the terms of the Lisp Lesser GNU Public License
12 ;;;; (http://opensource.franz.com/preamble.html), also known as the LLGPL.
13 ;;;; *************************************************************************
14
15 (in-package #:clsql-sys)
16   
17 ;;; Basic operations on databases
18
19 (defmethod database-query-result-set ((expr %sql-expression) database
20                                       &key full-set result-types)
21   (database-query-result-set (sql-output expr database) database
22                              :full-set full-set :result-types result-types))
23
24 (defmethod execute-command ((expr %sql-expression)
25                             &key (database *default-database*))
26   (execute-command (sql-output expr database) :database database)
27   (values))
28
29
30 (defmethod query ((expr %sql-expression) &key (database *default-database*)
31                   (result-types :auto) (flatp nil) (field-names t))
32   (query (sql-output expr database) :database database :flatp flatp
33          :result-types result-types :field-names field-names))
34
35 (defmethod query ((expr sql-object-query) &key (database *default-database*)
36                   (result-types :auto) (flatp nil) (field-names t))
37   (declare (ignore result-types field-names))
38   (apply #'select (append (slot-value expr 'objects)
39                           (slot-value expr 'exp) 
40                           (when (slot-value expr 'refresh) 
41                             (list :refresh (sql-output expr database)))
42                           (when (or flatp (slot-value expr 'flatp) )
43                             (list :flatp t))
44                           (list :database database))))
45
46 (defun truncate-database (&key (database *default-database*))
47   (unless (typep database 'database)
48     (signal-no-database-error database))
49   (unless (is-database-open database)
50     (database-reconnect database))
51   (when (eq :oracle (database-type database))
52     (ignore-errors (execute-command "PURGE RECYCLEBIN" :database database)))
53   (when (db-type-has-views? (database-underlying-type database))
54     (dolist (view (list-views :database database))
55       (drop-view view :database database)))
56   (dolist (table (list-tables :database database))
57     (drop-table table :database database))
58   (dolist (index (list-indexes :database database))
59     (drop-index index :database database))
60   (dolist (seq (list-sequences :database database))
61     (drop-sequence seq :database database))
62   (when (eq :oracle (database-type database))
63     (ignore-errors (execute-command "PURGE RECYCLEBIN" :database database))))
64
65 (defun print-query (query-exp &key titles (formats t) (sizes t) (stream t)
66                               (database *default-database*))
67   "Prints a tabular report of the results returned by the SQL
68 query QUERY-EXP, which may be a symbolic SQL expression or a
69 string, in DATABASE which defaults to *DEFAULT-DATABASE*. The
70 report is printed onto STREAM which has a default value of t
71 which means that *STANDARD-OUTPUT* is used. The TITLE argument,
72 which defaults to nil, allows the specification of a list of
73 strings to use as column titles in the tabular output. SIZES
74 accepts a list of column sizes, one for each column selected by
75 QUERY-EXP, to use in formatting the tabular report. The default
76 value of t means that minimum sizes are computed. FORMATS is a
77 list of format strings to be used for printing each column
78 selected by QUERY-EXP. The default value of FORMATS is t meaning
79 that ~A is used to format all columns or ~VA if column sizes are
80 used."
81   (flet ((compute-sizes (data)
82            (mapcar #'(lambda (x) 
83                        (apply #'max (mapcar #'(lambda (y) 
84                                                 (if (null y) 3 (length y)))
85                                             x)))
86                    (apply #'mapcar (cons #'list data))))
87          (format-record (record control sizes)
88            (format stream "~&~?" control
89                    (if (null sizes) record
90                        (mapcan #'(lambda (s f) (list s f)) sizes record)))))
91     (let* ((query-exp (etypecase query-exp
92                         (string query-exp)
93                         (sql-query (sql-output query-exp database))))
94            (data (query query-exp :database database :result-types nil 
95                         :field-names nil))
96            (sizes (if (or (null sizes) (listp sizes)) sizes 
97                       (compute-sizes (if titles (cons titles data) data))))
98            (formats (if (or (null formats) (not (listp formats)))
99                         (make-list (length (car data)) :initial-element
100                                    (if (null sizes) "~A " "~VA "))
101                         formats))
102            (control-string (format nil "~{~A~}" formats)))
103       (when titles (format-record titles control-string sizes))
104       (dolist (d data (values)) (format-record d control-string sizes)))))
105
106 (defun insert-records (&key (into nil)
107                             (attributes nil)
108                             (values nil)
109                             (av-pairs nil)
110                             (query nil)
111                             (database *default-database*))
112   "Inserts records into the table specified by INTO in DATABASE
113 which defaults to *DEFAULT-DATABASE*. There are five ways of
114 specifying the values inserted into each row. In the first VALUES
115 contains a list of values to insert and ATTRIBUTES, AV-PAIRS and
116 QUERY are nil. This can be used when values are supplied for all
117 attributes in INTO. In the second, ATTRIBUTES is a list of column
118 names, VALUES is a corresponding list of values and AV-PAIRS and
119 QUERY are nil. In the third, ATTRIBUTES, VALUES and QUERY are nil
120 and AV-PAIRS is an alist of (attribute value) pairs. In the
121 fourth, VALUES, AV-PAIRS and ATTRIBUTES are nil and QUERY is a
122 symbolic SQL query expression in which the selected columns also
123 exist in INTO. In the fifth method, VALUES and AV-PAIRS are nil
124 and ATTRIBUTES is a list of column names and QUERY is a symbolic
125 SQL query expression which returns values for the specified
126 columns."
127   (let ((stmt (make-sql-insert :into into :attrs attributes
128                                :vals values :av-pairs av-pairs
129                                :subquery query)))
130     (execute-command stmt :database database)))
131
132 (defun make-sql-insert (&key (into nil)
133                             (attrs nil)
134                             (vals nil)
135                             (av-pairs nil)
136                             (subquery nil))
137   (unless into
138       (error 'sql-user-error :message ":into keyword not supplied"))
139   (let ((insert (make-instance 'sql-insert :into into)))
140     (with-slots (attributes values query)
141       insert
142       (cond ((and vals (not attrs) (not query) (not av-pairs))
143              (setf values vals))
144             ((and vals attrs (not subquery) (not av-pairs))
145              (setf attributes attrs)
146              (setf values vals))
147             ((and av-pairs (not vals) (not attrs) (not subquery))
148              (setf attributes (mapcar #'car av-pairs))
149              (setf values (mapcar #'cadr av-pairs)))
150             ((and subquery (not vals) (not attrs) (not av-pairs))
151              (setf query subquery))
152             ((and subquery attrs (not vals) (not av-pairs))
153              (setf attributes attrs)
154              (setf query subquery))
155             (t
156              (error 'sql-user-error
157                     :message "bad or ambiguous keyword combination.")))
158       insert)))
159     
160 (defun delete-records (&key (from nil)
161                             (where nil)
162                             (database *default-database*))
163   "Deletes records satisfying the SQL expression WHERE from the
164 table specified by FROM in DATABASE specifies a database which
165 defaults to *DEFAULT-DATABASE*."
166   (let ((stmt (make-instance 'sql-delete :from from :where where)))
167     (execute-command stmt :database database)))
168
169 (defun update-records (table &key (attributes nil)
170                             (values nil)
171                             (av-pairs nil)
172                             (where nil)
173                             (database *default-database*))
174   "Updates the attribute values of existing records satsifying
175 the SQL expression WHERE in the table specified by TABLE in
176 DATABASE which defaults to *DEFAULT-DATABASE*. There are three
177 ways of specifying the values to update for each row. In the
178 first, VALUES contains a list of values to use in the update and
179 ATTRIBUTES, AV-PAIRS and QUERY are nil. This can be used when
180 values are supplied for all attributes in TABLE. In the second,
181 ATTRIBUTES is a list of column names, VALUES is a corresponding
182 list of values and AV-PAIRS and QUERY are nil. In the third,
183 ATTRIBUTES, VALUES and QUERY are nil and AV-PAIRS is an alist
184 of (attribute value) pairs."
185   (when av-pairs
186     (setf attributes (mapcar #'car av-pairs)
187           values (mapcar #'cadr av-pairs)))
188   (let ((stmt (make-instance 'sql-update :table table
189                              :attributes attributes
190                              :values values
191                              :where where)))
192     (execute-command stmt :database database)))
193
194
195 ;; iteration 
196
197 ;; output-sql
198
199 (defmethod database-output-sql ((str string) database)
200   (declare (ignore database)
201            (optimize (speed 3) (safety 1) #+cmu (extensions:inhibit-warnings 3))
202            (type (simple-array * (*)) str))
203   (let ((len (length str)))
204     (declare (type fixnum len))
205     (cond ((= len 0)
206            +empty-string+)
207           ((and (null (position #\' str))
208                 (null (position #\\ str)))
209            (concatenate 'string "'" str "'"))
210           (t
211            (let ((buf (make-string (+ (* len 2) 2) :initial-element #\')))
212              (do* ((i 0 (incf i))
213                    (j 1 (incf j)))
214                   ((= i len) (subseq buf 0 (1+ j)))
215                (declare (type integer i j))
216                (let ((char (aref str i)))
217                  (cond ((eql char #\')
218                         (setf (aref buf j) #\\)
219                         (incf j)
220                         (setf (aref buf j) #\'))
221                        ((eql char #\\)
222                         (setf (aref buf j) #\\)
223                         (incf j)
224                         (setf (aref buf j) #\\))
225                        (t
226                         (setf (aref buf j) char))))))))))
227
228 (let ((keyword-package (symbol-package :foo)))
229   (defmethod database-output-sql ((sym symbol) database)
230     (convert-to-db-default-case
231      (if (equal (symbol-package sym) keyword-package)
232          (concatenate 'string "'" (string sym) "'")
233          (symbol-name sym))
234      database)))
235
236 (defmethod database-output-sql ((tee (eql t)) database)
237   (declare (ignore database))
238   "'Y'")
239
240 (defmethod database-output-sql ((num number) database)
241   (declare (ignore database))
242   (princ-to-string num))
243
244 (defmethod database-output-sql ((arg list) database)
245   (if (null arg)
246       "NULL"
247       (format nil "(~{~A~^,~})" (mapcar #'(lambda (val)
248                                             (sql-output val database))
249                                         arg))))
250
251 (defmethod database-output-sql ((arg vector) database)
252   (format nil "~{~A~^,~}" (map 'list #'(lambda (val)
253                                          (sql-output val database))
254                                arg)))
255
256 (defmethod database-output-sql ((self wall-time) database)
257   (declare (ignore database))
258   (db-timestring self))
259
260 (defmethod database-output-sql ((self duration) database)
261   (declare (ignore database))
262   (format nil "'~a'" (duration-timestring self)))
263
264 (defmethod database-output-sql (thing database)
265   (if (or (null thing)
266           (eq 'null thing))
267       "NULL"
268     (error 'sql-user-error
269            :message
270            (format nil
271                    "No type conversion to SQL for ~A is defined for DB ~A."
272                    (type-of thing) (type-of database)))))
273
274
275 (defmethod output-sql-hash-key ((arg vector) database)
276   (list 'vector (map 'list (lambda (arg)
277                              (or (output-sql-hash-key arg database)
278                                  (return-from output-sql-hash-key nil)))
279                      arg)))
280
281 (defmethod output-sql (expr database)
282   (write-string (database-output-sql expr database) *sql-stream*)
283   (values))
284
285 (defmethod output-sql ((expr list) database)
286   (if (null expr)
287       (write-string +null-string+ *sql-stream*)
288       (progn
289         (write-char #\( *sql-stream*)
290         (do ((item expr (cdr item)))
291             ((null (cdr item))
292              (output-sql (car item) database))
293           (output-sql (car item) database)
294           (write-char #\, *sql-stream*))
295         (write-char #\) *sql-stream*)))
296   t)
297
298 (defmethod describe-table ((table sql-create-table)
299                            &key (database *default-database*))
300   (database-describe-table
301    database
302    (convert-to-db-default-case 
303     (symbol-name (slot-value table 'name)) database)))
304
305 #+nil
306 (defmethod add-storage-class ((self database) (class symbol) &key (sequence t))
307   (let ((tablename (view-table (find-class class))))
308     (unless (tablep tablename)
309       (create-view-from-class class)
310       (when sequence
311         (create-sequence-from-class class)))))
312  
313 ;;; Iteration
314
315
316 (defmacro do-query (((&rest args) query-expression
317                      &key (database '*default-database*) (result-types :auto))
318                     &body body)
319   "Repeatedly executes BODY within a binding of ARGS on the
320 fields of each row selected by the SQL query QUERY-EXPRESSION,
321 which may be a string or a symbolic SQL expression, in DATABASE
322 which defaults to *DEFAULT-DATABASE*. The values returned by the
323 execution of BODY are returned. RESULT-TYPES is a list of symbols
324 which specifies the lisp type for each field returned by
325 QUERY-EXPRESSION. If RESULT-TYPES is nil all results are returned
326 as strings whereas the default value of :auto means that the lisp
327 types are automatically computed for each field."
328   (let ((result-set (gensym "RESULT-SET-"))
329         (qe (gensym "QUERY-EXPRESSION-"))
330         (columns (gensym "COLUMNS-"))
331         (row (gensym "ROW-"))
332         (db (gensym "DB-")))
333     `(let ((,qe ,query-expression))
334       (typecase ,qe
335         (sql-object-query
336          (dolist (,row (query ,qe))
337            (destructuring-bind ,args 
338                ,row
339              ,@body)))
340         (t
341          ;; Functional query 
342          (let ((,db ,database))
343            (multiple-value-bind (,result-set ,columns)
344                (database-query-result-set ,qe ,db
345                                           :full-set nil 
346                                           :result-types ,result-types)
347              (when ,result-set
348                (unwind-protect
349                     (do ((,row (make-list ,columns)))
350                         ((not (database-store-next-row ,result-set ,db ,row))
351                          nil)
352                       (destructuring-bind ,args ,row
353                         ,@body))
354                  (database-dump-result-set ,result-set ,db))))))))))
355
356 (defun map-query (output-type-spec function query-expression
357                   &key (database *default-database*)
358                   (result-types :auto))
359   "Map the function FUNCTION over the attribute values of each
360 row selected by the SQL query QUERY-EXPRESSION, which may be a
361 string or a symbolic SQL expression, in DATABASE which defaults
362 to *DEFAULT-DATABASE*. The results of the function are collected
363 as specified in OUTPUT-TYPE-SPEC and returned like in
364 MAP. RESULT-TYPES is a list of symbols which specifies the lisp
365 type for each field returned by QUERY-EXPRESSION. If RESULT-TYPES
366 is nil all results are returned as strings whereas the default
367 value of :auto means that the lisp types are automatically
368 computed for each field."
369   (typecase query-expression
370     (sql-object-query
371      (map output-type-spec #'(lambda (x) (apply function x))
372           (query query-expression)))
373     (t
374      ;; Functional query 
375      (macrolet ((type-specifier-atom (type)
376                   `(if (atom ,type) ,type (car ,type))))
377        (case (type-specifier-atom output-type-spec)
378          ((nil) 
379           (map-query-for-effect function query-expression database 
380                                 result-types))
381          (list 
382           (map-query-to-list function query-expression database result-types))
383          ((simple-vector simple-string vector string array simple-array
384                          bit-vector simple-bit-vector base-string
385                          simple-base-string)
386           (map-query-to-simple output-type-spec function query-expression 
387                                database result-types))
388          (t
389           (funcall #'map-query 
390                    (cmucl-compat:result-type-or-lose output-type-spec t)
391                    function query-expression :database database 
392                    :result-types result-types)))))))
393   
394 (defun map-query-for-effect (function query-expression database result-types)
395   (multiple-value-bind (result-set columns)
396       (database-query-result-set query-expression database :full-set nil
397                                  :result-types result-types)
398     (let ((flatp (and (= columns 1) 
399                       (typecase query-expression 
400                         (string t) 
401                         (sql-query 
402                          (slot-value query-expression 'flatp))))))
403       (when result-set
404         (unwind-protect
405              (do ((row (make-list columns)))
406                  ((not (database-store-next-row result-set database row))
407                   nil)
408                (if flatp
409                    (apply function row)
410                    (funcall function row)))
411           (database-dump-result-set result-set database))))))
412                      
413 (defun map-query-to-list (function query-expression database result-types)
414   (multiple-value-bind (result-set columns)
415       (database-query-result-set query-expression database :full-set nil
416                                  :result-types result-types)
417     (let ((flatp (and (= columns 1) 
418                       (typecase query-expression 
419                         (string t) 
420                         (sql-query 
421                          (slot-value query-expression 'flatp))))))
422       (when result-set
423         (unwind-protect
424              (let ((result (list nil)))
425                (do ((row (make-list columns))
426                     (current-cons result (cdr current-cons)))
427                    ((not (database-store-next-row result-set database row))
428                     (cdr result))
429                  (rplacd current-cons 
430                          (list (if flatp 
431                                    (apply function row)
432                                    (funcall function (copy-list row)))))))
433           (database-dump-result-set result-set database))))))
434
435 (defun map-query-to-simple (output-type-spec function query-expression database result-types)
436   (multiple-value-bind (result-set columns rows)
437       (database-query-result-set query-expression database :full-set t
438                                  :result-types result-types)
439     (let ((flatp (and (= columns 1) 
440                       (typecase query-expression 
441                         (string t) 
442                         (sql-query
443                          (slot-value query-expression 'flatp))))))
444       (when result-set
445         (unwind-protect
446              (if rows
447                  ;; We know the row count in advance, so we allocate once
448                  (do ((result
449                        (cmucl-compat:make-sequence-of-type output-type-spec rows))
450                       (row (make-list columns))
451                       (index 0 (1+ index)))
452                      ((not (database-store-next-row result-set database row))
453                       result)
454                    (declare (fixnum index))
455                    (setf (aref result index)
456                          (if flatp 
457                              (apply function row)
458                              (funcall function (copy-list row)))))
459                  ;; Database can't report row count in advance, so we have
460                  ;; to grow and shrink our vector dynamically
461                  (do ((result
462                        (cmucl-compat:make-sequence-of-type output-type-spec 100))
463                       (allocated-length 100)
464                       (row (make-list columns))
465                       (index 0 (1+ index)))
466                      ((not (database-store-next-row result-set database row))
467                       (cmucl-compat:shrink-vector result index))
468                    (declare (fixnum allocated-length index))
469                    (when (>= index allocated-length)
470                      (setq allocated-length (* allocated-length 2)
471                            result (adjust-array result allocated-length)))
472                    (setf (aref result index)
473                          (if flatp 
474                              (apply function row)
475                              (funcall function (copy-list row))))))
476           (database-dump-result-set result-set database))))))
477
478 ;;; Row processing macro from CLSQL
479
480 (defmacro for-each-row (((&rest fields) &key from order-by where distinct limit) &body body)
481   (let ((d (gensym "DISTINCT-"))
482         (bind-fields (loop for f in fields collect (car f)))
483         (w (gensym "WHERE-"))
484         (o (gensym "ORDER-BY-"))
485         (frm (gensym "FROM-"))
486         (l (gensym "LIMIT-"))
487         (q (gensym "QUERY-")))
488     `(let ((,frm ,from)
489            (,w ,where)
490            (,d ,distinct)
491            (,l ,limit)
492            (,o ,order-by))
493       (let ((,q (query-string ',fields ,frm ,w ,d ,o ,l)))
494         (loop for tuple in (query ,q)
495               collect (destructuring-bind ,bind-fields tuple
496                    ,@body))))))
497
498 (defun query-string (fields from where distinct order-by limit)
499   (concatenate
500    'string
501    (format nil "select ~A~{~A~^,~} from ~{~A~^ and ~}" 
502            (if distinct "distinct " "") (field-names fields)
503            (from-names from))
504    (if where (format nil " where ~{~A~^ ~}"
505                      (where-strings where)) "")
506    (if order-by (format nil " order by ~{~A~^, ~}"
507                         (order-by-strings order-by)))
508    (if limit (format nil " limit ~D" limit) "")))
509
510 (defun lisp->sql-name (field)
511   (typecase field
512     (string field)
513     (symbol (string-upcase (symbol-name field)))
514     (cons (cadr field))
515     (t (format nil "~A" field))))
516
517 (defun field-names (field-forms)
518   "Return a list of field name strings from a fields form"
519   (loop for field-form in field-forms
520         collect
521         (lisp->sql-name
522          (if (cadr field-form)
523              (cadr field-form)
524              (car field-form)))))
525
526 (defun from-names (from)
527   "Return a list of field name strings from a fields form"
528   (loop for table in (if (atom from) (list from) from)
529         collect (lisp->sql-name table)))
530
531
532 (defun where-strings (where)
533   (loop for w in (if (atom (car where)) (list where) where)
534         collect
535         (if (consp w)
536             (format nil "~A ~A ~A" (second w) (first w) (third w))
537             (format nil "~A" w))))
538
539 (defun order-by-strings (order-by)
540   (loop for o in order-by
541         collect
542         (if (atom o)
543             (lisp->sql-name o)
544             (format nil "~A ~A" (lisp->sql-name (car o))
545                     (lisp->sql-name (cadr o))))))
546
547
548