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