r8852: package renaming
[clsql.git] / sql / objects.lisp
1 ;;;; -*- Mode: LISP; Syntax: ANSI-Common-Lisp; Base: 10 -*-
2 ;;;; ======================================================================
3 ;;;; $Id: $
4 ;;;;
5 ;;;; Description ==========================================================
6 ;;;; ======================================================================
7 ;;;;
8 ;;;; The CLSQL-USQL Object Oriented Data Definitional Language (OODDL)
9 ;;;; and Object Oriented Data Manipulation Language (OODML).
10 ;;;;
11 ;;;; ======================================================================
12
13 (in-package #:clsql-sys)
14
15 (defclass standard-db-object ()
16   ((view-database
17     :initform nil
18     :initarg :view-database
19     :db-kind :virtual))
20   (:metaclass standard-db-class)
21   (:documentation "Superclass for all CLSQL-USQL View Classes."))
22
23 (defmethod view-database ((self standard-db-object))
24   (slot-value self 'view-database))
25
26 (defvar *db-deserializing* nil)
27 (defvar *db-initializing* nil)
28
29 (defmethod slot-value-using-class ((class standard-db-class) instance slot)
30   (declare (optimize (speed 3)))
31   (unless *db-deserializing*
32     (let ((slot-name (%slot-name slot))
33           (slot-object (%slot-object slot class)))
34       (when (and (eql (view-class-slot-db-kind slot-object) :join)
35                  (not (slot-boundp instance slot-name)))
36         (let ((*db-deserializing* t))
37           (if (view-database instance)
38               (setf (slot-value instance slot-name)
39                     (fault-join-slot class instance slot-object))
40               (setf (slot-value instance slot-name) nil))))))
41   (call-next-method))
42
43 (defmethod (setf slot-value-using-class) (new-value (class standard-db-class)
44                                           instance slot)
45   (declare (ignore new-value instance slot))
46   (call-next-method))
47
48 ;; JMM - Can't go around trying to slot-access a symbol!  Guess in
49 ;; CMUCL slot-name is the actual slot _object_, while in lispworks it
50 ;; is a lowly symbol (the variable is called slot-name after all) so
51 ;; the object (or in MOP terminology- the "slot definition") has to be
52 ;; retrieved using find-slot-definition
53
54 (defun %slot-name (slot)
55   #+lispworks slot
56   #-lispworks (slot-definition-name slot))
57
58 (defun %slot-object (slot class)
59   (declare (ignorable class))
60   #+lispworks (clos:find-slot-definition slot class)
61   #-lispworks slot)
62
63 (defmethod initialize-instance :around ((class standard-db-object)
64                                         &rest all-keys
65                                         &key &allow-other-keys)
66   (declare (ignore all-keys))
67   (let ((*db-deserializing* t))
68     (call-next-method)))
69
70 (defun sequence-from-class (view-class-name)
71   (sql-escape
72    (concatenate
73     'string
74     (symbol-name (view-table (find-class view-class-name)))
75     "-SEQ")))
76
77 (defun create-sequence-from-class (view-class-name
78                                    &key (database *default-database*))
79   (create-sequence (sequence-from-class view-class-name) :database database))
80
81 (defun drop-sequence-from-class (view-class-name
82                                  &key (if-does-not-exist :error)
83                                  (database *default-database*))
84   (drop-sequence (sequence-from-class view-class-name)
85                  :if-does-not-exist if-does-not-exist
86                  :database database))
87
88 ;;
89 ;; Build the database tables required to store the given view class
90 ;;
91
92 (defmethod database-pkey-constraint ((class standard-db-class) database)
93   (let ((keylist (mapcar #'view-class-slot-column (keyslots-for-class class))))
94     (when keylist 
95       (format nil "CONSTRAINT ~APK PRIMARY KEY~A"
96               (database-output-sql (view-table class) database)
97               (database-output-sql keylist database)))))
98
99
100 #.(locally-enable-sql-reader-syntax)
101
102 (defun ensure-schema-version-table (database)
103   (unless (table-exists-p "usql_object_v" :database database)
104     (create-table [usql_object_v] '(([name] (string 32))
105                                     ([vers] integer)
106                                     ([def] (string 32)))
107                   :database database)))
108
109 (defun update-schema-version-records (view-class-name
110                                       &key (database *default-database*))
111   (let ((schemadef nil)
112         (tclass (find-class view-class-name)))
113     (dolist (slotdef (class-slots tclass))
114       (let ((res (database-generate-column-definition view-class-name
115                                                       slotdef database)))
116         (when res (setf schemadef (cons res schemadef)))))
117     (when schemadef
118       (delete-records :from [usql_object_v]
119                       :where [= [name] (sql-escape (class-name tclass))]
120                       :database database)
121       (insert-records :into [usql_object_v]
122                       :av-pairs `(([name] ,(sql-escape (class-name tclass)))
123                                   ([vers] ,(car (object-version tclass)))
124                                   ([def] ,(prin1-to-string
125                                            (object-definition tclass))))
126                       :database database))))
127
128 #.(restore-sql-reader-syntax-state)
129
130 (defun create-view-from-class (view-class-name
131                                &key (database *default-database*))
132   "Creates a view in DATABASE based on VIEW-CLASS-NAME which defines
133 the view. The argument DATABASE has a default value of
134 *DEFAULT-DATABASE*."
135   (let ((tclass (find-class view-class-name)))
136     (if tclass
137         (let ((*default-database* database))
138           (%install-class tclass database)
139           (ensure-schema-version-table database)
140           (update-schema-version-records view-class-name :database database))
141         (error "Class ~s not found." view-class-name)))
142   (values))
143
144 (defmethod %install-class ((self standard-db-class) database &aux schemadef)
145   (dolist (slotdef (class-slots self))
146     (let ((res (database-generate-column-definition (class-name self)
147                                                     slotdef database)))
148       (when res 
149         (push res schemadef))))
150   (unless schemadef
151     (error "Class ~s has no :base slots" self))
152   (create-table (sql-expression :table (view-table self)) schemadef
153                 :database database
154                 :constraints (database-pkey-constraint self database))
155   (push self (database-view-classes database))
156   t)
157
158 ;;
159 ;; Drop the tables which store the given view class
160 ;;
161
162 #.(locally-enable-sql-reader-syntax)
163
164 (defun drop-view-from-class (view-class-name &key (database *default-database*))
165   "Deletes a view or base table from DATABASE based on VIEW-CLASS-NAME
166 which defines that view. The argument DATABASE has a default value of
167 *DEFAULT-DATABASE*."
168   (let ((tclass (find-class view-class-name)))
169     (if tclass
170         (let ((*default-database* database))
171           (%uninstall-class tclass)
172           (delete-records :from [usql_object_v]
173                           :where [= [name] (sql-escape view-class-name)]))
174         (error "Class ~s not found." view-class-name)))
175   (values))
176
177 #.(restore-sql-reader-syntax-state)
178
179 (defun %uninstall-class (self &key (database *default-database*))
180   (drop-table (sql-expression :table (view-table self))
181               :if-does-not-exist :ignore
182               :database database)
183   (setf (database-view-classes database)
184         (remove self (database-view-classes database))))
185
186
187 ;;
188 ;; List all known view classes
189 ;;
190
191 (defun list-classes (&key (test #'identity)
192                           (root-class 'standard-db-object)
193                           (database *default-database*))
194   "Returns a list of View Classes connected to a given DATABASE which
195 defaults to *DEFAULT-DATABASE*."
196   (declare (ignore root-class))
197   (remove-if #'(lambda (c) (not (funcall test c)))
198              (database-view-classes database)))
199
200 ;;
201 ;; Define a new view class
202 ;;
203
204 (defmacro def-view-class (class supers slots &rest options)
205   "Extends the syntax of defclass to allow special slots to be mapped
206 onto the attributes of database views. The macro DEF-VIEW-CLASS
207 creates a class called CLASS which maps onto a database view. Such a
208 class is called a View Class. The macro DEF-VIEW-CLASS extends the
209 syntax of DEFCLASS to allow special base slots to be mapped onto the
210 attributes of database views (presently single tables). When a select
211 query that names a View Class is submitted, then the corresponding
212 database view is queried, and the slots in the resulting View Class
213 instances are filled with attribute values from the database. If
214 SUPERS is nil then STANDARD-DB-OBJECT automatically becomes the
215 superclass of the newly-defined View Class."
216   `(progn
217      (defclass ,class ,supers ,slots ,@options
218                (:metaclass standard-db-class))
219      (finalize-inheritance (find-class ',class))))
220
221 (defun keyslots-for-class (class)
222   (slot-value class 'key-slots))
223
224 (defun key-qualifier-for-instance (obj &key (database *default-database*))
225   (let ((tb (view-table (class-of obj))))
226     (flet ((qfk (k)
227              (sql-operation '==
228                             (sql-expression :attribute
229                                             (view-class-slot-column k)
230                                             :table tb)
231                             (db-value-from-slot
232                              k
233                              (slot-value obj (slot-definition-name k))
234                              database))))
235       (let* ((keys (keyslots-for-class (class-of obj)))
236              (keyxprs (mapcar #'qfk (reverse keys))))
237         (cond
238           ((= (length keyxprs) 0) nil)
239           ((= (length keyxprs) 1) (car keyxprs))
240           ((> (length keyxprs) 1) (apply #'sql-operation 'and keyxprs)))))))
241
242 ;;
243 ;; Function used by 'generate-selection-list'
244 ;;
245
246 (defun generate-attribute-reference (vclass slotdef)
247   (cond
248    ((eq (view-class-slot-db-kind slotdef) :base)
249     (sql-expression :attribute (view-class-slot-column slotdef)
250                     :table (view-table vclass)))
251    ((eq (view-class-slot-db-kind slotdef) :key)
252     (sql-expression :attribute (view-class-slot-column slotdef)
253                     :table (view-table vclass)))
254    (t nil)))
255
256 ;;
257 ;; Function used by 'find-all'
258 ;;
259
260 (defun generate-selection-list (vclass)
261   (let ((sels nil))
262     (dolist (slotdef (class-slots vclass))
263       (let ((res (generate-attribute-reference vclass slotdef)))
264         (when res
265           (push (cons slotdef res) sels))))
266     (if sels
267         sels
268         (error "No slots of type :base in view-class ~A" (class-name vclass)))))
269
270 ;;
271 ;; Used by 'create-view-from-class'
272 ;;
273
274
275 (defmethod database-generate-column-definition (class slotdef database)
276   (declare (ignore database class))
277   (when (member (view-class-slot-db-kind slotdef) '(:base :key))
278     (let ((cdef
279            (list (sql-expression :attribute (view-class-slot-column slotdef))
280                  (slot-type slotdef))))
281       (let ((const (view-class-slot-db-constraints slotdef)))
282         (when const 
283           (setq cdef (append cdef (list const)))))
284       cdef)))
285
286 ;;
287 ;; Called by 'get-slot-values-from-view'
288 ;;
289
290 (declaim (inline delistify))
291 (defun delistify (list)
292   (if (listp list)
293       (car list)
294       list))
295
296 (defun slot-type (slotdef)
297   (let ((slot-type (slot-definition-type slotdef)))
298     (if (listp slot-type)
299         (cons (find-symbol (symbol-name (car slot-type)) :usql-sys)
300               (cdr slot-type))
301         (find-symbol (symbol-name slot-type) :usql-sys))))
302
303 (defmethod update-slot-from-db ((instance standard-db-object) slotdef value)
304   (declare (optimize (speed 3) #+cmu (extensions:inhibit-warnings 3)))
305   (let ((slot-reader (view-class-slot-db-reader slotdef))
306         (slot-name   (slot-definition-name slotdef))
307         (slot-type   (slot-type slotdef)))
308     (cond ((and value (null slot-reader))
309            (setf (slot-value instance slot-name)
310                  (read-sql-value value (delistify slot-type)
311                                  (view-database instance))))
312           ((null value)
313            (update-slot-with-null instance slot-name slotdef))
314           ((typep slot-reader 'string)
315            (setf (slot-value instance slot-name)
316                  (format nil slot-reader value)))
317           ((typep slot-reader 'function)
318            (setf (slot-value instance slot-name)
319                  (apply slot-reader (list value))))
320           (t
321            (error "Slot reader is of an unusual type.")))))
322
323 (defmethod key-value-from-db (slotdef value database) 
324   (declare (optimize (speed 3) #+cmu (extensions:inhibit-warnings 3)))
325   (let ((slot-reader (view-class-slot-db-reader slotdef))
326         (slot-type (slot-type slotdef)))
327     (cond ((and value (null slot-reader))
328            (read-sql-value value (delistify slot-type) database))
329           ((null value)
330            nil)
331           ((typep slot-reader 'string)
332            (format nil slot-reader value))
333           ((typep slot-reader 'function)
334            (apply slot-reader (list value)))
335           (t
336            (error "Slot reader is of an unusual type.")))))
337
338 (defun db-value-from-slot (slotdef val database)
339   (let ((dbwriter (view-class-slot-db-writer slotdef))
340         (dbtype (slot-type slotdef)))
341     (typecase dbwriter
342       (string (format nil dbwriter val))
343       (function (apply dbwriter (list val)))
344       (t
345        (typecase dbtype
346          (cons
347           (database-output-sql-as-type (car dbtype) val database))
348          (t
349           (database-output-sql-as-type dbtype val database)))))))
350
351 (defun check-slot-type (slotdef val)
352   (let* ((slot-type (slot-type slotdef))
353          (basetype (if (listp slot-type) (car slot-type) slot-type)))
354     (when (and slot-type val)
355       (unless (typep val basetype)
356         (error 'clsql-type-error
357                :slotname (slot-definition-name slotdef)
358                :typespec slot-type
359                :value val)))))
360
361 ;;
362 ;; Called by find-all
363 ;;
364
365 (defmethod get-slot-values-from-view (obj slotdeflist values)
366     (flet ((update-slot (slot-def values)
367              (update-slot-from-db obj slot-def values)))
368       (mapc #'update-slot slotdeflist values)
369       obj))
370
371
372 (defun synchronize-keys (src srckey dest destkey)
373   (let ((skeys (if (listp srckey) srckey (list srckey)))
374         (dkeys (if (listp destkey) destkey (list destkey))))
375     (mapcar #'(lambda (sk dk)
376                 (setf (slot-value dest dk)
377                       (typecase sk
378                         (symbol
379                          (slot-value src sk))
380                         (t sk))))
381             skeys dkeys)))
382
383 (defun desynchronize-keys (dest destkey)
384   (let ((dkeys (if (listp destkey) destkey (list destkey))))
385     (mapcar #'(lambda (dk)
386                 (setf (slot-value dest dk) nil))
387             dkeys)))
388
389 (defmethod add-to-relation ((target standard-db-object)
390                             slot-name
391                             (value standard-db-object))
392   (let* ((objclass (class-of target))
393          (sdef (or (slotdef-for-slot-with-class slot-name objclass)
394                    (error "~s is not an known slot on ~s" slot-name target)))
395          (dbinfo (view-class-slot-db-info sdef))
396          (join-class (gethash :join-class dbinfo))
397          (homekey (gethash :home-key dbinfo))
398          (foreignkey (gethash :foreign-key dbinfo))
399          (to-many (gethash :set dbinfo)))
400     (unless (equal (type-of value) join-class)
401       (error 'clsql-type-error :slotname slot-name :typespec join-class
402              :value value))
403     (when (gethash :target-slot dbinfo)
404       (error "add-to-relation does not work with many-to-many relations yet."))
405     (if to-many
406         (progn
407           (synchronize-keys target homekey value foreignkey)
408           (if (slot-boundp target slot-name)
409               (unless (member value (slot-value target slot-name))
410                 (setf (slot-value target slot-name)
411                       (append (slot-value target slot-name) (list value))))
412               (setf (slot-value target slot-name) (list value))))
413         (progn
414           (synchronize-keys value foreignkey target homekey)
415           (setf (slot-value target slot-name) value)))))
416
417 (defmethod remove-from-relation ((target standard-db-object)
418                             slot-name (value standard-db-object))
419   (let* ((objclass (class-of target))
420          (sdef (slotdef-for-slot-with-class slot-name objclass))
421          (dbinfo (view-class-slot-db-info sdef))
422          (homekey (gethash :home-key dbinfo))
423          (foreignkey (gethash :foreign-key dbinfo))
424          (to-many (gethash :set dbinfo)))
425     (when (gethash :target-slot dbinfo)
426       (error "remove-relation does not work with many-to-many relations yet."))
427     (if to-many
428         (progn
429           (desynchronize-keys value foreignkey)
430           (if (slot-boundp target slot-name)
431               (setf (slot-value target slot-name)
432                     (remove value
433                             (slot-value target slot-name)
434                             :test #'equal))))
435         (progn
436           (desynchronize-keys target homekey)
437           (setf (slot-value target slot-name)
438                 nil)))))
439
440 (defgeneric update-record-from-slot (object slot &key database)
441   (:documentation
442    "The generic function UPDATE-RECORD-FROM-SLOT updates an individual
443 data item in the column represented by SLOT. The DATABASE is only used
444 if OBJECT is not yet associated with any database, in which case a
445 record is created in DATABASE. Only SLOT is initialized in this case;
446 other columns in the underlying database receive default values. The
447 argument SLOT is the CLOS slot name; the corresponding column names
448 are derived from the View Class definition."))
449    
450 (defmethod update-record-from-slot ((obj standard-db-object) slot &key
451                                         (database *default-database*))
452   (let* ((vct (view-table (class-of obj)))
453          (sd (slotdef-for-slot-with-class slot (class-of obj))))
454     (check-slot-type sd (slot-value obj slot))
455     (let* ((att (view-class-slot-column sd))
456            (val (db-value-from-slot sd (slot-value obj slot) database)))
457       (cond ((and vct sd (view-database obj))
458              (update-records (sql-expression :table vct)
459                              :attributes (list (sql-expression
460                                                 :attribute att))
461                              :values (list val)
462                              :where (key-qualifier-for-instance
463                                      obj :database database)
464                              :database (view-database obj)))
465             ((and vct sd (not (view-database obj)))
466              (install-instance obj :database database))
467             (t
468              (error "Unable to update record.")))))
469   (values))
470
471 (defgeneric update-record-from-slots (object slots &key database)
472   (:documentation 
473    "The generic function UPDATE-RECORD-FROM-SLOTS updates data in the
474 columns represented by SLOTS. The DATABASE is only used if OBJECT is
475 not yet associated with any database, in which case a record is
476 created in DATABASE. Only slots are initialized in this case; other
477 columns in the underlying database receive default values. The
478 argument SLOTS contains the CLOS slot names; the corresponding column
479 names are derived from the view class definition."))
480
481 (defmethod update-record-from-slots ((obj standard-db-object) slots &key
482                                      (database *default-database*))
483   (let* ((vct (view-table (class-of obj)))
484          (sds (slotdefs-for-slots-with-class slots (class-of obj)))
485          (avps (mapcar #'(lambda (s)
486                            (let ((val (slot-value
487                                        obj (slot-definition-name s))))
488                              (check-slot-type s val)
489                              (list (sql-expression
490                                     :attribute (view-class-slot-column s))
491                                    (db-value-from-slot s val database))))
492                        sds)))
493     (cond ((and avps (view-database obj))
494            (update-records (sql-expression :table vct)
495                            :av-pairs avps
496                            :where (key-qualifier-for-instance
497                                    obj :database database)
498                            :database (view-database obj)))
499           ((and avps (not (view-database obj)))
500            (insert-records :into (sql-expression :table vct)
501                            :av-pairs avps
502                            :database database)
503            (setf (slot-value obj 'view-database) database))
504           (t
505            (error "Unable to update records"))))
506   (values))
507
508 (defgeneric update-records-from-instance (object &key database)
509   (:documentation
510    "Using an instance of a view class, update the database table that
511 stores its instance data. If the instance is already associated with a
512 database, that database is used, and database is ignored. If instance
513 is not yet associated with a database, a record is created for
514 instance in the appropriate table of database and the instance becomes
515 associated with that database."))
516
517 (defmethod update-records-from-instance ((obj standard-db-object)
518                                          &key (database *default-database*))
519   (labels ((slot-storedp (slot)
520              (and (member (view-class-slot-db-kind slot) '(:base :key))
521                   (slot-boundp obj (slot-definition-name slot))))
522            (slot-value-list (slot)
523              (let ((value (slot-value obj (slot-definition-name slot))))
524                (check-slot-type slot value)
525                (list (sql-expression :attribute (view-class-slot-column slot))
526                      (db-value-from-slot slot value database)))))
527     (let* ((view-class (class-of obj))
528            (view-class-table (view-table view-class))
529            (slots (remove-if-not #'slot-storedp (class-slots view-class)))
530            (record-values (mapcar #'slot-value-list slots)))
531       (unless record-values
532         (error "No settable slots."))
533       (if (view-database obj)
534           (update-records (sql-expression :table view-class-table)
535                           :av-pairs record-values
536                           :where (key-qualifier-for-instance
537                                   obj :database database)
538                           :database (view-database obj))
539           (progn
540             (insert-records :into (sql-expression :table view-class-table)
541                             :av-pairs record-values
542                             :database database)
543             (setf (slot-value obj 'view-database) database)))
544       (values))))
545
546 (defmethod install-instance ((obj standard-db-object)
547                              &key (database *default-database*))
548   (labels ((slot-storedp (slot)
549              (and (member (view-class-slot-db-kind slot) '(:base :key))
550                   (slot-boundp obj (slot-definition-name slot))))
551            (slot-value-list (slot)
552              (let ((value (slot-value obj (slot-definition-name slot))))
553                (check-slot-type slot value)
554                (list (sql-expression :attribute (view-class-slot-column slot))
555                      (db-value-from-slot slot value database)))))
556     (let* ((view-class (class-of obj))
557            (view-class-table (view-table view-class))
558            (slots (remove-if-not #'slot-storedp (class-slots view-class)))
559            (record-values (mapcar #'slot-value-list slots)))
560       (unless record-values
561         (error "No settable slots."))
562       (unless
563           (let ((obj-db (slot-value obj 'view-database)))
564             (when obj-db 
565               (equal obj-db database))))
566         (insert-records :into (sql-expression :table view-class-table)
567                         :av-pairs record-values
568                         :database database)
569         (setf (slot-value obj 'view-database) database))
570     (values)))
571
572 ;; Perhaps the slot class is not correct in all CLOS implementations,
573 ;; tho I have not run across a problem yet.
574
575 (defmethod handle-cascade-delete-rule ((instance standard-db-object)
576                                        (slot
577                                         view-class-effective-slot-definition))
578   (let ((val (slot-value instance (slot-definition-name slot))))
579     (typecase val
580       (list
581        (if (gethash :target-slot (view-class-slot-db-info slot))
582            ;; For relations with target-slot, we delete just the join instance
583            (mapcar #'(lambda (obj)
584                        (delete-instance-records obj))
585                    (fault-join-slot-raw (class-of instance) instance slot))
586            (dolist (obj val)
587              (delete-instance-records obj))))
588       (standard-db-object
589        (delete-instance-records val)))))
590
591 (defmethod nullify-join-foreign-keys ((instance standard-db-object) slot)
592     (let* ((dbi (view-class-slot-db-info slot))
593            (fkeys (gethash :foreign-keys dbi)))
594       (mapcar #'(lambda (fk)
595                   (if (view-class-slot-nulls-ok slot)
596                       (setf (slot-value instance fk) nil)
597                       (warn "Nullify delete rule cannot set slot not allowing nulls to nil")))
598               (if (listp fkeys) fkeys (list fkeys)))))
599
600 (defmethod handle-nullify-delete-rule ((instance standard-db-object)
601                                        (slot
602                                         view-class-effective-slot-definition))
603     (let ((dbi (view-class-slot-db-info slot)))
604       (if (gethash :set dbi)
605           (if (gethash :target-slot (view-class-slot-db-info slot))
606               ;;For relations with target-slot, we delete just the join instance
607               (mapcar #'(lambda (obj)
608                           (nullify-join-foreign-keys obj slot))
609                       (fault-join-slot-raw (class-of instance) instance slot))
610               (dolist (obj (slot-value instance (slot-definition-name slot)))
611                 (nullify-join-foreign-keys obj slot)))
612           (nullify-join-foreign-keys
613            (slot-value instance (slot-definition-name slot)) slot))))
614
615 (defmethod propogate-deletes ((instance standard-db-object))
616   (let* ((view-class (class-of instance))
617          (joins (remove-if #'(lambda (sd)
618                                (not (equal (view-class-slot-db-kind sd) :join)))
619                            (class-slots view-class))))
620     (dolist (slot joins)
621       (let ((delete-rule (gethash :delete-rule (view-class-slot-db-info slot))))
622         (cond
623           ((eql delete-rule :cascade)
624            (handle-cascade-delete-rule instance slot))
625           ((eql delete-rule :deny)
626            (when (slot-value instance (slot-definition-name slot))
627              (error
628               "Unable to delete slot ~A, because it has a deny delete rule."
629               slot)))
630           ((eql delete-rule :nullify)
631            (handle-nullify-delete-rule instance slot))
632           (t t))))))
633
634 (defgeneric delete-instance-records (instance)
635   (:documentation
636    "Deletes the records represented by INSTANCE from the database
637 associated with it. If instance has no associated database, an error
638 is signalled."))
639
640 (defmethod delete-instance-records ((instance standard-db-object))
641   (let ((vt (sql-expression :table (view-table (class-of instance))))
642         (vd (or (view-database instance) *default-database*)))
643     (when vd
644       (let ((qualifier (key-qualifier-for-instance instance :database vd)))
645         (with-transaction (:database vd)
646           (propogate-deletes instance)
647           (delete-records :from vt :where qualifier :database vd)
648           (setf (slot-value instance 'view-database) nil)))))
649   (values))
650
651 (defgeneric update-instance-from-records (instance &key database)
652   (:documentation
653    "Updates the values in the slots of the View Class instance
654 INSTANCE using the data in the database DATABASE which defaults to the
655 database that INSTANCE is associated with, or the value of
656 *DEFAULT-DATABASE*."))
657
658 (defmethod update-instance-from-records ((instance standard-db-object)
659                                          &key (database *default-database*))
660   (let* ((view-class (find-class (class-name (class-of instance))))
661          (view-table (sql-expression :table (view-table view-class)))
662          (vd (or (view-database instance) database))
663          (view-qual (key-qualifier-for-instance instance :database vd))
664          (sels (generate-selection-list view-class))
665          (res (apply #'select (append (mapcar #'cdr sels)
666                                       (list :from  view-table
667                                             :where view-qual)))))
668     (get-slot-values-from-view instance (mapcar #'car sels) (car res))))
669
670 (defgeneric update-slot-from-record (instance slot &key database)
671   (:documentation
672    "Updates the value in the slot SLOT of the View Class instance
673 INSTANCE using the data in the database DATABASE which defaults to the
674 database that INSTANCE is associated with, or the value of
675 *DEFAULT-DATABASE*."))
676
677 (defmethod update-slot-from-record ((instance standard-db-object)
678                                     slot &key (database *default-database*))
679   (let* ((view-class (find-class (class-name (class-of instance))))
680          (view-table (sql-expression :table (view-table view-class)))
681          (vd (or (view-database instance) database))
682          (view-qual (key-qualifier-for-instance instance :database vd))
683          (slot-def (slotdef-for-slot-with-class slot view-class))
684          (att-ref (generate-attribute-reference view-class slot-def))
685          (res (select att-ref :from  view-table :where view-qual)))
686     (get-slot-values-from-view instance (list slot-def) (car res))))
687
688
689 (defgeneric database-null-value (type)
690   (:documentation "Return an expression of type TYPE which SQL NULL values
691 will be converted into."))
692
693 (defmethod database-null-value ((type t))
694     (cond
695      ((subtypep type 'string) "")
696      ((subtypep type 'integer) 0)
697      ((subtypep type 'float) (float 0.0))
698      ((subtypep type 'list) nil)
699      ((subtypep type 'boolean) nil)
700      ((subtypep type 'symbol) nil)
701      ((subtypep type 'keyword) nil)
702      ((subtypep type 'wall-time) nil)
703      (t
704       (error "Unable to handle null for type ~A" type))))
705
706 (defgeneric update-slot-with-null (instance slotname slotdef)
707   (:documentation "Called to update a slot when its column has a NULL
708 value.  If nulls are allowed for the column, the slot's value will be
709 nil, otherwise its value will be set to the result of calling
710 DATABASE-NULL-VALUE on the type of the slot."))
711
712 (defmethod update-slot-with-null ((instance standard-db-object)
713                                   slotname
714                                   slotdef)
715   (let ((st (slot-type slotdef))
716         (allowed (slot-value slotdef 'nulls-ok)))
717     (if allowed
718         (setf (slot-value instance slotname) nil)
719         (setf (slot-value instance slotname)
720               (database-null-value st)))))
721
722 (defvar +no-slot-value+ '+no-slot-value+)
723
724 (defsql sql-slot-value (:symbol "slot-value") (classname slot &optional (value +no-slot-value+) (database *default-database*))
725   (let* ((class (find-class classname))
726          (sld (slotdef-for-slot-with-class slot class)))
727     (if sld
728         (if (eq value +no-slot-value+)
729             (sql-expression :attribute (view-class-slot-column sld)
730                             :table (view-table class))
731             (db-value-from-slot
732              sld
733              value
734              database))
735         (error "Unknown slot ~A for class ~A" slot classname))))
736
737 (defsql sql-view-class (:symbol "view-class") (classname &optional (database *default-database*))
738         (declare (ignore database))
739         (let* ((class (find-class classname)))
740           (unless (view-table class)
741             (error "No view-table for class ~A"  classname))
742           (sql-expression :table (view-table class))))
743
744 (defmethod database-get-type-specifier (type args database)
745   (declare (ignore type args))
746   (if (member (database-type database) '(:postgresql :postgresql-socket))
747           "VARCHAR"
748           "VARCHAR(255)"))
749
750 (defmethod database-get-type-specifier ((type (eql 'integer)) args database)
751   (declare (ignore database))
752   ;;"INT8")
753   (if args
754       (format nil "INT(~A)" (car args))
755       "INT"))
756               
757 (defmethod database-get-type-specifier ((type (eql 'simple-base-string)) args
758                                         database)
759   (if args
760       (format nil "VARCHAR(~A)" (car args))
761       (if (member (database-type database) '(:postgresql :postgresql-socket))
762           "VARCHAR"
763           "VARCHAR(255)")))
764
765 (defmethod database-get-type-specifier ((type (eql 'simple-string)) args
766                                         database)
767   (if args
768       (format nil "VARCHAR(~A)" (car args))
769       (if (member (database-type database) '(:postgresql :postgresql-socket))
770           "VARCHAR"
771           "VARCHAR(255)")))
772
773 (defmethod database-get-type-specifier ((type (eql 'string)) args database)
774   (if args
775       (format nil "VARCHAR(~A)" (car args))
776       (if (member (database-type database) '(:postgresql :postgresql-socket))
777           "VARCHAR"
778           "VARCHAR(255)")))
779
780 (defmethod database-get-type-specifier ((type (eql 'wall-time)) args database)
781   (declare (ignore args))
782   (case (database-type database)
783     (:postgresql
784      "TIMESTAMP WITHOUT TIME ZONE")
785     (:postgresql-socket
786      "TIMESTAMP WITHOUT TIME ZONE")
787     (:mysql
788      "DATETIME")
789     (t "TIMESTAMP")))
790
791 (defmethod database-get-type-specifier ((type (eql 'duration)) args database)
792   (declare (ignore database args))
793   "INT8")
794
795 (deftype raw-string (&optional len)
796   "A string which is not trimmed when retrieved from the database"
797   `(string ,len))
798
799 (defmethod database-get-type-specifier ((type (eql 'raw-string)) args database)
800   (declare (ignore database))
801   (if args
802       (format nil "VARCHAR(~A)" (car args))
803       "VARCHAR"))
804
805 (defmethod database-get-type-specifier ((type (eql 'float)) args database)
806   (declare (ignore database))
807   (if args
808       (format nil "FLOAT(~A)" (car args))
809       "FLOAT"))
810
811 (defmethod database-get-type-specifier ((type (eql 'long-float)) args database)
812   (declare (ignore database))
813   (if args
814       (format nil "FLOAT(~A)" (car args))
815       "FLOAT"))
816
817 (defmethod database-get-type-specifier ((type (eql 'boolean)) args database)
818   (declare (ignore args database))
819   "BOOL")
820
821 (defmethod database-output-sql-as-type (type val database)
822   (declare (ignore type database))
823   val)
824
825 (defmethod database-output-sql-as-type ((type (eql 'list)) val database)
826   (declare (ignore database))
827   (progv '(*print-circle* *print-array*) '(t t)
828     (prin1-to-string val)))
829
830 (defmethod database-output-sql-as-type ((type (eql 'symbol)) val database)
831   (declare (ignore database))
832   (if (keywordp val)
833       (symbol-name val)
834       (if val
835           (concatenate 'string
836                        (package-name (symbol-package val))
837                        "::"
838                        (symbol-name val))
839           "")))
840
841 (defmethod database-output-sql-as-type ((type (eql 'keyword)) val database)
842   (declare (ignore database))
843   (if val
844       (symbol-name val)
845       ""))
846
847 (defmethod database-output-sql-as-type ((type (eql 'vector)) val database)
848   (declare (ignore database))
849   (progv '(*print-circle* *print-array*) '(t t)
850     (prin1-to-string val)))
851
852 (defmethod database-output-sql-as-type ((type (eql 'array)) val database)
853   (declare (ignore database))
854   (progv '(*print-circle* *print-array*) '(t t)
855     (prin1-to-string val)))
856
857 (defmethod database-output-sql-as-type ((type (eql 'boolean)) val database)
858   (declare (ignore database))
859   (if val "t" "f"))
860
861 (defmethod database-output-sql-as-type ((type (eql 'string)) val database)
862   (declare (ignore database))
863   val)
864
865 (defmethod database-output-sql-as-type ((type (eql 'simple-string))
866                                         val database)
867   (declare (ignore database))
868   val)
869
870 (defmethod database-output-sql-as-type ((type (eql 'simple-base-string))
871                                         val database)
872   (declare (ignore database))
873   val)
874
875 (defmethod read-sql-value (val type database)
876   (declare (ignore type database))
877   (read-from-string val))
878
879 (defmethod read-sql-value (val (type (eql 'string)) database)
880   (declare (ignore database))
881   val)
882
883 (defmethod read-sql-value (val (type (eql 'simple-string)) database)
884   (declare (ignore database))
885   val)
886
887 (defmethod read-sql-value (val (type (eql 'simple-base-string)) database)
888   (declare (ignore database))
889   val)
890
891 (defmethod read-sql-value (val (type (eql 'raw-string)) database)
892   (declare (ignore database))
893   val)
894
895 (defmethod read-sql-value (val (type (eql 'keyword)) database)
896   (declare (ignore database))
897   (when (< 0 (length val))
898     (intern (string-upcase val) "KEYWORD")))
899
900 (defmethod read-sql-value (val (type (eql 'symbol)) database)
901   (declare (ignore database))
902   (when (< 0 (length val))
903     (if (find #\: val)
904         (read-from-string val)
905         (intern (string-upcase val) "KEYWORD"))))
906
907 (defmethod read-sql-value (val (type (eql 'integer)) database)
908   (declare (ignore database))
909   (etypecase val
910     (string
911      (read-from-string val))
912     (number val)))
913
914 (defmethod read-sql-value (val (type (eql 'float)) database)
915   (declare (ignore database))
916   ;; writing 1.0 writes 1, so we we *really* want a float, must do (float ...)
917   (float (read-from-string val))) 
918
919 (defmethod read-sql-value (val (type (eql 'boolean)) database)
920   (declare (ignore database))
921   (equal "t" val))
922
923 (defmethod read-sql-value (val (type (eql 'wall-time)) database)
924   (declare (ignore database))
925   (unless (eq 'NULL val)
926     (parse-timestring val)))
927
928
929 ;; ------------------------------------------------------------
930 ;; Logic for 'faulting in' :join slots
931
932 (defun fault-join-slot-raw (class instance slot-def)
933   (let* ((dbi (view-class-slot-db-info slot-def))
934          (jc (gethash :join-class dbi)))
935     (let ((jq (join-qualifier class instance slot-def)))
936       (when jq 
937         (select jc :where jq)))))
938
939 (defun fault-join-slot (class instance slot-def)
940   (let* ((dbi (view-class-slot-db-info slot-def))
941          (ts (gethash :target-slot dbi))
942          (res (fault-join-slot-raw class instance slot-def)))
943     (when res
944       (cond
945         ((and ts (gethash :set dbi))
946          (mapcar (lambda (obj)
947                    (cons obj (slot-value obj ts))) res))
948         ((and ts (not (gethash :set dbi)))
949          (mapcar (lambda (obj) (slot-value obj ts)) res))
950         ((and (not ts) (not (gethash :set dbi)))
951          (car res))
952         ((and (not ts) (gethash :set dbi))
953          res)))))
954
955 (defun join-qualifier (class instance slot-def)
956     (declare (ignore class))
957     (let* ((dbi (view-class-slot-db-info slot-def))
958            (jc (find-class (gethash :join-class dbi)))
959            ;;(ts (gethash :target-slot dbi))
960            ;;(tsdef (if ts (slotdef-for-slot-with-class ts jc)))
961            (foreign-keys (gethash :foreign-key dbi))
962            (home-keys (gethash :home-key dbi)))
963       (when (every #'(lambda (slt)
964                        (and (slot-boundp instance slt)
965                             (not (null (slot-value instance slt)))))
966                    (if (listp home-keys) home-keys (list home-keys)))
967         (let ((jc
968                (mapcar #'(lambda (hk fk)
969                            (let ((fksd (slotdef-for-slot-with-class fk jc)))
970                              (sql-operation '==
971                                             (typecase fk
972                                               (symbol
973                                                (sql-expression
974                                                 :attribute
975                                                 (view-class-slot-column fksd)
976                                                 :table (view-table jc)))
977                                               (t fk))
978                                             (typecase hk
979                                               (symbol
980                                                (slot-value instance hk))
981                                               (t
982                                                hk)))))
983                        (if (listp home-keys)
984                            home-keys
985                            (list home-keys))
986                        (if (listp foreign-keys)
987                            foreign-keys
988                            (list foreign-keys)))))
989           (when jc
990             (if (> (length jc) 1)
991                 (apply #'sql-and jc)
992                 jc))))))
993
994
995 (defun find-all (view-classes &rest args &key all set-operation distinct from
996                  where group-by having order-by order-by-descending offset limit
997                  (database *default-database*))
998   "tweeze me apart someone pleeze"
999   (declare (ignore all set-operation from group-by having offset limit)
1000            (optimize (debug 3) (speed 1)))
1001   (let* ((*db-deserializing* t)
1002          (*default-database* (or database (error 'clsql-nodb-error))))
1003     (flet ((table-sql-expr (table)
1004              (sql-expression :table (view-table table)))
1005            (ref-equal (ref1 ref2)
1006              (equal (sql ref1)
1007                     (sql ref2)))
1008            (tables-equal (table-a table-b)
1009              (string= (string (slot-value table-a 'name))
1010                       (string (slot-value table-b 'name)))))
1011
1012       (let* ((sclasses (mapcar #'find-class view-classes))
1013              (sels (mapcar #'generate-selection-list sclasses))
1014              (fullsels (apply #'append sels))
1015              (sel-tables (collect-table-refs where))
1016              (tables
1017               (remove-duplicates
1018                (append (mapcar #'table-sql-expr sclasses) sel-tables)
1019                :test #'tables-equal))
1020              (res nil))
1021         (dolist (ob (listify order-by))
1022           (when (and ob (not (member ob (mapcar #'cdr fullsels)
1023                                      :test #'ref-equal)))
1024             (setq fullsels
1025                   (append fullsels (mapcar #'(lambda (att) (cons nil att))
1026                                            (listify ob))))))
1027         (dolist (ob (listify order-by-descending))
1028           (when (and ob (not (member ob (mapcar #'cdr fullsels)
1029                                      :test #'ref-equal)))
1030             (setq fullsels
1031                   (append fullsels (mapcar #'(lambda (att) (cons nil att))
1032                                            (listify ob))))))
1033         (dolist (ob (listify distinct))
1034           (when (and (typep ob 'sql-ident)
1035                      (not (member ob (mapcar #'cdr fullsels)
1036                                   :test #'ref-equal)))
1037             (setq fullsels
1038                   (append fullsels (mapcar #'(lambda (att) (cons nil att))
1039                                            (listify ob))))))
1040         ;;(format t "~%fullsels is : ~A" fullsels)
1041         (setq res (apply #'select (append (mapcar #'cdr fullsels)
1042                                           (cons :from (list tables)) args)))
1043         (flet ((build-instance (vals)
1044                  (flet ((%build-instance (vclass selects)
1045                           (let ((class-name (class-name vclass))
1046                                 (db-vals (butlast vals
1047                                                   (- (list-length vals)
1048                                                      (list-length selects))))
1049                                 cache-key)
1050                             (setf vals (nthcdr (list-length selects) vals))
1051                             (loop for select in selects
1052                                   for value in db-vals
1053                                   do
1054                                   (when (eql (slot-value (car select) 'db-kind)
1055                                              :key)
1056                                     (push
1057                                      (key-value-from-db (car select) value
1058                                                         *default-database*)
1059                                      cache-key)))
1060                             (push class-name cache-key)
1061                             (%make-fresh-object class-name
1062                                                 (mapcar #'car selects)
1063                                                 db-vals))))
1064                    (let ((instances (mapcar #'%build-instance sclasses sels)))
1065                      (if (= (length sclasses) 1)
1066                          (car instances)
1067                          instances)))))
1068           (remove-if #'null (mapcar #'build-instance res)))))))
1069
1070 (defun %make-fresh-object (class-name slots values)
1071   (let* ((*db-initializing* t)
1072          (obj (make-instance class-name
1073                              :view-database *default-database*)))
1074     (setf obj (get-slot-values-from-view obj slots values))
1075     (postinitialize obj)
1076     obj))
1077
1078 (defmethod postinitialize ((self t))
1079   )
1080
1081 (defun select (&rest select-all-args)
1082   "Selects data from database given the constraints specified. Returns
1083 a list of lists of record values as specified by select-all-args. By
1084 default, the records are each represented as lists of attribute
1085 values. The selections argument may be either db-identifiers, literal
1086 strings or view classes.  If the argument consists solely of view
1087 classes, the return value will be instances of objects rather than raw
1088 tuples."
1089   (flet ((select-objects (target-args)
1090            (and target-args
1091                 (every #'(lambda (arg)
1092                            (and (symbolp arg)
1093                                 (find-class arg nil)))
1094                        target-args))))
1095     (multiple-value-bind (target-args qualifier-args)
1096         (query-get-selections select-all-args)
1097       (if (select-objects target-args)
1098           (apply #'find-all target-args qualifier-args)
1099           (let ((expr (apply #'make-query select-all-args)))
1100             (destructuring-bind (&key (flatp nil)
1101                                       (database *default-database*)
1102                                       &allow-other-keys)
1103                 qualifier-args
1104               (let ((res (query expr :database database)))
1105                 (if (and flatp
1106                          (= (length (slot-value expr 'selections)) 1))
1107                     (mapcar #'car res)
1108                   res))))))))