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