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