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