Mewa changes, mostly refactoring and removing backwards compat cruft.
[clinton/lisp-on-lines.git] / src / mewa.lisp
dissimilarity index 94%
index a0300f6..7a27b77 100644 (file)
-
-
-(in-package :mewa)
-(defparameter *default-type* :ucw)
-
-;;; maps meta-model slot-types to slot-presentation
-(defparameter *slot-type-map* '(number ucw:currency))
-
-;;; an alist of model-class-name . attributes
-;;; should really be a hash-table.
-(defvar *attribute-map* (list)) 
-
-;;; some utilities for merging plists
-
-(defun plist-nunion (new-props plist)
-  (loop for cons on new-props
-       for i from 1
-       when (oddp i)
-       do (setf (getf plist (first cons)) (second cons))
-       finally (return plist)))
-
-(defun plist-union (new-props plist)
-  "Non-destructive version of plist-nunion"
-                  (plist-nunion new-props (copy-list plist)))
-
-(defun gen-ptype (type)
-  (or (getf *slot-type-map* type) type))
-
-(defun gen-presentation-slots (instance)
-  (mapcar #'(lambda (x) (gen-pslot (cadr x) 
-                                  (string (car x)) 
-                                  (car x))) 
-         (list-slot-types instance)))
-
-
-(defun gen-pslot (type label slot-name)
-  (copy-list `(,(gen-ptype type) 
-              :label ,label
-              :slot-name ,slot-name))) 
-
-(defun gen-presentation-args (instance args)
-  (declare (ignore instance))
-  (if args args nil))
-
-
-(defun find-or-create-attributes (class-name)
-  "return an exisiting class attribute map or create one. 
-
-A map is a cons of class-name . attributes. 
-attributes is an alist keyed on the attribute nreeame."
-  (or (assoc class-name *attribute-map*) 
-      (progn 
-       (setf *attribute-map* (acons class-name (list (list)) *attribute-map*)) 
-       (assoc class-name *attribute-map*))))
-
-(defgeneric find-class-attributes (class))
-
-(defmethod find-class-attributes ((model t))
-  (find-or-create-attributes (class-name (class-of model))))
-
-(defmethod find-class-attributes ((model symbol))
-  (find-or-create-attributes model))
-
-(defmethod add-attribute ((model t) name def)
-  (let ((map (find-class-attributes model)))
-    (setf (cdr map) (acons name def (cdr map)))))
-
-(defmethod find-attribute ((model t) name)
-  (assoc name (cdr (find-class-attributes model))))
-
-(defmethod (setf find-attribute) ((def list) (model t) name)
-  (let ((attr (find-attribute model name)))
-    (if attr
-       (prog2 
-           (setf (cdr attr) def) 
-           attr)
-        (prog2 
-           (add-attribute model name def) 
-           (find-attribute model name)))))
-
-(defmethod set-attribute ((model t) name definition &key (inherit t))
-  (setf (find-attribute model name) 
-       (if inherit
-           (cons (car definition) 
-                 (plist-union (cdr definition)
-                        (cddr (find-attribute model name))))
-           definition)))
-
-
-(defgeneric attributes-getter (model))
-         
-(defcomponent mewa ()
-  ((attributes
-    :initarg :attributes
-    :accessor attributes
-    :initform nil)
-   (attributes-getter
-    :accessor attributes-getter
-    :initform #'get-attributes
-    :initarg :attributes-getter)
-   (global-properties
-    :initarg :global-properties
-    :accessor global-properties
-    :initform nil)
-   (classes 
-    :initarg :classes 
-    :accessor classes 
-    :initform nil)
-   (use-instance-class-p 
-    :initarg :use-instance-class-p 
-    :accessor use-instance-class-p 
-    :initform t)
-   (initializedp :initform nil)
-   (modifiedp :accessor modifiedp :initform nil)))
-
-(defcomponent mewa-object-presentation (mewa object-presentation) ())
-
-(defcomponent mewa-one-line-presentation (mewa one-line-presentation)
-  ()
-  (:default-initargs :attributes-getter #'one-line-attributes-getter))
-
-(defmethod attributes :around ((self mewa))
-  (let ((a (call-next-method)))
-    (or a (funcall (attributes-getter self) self))))
-
-(defmethod get-attributes ((self mewa))
-  (if (instance self)
-  (append (meta-model:list-slots (instance self))
-         (meta-model:list-has-many (instance self)))
-  nil))
-
-(defmethod one-line-attributes-getter ((self mewa))
-  (or (meta-model:list-keys (instance self))))
-
-
-
-(defmethod find-instance-classes ((self mewa))
-  (mapcar #'class-name 
-         (it.bese.arnesi.mopp:compute-class-precedence-list (class-of (instance self)))))
-
-(defmethod find-all-attributes ((self mewa))
-  (reduce #'append 
-         (mapcar #'(lambda (x) 
-                     (cdr (find-class-attributes x)))
-                 (classes self))))
-
-(defun make-attribute (&rest props &key type &allow-other-keys)
-       (remf props :type)
-       (cons (gensym) (cons type props)))
-
-
-(defmethod find-applicable-attributes ((self mewa))
-  (let ((all-attributes (find-all-attributes self)))
-    (flet ((gen-att (x) (let ((att (assoc x all-attributes)))
-                                    (when att 
-                                      (setf (cddr att) (plist-union (global-properties self) (cddr att)))
-                                      att))))
-    (if (attributes self)
-       (remove 'nil 
-               (mapcar #'(lambda (x)
-                           (cond 
-                            ;;simple casee
-                            ((symbolp x) 
-                             (gen-att x))
-                            ;;if the car is a keyword then this is an inline def
-                            ((and (listp x) (keywordp (car x)))
-                             (let ((att (apply #'make-attribute x)))
-                               (setf (cddr att) 
-                                     (plist-union (cddr att) (global-properties self)))
-                               att))
-                            ;; if the plist has a :type          
-                            ((and (listp x) (getf (cdr x) :type))
-                             (let ((new (cdr (apply #'make-attribute (cdr x))))
-                                   (def (gen-att (car x))))
-                               (setf (cdr new) (plist-union (cdr new) (cddr def)))
-                               (cons (car def) new)))
-                            ;;finally if we are just overiding the props
-                            ((and (listp x) (symbolp (car x)))
-                             (let ((new (cdr (apply #'make-attribute (cdr x))))
-                                   (def (gen-att (car x))))
-                               (setf (cdr new) (plist-union (cdr new) (cddr def)))
-                               (cons (car def) (cons (second def) (cdr new)))))
-
-                             )
-                            )
-                                  
-                       (attributes self)))
-      all-attributes))))
-
-(defmethod find-slot-presentations ((self mewa))
-  (mapcar #'(lambda (s)
-             (let ((class-name (or (gethash (second s) ucw::*slot-type-mapping*) 'mewa-object-presentation)))
-             (apply #'make-instance 
-                    class-name
-                    (append (cddr s) (list :parent self)))))
-         (find-applicable-attributes self)))
-
-(defmethod default-attributes ((model t))
-  (append (mapcar #'(lambda (s) (cons (car s) (gen-pslot (if (meta-model:foreign-key-p model (car s))
-                                                  'ucw::foreign-key
-                                                  (cadr s))
-                                                (string (car s)) (car s)))) 
-         (meta-model:list-slot-types model))
-         (mapcar #'(lambda (s) (cons s (append (gen-pslot 'ucw::has-many (string s) s) `(:presentation (make-presentation ,model :type :one-line)))))
-                 (meta-model:list-has-many model))))
-
-(defmethod set-default-attributes ((model t))
-  (mapcar #'(lambda (x) 
-             (setf (find-attribute model (car x)) (cdr x)))
-         (default-attributes model)))
-
-
-(defcomponent mewa-object-presentation (mewa ucw:object-presentation) ())
-
-(defcomponent mewa-list-presentation (mewa ucw:list-presentation) 
-  ((it.bese.ucw::instances :accessor instances :initarg :instances :initform nil)
-      (instance :accessor instance))) ;to make make-presentation happy
-
-(defmethod get-all-instances ((self mewa-list-presentation))
-  (instances self))
-
-
-
-
-(defmethod initialize-slots ((self mewa))
-  (when (use-instance-class-p self)
-    (setf (classes self) 
-         (append (find-instance-classes self)
-                 (classes self))))
-  (setf (slots self) (find-slot-presentations   self)))
-  
-
-(defmethod render-on :around ((res response) (self mewa))
-  (unless (slot-value self 'initializedp)
-    (initialize-slots self))
-  (setf (slot-value self 'initializedp) t)
-  (call-next-method))
-
-
-(defmethod make-presentation ((object t) &key (type :viewer) (initargs nil))
-  (let* ((p (make-instance 'mewa-object-presentation))
-        (a (progn (setf (slot-value p 'instance) object)
-                  (initialize-slots p) 
-                  (assoc type (find-all-attributes p))))
-        
-        (i (apply #'make-instance (second a) (plist-union initargs (cddr a)))))
-    (setf (slot-value i 'instance) object)
-    i))
-
-(defmethod call-component :before ((from standard-component) (to mewa))
-  (unless (slot-value to 'initializedp)
-    (initialize-slots to))
-  (setf (slot-value to 'initializedp) t)
-  (setf (slots to) (mapcar #'(lambda (x) (prog2 
-                                            (setf (component.place x) (component.place from))
-                                            x))
-                            (slots to))))
-
-(defmacro call-presentation (object &rest args)
-  `(present-object ,object :presentation (make-presentation ,object ,@args)))
\ No newline at end of file
+(declaim (optimize (speed 2) (space 3) (safety 0)))
+
+(in-package :lisp-on-lines)
+
+(defparameter *default-type* :ucw)
+
+(define-layered-class description ()
+  ((description-type
+    :initarg :type
+    :accessor description.type
+    :initform 'viewer
+    :special t)
+   (description-layers
+    :initarg :layers
+    :accessor description.layers
+    :initform nil
+    :special t)
+   (description-properties
+    :accessor description.properties
+    :initform nil
+    :special t)
+   (described-object
+    :layered-accessor object
+    :initform nil
+    :special t)
+   (description-default-attributes
+    :accessor default-attributes
+    :initarg :default-attributes
+    :initform nil
+    :special t)
+   (description-attributes
+    :accessor attributes
+    :initarg :attributes
+    :initform nil
+    :special t)))
+
+(defmethod print-object ((self description) stream)
+  (print-unreadable-object (self stream :type t)
+    (with-slots (description-type) self
+      (format t "~A" description-type))))
+
+;;;; * Occurences
+
+(defvar *occurence-map* (make-hash-table)
+  "a display is generated by associating an 'occurence' 
+with an instance of a class. This is usually keyed off class-name,
+although an arbitrary occurence can be used with an arbitrary class.")
+
+(define-layered-class
+    standard-occurence (description)
+    ((occurence-name :accessor name :initarg :name)
+     (attribute-map :accessor attribute-map :initform (make-hash-table)))
+    (:documentation
+     "an occurence holds the attributes like a class holds slot-definitions.
+Attributes are the metadata used to display, validate, and otherwise manipulate actual values stored in lisp objects."))
+
+(defun find-or-create-occurence (name)
+  "Returns the occurence associated with this name."
+  (let ((occurence (gethash name *occurence-map*)))
+    (if occurence
+       occurence
+       (let ((new-occurence (make-instance 'standard-occurence :name name)))
+         (setf (gethash name *occurence-map*) new-occurence)
+         new-occurence))))
+
+(defun clear-occurence (occurence)
+  "removes all attributes from the occurence"
+  (setf (attribute-map occurence) (make-hash-table)))
+
+(defgeneric find-occurence (name)
+  (:method (thing)
+    nil)
+  (:method ((name symbol))
+    (find-or-create-occurence name))
+  (:method ((instance standard-object))
+    (find-or-create-occurence (class-name (class-of instance)))))
+
+
+(define-layered-class
+    attribute (description)
+    ((attribute-name :layered-accessor attribute.name
+          :initarg :name
+          :initform (gensym "ATTRIBUTE-")
+          :special t)
+     (occurence :accessor occurence :initarg :occurence :initform nil)
+     (label :initarg :label :layered-accessor label :initform nil :special t)))
+
+;;;; * Attributes
+(defmethod print-object ((self attribute) stream)
+  (print-unreadable-object (self stream :type t)
+    (with-slots (attribute-name description-type) self
+      (format stream "~A ~A" description-type attribute-name))))
+
+(define-layered-class
+    standard-attribute (attribute)
+    ((setter :accessor setter :initarg :setter :special t :initform nil)
+     (getter :accessor getter :initarg :getter :special t :initform nil)
+     (value :accessor value :initarg :value :special t)
+     (slot-name :accessor slot-name :initarg :slot-name :special t :initform nil))
+    (:documentation "Attributes are used to display a part of a thing, such as a slot of an object, a text label, the car of a list, etc."))
+
+(defmacro defattribute (name supers slots &rest args)
+  (let* (
+       (type-provided-p (second (assoc :type-name args)))
+       (type (or type-provided-p name))
+       (layer (or (second (assoc :in-layer args)) nil))
+       (properties (cdr (assoc :default-properties args)))
+       (cargs (remove-if #'(lambda (key)
+                  (or (eql key :type-name)
+                      (eql key :default-properties)
+                      (eql key :default-initargs)
+                      (eql key :in-layer)))
+                        args
+              :key #'car)))
+    
+    `(progn
+      (define-layered-class
+         ;;;; TODO: fix the naive way of making sure s-a is a superclass
+         ;;;; Need some MOPey goodness.
+         ,name ,@ (when layer `(:in-layer ,layer)),(or supers '(standard-attribute))
+         ,(append slots (properties-as-slots properties)) 
+         #+ (or) ,@ (cdr cargs)
+         ,@cargs
+         (:default-initargs :properties (list ,@properties)
+           ,@ (cdr (assoc :default-initargs args))))
+
+      ,(when (or
+            type-provided-p
+            (not (find-attribute-class-for-type name)))
+        `(defmethod find-attribute-class-for-type ((type (eql ',type)))
+          ',name)))))
+(define-layered-class
+    display-attribute (attribute)
+    ()
+    (:documentation "Presentation Attributes are used to display objects 
+using the attributes defined in an occurence. Presentation Attributes are always named using keywords."))
+
+(defun clear-attributes (name)
+  "removes all attributes from an occurance"
+  (clear-occurence (find-occurence name)))
+
+(defmethod find-attribute-class-for-type (type)
+  nil)
+
+(defun make-attribute (&rest args &key type &allow-other-keys)
+  (apply #'make-instance
+        (or (find-attribute-class-for-type type)
+            'standard-attribute)
+        :properties args
+        args)) 
+
+(defmethod ensure-attribute ((occurence standard-occurence) &rest args &key name &allow-other-keys)
+  "Creates an attribute in the given occurence"
+  (let ((attribute (apply #'make-attribute :occurence occurence args)))
+    (setf (find-attribute occurence name) attribute)))
+
+(defmethod find-attribute ((occurence null) name)
+  nil)
+
+(defmethod find-attribute ((occurence standard-occurence) name)
+  (or (gethash name (attribute-map occurence))
+      (let* ((class (ignore-errors (find-class (name occurence))))
+            (class-direct-superclasses
+             (when class
+               (closer-mop:class-direct-superclasses
+                class))))
+       (when class-direct-superclasses 
+         (let ((attribute
+                (find-attribute
+                 (find-occurence (class-name
+                                  (car
+                                   class-direct-superclasses)))
+                 name)))
+           attribute)))))
+
+(defmethod find-all-attributes ((occurence standard-occurence))
+  (loop for att being the hash-values of (attribute-map occurence)
+       collect att))
+
+(defmethod ensure-attribute (occurence-name &rest args &key name type &allow-other-keys)
+  (declare (ignore name type))
+  (apply #'ensure-attribute
+   (find-occurence occurence-name)
+   args)) 
+
+;;;; The following functions make up the public interface to the
+;;;; MEWA Attribute Occurence system.
+
+(defmethod find-all-attributes (occurence-name)
+  (find-all-attributes (find-occurence occurence-name)))
+
+(defmethod find-attribute (occurence-name attribute-name)
+  "Return the ATTRIBUTE named by ATTRIBUTE-NAME in OCCURANCE-name"
+  (find-attribute (find-occurence occurence-name) attribute-name))
+
+(defmethod (setf find-attribute) ((attribute-spec list) occurence-name attribute-name)
+  "Create a new attribute in the occurence.
+ATTRIBUTE-SPEC: a list of (type name &rest initargs)"
+  (apply #'ensure-attribute occurence-name :name attribute-name :type (first attribute-spec) (rest attribute-spec)))
+
+(defmethod (setf find-attribute) ((attribute standard-attribute) occurence attribute-name)
+  "Create a new attribute in the occurence.
+ATTRIBUTE-SPEC: a list of (type name &rest initargs)"
+  (setf (gethash attribute-name (attribute-map occurence))
+         attribute))
+
+(defmethod (setf find-attribute) ((attribute null) occurence attribute-name)
+  "Create a new attribute in the occurence.
+ATTRIBUTE-SPEC: a list of (type name &rest initargs)"
+  (setf (gethash attribute-name (attribute-map occurence))
+         attribute))
+
+
+(defmethod find-attribute ((attribute-with-occurence attribute) attribute-name)
+  (find-attribute (occurence attribute-with-occurence) attribute-name))
+
+(defmethod set-attribute-properties ((occurence-name t) attribute properties)
+  (setf (description.properties attribute) (plist-nunion
+                                           properties
+                                           (description.properties attribute)))
+  (loop for (initarg value) on (description.properties attribute) 
+             by #'cddr
+             with map = (initargs.slot-names attribute)
+             do (let ((s-n (assoc-if #'(lambda (x) (member initarg x)) map)))
+                  
+                  (if s-n
+                      (progn
+                        (setf (slot-value attribute
+                                          (cdr s-n))
+                              value))
+                      (warn "Cannot find initarg ~A in attribute ~S" initarg attribute)))
+             finally (return attribute)))
+
+(defmethod set-attribute (occurence-name attribute-name attribute-spec &key (inherit t))
+  "If inherit is T, sets the properties of the attribute only, unless the type has changed.
+otherwise, (setf find-attribute)"
+  (let ((att (find-attribute occurence-name attribute-name)))
+    (if (and att inherit (or (eql (car attribute-spec)
+                             (description.type att))
+                            (eq (car attribute-spec) t)))
+       (set-attribute-properties occurence-name att (cdr attribute-spec))
+       (setf (find-attribute occurence-name attribute-name)
+             (cons  (car attribute-spec)
+                    (plist-nunion
+                     (cdr attribute-spec) 
+                     (when att (description.properties att))))))))
+
+(defmethod perform-define-attributes ((occurence-name t) attributes)
+  (loop for attribute in attributes
+       do (destructuring-bind (name type &rest args)
+                 attribute
+            (cond ((not (null type))
+                   ;;set the type as well
+                   (set-attribute occurence-name name (cons type args)))))))
+                      
+(defmacro define-attributes (occurence-names &body attribute-definitions)
+  `(progn
+    ,@(loop for occurence-name in occurence-names
+           collect `(perform-define-attributes (quote ,occurence-name) (quote ,attribute-definitions)))))
+
+(defmethod find-display-attribute (occurence name)
+  (find-attribute occurence (intern (symbol-name name) "KEYWORD")))
+
+(defmethod find-description (object type)
+  (let ((occurence (find-occurence object)))
+    (or (find-display-attribute
+        occurence
+        type)
+       occurence)))
+
+;;"Unused???"
+(defmethod setter (attribute)
+  (warn "Setting ~A in ~A" attribute *context*)
+  (let ((setter (getf (description.properties attribute) :setter))
+       (slot-name (getf (description.properties attribute) :slot-name)))
+    (cond (setter
+          setter)
+         (slot-name
+          #'(lambda (value object)
+              (setf (slot-value object slot-name) value)))
+         (t
+          #'(lambda (value object)
+              (warn "Can't find anywere to set ~A in ~A using ~A" value object attribute))))))
+    
+
+(define-layered-function attribute-value (instance attribute)
+  (:documentation " Like SLOT-VALUE for instances, the base method calls GETTER."))
+
+(defmethod attribute-slot-value (instance attribute)
+  "Return (VALUES slot-value-or-nil existsp boundp"
+  (let (existsp boundp slot-value-or-nil)
+    (cond 
+      ((and (slot-boundp attribute 'slot-name) (slot-name attribute))
+        (when (slot-exists-p instance (slot-name attribute))
+          (setf existsp t)
+          (when (slot-boundp instance (slot-name attribute))
+            (setf boundp t
+                  slot-value-or-nil (slot-value
+                                     instance
+                                     (slot-name attribute))))))
+       ((and (slot-exists-p instance (attribute.name attribute)))
+        (setf existsp t)
+        (when (slot-boundp instance (attribute.name attribute))
+          (setf boundp t
+                slot-value-or-nil (slot-value
+                                   instance
+                                   (attribute.name attribute))))))
+    (VALUES slot-value-or-nil existsp boundp)))
+  
+(define-layered-method attribute-value (instance (attribute standard-attribute))
+ "return the attribute value or NIL if it cannot be found"                    
+    (with-slots (getter value) attribute
+      (when (slot-boundp attribute 'value)
+       (setf getter (constantly value)))
+      (if (and (slot-boundp attribute 'getter) getter)
+         ;;;; call the getter
+         (funcall getter instance)
+         ;;;; or default to the attribute-slot-value
+         (attribute-slot-value instance attribute))))
+
+(define-layered-function (setf attribute-value) (value instance attribute))
+
+(define-layered-method
+    (setf attribute-value) (value instance (attribute standard-attribute))
+  (with-slots (setter slot-name) attribute 
+    (cond ((and (slot-boundp attribute 'setter) setter)
+          (funcall setter value instance))
+         ((and (slot-boundp attribute 'slot-name) slot-name)
+          (setf (slot-value instance slot-name) value))
+         ((and (slot-exists-p instance (attribute.name attribute)))
+          (setf (slot-value instance (attribute.name attribute)) value))
+         (t
+          (error "Cannot set ~A in ~A" attribute instance)))))
+
+
+
+;;;; ** Default Attributes
+
+
+;;;; The default mewa class contains the types use as defaults.
+;;;; maps meta-model slot-types to slot-presentation
+
+(defvar *default-attributes-class-name* 'default)
+
+(defmacro with-default-attributes ((occurence-name) &body body)
+  `(let ((*default-attributes-class-name* ',occurence-name))
+    ,@body))
+
+(define-attributes (default)
+  (boolean boolean)
+  (string string)
+  (number currency)
+  (integer   integer)
+  (currency  currency)
+  (clsql:generalized-boolean boolean)
+  (foreign-key foreign-key))
+
+(defun find-presentation-attributes (occurence-name)
+  (loop for att in (find-all-attributes occurence-name)
+       when (typep att 'display-attribute)
+        collect att))
+
+(defun attribute-to-definition (attribute)
+  (nconc (list (attribute.name attribute)
+              (description.type attribute))
+        (description.properties attribute)))
+
+(defun find-default-presentation-attribute-definitions ()
+  (if (eql *default-attributes-class-name* 'default)
+      (mapcar #'attribute-to-definition (find-presentation-attributes 'default)) 
+      (remove-duplicates (mapcar #'attribute-to-definition
+                                (append
+                                 (find-presentation-attributes 'default)
+                                 (find-presentation-attributes
+                                  *default-attributes-class-name*))))))
+(defun gen-ptype (type)
+  (let* ((type (if (consp type) (car type) type))
+        (possible-default (find-attribute *default-attributes-class-name* type))
+        (real-default (find-attribute 'default type)))
+    (cond
+      (possible-default
+       (description.type possible-default))
+       (real-default
+       (description.type real-default))
+       (t type))))
+
+(defun gen-presentation-slots (instance)
+  (mapcar #'(lambda (x) (gen-pslot (cadr x) 
+                                  (string (car x)) 
+                                  (car x))) 
+         (meta-model:list-slot-types instance)))
+
+
+(defun gen-pslot (type label slot-name)
+  (copy-list `(,(gen-ptype type) 
+              :label ,label
+              :slot-name ,slot-name))) 
+
+;; This software is Copyright (c) Drew Crampsie, 2004-2005.