14 Sep 2007 Kevin Rosenberg <kevin@rosenberg.net>
[clsql.git] / sql / metaclasses.lisp
1 ;;;; -*- Mode: LISP; Syntax: ANSI-Common-Lisp; Base: 10 -*-
2 ;;;; *************************************************************************
3 ;;;;
4 ;;;; $Id$
5 ;;;;
6 ;;;; CLSQL metaclass for standard-db-objects created in the OODDL.
7 ;;;;
8 ;;;; This file is part of CLSQL.
9 ;;;;
10 ;;;; CLSQL users are granted the rights to distribute and use this software
11 ;;;; as governed by the terms of the Lisp Lesser GNU Public License
12 ;;;; (http://opensource.franz.com/preamble.html), also known as the LLGPL.
13 ;;;; *************************************************************************
14
15 (in-package #:clsql-sys)
16
17 (eval-when (:compile-toplevel :load-toplevel :execute)
18   (when (>= (length (generic-function-lambda-list
19                      (ensure-generic-function
20                       'compute-effective-slot-definition)))
21             3)
22     (pushnew :kmr-normal-cesd cl:*features*))
23
24   (when (>= (length (generic-function-lambda-list
25                      (ensure-generic-function
26                       'direct-slot-definition-class)))
27             3)
28     (pushnew :kmr-normal-dsdc cl:*features*))
29
30   (when (>= (length (generic-function-lambda-list
31                      (ensure-generic-function
32                       'effective-slot-definition-class)))
33             3)
34     (pushnew :kmr-normal-esdc cl:*features*)))
35
36
37 ;; ------------------------------------------------------------
38 ;; metaclass: view-class
39
40 (defclass standard-db-class (standard-class)
41   ((view-table
42     :accessor view-table
43     :initarg :view-table)
44    (definition
45     :accessor object-definition
46     :initarg :definition
47     :initform nil)
48    (key-slots
49     :accessor key-slots
50     :initform nil)
51    (class-qualifier
52     :accessor view-class-qualifier
53     :initarg :qualifier
54     :initform nil))
55   (:documentation "Metaclass for all CLSQL View Classes."))
56
57 ;;; Lispworks 4.2 and before requires special processing of extra slot and class options
58
59 (defvar +extra-slot-options+ '(:column :db-kind :db-type :db-reader :void-value :db-constraints
60                                :db-writer :db-info))
61 (defvar +extra-class-options+ '(:base-table))
62
63 #+lispworks
64 (dolist (slot-option +extra-slot-options+)
65   (eval `(process-slot-option standard-db-class ,slot-option)))
66
67 #+lispworks
68 (dolist (class-option +extra-class-options+)
69   (eval `(process-class-option standard-db-class ,class-option)))
70
71 (defmethod validate-superclass ((class standard-db-class)
72                                 (superclass standard-class))
73   t)
74
75 (defun table-name-from-arg (arg)
76   (cond ((symbolp arg)
77          (intern (sql-escape arg)))
78         ((typep arg 'sql-ident)
79          (if (symbolp (slot-value arg 'name))
80              (intern (sql-escape (slot-value arg 'name)))
81              (sql-escape (slot-value arg 'name))))
82         ((stringp arg)
83          (sql-escape arg))))
84
85 (defun column-name-from-arg (arg)
86   (cond ((symbolp arg)
87          arg)
88         ((typep arg 'sql-ident)
89          (slot-value arg 'name))
90         ((stringp arg)
91          (intern (symbol-name-default-case arg)))))
92
93
94 (defun remove-keyword-arg (arglist akey)
95   (let ((mylist arglist)
96         (newlist ()))
97     (labels ((pop-arg (alist)
98              (let ((arg (pop alist))
99                    (val (pop alist)))
100                (unless (equal arg akey)
101                  (setf newlist (append (list arg val) newlist)))
102                (when alist (pop-arg alist)))))
103       (pop-arg mylist))
104     newlist))
105
106 (defmethod initialize-instance :around ((class standard-db-class)
107                                         &rest all-keys
108                                         &key direct-superclasses base-table
109                                         qualifier
110                                         &allow-other-keys)
111   (let ((root-class (find-class 'standard-db-object nil))
112         (vmc 'standard-db-class))
113     (setf (view-class-qualifier class)
114           (car qualifier))
115     (if root-class
116         (if (some #'(lambda (super) (typep super vmc))
117                   direct-superclasses)
118             (call-next-method)
119             (apply #'call-next-method
120                    class
121                    :direct-superclasses (append (list root-class)
122                                                 direct-superclasses)
123                    (remove-keyword-arg all-keys :direct-superclasses)))
124         (call-next-method))
125     (setf (view-table class)
126           (table-name-from-arg (or (and base-table
127                                         (if (listp base-table)
128                                             (car base-table)
129                                             base-table))
130                                    (class-name class))))
131     (register-metaclass class (nth (1+ (position :direct-slots all-keys))
132                                    all-keys))))
133
134 (defmethod reinitialize-instance :around ((class standard-db-class)
135                                           &rest all-keys
136                                           &key base-table
137                                           direct-superclasses qualifier
138                                           &allow-other-keys)
139   (let ((root-class (find-class 'standard-db-object nil))
140         (vmc 'standard-db-class))
141     (setf (view-table class)
142           (table-name-from-arg (sql-escape (or (and base-table
143                                                     (if (listp base-table)
144                                                         (car base-table)
145                                                         base-table))
146                                                (class-name class)))))
147     (setf (view-class-qualifier class)
148           (car qualifier))
149     (if (and root-class (not (equal class root-class)))
150         (if (some #'(lambda (super) (typep super vmc))
151                   direct-superclasses)
152             (call-next-method)
153             (apply #'call-next-method
154                    class
155                    :direct-superclasses (append (list root-class)
156                                                 direct-superclasses)
157                    (remove-keyword-arg all-keys :direct-superclasses)))
158         (call-next-method)))
159   (register-metaclass class (nth (1+ (position :direct-slots all-keys))
160                                  all-keys)))
161
162
163 (defun get-keywords (keys list)
164   (flet ((extract (key)
165            (let ((pos (position key list)))
166              (when pos
167                (nth (1+ pos) list)))))
168     (mapcar #'extract keys)))
169
170 (defun describe-db-layout (class)
171   (flet ((not-db-col (col)
172            (not (member (nth 2 col) '(nil :base :key))))
173          (frob-slot (slot)
174            (let ((type (slot-definition-type slot)))
175              (if (eq type t)
176                  (setq type nil))
177              (list (slot-value slot 'name)
178                    type
179                    (slot-value slot 'db-kind)
180                    (and (slot-boundp slot 'column)
181                         (slot-value slot 'column))))))
182     (let ((all-slots (mapcar #'frob-slot (ordered-class-slots class))))
183       (setq all-slots (remove-if #'not-db-col all-slots))
184       (setq all-slots (stable-sort all-slots #'string< :key #'car))
185       ;;(mapcar #'dink-type all-slots)
186       all-slots)))
187
188 (defun register-metaclass (class slots)
189   (labels ((not-db-col (col)
190              (not (member (nth 2 col)  '(nil :base :key))))
191            (frob-slot (slot)
192              (get-keywords '(:name :type :db-kind :column) slot)))
193     (let ((all-slots (mapcar #'frob-slot slots)))
194       (setq all-slots (remove-if #'not-db-col all-slots))
195       (setq all-slots (stable-sort all-slots #'string< :key #'car))
196       (setf (object-definition class) all-slots))
197     #-(or sbcl allegro)
198     (setf (key-slots class) (remove-if-not (lambda (slot)
199                                              (eql (slot-value slot 'db-kind)
200                                                   :key))
201                                            (ordered-class-slots class)))))
202
203 #+(or sbcl allegro)
204 (defmethod finalize-inheritance :after ((class standard-db-class))
205   (setf (key-slots class) (remove-if-not (lambda (slot)
206                                            (eql (slot-value slot 'db-kind)
207                                                 :key))
208                                          (ordered-class-slots class))))
209
210 ;; return the deepest view-class ancestor for a given view class
211
212 (defun base-db-class (classname)
213   (let* ((class (find-class classname))
214          (db-class (find-class 'standard-db-object)))
215     (loop
216      (let ((cds (class-direct-superclasses class)))
217        (cond ((null cds)
218               (error "not a db class"))
219              ((member db-class cds)
220               (return (class-name class))))
221        (setq class (car cds))))))
222
223 (defun db-ancestors (classname)
224   (let ((class (find-class classname))
225         (db-class (find-class 'standard-db-object)))
226     (labels ((ancestors (class)
227              (let ((scs (class-direct-superclasses class)))
228                (if (member db-class scs)
229                    (list class)
230                    (append (list class) (mapcar #'ancestors scs))))))
231       (ancestors class))))
232
233 (defclass view-class-slot-definition-mixin ()
234   ((column
235     :accessor view-class-slot-column
236     :initarg :column
237     :documentation
238     "The name of the SQL column this slot is stored in.  Defaults to
239 the slot name.")
240    (db-kind
241     :accessor view-class-slot-db-kind
242     :initarg :db-kind
243     :initform :base
244     ;; openmcl 0.14.2 stores the value as list in the DSD
245     ;; :type (or list keyword)
246     #-openmcl :type #-openmcl keyword
247     :documentation
248     "The kind of DB mapping which is performed for this slot.  :base
249 indicates the slot maps to an ordinary column of the DB view.  :key
250 indicates that this slot corresponds to part of the unique keys for
251 this view, :join indicates ... and :virtual indicates that this slot
252 is an ordinary CLOS slot.  Defaults to :base.")
253    (db-reader
254     :accessor view-class-slot-db-reader
255     :initarg :db-reader
256     :initform nil
257     :documentation
258     "If a string, then when reading values from the DB, the string
259 will be used for a format string, with the only value being the value
260 from the database.  The resulting string will be used as the slot
261 value.  If a function then it will take one argument, the value from
262 the database, and return the value that should be put into the slot.")
263    (db-writer
264     :accessor view-class-slot-db-writer
265     :initarg :db-writer
266     :initform nil
267     :documentation
268     "If a string, then when reading values from the slot for the DB,
269 the string will be used for a format string, with the only value being
270 the value of the slot.  The resulting string will be used as the
271 column value in the DB.  If a function then it will take one argument,
272 the value of the slot, and return the value that should be put into
273 the database.")
274    (db-type
275     :accessor view-class-slot-db-type
276     :initarg :db-type
277     :initform nil
278     :documentation
279     "A string which will be used as the type specifier for this slots
280 column definition in the database.")
281    (db-constraints
282     :accessor view-class-slot-db-constraints
283     :initarg :db-constraints
284     :initform nil
285     :documentation
286     "A keyword symbol representing a single SQL column constraint or list of such symbols.")
287    (void-value
288     :accessor view-class-slot-void-value
289     :initarg :void-value
290     :initform nil
291     :documentation
292     "Value to store if the SQL value is NULL. Default is NIL.")
293    (db-info
294     :accessor view-class-slot-db-info
295     :initarg :db-info
296     :documentation "Description of the join.")
297    (specified-type
298     :accessor specified-type
299     :initarg specified-type
300     :initform nil
301     :documentation "Internal slot storing the :type specified by user.")))
302
303 (defparameter *db-info-lambda-list*
304   '(&key join-class
305          home-key
306          foreign-key
307          (key-join nil)
308          (target-slot nil)
309          (retrieval :immmediate)
310          (set nil)))
311
312 (defun parse-db-info (db-info-list)
313   (destructuring-bind
314         (&key join-class home-key key-join foreign-key (delete-rule nil)
315               (target-slot nil) (retrieval :deferred) (set t))
316       db-info-list
317     (let ((ih (make-hash-table :size 6)))
318       (if join-class
319           (setf (gethash :join-class ih) join-class)
320           (error "Must specify :join-class in :db-info"))
321       (if home-key
322           (setf (gethash :home-key ih) home-key)
323           (error "Must specify :home-key in :db-info"))
324       (when delete-rule
325         (setf (gethash :delete-rule ih) delete-rule))
326       (if foreign-key
327           (setf (gethash :foreign-key ih) foreign-key)
328           (error "Must specify :foreign-key in :db-info"))
329       (when key-join
330         (setf (gethash :key-join ih) t))
331       (when target-slot
332         (setf (gethash :target-slot ih) target-slot))
333       (when set
334         (setf (gethash :set ih) set))
335       (when retrieval
336         (progn
337           (setf (gethash :retrieval ih) retrieval)
338           (if (eql retrieval :immediate)
339               (setf (gethash :set ih) nil))))
340       ih)))
341
342 (defclass view-class-direct-slot-definition (view-class-slot-definition-mixin
343                                              standard-direct-slot-definition)
344   ())
345
346 (defclass view-class-effective-slot-definition (view-class-slot-definition-mixin
347                                                 standard-effective-slot-definition)
348   ())
349
350 (defmethod direct-slot-definition-class ((class standard-db-class)
351                                          #+kmr-normal-dsdc &rest
352                                          initargs)
353   (declare (ignore initargs))
354   (find-class 'view-class-direct-slot-definition))
355
356 (defmethod effective-slot-definition-class ((class standard-db-class)
357                                             #+kmr-normal-esdc &rest
358                                             initargs)
359   (declare (ignore initargs))
360   (find-class 'view-class-effective-slot-definition))
361
362 #+openmcl
363 (when (not (symbol-function 'compute-class-precedence-list))
364   (eval
365    (defun compute-class-precedence-list (class)
366      (class-precedence-list class))))
367
368 #-mop-slot-order-reversed
369 (defmethod compute-slots ((class standard-db-class))
370   "Need to sort order of class slots so they are the same across
371 implementations."
372   (let ((slots (call-next-method))
373         desired-sequence
374         output-slots)
375     (dolist (c (compute-class-precedence-list class))
376       (dolist (s (class-direct-slots c))
377         (let ((name (slot-definition-name s)))
378           (unless (find name desired-sequence)
379             (push name desired-sequence)))))
380     (dolist (desired desired-sequence)
381       (let ((slot (find desired slots :key #'slot-definition-name)))
382         (assert slot)
383         (push slot output-slots)))
384     output-slots))
385
386 (defun compute-lisp-type-from-specified-type (specified-type db-constraints)
387   "Computes the Lisp type for a user-specified type."
388   (let ((type
389          (cond
390            ((consp specified-type)
391             (let* ((first (first specified-type))
392                    (name (etypecase first
393                            (symbol (symbol-name first))
394                            (string first))))
395               (cond
396                ((or (string-equal name "string")
397                     (string-equal name "varchar")
398                     (string-equal name "char"))
399                 'string)
400                (t
401                 specified-type))))
402            ((eq (ensure-keyword specified-type) :bigint)
403             'integer)
404            ((eq (ensure-keyword specified-type) :char)
405             'character)
406            ((eq (ensure-keyword specified-type) :varchar)
407             'string)
408            (t
409             specified-type))))
410     (if (and type (not (member :not-null (listify db-constraints))))
411         `(or null ,type)
412       type)))
413
414 ;; Compute the slot definition for slots in a view-class.  Figures out
415 ;; what kind of database value (if any) is stored there, generates and
416 ;; verifies the column name.
417
418 (declaim (inline delistify))
419 (defun delistify (list)
420   "Some MOPs, like openmcl 0.14.2, cons attribute values in a list."
421   (if (listp list)
422       (car list)
423       list))
424
425 (declaim (inline delistify-dsd))
426 (defun delistify-dsd (list)
427   "Some MOPs, like openmcl 0.14.2, cons attribute values in a list."
428   (if (and (listp list) (null (cdr list)))
429       (car list)
430       list))
431
432 (defmethod initialize-instance :around ((obj view-class-direct-slot-definition)
433                                         &rest initargs)
434   (do* ((parsed (list obj))
435         (name (first initargs) (first initargs))
436         (val (second initargs) (second initargs))
437         (type nil)
438         (db-constraints nil))
439       ((null initargs)
440        (setq parsed
441              (append parsed
442                      (list 'specified-type type
443                            :type (compute-lisp-type-from-specified-type
444                                   type db-constraints))))
445        (apply #'call-next-method parsed))
446     (case name
447       (:db-constraints
448        (setq db-constraints val)
449        (setq parsed (append parsed (list name val))))
450       (:type
451        (setq type val))
452       (t
453        (setq parsed (append parsed (list name val)))))
454     (setq initargs (cddr initargs))))
455
456 (defmethod compute-effective-slot-definition ((class standard-db-class)
457                                               #+kmr-normal-cesd slot-name
458                                               direct-slots)
459   #+kmr-normal-cesd (declare (ignore slot-name))
460
461   ;; KMR: store the user-specified type and then compute
462   ;; real Lisp type and store it
463   (let ((dsd (car direct-slots)))
464     (let ((esd (call-next-method)))
465       (typecase dsd
466         (view-class-slot-definition-mixin
467          ;; Use the specified :column argument if it is supplied, otherwise
468          ;; the column slot is filled in with the slot-name,  but transformed
469          ;; to be sql safe, - to _ and such.
470          (setf (slot-value esd 'column)
471            (column-name-from-arg
472             (if (slot-boundp dsd 'column)
473                 (delistify-dsd (view-class-slot-column dsd))
474               (column-name-from-arg
475                (sql-escape (slot-definition-name dsd))))))
476
477          (setf (slot-value esd 'db-type)
478            (when (slot-boundp dsd 'db-type)
479              (delistify-dsd
480               (view-class-slot-db-type dsd))))
481
482          (setf (slot-value esd 'void-value)
483                (delistify-dsd
484                 (view-class-slot-void-value dsd)))
485
486          ;; :db-kind slot value defaults to :base (store slot value in
487          ;; database)
488
489          (setf (slot-value esd 'db-kind)
490            (if (slot-boundp dsd 'db-kind)
491                (delistify-dsd (view-class-slot-db-kind dsd))
492              :base))
493
494          (setf (slot-value esd 'db-reader)
495            (when (slot-boundp dsd 'db-reader)
496              (delistify-dsd (view-class-slot-db-reader dsd))))
497          (setf (slot-value esd 'db-writer)
498            (when (slot-boundp dsd 'db-writer)
499              (delistify-dsd (view-class-slot-db-writer dsd))))
500          (setf (slot-value esd 'db-constraints)
501            (when (slot-boundp dsd 'db-constraints)
502              (delistify-dsd (view-class-slot-db-constraints dsd))))
503
504          ;; I wonder if this slot option and the previous could be merged,
505          ;; so that :base and :key remain keyword options, but :db-kind
506          ;; :join becomes :db-kind (:join <db info .... >)?
507
508          (setf (slot-value esd 'db-info)
509                (when (slot-boundp dsd 'db-info)
510                  (let ((dsd-info (view-class-slot-db-info dsd)))
511                    (cond
512                      ((atom dsd-info)
513                       dsd-info)
514                      ((and (listp dsd-info) (> (length dsd-info) 1)
515                            (atom (car dsd-info)))
516                       (parse-db-info dsd-info))
517                      ((and (listp dsd-info) (= 1 (length dsd-info))
518                            (listp (car dsd-info)))
519                       (parse-db-info (car dsd-info)))))))
520
521          (setf (specified-type esd)
522                (delistify-dsd (specified-type dsd)))
523
524          )
525         ;; all other slots
526         (t
527          (unless (typep esd 'view-class-effective-slot-definition)
528            (warn "Non view-class-direct-slot object with non-view-class-effective-slot-definition in compute-effective-slot-definition")
529
530            (let ((type-predicate #+openmcl (slot-value esd 'ccl::type-predicate)))
531              #-openmcl (declare (ignore type-predicate))
532              #-(or clisp sbcl)  (change-class esd 'view-class-effective-slot-definition
533                                               #+allegro :name
534                                               #+allegro (slot-definition-name dsd))
535              #+openmcl (setf (slot-value esd 'ccl::type-predicate)
536                              type-predicate)))
537
538          (setf (slot-value esd 'column)
539            (column-name-from-arg
540             (sql-escape (slot-definition-name dsd))))
541
542          (setf (slot-value esd 'db-info) nil)
543          (setf (slot-value esd 'db-kind) :virtual)
544          (setf (specified-type esd) (slot-definition-type dsd)))
545         )
546       esd)))
547
548 (defun slotdefs-for-slots-with-class (slots class)
549   (let ((result nil))
550     (dolist (s slots)
551       (let ((c (slotdef-for-slot-with-class s class)))
552         (if c (setf result (cons c result)))))
553     result))
554
555 (defun slotdef-for-slot-with-class (slot class)
556   (find-if #'(lambda (d) (eql slot (slot-definition-name d)))
557            (class-slots class)))
558
559 #+ignore
560 (eval-when (:compile-toplevel :load-toplevel :execute)
561   #+kmr-normal-cesd
562   (setq cl:*features* (delete :kmr-normal-cesd cl:*features*))
563   #+kmr-normal-dsdc
564   (setq cl:*features* (delete :kmr-normal-dsdc cl:*features*))
565   #+kmr-normal-esdc
566   (setq cl:*features* (delete :kmr-normal-esdc cl:*features*))
567   )