Refactoring join-qualifier for readability
[clsql.git] / sql / oodml.lisp
1 ;;;; -*- Mode: LISP; Syntax: ANSI-Common-Lisp; Base: 10 -*-
2 ;;;; *************************************************************************
3 ;;;;
4 ;;;; The CLSQL Object Oriented Data Manipulation Language (OODML).
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 (defun find-normalized-key (obj)
16   "Find the first / primary key of a normalized object"
17   (find-slot-if obj #'key-slot-p T T))
18
19 (defun normalized-key-value (obj)
20   "Normalized classes share a single key for all their key slots"
21   (when (normalizedp (class-of obj))
22     (easy-slot-value obj (find-normalized-key obj))))
23
24 (defun key-qualifier-for-instance (obj &key (database *default-database*) this-class)
25   "Generate a boolean sql-expression that identifies an object by its keys"
26   (let* ((obj-class (or this-class (class-of obj)))
27          (keys (keyslots-for-class obj-class))
28          (normal-db-value (normalized-key-value obj)))
29     (when keys
30       (labels ((db-value (k)
31                  (or normal-db-value
32                      (db-value-from-slot
33                       k
34                       (easy-slot-value obj k)
35                       database)))
36                (key-equal-exp (k)
37                  (sql-operation '== (generate-attribute-reference obj-class k database)
38                                 (db-value k))))
39         (clsql-ands (mapcar #'key-equal-exp keys))))))
40
41 (defun generate-attribute-reference (vclass slotdef &optional (database *default-database*))
42   "Turns key class and slot-def into a sql-expression representing the
43    table and column it comes from
44
45    used by things like generate-selection-list, update-slot-from-record"
46   (when (key-or-base-slot-p slotdef)
47     (sql-expression :attribute (database-identifier slotdef database)
48                     :table (database-identifier vclass database))))
49
50 ;;
51 ;; Function used by 'find-all'
52 ;;
53
54 (defun generate-selection-list (vclass)
55   (let* ((sels nil)
56          (this-class vclass)
57          (slots (if (normalizedp vclass)
58                     (labels ((getdslots ()
59                                (let ((sl (ordered-class-direct-slots this-class)))
60                                  (cond (sl)
61                                        (t
62                                         (setf this-class
63                                               (car (class-direct-superclasses this-class)))
64                                         (getdslots))))))
65                       (getdslots))
66                     (ordered-class-slots this-class))))
67     (dolist (slotdef slots)
68       (let ((res (generate-attribute-reference this-class slotdef)))
69         (when res
70           (push (cons slotdef res) sels))))
71     (if sels
72         sels
73         (error "No slots of type :base in view-class ~A" (class-name vclass)))))
74
75
76
77 (defun generate-retrieval-joins-list (vclass retrieval-method)
78   "Returns list of immediate join slots for a class."
79   (let ((join-slotdefs nil))
80     (dolist (slotdef (ordered-class-slots vclass) join-slotdefs)
81       (when (and (eq :join (view-class-slot-db-kind slotdef))
82                  (eq retrieval-method (gethash :retrieval (view-class-slot-db-info slotdef))))
83         (push slotdef join-slotdefs)))))
84
85 (defun generate-immediate-joins-selection-list (vclass)
86   "Returns list of immediate join slots for a class."
87   (let (sels)
88     (dolist (joined-slot (generate-retrieval-joins-list vclass :immediate) sels)
89       (let* ((join-class-name (gethash :join-class (view-class-slot-db-info joined-slot)))
90              (join-class (when join-class-name (find-class join-class-name))))
91         (dolist (slotdef (ordered-class-slots join-class))
92           (let ((res (generate-attribute-reference join-class slotdef)))
93             (when res
94               (push (cons slotdef res) sels))))))
95     sels))
96
97 (defmethod choose-database-for-instance ((obj standard-db-object) &optional database)
98   "Determine which database connection to use for a standard-db-object.
99         Errs if none is available."
100   (or (find-if #'(lambda (db)
101                    (and db (is-database-open db)))
102                (list (view-database obj)
103                      database
104                      *default-database*))
105       (signal-no-database-error nil)))
106
107
108
109 (defmethod update-slot-with-null ((object standard-db-object) slotdef)
110   "sets a slot to the void value of the slot-def (usually nil)"
111   (setf (easy-slot-value object slotdef)
112         (slot-value slotdef 'void-value)))
113
114 (defmethod update-slot-from-db-value ((instance standard-db-object) slotdef value)
115   "This gets a value from the database and turns it itno a lisp value
116    based on the slot's slot-db-reader or baring that read-sql-value"
117   (declare (optimize (speed 3) #+cmu (extensions:inhibit-warnings 3)))
118   (let* ((slot-reader (view-class-slot-db-reader slotdef))
119          (slot-type   (specified-type slotdef)))
120     (cond
121       ((null value) (update-slot-with-null instance slotdef))
122       ((null slot-reader)
123        (setf (easy-slot-value instance slotdef)
124              (read-sql-value value (delistify slot-type)
125                              (choose-database-for-instance instance)
126                              (database-underlying-type
127                               (choose-database-for-instance instance)))))
128       (t (etypecase slot-reader
129            ((or symbol function)
130             (setf (easy-slot-value instance slotdef)
131                   (apply slot-reader (list value))))
132            (string
133             (setf (easy-slot-value instance slotdef)
134                   (format nil slot-reader value))))))))
135
136 (defmethod key-value-from-db (slotdef value database)
137   "TODO: is this deprecated? there are no uses anywhere in clsql"
138   (declare (optimize (speed 3) #+cmu (extensions:inhibit-warnings 3)))
139   (let ((slot-reader (view-class-slot-db-reader slotdef))
140         (slot-type (specified-type slotdef)))
141     (cond ((and value (null slot-reader))
142            (read-sql-value value (delistify slot-type) database
143                            (database-underlying-type database)))
144           ((null value)
145            nil)
146           ((typep slot-reader 'string)
147            (format nil slot-reader value))
148           ((typep slot-reader '(or symbol function))
149            (apply slot-reader (list value)))
150           (t
151            (error "Slot reader is of an unusual type.")))))
152
153 (defun db-value-from-slot (slotdef val database)
154   (let ((dbwriter (view-class-slot-db-writer slotdef))
155         (dbtype (specified-type slotdef)))
156     (typecase dbwriter
157       (string (format nil dbwriter val))
158       ((and (or symbol function) (not null)) (apply dbwriter (list val)))
159       (t
160        (database-output-sql-as-type
161         (typecase dbtype
162           (cons (car dbtype))
163           (t dbtype))
164         val database (database-underlying-type database))))))
165
166 (defun check-slot-type (slotdef val)
167   (let* ((slot-type (specified-type slotdef))
168          (basetype (if (listp slot-type) (car slot-type) slot-type)))
169     (when (and slot-type val)
170       (unless (typep val basetype)
171         (error 'sql-user-error
172                :message
173                (format nil "Invalid value ~A in slot ~A, not of type ~A."
174                        val (slot-definition-name slotdef) slot-type))))))
175
176 (defmethod get-slot-values-from-view (obj slotdeflist values)
177   "Used to copy values from the database into the object
178    used by things like find-all and select"
179   (loop for slot in slotdeflist
180         for value in values
181         do (update-slot-from-db-value obj slot value))
182   obj)
183
184 (defclass class-and-slots ()
185   ((view-class :accessor view-class :initarg :view-class :initform nil)
186    (slot-defs :accessor slot-defs :initarg :slot-defs :initform nil))
187   (:documentation "A helper class to keep track of which slot-defs from a
188    table need to be updated, a normalized class might have many of these
189    because each of its parent classes might represent some other table and we
190    need to match which slots came from which parent class/table"))
191
192 (defun make-class-and-slots (c &optional s)
193   "Create a new class-and-slots object"
194   (make-instance 'class-and-slots :view-class c :slot-defs (listify s) ))
195
196 (defmethod view-table ((o class-and-slots))
197   "get the view-table of the view-class of o"
198   (view-table (view-class o)))
199
200 (defmethod view-table-exp ((o class-and-slots))
201   (sql-expression :table (view-table o)))
202
203 (defmethod view-table-exp ((o standard-db-class))
204   (sql-expression :table (view-table o)))
205
206 (defmethod attribute-references ((o class-and-slots))
207   "build sql-ident-attributes for a given class-and-slots"
208   (loop
209     with class = (view-class o)
210     for sd in (slot-defs o)
211     collect (generate-attribute-reference class sd)))
212
213 (defmethod attribute-value-pairs ((def class-and-slots) (o standard-db-object)
214                                   database)
215   "for a given class-and-slots and object, create the sql-expression & value pairs
216    that need to be sent to the database"
217   (loop for s in (slot-defs def)
218         for n = (to-slot-name s)
219         when (slot-boundp o n)
220         collect (make-attribute-value-pair s (slot-value o n) database)))
221
222 (defmethod view-classes-and-slots-by-name ((obj standard-db-object) slots-to-match)
223   "If it's normalized, find the class that actually contains
224    the slot that's tied to the db,
225
226    otherwise just search the current class
227   "
228   (let* ((view-class (class-of obj))
229          (normalizedp (normalizedp view-class))
230          rtns)
231     (labels ((get-c&s-obj (class)
232                (or (find class rtns :key #'view-class)
233                    (first (push (make-class-and-slots class) rtns))))
234              (associate-slot-with-class (class slot)
235                "Find the best class to associate with the slot. If it is
236                 normalized then it needs to be a direct slot otherwise it just
237                 needs to be on the class."
238                (let ((sd (find-slot-by-name class slot normalizedp nil)))
239                  (if sd
240                      ;;we found it directly or it's (not normalized)
241                      (pushnew sd (slot-defs (get-c&s-obj class)))
242                      (when normalizedp
243                        (loop for parent in (class-direct-superclasses class)
244                              until (associate-slot-with-class parent slot))))
245                  sd)))
246       (loop
247         for in-slot in (listify slots-to-match)
248         do (associate-slot-with-class view-class in-slot)))
249     rtns))
250
251 (defun update-auto-increments-keys (class obj database)
252   " handle pulling any autoincrement values into the object
253    if normalized and we now that all the "
254   (let ((pk-slots (keyslots-for-class class))
255         (table (view-table class))
256         new-pk-value)
257     (labels ((do-update (slot)
258                (when (and (null (easy-slot-value obj slot))
259                           (auto-increment-column-p slot database))
260                  (update-slot-from-db-value
261                   obj slot
262                   (or new-pk-value
263                       (setf new-pk-value
264                             (database-last-auto-increment-id
265                              database table slot))))))
266              (chain-primary-keys (in-class)
267                "This seems kindof wrong, but this is mostly how it was working, so
268                   its here to keep the normalized code path working"
269                (when (typep in-class 'standard-db-class)
270                  (loop for slot in (ordered-class-slots in-class)
271                        when (key-slot-p slot)
272                        do (do-update slot)))))
273       (loop for slot in pk-slots do (do-update slot))
274       (let ((direct-class (to-class obj)))
275         (when (and new-pk-value (normalizedp direct-class))
276           (chain-primary-keys direct-class)))
277       new-pk-value)))
278
279 (defmethod %update-instance-helper
280     (class-and-slots obj database
281      &aux (avps (attribute-value-pairs class-and-slots obj database)))
282   "A function to help us update a given table (based on class-and-slots)
283    with values from an object"
284   ;; we dont actually need to update anything on this particular
285   ;; class / parent class
286   (unless avps (return-from %update-instance-helper))
287
288   (let* ((view-class (view-class class-and-slots))
289          (table (view-table view-class))
290          (table-sql (sql-expression :table table)))
291
292     ;; view database is the flag we use to tell it was pulled from a database
293     ;; and thus probably needs an update instead of an insert
294     (cond ((view-database obj)
295            (let ((where (key-qualifier-for-instance
296                          obj :database database :this-class view-class)))
297              (unless where
298                (error "update-record-from-*: could not generate a where clause for ~a using ~A"
299                       obj view-class))
300              (update-records table-sql
301                              :av-pairs avps
302                              :where where
303                              :database database)))
304           (T ;; was not pulled from the db so insert it
305            ;; avps MUST contain any primary key slots set
306            ;; by previous inserts of the same object into different
307            ;; tables (ie: normalized stuff)
308            (insert-records :into table-sql
309                            :av-pairs avps
310                            :database database)
311            (update-auto-increments-keys view-class obj database)
312            ;; we dont set view database here, because there could be
313            ;; N of these for each call to update-record-from-* because
314            ;; of normalized classes
315            ))
316     (update-slot-default-values obj class-and-slots)))
317
318 (defmethod update-record-from-slots ((obj standard-db-object) slots
319                                      &key (database *default-database*))
320   "For a given list of slots, update all records associated with those slots
321    and classes.
322
323    Generally this will update the single record associated with this object,
324    but for normalized classes might update as many records as there are
325    inheritances "
326   (setf slots (listify slots))
327   (let* ((classes-and-slots (view-classes-and-slots-by-name obj slots))
328          (database (choose-database-for-instance obj database)))
329     (loop for class-and-slots in classes-and-slots
330           do (%update-instance-helper class-and-slots obj database))
331     (setf (slot-value obj 'view-database) database))
332   (values))
333
334 (defmethod update-record-from-slot
335     ((obj standard-db-object) slot &key (database *default-database*))
336   "just call update-records-from-slots which now handles this.
337
338    This function is only here to maintain backwards compatibility in
339    the public api"
340   (update-record-from-slots obj slot :database database))
341
342 (defun view-classes-and-storable-slots (class)
343   "Get a list of all the tables we need to update and the slots on them
344
345    for non normalized classes we return the class and all its storable slots
346
347    for normalized classes we return a list of direct slots and the class they
348    came from for each normalized view class
349   "
350   (setf class (to-class class))
351   (let* (rtns)
352     (labels ((storable-slots (class)
353                (loop for sd in (slots-for-possibly-normalized-class class)
354                      when (key-or-base-slot-p sd)
355                      collect sd))
356              (get-classes-and-slots (class &aux (normalizedp (normalizedp class)))
357                (let ((slots (storable-slots class)))
358                  (when slots
359                    (push (make-class-and-slots class slots) rtns)))
360                (when normalizedp
361                  (loop for new-class in (class-direct-superclasses class)
362                        do (when (typep new-class 'standard-db-class)
363                             (get-classes-and-slots new-class))))))
364       (get-classes-and-slots class))
365     rtns))
366
367 (defmethod primary-key-slot-values ((obj standard-db-object)
368                                     &key class slots )
369   "Returns the values of all key-slots for a given class"
370   (defaulting class (class-of obj)
371               slots (keyslots-for-class class))
372   (loop for slot in slots
373         collect (easy-slot-value obj slot)))
374
375 (defmethod update-slot-default-values ((obj standard-db-object)
376                                        classes-and-slots)
377   "Makes sure that if a class has unfilled slots that claim to have a default,
378    that we retrieve those defaults from the database
379
380    TODO: use update slots-from-record instead to batch this!"
381   (loop for class-and-slots in (listify classes-and-slots)
382         do (loop for slot in (slot-defs class-and-slots)
383                  do (when (and (slot-has-default-p slot)
384                                (not (easy-slot-value obj slot)))
385                       (update-slot-from-record obj (to-slot-name slot))))))
386
387 (defmethod update-records-from-instance ((obj standard-db-object)
388                                          &key (database *default-database*))
389   "Updates the records in the database associated with this object if
390    view-database slot on the object is nil then the object is assumed to be
391    new and is inserted"
392   (let ((database (choose-database-for-instance obj database))
393         (classes-and-slots (view-classes-and-storable-slots obj)))
394     (loop for class-and-slots in classes-and-slots
395           do (%update-instance-helper class-and-slots obj database))
396     (setf (slot-value obj 'view-database) database)
397     (primary-key-slot-values obj)))
398
399 (defmethod delete-instance-records ((instance standard-db-object) &key database)
400   "Removes the records associated with a given instance
401    (as determined by key-qualifier-for-instance)
402
403    TODO: Doesnt handle normalized classes at all afaict"
404   (let ((database (choose-database-for-instance instance database))
405         (vt (sql-expression :table (view-table (class-of instance)))))
406     (if database
407         (let ((qualifier (key-qualifier-for-instance instance :database database)))
408           (delete-records :from vt :where qualifier :database database)
409           (setf (record-caches database) nil)
410           (setf (slot-value instance 'view-database) nil)
411           (values))
412         (signal-no-database-error database))))
413
414 (defmethod update-instance-from-records ((instance standard-db-object)
415                                          &key (database *default-database*)
416                                          this-class)
417   (let* ((view-class (or this-class (class-of instance)))
418          (pclass (car (class-direct-superclasses view-class)))
419          (pres nil))
420     (when (normalizedp view-class)
421       (setf pres (update-instance-from-records instance :database database
422                                                :this-class pclass)))
423     (let* ((view-table (sql-expression :table (view-table view-class)))
424            (vd (choose-database-for-instance instance database))
425            (view-qual (key-qualifier-for-instance instance :database vd
426                                                            :this-class view-class))
427            (sels (generate-selection-list view-class))
428            (res nil))
429       (cond (view-qual
430              (setf res (apply #'select (append (mapcar #'cdr sels)
431                                                (list :from  view-table
432                                                      :where view-qual
433                                                      :result-types nil
434                                                      :database vd))))
435              (when res
436                (setf (slot-value instance 'view-database) vd)
437                (get-slot-values-from-view instance (mapcar #'car sels) (car res))))
438             (pres)
439             (t nil)))))
440
441
442 (defmethod get-slot-value-from-record ((instance standard-db-object)
443                                        slot &key (database *default-database*))
444   (let* ((class-and-slot
445            (first
446             (view-classes-and-slots-by-name instance slot)))
447          (view-class (view-class class-and-slot))
448          (slot-def (first (slot-defs class-and-slot)))
449          (vd (choose-database-for-instance instance database))
450          (att-ref (first (attribute-references class-and-slot)))
451          (res (first
452                (select att-ref
453                  :from (view-table-exp class-and-slot)
454                  :where (key-qualifier-for-instance
455                          instance
456                          :database vd
457                          :this-class view-class)
458                  :result-types nil
459                  :flatp T))))
460     (values res slot-def)))
461
462 (defmethod update-slot-from-record ((instance standard-db-object)
463                                     slot &key (database *default-database*))
464   "Pulls the value of a given slot form the database and stores that in the
465    appropriate slot on instance"
466   (multiple-value-bind (res slot-def)
467       (get-slot-value-from-record instance slot :database database)
468     (let ((vd (choose-database-for-instance instance database)))
469       (setf (slot-value instance 'view-database) vd)
470       (update-slot-from-db-value instance slot-def res))))
471
472
473 (defvar +no-slot-value+ '+no-slot-value+)
474
475 (defsql sql-slot-value (:symbol "slot-value") (classname slot &optional (value +no-slot-value+) (database *default-database*))
476         (let* ((class (find-class classname))
477                (sld (slotdef-for-slot-with-class slot class)))
478           (if sld
479               (if (eq value +no-slot-value+)
480                   (sql-expression :attribute (database-identifier sld database)
481                                   :table (view-table class))
482                   (db-value-from-slot
483                    sld
484                    value
485                    database))
486               (error "Unknown slot ~A for class ~A" slot classname))))
487
488 (defsql sql-view-class (:symbol "view-class") (classname &optional (database *default-database*))
489         (declare (ignore database))
490         (let* ((class (find-class classname)))
491           (unless (view-table class)
492             (error "No view-table for class ~A"  classname))
493           (sql-expression :table (view-table class))))
494
495
496 (defmethod database-get-type-specifier (type args database db-type)
497   (declare (ignore type args database db-type))
498   (format nil "VARCHAR(~D)" *default-string-length*))
499
500 (defmethod database-get-type-specifier ((type (eql 'integer)) args database db-type)
501   (declare (ignore database db-type))
502   (if args
503       (format nil "INT(~A)" (car args))
504       "INT"))
505
506 (deftype tinyint ()
507   "An 8-bit integer, this width may vary by SQL implementation."
508   'integer)
509
510 (defmethod database-get-type-specifier ((type (eql 'tinyint)) args database db-type)
511   (declare (ignore args database db-type))
512   "INT")
513
514 (deftype smallint ()
515   "An integer smaller than a 32-bit integer. this width may vary by SQL implementation."
516   'integer)
517
518 (defmethod database-get-type-specifier ((type (eql 'smallint)) args database db-type)
519   (declare (ignore args database db-type))
520   "INT")
521
522 (deftype mediumint ()
523   "An integer smaller than a 32-bit integer, but may be larger than a smallint. This width may vary by SQL implementation."
524   'integer)
525
526 (defmethod database-get-type-specifier ((type (eql 'mediumint)) args database db-type)
527   (declare (ignore args database db-type))
528   "INT")
529
530 (deftype bigint ()
531   "An integer larger than a 32-bit integer, this width may vary by SQL implementation."
532   'integer)
533
534 (defmethod database-get-type-specifier ((type (eql 'bigint)) args database db-type)
535   (declare (ignore args database db-type))
536   "BIGINT")
537
538 (deftype varchar (&optional size)
539   "A variable length string for the SQL varchar type."
540   (declare (ignore size))
541   'string)
542
543 (defmethod database-get-type-specifier ((type (eql 'varchar)) args
544                                         database db-type)
545   (declare (ignore database db-type))
546   (if args
547       (format nil "VARCHAR(~A)" (car args))
548       (format nil "VARCHAR(~D)" *default-string-length*)))
549
550 (defmethod database-get-type-specifier ((type (eql 'string)) args database db-type)
551   (declare (ignore database db-type))
552   (if args
553       (format nil "CHAR(~A)" (car args))
554       (format nil "VARCHAR(~D)" *default-string-length*)))
555
556 (deftype universal-time ()
557   "A positive integer as returned by GET-UNIVERSAL-TIME."
558   '(integer 1 *))
559
560 (defmethod database-get-type-specifier ((type (eql 'universal-time)) args database db-type)
561   (declare (ignore args database db-type))
562   "BIGINT")
563
564 (defmethod database-get-type-specifier ((type (eql 'wall-time)) args database db-type)
565   (declare (ignore args database db-type))
566   "TIMESTAMP")
567
568 (defmethod database-get-type-specifier ((type (eql 'date)) args database db-type)
569   (declare (ignore args database db-type))
570   "DATE")
571
572 (defmethod database-get-type-specifier ((type (eql 'duration)) args database db-type)
573   (declare (ignore database args db-type))
574   "VARCHAR")
575
576 (defmethod database-get-type-specifier ((type (eql 'money)) args database db-type)
577   (declare (ignore database args db-type))
578   "INT8")
579
580 #+ignore
581 (deftype char (&optional len)
582   "A lisp type for the SQL CHAR type."
583   `(string ,len))
584
585 (defmethod database-get-type-specifier ((type (eql 'float)) args database db-type)
586   (declare (ignore database db-type))
587   (if args
588       (format nil "FLOAT(~A)" (car args))
589       "FLOAT"))
590
591 (defmethod database-get-type-specifier ((type (eql 'long-float)) args database db-type)
592   (declare (ignore database db-type))
593   (if args
594       (format nil "FLOAT(~A)" (car args))
595       "FLOAT"))
596
597 (deftype generalized-boolean ()
598   "A type which outputs a SQL boolean value, though any lisp type can be stored in the slot."
599   t)
600
601 (defmethod database-get-type-specifier ((type (eql 'boolean)) args database db-type)
602   (declare (ignore args database db-type))
603   "BOOL")
604
605 (defmethod database-get-type-specifier ((type (eql 'generalized-boolean)) args database db-type)
606   (declare (ignore args database db-type))
607   "BOOL")
608
609 (defmethod database-get-type-specifier ((type (eql 'number)) args database db-type)
610   (declare (ignore database db-type))
611   (cond
612     ((and (consp args) (= (length args) 2))
613      (format nil "NUMBER(~D,~D)" (first args) (second args)))
614     ((and (consp args) (= (length args) 1))
615      (format nil "NUMBER(~D)" (first args)))
616     (t
617      "NUMBER")))
618
619 (defmethod database-get-type-specifier ((type (eql 'char)) args database db-type)
620   (declare (ignore database db-type))
621   (if args
622       (format nil "CHAR(~D)" (first args))
623       "CHAR(1)"))
624
625
626 (defmethod database-output-sql-as-type (type val database db-type)
627   (declare (ignore type database db-type))
628   val)
629
630 (defmethod database-output-sql-as-type ((type (eql 'list)) val database db-type)
631   (declare (ignore database db-type))
632   (progv '(*print-circle* *print-array*) '(t t)
633     (let ((escaped (prin1-to-string val)))
634       (substitute-char-string
635        escaped #\Null " "))))
636
637 (defmethod database-output-sql-as-type ((type (eql 'symbol)) val database db-type)
638   (declare (ignore database db-type))
639   (if val
640       (concatenate 'string
641                    (package-name (symbol-package val))
642                    "::"
643                    (symbol-name val))
644       ""))
645
646 (defmethod database-output-sql-as-type ((type (eql 'keyword)) val database db-type)
647   (declare (ignore database db-type))
648   (if val
649       (symbol-name val)
650       ""))
651
652 (defmethod database-output-sql-as-type ((type (eql 'vector)) val database db-type)
653   (declare (ignore database db-type))
654   (progv '(*print-circle* *print-array*) '(t t)
655     (prin1-to-string val)))
656
657 (defmethod database-output-sql-as-type ((type (eql 'array)) val database db-type)
658   (declare (ignore database db-type))
659   (progv '(*print-circle* *print-array*) '(t t)
660     (prin1-to-string val)))
661
662 (defmethod database-output-sql-as-type ((type (eql 'boolean)) val database db-type)
663   (declare (ignore database db-type))
664   (if val "t" "f"))
665
666 (defmethod database-output-sql-as-type ((type (eql 'generalized-boolean)) val database db-type)
667   (declare (ignore database db-type))
668   (if val "t" "f"))
669
670 (defmethod database-output-sql-as-type ((type (eql 'string)) val database db-type)
671   (declare (ignore database db-type))
672   val)
673
674 (defmethod database-output-sql-as-type ((type (eql 'char)) val database db-type)
675   (declare (ignore database db-type))
676   (etypecase val
677     (character (write-to-string val))
678     (string val)))
679
680 (defmethod database-output-sql-as-type ((type (eql 'float)) val database db-type)
681   (declare (ignore database db-type))
682   (if (eq (type-of val) 'null)
683       nil
684       (let ((*read-default-float-format* (type-of val)))
685        (format nil "~F" val))))
686
687 (defmethod read-sql-value (val type database db-type)
688   (declare (ignore database db-type))
689   (cond
690     ((null type) val) ;;we have no desired type, just give the value
691     ((typep val type) val) ;;check that it hasn't already been converted.
692     ((typep val 'string) (read-from-string val)) ;;maybe read will just take care of it?
693     (T (error "Unable to read-sql-value ~a as type ~a" val type))))
694
695 (defmethod read-sql-value (val (type (eql 'string)) database db-type)
696   (declare (ignore database db-type))
697   val)
698
699 (defmethod read-sql-value (val (type (eql 'varchar)) database db-type)
700   (declare (ignore database db-type))
701   val)
702
703 (defmethod read-sql-value (val (type (eql 'char)) database db-type)
704   (declare (ignore database db-type))
705   (schar val 0))
706
707 (defmethod read-sql-value (val (type (eql 'keyword)) database db-type)
708   (declare (ignore database db-type))
709   (when (< 0 (length val))
710     (intern (symbol-name-default-case val)
711             (find-package '#:keyword))))
712
713 (defmethod read-sql-value (val (type (eql 'symbol)) database db-type)
714   (declare (ignore database db-type))
715   (when (< 0 (length val))
716     (unless (string= val (symbol-name-default-case "NIL"))
717       (read-from-string val))))
718
719 (defmethod read-sql-value (val (type (eql 'integer)) database db-type)
720   (declare (ignore database db-type))
721   (etypecase val
722     (string
723      (unless (string-equal "NIL" val)
724        (parse-integer val)))
725     (number val)))
726
727 (defmethod read-sql-value (val (type (eql 'smallint)) database db-type)
728   (declare (ignore database db-type))
729   (etypecase val
730     (string
731      (unless (string-equal "NIL" val)
732        (parse-integer val)))
733     (number val)))
734
735 (defmethod read-sql-value (val (type (eql 'bigint)) database db-type)
736   (declare (ignore database db-type))
737   (etypecase val
738     (string
739      (unless (string-equal "NIL" val)
740        (parse-integer val)))
741     (number val)))
742
743 (defmethod read-sql-value (val (type (eql 'float)) database db-type)
744   (declare (ignore database db-type))
745   ;; writing 1.0 writes 1, so we we *really* want a float, must do (float ...)
746   (etypecase val
747     (string (float (read-from-string val)))
748     (float val)))
749
750 (defmethod read-sql-value (val (type (eql 'double-float)) database db-type)
751   (declare (ignore database db-type))
752   ;; writing 1.0 writes 1, so if we *really* want a float, must do (float ...)
753   (etypecase val
754     (string (float
755              (let ((*read-default-float-format* 'double-float))
756                (read-from-string val))
757              1.0d0))
758     (double-float val)
759     (float (coerce val 'double-float))))
760
761 (defmethod read-sql-value (val (type (eql 'boolean)) database db-type)
762   (declare (ignore database db-type))
763   (equal "t" val))
764
765 (defmethod read-sql-value (val (type (eql 'generalized-boolean)) database db-type)
766   (declare (ignore database db-type))
767   (equal "t" val))
768
769 (defmethod read-sql-value (val (type (eql 'number)) database db-type)
770   (declare (ignore database db-type))
771   (etypecase val
772     (string
773      (unless (string-equal "NIL" val)
774        (read-from-string val)))
775     (number val)))
776
777 (defmethod read-sql-value (val (type (eql 'universal-time)) database db-type)
778   (declare (ignore database db-type))
779   (unless (eq 'NULL val)
780     (etypecase val
781       (string
782        (parse-integer val))
783       (number val))))
784
785 (defmethod read-sql-value (val (type (eql 'wall-time)) database db-type)
786   (declare (ignore database db-type))
787   (unless (eq 'NULL val)
788     (parse-timestring val)))
789
790 (defmethod read-sql-value (val (type (eql 'date)) database db-type)
791   (declare (ignore database db-type))
792   (unless (eq 'NULL val)
793     (parse-datestring val)))
794
795 (defmethod read-sql-value (val (type (eql 'duration)) database db-type)
796   (declare (ignore database db-type))
797   (unless (or (eq 'NULL val)
798               (equal "NIL" val))
799     (parse-timestring val)))
800
801 ;; ------------------------------------------------------------
802 ;; Logic for 'faulting in' :join slots
803
804 ;; this works, but is inefficient requiring (+ 1 n-rows)
805 ;; SQL queries
806 #+ignore
807 (defun fault-join-target-slot (class object slot-def)
808   (let* ((res (fault-join-slot-raw class object slot-def))
809          (dbi (view-class-slot-db-info slot-def))
810          (target-name (gethash :target-slot dbi))
811          (target-class (find-class target-name)))
812     (when res
813       (mapcar (lambda (obj)
814                 (list
815                  (car
816                   (fault-join-slot-raw
817                    target-class
818                    obj
819                    (find target-name (class-slots (class-of obj))
820                          :key #'slot-definition-name)))
821                  obj))
822               res)
823       #+ignore ;; this doesn't work when attempting to call slot-value
824       (mapcar (lambda (obj)
825                 (cons obj (slot-value obj ts))) res))))
826
827 (defun fault-join-target-slot (class object slot-def)
828   (let* ((dbi (view-class-slot-db-info slot-def))
829          (ts (gethash :target-slot dbi))
830          (jc  (gethash :join-class dbi))
831          (jc-view-table (view-table (find-class jc)))
832          (tdbi (view-class-slot-db-info
833                 (find ts (class-slots (find-class jc))
834                       :key #'slot-definition-name)))
835          (retrieval (gethash :retrieval tdbi))
836          (tsc (gethash :join-class tdbi))
837          (ts-view-table (view-table (find-class tsc)))
838          (jq (join-qualifier class object slot-def))
839          (key (slot-value object (gethash :home-key dbi))))
840
841     (when jq
842       (ecase retrieval
843         (:immediate
844          (let ((res
845                 (find-all (list tsc)
846                           :inner-join (sql-expression :table jc-view-table)
847                           :on (sql-operation
848                                '==
849                                (sql-expression
850                                 :attribute (gethash :foreign-key tdbi)
851                                 :table ts-view-table)
852                                (sql-expression
853                                 :attribute (gethash :home-key tdbi)
854                                 :table jc-view-table))
855                           :where jq
856                           :result-types :auto
857                           :database (choose-database-for-instance object))))
858            (mapcar #'(lambda (i)
859                        (let* ((instance (car i))
860                               (jcc (make-instance jc :view-database (choose-database-for-instance instance))))
861                          (setf (slot-value jcc (gethash :foreign-key dbi))
862                                key)
863                          (setf (slot-value jcc (gethash :home-key tdbi))
864                                (slot-value instance (gethash :foreign-key tdbi)))
865                          (list instance jcc)))
866                    res)))
867         (:deferred
868          ;; just fill in minimal slots
869          (mapcar
870           #'(lambda (k)
871               (let ((instance (make-instance tsc :view-database (choose-database-for-instance object)))
872                     (jcc (make-instance jc :view-database (choose-database-for-instance object)))
873                     (fk (car k)))
874                 (setf (slot-value instance (gethash :home-key tdbi)) fk)
875                 (setf (slot-value jcc (gethash :foreign-key dbi))
876                       key)
877                 (setf (slot-value jcc (gethash :home-key tdbi))
878                       fk)
879                 (list instance jcc)))
880           (select (sql-expression :attribute (gethash :foreign-key tdbi) :table jc-view-table)
881                   :from (sql-expression :table jc-view-table)
882                   :where jq
883                   :database (choose-database-for-instance object))))))))
884
885
886 ;;; Remote Joins
887
888 (defvar *default-update-objects-max-len* nil
889   "The default value to use for the MAX-LEN keyword argument to
890   UPDATE-OBJECT-JOINS.")
891
892 (defun update-objects-joins (objects &key (slots t) (force-p t)
893                              class-name (max-len
894                                          *default-update-objects-max-len*))
895   "Updates from the records of the appropriate database tables
896 the join slots specified by SLOTS in the supplied list of View
897 Class instances OBJECTS.  SLOTS is t by default which means that
898 all join slots with :retrieval :immediate are updated. CLASS-NAME
899 is used to specify the View Class of all instance in OBJECTS and
900 default to nil which means that the class of the first instance
901 in OBJECTS is used. FORCE-P is t by default which means that all
902 join slots are updated whereas a value of nil means that only
903 unbound join slots are updated. MAX-LEN defaults to
904 *DEFAULT-UPDATE-OBJECTS-MAX-LEN* and when non-nil specifies that
905 UPDATE-OBJECT-JOINS may issue multiple database queries with a
906 maximum of MAX-LEN instances updated in each query."
907   (assert (or (null max-len) (plusp max-len)))
908   (when objects
909     (unless class-name
910       (setq class-name (class-name (class-of (first objects)))))
911     (let* ((class (find-class class-name))
912            (class-slots (ordered-class-slots class))
913            (slotdefs
914             (if (eq t slots)
915                 (generate-retrieval-joins-list class :deferred)
916                 (remove-if #'null
917                            (mapcar #'(lambda (name)
918                                        (let ((slotdef (find name class-slots :key #'slot-definition-name)))
919                                          (unless slotdef
920                                            (warn "Unable to find slot named ~S in class ~S." name class))
921                                          slotdef))
922                                    slots)))))
923       (dolist (slotdef slotdefs)
924         (let* ((dbi (view-class-slot-db-info slotdef))
925                (slotdef-name (slot-definition-name slotdef))
926                (foreign-key (gethash :foreign-key dbi))
927                (home-key (gethash :home-key dbi))
928                (object-keys
929                 (remove-duplicates
930                  (if force-p
931                      (mapcar #'(lambda (o) (slot-value o home-key)) objects)
932                      (remove-if #'null
933                                 (mapcar
934                                  #'(lambda (o) (if (slot-boundp o slotdef-name)
935                                                    nil
936                                                    (slot-value o home-key)))
937                                  objects)))))
938                (n-object-keys (length object-keys))
939                (query-len (or max-len n-object-keys)))
940
941           (do ((i 0 (+ i query-len)))
942               ((>= i n-object-keys))
943             (let* ((keys (if max-len
944                              (subseq object-keys i (min (+ i query-len) n-object-keys))
945                              object-keys))
946                    (results (unless (gethash :target-slot dbi)
947                               (find-all (list (gethash :join-class dbi))
948                                         :where (make-instance 'sql-relational-exp
949                                                               :operator 'in
950                                                               :sub-expressions (list (sql-expression :attribute foreign-key)
951                                                                                      keys))
952                                         :result-types :auto
953                                         :flatp t)) ))
954
955               (dolist (object objects)
956                 (when (or force-p (not (slot-boundp object slotdef-name)))
957                   (let ((res (if results
958                                  (remove-if-not #'(lambda (obj)
959                                                     (equal obj (slot-value
960                                                                 object
961                                                                 home-key)))
962                                                 results
963                                                 :key #'(lambda (res)
964                                                          (slot-value res
965                                                                      foreign-key)))
966
967                                  (progn
968                                    (when (gethash :target-slot dbi)
969                                      (fault-join-target-slot class object slotdef))))))
970                     (when res
971                       (setf (slot-value object slotdef-name)
972                             (if (gethash :set dbi) res (car res)))))))))))))
973   (values))
974
975 (defun fault-join-slot-raw (class object slot-def)
976   (let* ((dbi (view-class-slot-db-info slot-def))
977          (jc (gethash :join-class dbi)))
978     (let ((jq (join-qualifier class object slot-def)))
979       (when jq
980         (select jc :where jq :flatp t :result-types nil
981                 :database (choose-database-for-instance object))))))
982
983
984
985 (defun fault-join-slot (class object slot-def)
986   (let* ((dbi (view-class-slot-db-info slot-def))
987          (ts (gethash :target-slot dbi))
988          (dbi-set (gethash :set dbi)))
989     (if (and ts dbi-set)
990         (fault-join-target-slot class object slot-def)
991         (let ((res (fault-join-slot-raw class object slot-def)))
992           (when res
993             (cond
994               ((and ts (not dbi-set))
995                (mapcar (lambda (obj) (slot-value obj ts)) res))
996               ((and (not ts) (not dbi-set))
997                (car res))
998               ((and (not ts) dbi-set)
999                res)))))))
1000
1001 (defun update-fault-join-normalized-slot (class object slot-def)
1002   (if (and (normalizedp class) (key-slot-p slot-def))
1003       (setf (easy-slot-value object slot-def)
1004             (normalized-key-value object))
1005       (update-slot-from-record object slot-def)))
1006
1007 (defun all-home-keys-have-values-p (object slot-def)
1008   "Do all of the home-keys have values ?"
1009   (let ((home-keys (join-slot-info-value slot-def :home-key)))
1010     (loop for key in (listify home-keys)
1011           always (easy-slot-value object key))))
1012
1013 (defun join-qualifier (class object slot-def)
1014   "Builds the join where clause based on the keys of the join slot and values
1015    of the object"
1016   (declare (ignore class))
1017   (let* ((jc (join-slot-class slot-def))
1018          ;;(ts (gethash :target-slot dbi))
1019          ;;(tsdef (if ts (slotdef-for-slot-with-class ts jc)))
1020          (foreign-keys (listify (join-slot-info-value slot-def :foreign-key)))
1021          (home-keys (listify (join-slot-info-value slot-def :home-key))))
1022     (when (all-home-keys-have-values-p object slot-def)
1023       (clsql-ands
1024        (loop for hk in home-keys
1025              for fk in foreign-keys
1026              for fksd = (slotdef-for-slot-with-class fk jc)
1027              for fk-sql = (typecase fk
1028                             (symbol
1029                              (sql-expression
1030                               :attribute (database-identifier fksd nil)
1031                               :table (database-identifier jc nil)))
1032                             (t fk))
1033              for hk-val = (typecase hk
1034                             ((or symbol
1035                                  view-class-effective-slot-definition
1036                                  view-class-direct-slot-definition)
1037                              (easy-slot-value object hk))
1038                             (t hk))
1039              collect (sql-operation '== fk-sql hk-val))))))
1040
1041 ;; FIXME: add retrieval immediate for efficiency
1042 ;; For example, for (select 'employee-address) in test suite =>
1043 ;; select addr.*,ea_join.* FROM addr,ea_join WHERE ea_join.aaddressid=addr.addressid\g
1044
1045 (defun build-objects (vals sclasses immediate-join-classes sels immediate-joins database refresh flatp instances)
1046   "Used by find-all to build objects."
1047   (labels ((build-object (vals vclass jclasses selects immediate-selects instance)
1048              (let* ((db-vals (butlast vals (- (list-length vals)
1049                                               (list-length selects))))
1050                     (obj (if instance instance (make-instance (class-name vclass) :view-database database)))
1051                     (join-vals (subseq vals (list-length selects)))
1052                     (joins (mapcar #'(lambda (c) (when c (make-instance c :view-database database)))
1053                                    jclasses)))
1054
1055                ;;(format t "joins: ~S~%db-vals: ~S~%join-values: ~S~%selects: ~S~%immediate-selects: ~S~%"
1056                ;;joins db-vals join-vals selects immediate-selects)
1057
1058                ;; use refresh keyword here
1059                (setf obj (get-slot-values-from-view obj (mapcar #'car selects) db-vals))
1060                (mapc #'(lambda (jo)
1061                          ;; find all immediate-select slots and join-vals for this object
1062                          (let* ((jo-class (class-of jo))
1063                                 (slots (slots-for-possibly-normalized-class jo-class))
1064                                 (pos-list (remove-if #'null
1065                                                      (mapcar
1066                                                       #'(lambda (s)
1067                                                           (position s immediate-selects
1068                                                                     :key #'car
1069                                                                     :test #'eq))
1070                                                       slots))))
1071                            (get-slot-values-from-view jo
1072                                                       (mapcar #'car
1073                                                               (mapcar #'(lambda (pos)
1074                                                                           (nth pos immediate-selects))
1075                                                                       pos-list))
1076                                                       (mapcar #'(lambda (pos) (nth pos join-vals))
1077                                                               pos-list))))
1078                      joins)
1079                (mapc
1080                 #'(lambda (jc)
1081                     (let* ((vslots
1082                             (class-slots vclass))
1083                            (slot (find (class-name (class-of jc)) vslots
1084                                        :key #'(lambda (slot)
1085                                                 (when (and (eq :join (view-class-slot-db-kind slot))
1086                                                            (eq (slot-definition-name slot)
1087                                                                (gethash :join-class (view-class-slot-db-info slot))))
1088                                                   (slot-definition-name slot))))))
1089                       (when slot
1090                         (setf (slot-value obj (slot-definition-name slot)) jc))))
1091                 joins)
1092                (when refresh (instance-refreshed obj))
1093                obj)))
1094     (let* ((objects
1095             (mapcar #'(lambda (sclass jclass sel immediate-join instance)
1096                         (prog1
1097                             (build-object vals sclass jclass sel immediate-join instance)
1098                           (setf vals (nthcdr (+ (list-length sel) (list-length immediate-join))
1099                                              vals))))
1100                     sclasses immediate-join-classes sels immediate-joins instances)))
1101       (if (and flatp (= (length sclasses) 1))
1102           (car objects)
1103           objects))))
1104
1105 (defmethod select-table-sql-expr ((table T))
1106   "Turns an object representing a table into the :from part of the sql expression that will be executed "
1107   (sql-expression :table (view-table table)))
1108
1109
1110 (defun find-all (view-classes
1111                  &rest args
1112                  &key all set-operation distinct from where group-by having
1113                  order-by offset limit refresh flatp result-types
1114                  inner-join on
1115                  (database *default-database*)
1116                  instances parameters)
1117   "Called by SELECT to generate object query results when the
1118   View Classes VIEW-CLASSES are passed as arguments to SELECT."
1119   (declare (ignore all set-operation group-by having offset limit inner-join on parameters)
1120            (dynamic-extent args))
1121   (flet ((ref-equal (ref1 ref2)
1122            (string= (sql-output ref1 database)
1123                     (sql-output ref2 database))))
1124     (declare (dynamic-extent (function ref-equal)))
1125     (let ((args (filter-plist args :from :where :flatp :additional-fields :result-types :instances)))
1126       (let* ((*db-deserializing* t)
1127              (sclasses (mapcar #'find-class view-classes))
1128              (immediate-join-slots
1129                (mapcar #'(lambda (c) (generate-retrieval-joins-list c :immediate)) sclasses))
1130              (immediate-join-classes
1131                (mapcar #'(lambda (jcs)
1132                            (mapcar #'(lambda (slotdef)
1133                                        (find-class (gethash :join-class (view-class-slot-db-info slotdef))))
1134                                    jcs))
1135                        immediate-join-slots))
1136              (immediate-join-sels (mapcar #'generate-immediate-joins-selection-list sclasses))
1137              (sels (mapcar #'generate-selection-list sclasses))
1138              (fullsels (apply #'append (mapcar #'append sels immediate-join-sels)))
1139              (sel-tables (collect-table-refs where))
1140              (tables (remove-if #'null
1141                                 (remove-duplicates
1142                                  (append (mapcar #'select-table-sql-expr sclasses)
1143                                          (mapcan #'(lambda (jc-list)
1144                                                      (mapcar
1145                                                       #'(lambda (jc) (when jc (select-table-sql-expr jc)))
1146                                                       jc-list))
1147                                                  immediate-join-classes)
1148                                          sel-tables)
1149                                  :test #'database-identifier-equal)))
1150              (order-by-slots (mapcar #'(lambda (ob) (if (atom ob) ob (car ob)))
1151                                      (listify order-by)))
1152              (join-where nil))
1153
1154         ;;(format t "sclasses: ~W~%ijc: ~W~%tables: ~W~%" sclasses immediate-join-classes tables)
1155
1156         (dolist (ob order-by-slots)
1157           (when (and ob (not (member ob (mapcar #'cdr fullsels)
1158                                      :test #'ref-equal)))
1159             (setq fullsels
1160                   (append fullsels (mapcar #'(lambda (att) (cons nil att))
1161                                            order-by-slots)))))
1162         (dolist (ob (listify distinct))
1163           (when (and (typep ob 'sql-ident)
1164                      (not (member ob (mapcar #'cdr fullsels)
1165                                   :test #'ref-equal)))
1166             (setq fullsels
1167                   (append fullsels (mapcar #'(lambda (att) (cons nil att))
1168                                            (listify ob))))))
1169         (mapcar #'(lambda (vclass jclasses jslots)
1170                     (when jclasses
1171                       (mapcar
1172                        #'(lambda (jclass jslot)
1173                            (let ((dbi (view-class-slot-db-info jslot)))
1174                              (setq join-where
1175                                    (append
1176                                     (list (sql-operation '==
1177                                                          (sql-expression
1178                                                           :attribute (gethash :foreign-key dbi)
1179                                                           :table (view-table jclass))
1180                                                          (sql-expression
1181                                                           :attribute (gethash :home-key dbi)
1182                                                           :table (view-table vclass))))
1183                                     (when join-where (listify join-where))))))
1184                        jclasses jslots)))
1185                 sclasses immediate-join-classes immediate-join-slots)
1186         ;; Reported buggy on clsql-devel
1187         ;; (when where (setq where (listify where)))
1188         (cond
1189           ((and where join-where)
1190            (setq where (list (apply #'sql-and where join-where))))
1191           ((and (null where) (> (length join-where) 1))
1192            (setq where (list (apply #'sql-and join-where)))))
1193
1194         (let* ((rows (apply #'select
1195                             (append (mapcar #'cdr fullsels)
1196                                     (cons :from
1197                                           (list (append (when from (listify from))
1198                                                         (listify tables))))
1199                                     (list :result-types result-types)
1200                                     (when where
1201                                       (list :where where))
1202                                     args)))
1203                (instances-to-add (- (length rows) (length instances)))
1204                (perhaps-extended-instances
1205                  (if (plusp instances-to-add)
1206                      (append instances (do ((i 0 (1+ i))
1207                                             (res nil))
1208                                            ((= i instances-to-add) res)
1209                                          (push (make-list (length sclasses) :initial-element nil) res)))
1210                      instances))
1211                (objects (mapcar
1212                          #'(lambda (row instance)
1213                              (build-objects row sclasses immediate-join-classes sels
1214                                             immediate-join-sels database refresh flatp
1215                                             (if (and flatp (atom instance))
1216                                                 (list instance)
1217                                                 instance)))
1218                          rows perhaps-extended-instances)))
1219           objects)))))
1220
1221 (defmethod instance-refreshed ((instance standard-db-object)))
1222
1223 (defvar *default-caching* t
1224   "Controls whether SELECT caches objects by default. The CommonSQL
1225 specification states caching is on by default.")
1226
1227 (defun select (&rest select-all-args)
1228   "Executes a query on DATABASE, which has a default value of
1229 *DEFAULT-DATABASE*, specified by the SQL expressions supplied
1230 using the remaining arguments in SELECT-ALL-ARGS. The SELECT
1231 argument can be used to generate queries in both functional and
1232 object oriented contexts.
1233
1234 In the functional case, the required arguments specify the
1235 columns selected by the query and may be symbolic SQL expressions
1236 or strings representing attribute identifiers. Type modified
1237 identifiers indicate that the values selected from the specified
1238 column are converted to the specified lisp type. The keyword
1239 arguments ALL, DISTINCT, FROM, GROUP-by, HAVING, ORDER-BY,
1240 SET-OPERATION and WHERE are used to specify, using the symbolic
1241 SQL syntax, the corresponding components of the SQL query
1242 generated by the call to SELECT. RESULT-TYPES is a list of
1243 symbols which specifies the lisp type for each field returned by
1244 the query. If RESULT-TYPES is nil all results are returned as
1245 strings whereas the default value of :auto means that the lisp
1246 types are automatically computed for each field. FIELD-NAMES is t
1247 by default which means that the second value returned is a list
1248 of strings representing the columns selected by the query. If
1249 FIELD-NAMES is nil, the list of column names is not returned as a
1250 second value.
1251
1252 In the object oriented case, the required arguments to SELECT are
1253 symbols denoting View Classes which specify the database tables
1254 to query. In this case, SELECT returns a list of View Class
1255 instances whose slots are set from the attribute values of the
1256 records in the specified table. Slot-value is a legal operator
1257 which can be employed as part of the symbolic SQL syntax used in
1258 the WHERE keyword argument to SELECT. REFRESH is nil by default
1259 which means that the View Class instances returned are retrieved
1260 from a cache if an equivalent call to SELECT has previously been
1261 issued. If REFRESH is true, the View Class instances returned are
1262 updated as necessary from the database and the generic function
1263 INSTANCE-REFRESHED is called to perform any necessary operations
1264 on the updated instances.
1265
1266 In both object oriented and functional contexts, FLATP has a
1267 default value of nil which means that the results are returned as
1268 a list of lists. If FLATP is t and only one result is returned
1269 for each record selected in the query, the results are returned
1270 as elements of a list."
1271   (multiple-value-bind (target-args qualifier-args)
1272       (query-get-selections select-all-args)
1273     (unless (or *default-database* (getf qualifier-args :database))
1274       (signal-no-database-error nil))
1275
1276     (let ((caching (getf qualifier-args :caching *default-caching*))
1277           (result-types (getf qualifier-args :result-types :auto))
1278           (refresh (getf qualifier-args :refresh nil))
1279           (database (getf qualifier-args :database *default-database*)))
1280
1281       (cond
1282         ((and target-args
1283               (every #'(lambda (arg)
1284                          (and (symbolp arg)
1285                               (find-class arg nil)))
1286                      target-args))
1287
1288          (setf qualifier-args (filter-plist qualifier-args :caching :refresh :result-types))
1289
1290          ;; Add explicity table name to order-by if not specified and only
1291          ;; one selected table. This is required so FIND-ALL won't duplicate
1292          ;; the field
1293          (let ((order-by (getf qualifier-args :order-by)))
1294            (when (and order-by (= 1 (length target-args)))
1295              (let ((table-name (view-table (find-class (car target-args))))
1296                    (order-by-list (copy-seq (listify order-by))))
1297                (labels ((sv (val name) (ignore-errors (slot-value val name)))
1298                         (set-table-if-needed (val)
1299                           (typecase val
1300                             (sql-ident-attribute
1301                              (handler-case
1302                                  (if (sv val 'qualifier)
1303                                      val
1304                                      (make-instance 'sql-ident-attribute
1305                                                     :name (sv val 'name)
1306                                                     :qualifier table-name))
1307                                (simple-error ()
1308                                  ;; TODO: Check for a specific error we expect
1309                                  )))
1310                             (cons (cons (set-table-if-needed (car val))
1311                                         (cdr val)))
1312                             (t val))))
1313                  (setf order-by-list
1314                        (loop for i from 0 below (length order-by-list)
1315                              for id in order-by-list
1316                              collect (set-table-if-needed id))))
1317                (setf (getf qualifier-args :order-by) order-by-list))))
1318
1319          (cond
1320            ((null caching)
1321             (apply #'find-all target-args :result-types result-types :refresh refresh qualifier-args))
1322            (t
1323             (let ((cached (records-cache-results target-args qualifier-args database)))
1324               (if (and cached (not refresh))
1325                   cached
1326                   (let ((results (apply #'find-all target-args
1327                                         :result-types :auto :refresh refresh
1328                                         :instances cached
1329                                         qualifier-args)))
1330                     (setf (records-cache-results target-args qualifier-args database) results)
1331
1332                     results))))))
1333         (t
1334          (let* ((expr (apply #'make-query select-all-args))
1335                 (parameters (second (member :parameters select-all-args)))
1336                 (specified-types
1337                   (mapcar #'(lambda (attrib)
1338                               (if (typep attrib 'sql-ident-attribute)
1339                                   (let ((type (slot-value attrib 'type)))
1340                                     (if type
1341                                         type
1342                                         t))
1343                                   t))
1344                           (slot-value expr 'selections)))
1345                 (flatp (getf qualifier-args :flatp))
1346                 (field-names (getf qualifier-args :field-names t)))
1347
1348            (when parameters
1349              (setf expr (command-object (sql-output expr database) parameters)))
1350            (query expr :flatp flatp
1351                        :result-types
1352                        ;; specifying a type for an attribute overrides result-types
1353                        (if (some #'(lambda (x) (not (eq t x))) specified-types)
1354                            specified-types
1355                            result-types)
1356                        :field-names field-names
1357                        :database database)))))))
1358
1359 (defun compute-records-cache-key (targets qualifiers)
1360   (list targets
1361         (do ((args *select-arguments* (cdr args))
1362              (results nil))
1363             ((null args) results)
1364           (let* ((arg (car args))
1365                  (value (getf qualifiers arg)))
1366             (when value
1367               (push (list arg
1368                           (typecase value
1369                             (cons (cons (sql (car value)) (cdr value)))
1370                             (%sql-expression (sql value))
1371                             (t value)))
1372                     results))))))
1373
1374 (defun records-cache-results (targets qualifiers database)
1375   (when (record-caches database)
1376     (gethash (compute-records-cache-key targets qualifiers) (record-caches database))))
1377
1378 (defun (setf records-cache-results) (results targets qualifiers database)
1379   (unless (record-caches database)
1380     (setf (record-caches database)
1381           (make-weak-hash-table :test 'equal)))
1382   (setf (gethash (compute-records-cache-key (copy-list targets) qualifiers)
1383                  (record-caches database)) results)
1384   results)
1385
1386
1387
1388 ;;; Serialization functions
1389
1390 (defun write-instance-to-stream (obj stream)
1391   "Writes an instance to a stream where it can be later be read.
1392 NOTE: an error will occur if a slot holds a value which can not be written readably."
1393   (let* ((class (class-of obj))
1394          (alist '()))
1395     (dolist (slot (ordered-class-slots (class-of obj)))
1396       (let ((name (slot-definition-name slot)))
1397         (when (and (not (eq 'view-database name))
1398                    (slot-boundp obj name))
1399           (push (cons name (slot-value obj name)) alist))))
1400     (setq alist (reverse alist))
1401     (write (cons (class-name class) alist) :stream stream :readably t))
1402   obj)
1403
1404 (defun read-instance-from-stream (stream)
1405   (let ((raw (read stream nil nil)))
1406     (when raw
1407       (let ((obj (make-instance (car raw))))
1408         (dolist (pair (cdr raw))
1409           (setf (slot-value obj (car pair)) (cdr pair)))
1410         obj))))