c80723b24dd8a5b7b1d2622c1e0b5fbee258191e
[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
63 (defun print-query (query-exp &key titles (formats t) (sizes t) (stream t)
64                               (database *default-database*))
65   "The PRINT-QUERY function takes a symbolic SQL query expression and
66 formatting information and prints onto STREAM a table containing the
67 results of the query. A list of strings to use as column headings is
68 given by TITLES, which has a default value of NIL. The FORMATS
69 argument is a list of format strings used to print each attribute, and
70 has a default value of T, which means that ~A or ~VA are used if sizes
71 are provided or computed. The field sizes are given by SIZES. It has a
72 default value of T, which specifies that minimum sizes are
73 computed. The output stream is given by STREAM, which has a default
74 value of T. This specifies that *STANDARD-OUTPUT* is used."
75   (flet ((compute-sizes (data)
76            (mapcar #'(lambda (x) 
77                        (apply #'max (mapcar #'(lambda (y) 
78                                                 (if (null y) 3 (length y)))
79                                             x)))
80                    (apply #'mapcar (cons #'list data))))
81          (format-record (record control sizes)
82            (format stream "~&~?" control
83                    (if (null sizes) record
84                        (mapcan #'(lambda (s f) (list s f)) sizes record)))))
85     (let* ((query-exp (etypecase query-exp
86                         (string query-exp)
87                         (sql-query (sql-output query-exp database))))
88            (data (query query-exp :database database :result-types nil 
89                         :field-names nil))
90            (sizes (if (or (null sizes) (listp sizes)) sizes 
91                       (compute-sizes (if titles (cons titles data) data))))
92            (formats (if (or (null formats) (not (listp formats)))
93                         (make-list (length (car data)) :initial-element
94                                    (if (null sizes) "~A " "~VA "))
95                         formats))
96            (control-string (format nil "~{~A~}" formats)))
97       (when titles (format-record titles control-string sizes))
98       (dolist (d data (values)) (format-record d control-string sizes)))))
99
100 (defun insert-records (&key (into nil)
101                             (attributes nil)
102                             (values nil)
103                             (av-pairs nil)
104                             (query nil)
105                             (database *default-database*))
106   "Inserts a set of values into a table. The records created contain
107 values for attributes (or av-pairs). The argument VALUES is a list of
108 values. If ATTRIBUTES is supplied then VALUES must be a corresponding
109 list of values for each of the listed attribute names. If AV-PAIRS is
110 non-nil, then both ATTRIBUTES and VALUES must be nil. If QUERY is
111 non-nil, then neither VALUES nor AV-PAIRS should be. QUERY should be a
112 query expression, and the attribute names in it must also exist in the
113 table INTO. The default value of DATABASE is *DEFAULT-DATABASE*."
114   (let ((stmt (make-sql-insert :into into :attrs attributes
115                                :vals values :av-pairs av-pairs
116                                :subquery query)))
117     (execute-command stmt :database database)))
118
119 (defun make-sql-insert (&key (into nil)
120                             (attrs nil)
121                             (vals nil)
122                             (av-pairs nil)
123                             (subquery nil))
124   (unless into
125       (error 'sql-user-error :message ":into keyword not supplied"))
126   (let ((insert (make-instance 'sql-insert :into into)))
127     (with-slots (attributes values query)
128       insert
129       (cond ((and vals (not attrs) (not query) (not av-pairs))
130              (setf values vals))
131             ((and vals attrs (not subquery) (not av-pairs))
132              (setf attributes attrs)
133              (setf values vals))
134             ((and av-pairs (not vals) (not attrs) (not subquery))
135              (setf attributes (mapcar #'car av-pairs))
136              (setf values (mapcar #'cadr av-pairs)))
137             ((and subquery (not vals) (not attrs) (not av-pairs))
138              (setf query subquery))
139             ((and subquery attrs (not vals) (not av-pairs))
140              (setf attributes attrs)
141              (setf query subquery))
142             (t
143              (error 'sql-user-error
144                     :message "bad or ambiguous keyword combination.")))
145       insert)))
146     
147 (defun delete-records (&key (from nil)
148                             (where nil)
149                             (database *default-database*))
150   "Deletes rows from a database table specified by FROM in which the
151 WHERE condition is true. The argument DATABASE specifies a database
152 from which the records are to be removed, and defaults to
153 *default-database*."
154   (let ((stmt (make-instance 'sql-delete :from from :where where)))
155     (execute-command stmt :database database)))
156
157 (defun update-records (table &key (attributes nil)
158                             (values nil)
159                             (av-pairs nil)
160                             (where nil)
161                             (database *default-database*))
162   "Changes the values of existing fields in TABLE with columns
163 specified by ATTRIBUTES and VALUES (or AV-PAIRS) where the WHERE
164 condition is true."
165   (when av-pairs
166     (setf attributes (mapcar #'car av-pairs)
167           values (mapcar #'cadr av-pairs)))
168   (let ((stmt (make-instance 'sql-update :table table
169                              :attributes attributes
170                              :values values
171                              :where where)))
172     (execute-command stmt :database database)))
173
174
175 ;; iteration 
176
177 ;; output-sql
178
179 (defmethod database-output-sql ((str string) database)
180   (declare (ignore database)
181            (optimize (speed 3) (safety 1) #+cmu (extensions:inhibit-warnings 3))
182            (type (simple-array * (*)) str))
183   (let ((len (length str)))
184     (declare (type fixnum len))
185     (cond ((= len 0)
186            +empty-string+)
187           ((and (null (position #\' str))
188                 (null (position #\\ str)))
189            (concatenate 'string "'" str "'"))
190           (t
191            (let ((buf (make-string (+ (* len 2) 2) :initial-element #\')))
192              (do* ((i 0 (incf i))
193                    (j 1 (incf j)))
194                   ((= i len) (subseq buf 0 (1+ j)))
195                (declare (type integer i j))
196                (let ((char (aref str i)))
197                  (cond ((eql char #\')
198                         (setf (aref buf j) #\\)
199                         (incf j)
200                         (setf (aref buf j) #\'))
201                        ((eql char #\\)
202                         (setf (aref buf j) #\\)
203                         (incf j)
204                         (setf (aref buf j) #\\))
205                        (t
206                         (setf (aref buf j) char))))))))))
207
208 (let ((keyword-package (symbol-package :foo)))
209   (defmethod database-output-sql ((sym symbol) database)
210     (convert-to-db-default-case
211      (if (equal (symbol-package sym) keyword-package)
212          (concatenate 'string "'" (string sym) "'")
213          (symbol-name sym))
214      database)))
215
216 (defmethod database-output-sql ((tee (eql t)) database)
217   (declare (ignore database))
218   "'Y'")
219
220 (defmethod database-output-sql ((num number) database)
221   (declare (ignore database))
222   (princ-to-string num))
223
224 (defmethod database-output-sql ((arg list) database)
225   (if (null arg)
226       "NULL"
227       (format nil "(~{~A~^,~})" (mapcar #'(lambda (val)
228                                             (sql-output val database))
229                                         arg))))
230
231 (defmethod database-output-sql ((arg vector) database)
232   (format nil "~{~A~^,~}" (map 'list #'(lambda (val)
233                                          (sql-output val database))
234                                arg)))
235
236 (defmethod database-output-sql ((self wall-time) database)
237   (declare (ignore database))
238   (db-timestring self))
239
240 (defmethod database-output-sql ((self duration) database)
241   (declare (ignore database))
242   (format nil "'~a'" (duration-timestring self)))
243
244 (defmethod database-output-sql (thing database)
245   (if (or (null thing)
246           (eq 'null thing))
247       "NULL"
248     (error 'sql-user-error
249            :message
250            (format nil
251                    "No type conversion to SQL for ~A is defined for DB ~A."
252                    (type-of thing) (type-of database)))))
253
254
255 (defmethod output-sql-hash-key ((arg vector) database)
256   (list 'vector (map 'list (lambda (arg)
257                              (or (output-sql-hash-key arg database)
258                                  (return-from output-sql-hash-key nil)))
259                      arg)))
260
261 (defmethod output-sql (expr database)
262   (write-string (database-output-sql expr database) *sql-stream*)
263   (values))
264
265 (defmethod output-sql ((expr list) database)
266   (if (null expr)
267       (write-string +null-string+ *sql-stream*)
268       (progn
269         (write-char #\( *sql-stream*)
270         (do ((item expr (cdr item)))
271             ((null (cdr item))
272              (output-sql (car item) database))
273           (output-sql (car item) database)
274           (write-char #\, *sql-stream*))
275         (write-char #\) *sql-stream*)))
276   t)
277
278 (defmethod describe-table ((table sql-create-table)
279                            &key (database *default-database*))
280   (database-describe-table
281    database
282    (convert-to-db-default-case 
283     (symbol-name (slot-value table 'name)) database)))
284
285 #+nil
286 (defmethod add-storage-class ((self database) (class symbol) &key (sequence t))
287   (let ((tablename (view-table (find-class class))))
288     (unless (tablep tablename)
289       (create-view-from-class class)
290       (when sequence
291         (create-sequence-from-class class)))))
292  
293 ;;; Iteration
294
295
296 (defmacro do-query (((&rest args) query-expression
297                      &key (database '*default-database*) (result-types :auto))
298                     &body body)
299   "Repeatedly executes BODY within a binding of ARGS on the
300 attributes of each record resulting from QUERY-EXPRESSION. The
301 return value is determined by the result of executing BODY. The
302 default value of DATABASE is *DEFAULT-DATABASE*."
303   (let ((result-set (gensym "RESULT-SET-"))
304         (qe (gensym "QUERY-EXPRESSION-"))
305         (columns (gensym "COLUMNS-"))
306         (row (gensym "ROW-"))
307         (db (gensym "DB-")))
308     `(let ((,qe ,query-expression))
309       (typecase ,qe
310         (sql-object-query
311          (dolist (,row (query ,qe))
312            (destructuring-bind ,args 
313                ,row
314              ,@body)))
315         (t
316          ;; Functional query 
317          (let ((,db ,database))
318            (multiple-value-bind (,result-set ,columns)
319                (database-query-result-set ,qe ,db
320                                           :full-set nil 
321                                           :result-types ,result-types)
322              (when ,result-set
323                (unwind-protect
324                     (do ((,row (make-list ,columns)))
325                         ((not (database-store-next-row ,result-set ,db ,row))
326                          nil)
327                       (destructuring-bind ,args ,row
328                         ,@body))
329                  (database-dump-result-set ,result-set ,db))))))))))
330
331 (defun map-query (output-type-spec function query-expression
332                   &key (database *default-database*)
333                   (result-types :auto))
334   "Map the function over all tuples that are returned by the
335 query in QUERY-EXPRESSION. The results of the function are
336 collected as specified in OUTPUT-TYPE-SPEC and returned like in
337 MAP."
338   (typecase query-expression
339     (sql-object-query
340      (map output-type-spec #'(lambda (x) (apply function x))
341           (query query-expression)))
342     (t
343      ;; Functional query 
344      (macrolet ((type-specifier-atom (type)
345                   `(if (atom ,type) ,type (car ,type))))
346        (case (type-specifier-atom output-type-spec)
347          ((nil) 
348           (map-query-for-effect function query-expression database 
349                                 result-types))
350          (list 
351           (map-query-to-list function query-expression database result-types))
352          ((simple-vector simple-string vector string array simple-array
353                          bit-vector simple-bit-vector base-string
354                          simple-base-string)
355           (map-query-to-simple output-type-spec function query-expression 
356                                database result-types))
357          (t
358           (funcall #'map-query 
359                    (cmucl-compat:result-type-or-lose output-type-spec t)
360                    function query-expression :database database 
361                    :result-types result-types)))))))
362   
363 (defun map-query-for-effect (function query-expression database result-types)
364   (multiple-value-bind (result-set columns)
365       (database-query-result-set query-expression database :full-set nil
366                                  :result-types result-types)
367     (let ((flatp (and (= columns 1) 
368                       (typecase query-expression 
369                         (string t) 
370                         (sql-query 
371                          (slot-value query-expression 'flatp))))))
372       (when result-set
373         (unwind-protect
374              (do ((row (make-list columns)))
375                  ((not (database-store-next-row result-set database row))
376                   nil)
377                (if flatp
378                    (apply function row)
379                    (funcall function row)))
380           (database-dump-result-set result-set database))))))
381                      
382 (defun map-query-to-list (function query-expression database result-types)
383   (multiple-value-bind (result-set columns)
384       (database-query-result-set query-expression database :full-set nil
385                                  :result-types result-types)
386     (let ((flatp (and (= columns 1) 
387                       (typecase query-expression 
388                         (string t) 
389                         (sql-query 
390                          (slot-value query-expression 'flatp))))))
391       (when result-set
392         (unwind-protect
393              (let ((result (list nil)))
394                (do ((row (make-list columns))
395                     (current-cons result (cdr current-cons)))
396                    ((not (database-store-next-row result-set database row))
397                     (cdr result))
398                  (rplacd current-cons 
399                          (list (if flatp 
400                                    (apply function row)
401                                    (funcall function (copy-list row)))))))
402           (database-dump-result-set result-set database))))))
403
404 (defun map-query-to-simple (output-type-spec function query-expression database result-types)
405   (multiple-value-bind (result-set columns rows)
406       (database-query-result-set query-expression database :full-set t
407                                  :result-types result-types)
408     (let ((flatp (and (= columns 1) 
409                       (typecase query-expression 
410                         (string t) 
411                         (sql-query
412                          (slot-value query-expression 'flatp))))))
413       (when result-set
414         (unwind-protect
415              (if rows
416                  ;; We know the row count in advance, so we allocate once
417                  (do ((result
418                        (cmucl-compat:make-sequence-of-type output-type-spec rows))
419                       (row (make-list columns))
420                       (index 0 (1+ index)))
421                      ((not (database-store-next-row result-set database row))
422                       result)
423                    (declare (fixnum index))
424                    (setf (aref result index)
425                          (if flatp 
426                              (apply function row)
427                              (funcall function (copy-list row)))))
428                  ;; Database can't report row count in advance, so we have
429                  ;; to grow and shrink our vector dynamically
430                  (do ((result
431                        (cmucl-compat:make-sequence-of-type output-type-spec 100))
432                       (allocated-length 100)
433                       (row (make-list columns))
434                       (index 0 (1+ index)))
435                      ((not (database-store-next-row result-set database row))
436                       (cmucl-compat:shrink-vector result index))
437                    (declare (fixnum allocated-length index))
438                    (when (>= index allocated-length)
439                      (setq allocated-length (* allocated-length 2)
440                            result (adjust-array result allocated-length)))
441                    (setf (aref result index)
442                          (if flatp 
443                              (apply function row)
444                              (funcall function (copy-list row))))))
445           (database-dump-result-set result-set database))))))
446
447 ;;; Row processing macro from CLSQL
448
449 (defmacro for-each-row (((&rest fields) &key from order-by where distinct limit) &body body)
450   (let ((d (gensym "DISTINCT-"))
451         (bind-fields (loop for f in fields collect (car f)))
452         (w (gensym "WHERE-"))
453         (o (gensym "ORDER-BY-"))
454         (frm (gensym "FROM-"))
455         (l (gensym "LIMIT-"))
456         (q (gensym "QUERY-")))
457     `(let ((,frm ,from)
458            (,w ,where)
459            (,d ,distinct)
460            (,l ,limit)
461            (,o ,order-by))
462       (let ((,q (query-string ',fields ,frm ,w ,d ,o ,l)))
463         (loop for tuple in (query ,q)
464               collect (destructuring-bind ,bind-fields tuple
465                    ,@body))))))
466
467 (defun query-string (fields from where distinct order-by limit)
468   (concatenate
469    'string
470    (format nil "select ~A~{~A~^,~} from ~{~A~^ and ~}" 
471            (if distinct "distinct " "") (field-names fields)
472            (from-names from))
473    (if where (format nil " where ~{~A~^ ~}"
474                      (where-strings where)) "")
475    (if order-by (format nil " order by ~{~A~^, ~}"
476                         (order-by-strings order-by)))
477    (if limit (format nil " limit ~D" limit) "")))
478
479 (defun lisp->sql-name (field)
480   (typecase field
481     (string field)
482     (symbol (string-upcase (symbol-name field)))
483     (cons (cadr field))
484     (t (format nil "~A" field))))
485
486 (defun field-names (field-forms)
487   "Return a list of field name strings from a fields form"
488   (loop for field-form in field-forms
489         collect
490         (lisp->sql-name
491          (if (cadr field-form)
492              (cadr field-form)
493              (car field-form)))))
494
495 (defun from-names (from)
496   "Return a list of field name strings from a fields form"
497   (loop for table in (if (atom from) (list from) from)
498         collect (lisp->sql-name table)))
499
500
501 (defun where-strings (where)
502   (loop for w in (if (atom (car where)) (list where) where)
503         collect
504         (if (consp w)
505             (format nil "~A ~A ~A" (second w) (first w) (third w))
506             (format nil "~A" w))))
507
508 (defun order-by-strings (order-by)
509   (loop for o in order-by
510         collect
511         (if (atom o)
512             (lisp->sql-name o)
513             (format nil "~A ~A" (lisp->sql-name (car o))
514                     (lisp->sql-name (cadr o))))))
515
516
517