Refactoring of gobject:define-vtable
[cl-gtk2.git] / glib / gobject.meta.lisp
1 (in-package :gobject)
2
3 (defclass gobject-class (standard-class)
4   ((g-type-name :initform nil
5                 :accessor gobject-class-g-type-name)
6    (direct-g-type-name :initform nil
7                        :initarg :g-type-name
8                        :accessor gobject-class-direct-g-type-name)
9    (g-type-initializer :initform nil
10                        :initarg :g-type-initializer
11                        :reader gobject-class-g-type-initializer)
12    (interface-p :initform nil
13                 :initarg :g-interface-p
14                 :reader gobject-class-interface-p))
15   (:documentation "Metaclass for GObject-based classes."))
16
17 (defun initialize-gobject-class-g-type (class)
18   (if (gobject-class-g-type-initializer class)
19       (let* ((initializer-fn-ptr (foreign-symbol-pointer (gobject-class-g-type-initializer class)))
20              (type (when initializer-fn-ptr
21                      (foreign-funcall-pointer initializer-fn-ptr nil
22                                               g-type))))
23         (if (null initializer-fn-ptr)
24             (warn "Type initializer for class '~A' (GType '~A') is invalid: foreign symbol '~A'"
25                   (gobject-class-direct-g-type-name class) (class-name class) (gobject-class-g-type-initializer class))
26             (progn
27               (when (g-type= +g-type-invalid+ type)
28                 (warn "Declared GType name '~A' for class '~A' is invalid ('~A' returned 0)"
29                       (gobject-class-direct-g-type-name class) (class-name class)
30                       (gobject-class-g-type-initializer class)))
31               (unless (g-type= (gobject-class-direct-g-type-name class) type)
32                 (warn "Declared GType name '~A' for class '~A' does not match actual GType name '~A'"
33                       (gobject-class-direct-g-type-name class)
34                       (class-name class)
35                       (g-type-name type))))))
36       (unless (g-type-from-name (gobject-class-direct-g-type-name class))
37         (warn "Declared GType name '~A' for class '~A' is invalid (g_type_name returned 0)"
38               (gobject-class-direct-g-type-name class) (class-name class)))))
39
40 (defun filter-from-initargs (initargs removed-key)
41   (loop
42      for (key value) on initargs by #'cddr
43      unless (eq key removed-key)
44      collect key and collect value))
45
46 (defun initargs-have-base-in-superclass (initargs base-class)
47   (let ((d-s (getf initargs :direct-superclasses)))
48     (loop
49        for class in d-s
50        thereis (subtypep class base-class))))
51
52 (defun compute-new-initargs-for-metaclass (initargs base-class)
53   (if (initargs-have-base-in-superclass initargs base-class)
54       initargs
55       (append (filter-from-initargs initargs :direct-superclasses)
56               (list :direct-superclasses
57                     (append (getf initargs :direct-superclasses)
58                             (list (find-class base-class)))))))
59
60 (defmethod initialize-instance :around ((class gobject-class) &rest initargs)
61   (apply #'call-next-method class (compute-new-initargs-for-metaclass initargs 'g-object)))
62
63 (defmethod reinitialize-instance :around ((class gobject-class) &rest initargs &key (direct-superclasses nil d-s-p) &allow-other-keys)
64   (declare (ignore direct-superclasses))
65   (if d-s-p
66       (call-next-method)
67       (apply #'call-next-method class (compute-new-initargs-for-metaclass initargs 'g-object))))
68
69 (defmethod initialize-instance :after ((object gobject-class) &key &allow-other-keys)
70   (when (gobject-class-direct-g-type-name object)
71     (register-object-type (gobject-class-direct-g-type-name object) (class-name object))
72     (at-init (object) (initialize-gobject-class-g-type object))))
73
74 (defmethod finalize-inheritance :after ((class gobject-class))
75   (setf (gobject-class-g-type-name class)
76         (or (gobject-class-direct-g-type-name class)
77             (let ((gobject-superclass (iter (for superclass in (class-direct-superclasses class))
78                                             (finding superclass such-that (typep superclass 'gobject-class)))))
79               (assert gobject-superclass)
80               (gobject-class-g-type-name gobject-superclass)))))
81
82 (defclass gobject-direct-slot-definition (standard-direct-slot-definition)
83   ((g-property-type :initform nil
84                     :initarg :g-property-type
85                     :reader gobject-direct-slot-definition-g-property-type)))
86
87 (defclass gobject-effective-slot-definition (standard-effective-slot-definition)
88   ((g-property-type :initform nil
89                     :initarg :g-property-type
90                     :accessor gobject-effective-slot-definition-g-property-type)))
91
92 (defclass gobject-property-direct-slot-definition (gobject-direct-slot-definition)
93   ((g-property-name :initform nil
94                     :initarg :g-property-name
95                     :reader gobject-property-direct-slot-definition-g-property-name)))
96
97 (defclass gobject-property-effective-slot-definition (gobject-effective-slot-definition)
98   ((g-property-name :initform nil
99                     :initarg :g-property-name
100                     :accessor gobject-property-effective-slot-definition-g-property-name)))
101
102 (defclass gobject-fn-direct-slot-definition (gobject-direct-slot-definition)
103   ((g-getter-name :initform nil
104                   :initarg :g-getter
105                   :reader gobject-fn-direct-slot-definition-g-getter-name)
106    (g-setter-name :initform nil
107                   :initarg :g-setter
108                   :reader gobject-fn-direct-slot-definition-g-setter-name)))
109
110 (defclass gobject-fn-effective-slot-definition (gobject-effective-slot-definition)
111   ((g-getter-name :initform nil
112                   :initarg :g-getter
113                   :accessor gobject-fn-effective-slot-definition-g-getter-name)
114    (g-setter-name :initform nil
115                   :initarg :g-setter
116                   :accessor gobject-fn-effective-slot-definition-g-setter-name)
117    (g-getter-fn :initform nil
118                 :accessor gobject-fn-effective-slot-definition-g-getter-fn)
119    (g-setter-fn :initform nil
120                 :accessor gobject-fn-effective-slot-definition-g-setter-fn)))
121
122 (defmethod validate-superclass ((class gobject-class) (superclass standard-class))
123   t)
124
125 (defmethod direct-slot-definition-class ((class gobject-class) &rest initargs &key allocation &allow-other-keys)
126   (declare (ignore initargs))
127   (case allocation
128     (:gobject-property (find-class 'gobject-property-direct-slot-definition))
129     (:gobject-fn (find-class 'gobject-fn-direct-slot-definition))
130     (otherwise (call-next-method))))
131
132 (defvar *e-s-d* nil)
133
134 (defmethod effective-slot-definition-class ((class gobject-class) &rest initargs)
135   (declare (ignore initargs))
136   (or *e-s-d* (call-next-method)))
137
138 (defmethod compute-effective-slot-definition ((class gobject-class) name direct-slots)
139   (let ((effective-slot (let ((*e-s-d* (loop
140                                           for slot in direct-slots
141                                           when (typep slot 'gobject-direct-slot-definition)
142                                           return (etypecase slot
143                                                    (gobject-property-direct-slot-definition (find-class 'gobject-property-effective-slot-definition))
144                                                    (gobject-fn-direct-slot-definition (find-class 'gobject-fn-effective-slot-definition))))))
145                           (call-next-method))))
146     (when (typep effective-slot 'gobject-effective-slot-definition)
147       (let ((allocation (loop
148                               for direct-slot in direct-slots
149                               when (slot-definition-allocation direct-slot)
150                               return (slot-definition-allocation direct-slot)))
151             (property-name (loop
152                               for direct-slot in direct-slots
153                               when (and (typep direct-slot 'gobject-property-direct-slot-definition) (gobject-property-direct-slot-definition-g-property-name direct-slot))
154                               return (gobject-property-direct-slot-definition-g-property-name direct-slot)))
155             (property-type (loop
156                               for direct-slot in direct-slots
157                               when (gobject-direct-slot-definition-g-property-type direct-slot)
158                               return (gobject-direct-slot-definition-g-property-type direct-slot)))
159             (property-getter (loop
160                               for direct-slot in direct-slots
161                               when (and (typep direct-slot 'gobject-fn-direct-slot-definition) (gobject-fn-direct-slot-definition-g-getter-name direct-slot))
162                               return (gobject-fn-direct-slot-definition-g-getter-name direct-slot)))
163             (property-setter (loop
164                               for direct-slot in direct-slots
165                               when (and (typep direct-slot 'gobject-fn-direct-slot-definition) (gobject-fn-direct-slot-definition-g-setter-name direct-slot))
166                               return (gobject-fn-direct-slot-definition-g-setter-name direct-slot))))
167         (setf (gobject-effective-slot-definition-g-property-type effective-slot)
168               (gobject-effective-slot-definition-g-property-type effective-slot))
169         (ecase allocation
170           (:gobject-property (assert property-name nil "G-PROPERTY-NAME for slot ~A on class ~A must be specified" name (class-name class))
171                              (setf (gobject-property-effective-slot-definition-g-property-name effective-slot)
172                                    property-name))
173           (:gobject-fn (assert (or property-getter property-setter) nil "At least one of G-PROPERTY-GETTER or G-PROPERTY-SETTER for slot ~A on class ~A must be specified"
174                                name (class-name class))
175                        (when (or (and property-getter (stringp property-getter))
176                                  (and property-setter (stringp property-setter)))
177                         (assert property-type nil "G-PROPERTY-TYPE for slot ~A on class ~A must be specified because at least one of accessor is specified as a foreign function" name (class-name class)))
178                        
179                        (setf (gobject-fn-effective-slot-definition-g-getter-name effective-slot) property-getter
180                              (gobject-fn-effective-slot-definition-g-setter-name effective-slot) property-setter
181                              (gobject-fn-effective-slot-definition-g-getter-fn effective-slot)
182                              (and property-getter
183                                   (if (stringp property-getter)
184                                       (compile nil (if (foreign-symbol-pointer property-getter)
185                                                        `(lambda (object)
186                                                           (foreign-funcall ,property-getter
187                                                                            g-object object
188                                                                            ,property-type))
189                                                        `(lambda (object)
190                                                           (declare (ignore object))
191                                                           (error "Property getter ~A is not available" ,property-getter))
192                                                        ))
193                                       property-getter))
194                              (gobject-fn-effective-slot-definition-g-setter-fn effective-slot)
195                              (and property-setter
196                                   (if (stringp property-setter)
197                                       (compile nil (if (foreign-symbol-pointer property-setter)
198                                                        `(lambda (object new-value)
199                                                           (foreign-funcall ,property-setter
200                                                                            g-object object
201                                                                            ,property-type new-value
202                                                                            :void))
203                                                        `(lambda (object)
204                                                           (declare (ignore object))
205                                                           (error "Property setter ~A is not avaiable" ,property-setter))))
206                                       property-setter)))))))
207     effective-slot))
208
209 (defun create-gobject-from-class-and-initargs (class initargs)
210   (when (gobject-class-interface-p class)
211     (error "Trying to create instance of GInterface '~A' (class '~A')" (gobject-class-g-type-name class) (class-name class)))
212   (let (arg-names arg-values arg-types nc-setters nc-arg-values)
213     (declare (dynamic-extent arg-names arg-values arg-types nc-setters nc-arg-values))
214     (loop
215        for (arg-name arg-value) on initargs by #'cddr
216        for slot = (find arg-name (class-slots class) :key 'slot-definition-initargs :test 'member)
217        when (and slot (typep slot 'gobject-effective-slot-definition))
218        do (typecase slot
219             (gobject-property-effective-slot-definition
220              (push (gobject-property-effective-slot-definition-g-property-name slot) arg-names)
221              (push arg-value arg-values)
222              (push (gobject-effective-slot-definition-g-property-type slot) arg-types))
223             (gobject-fn-effective-slot-definition
224              (push (gobject-fn-effective-slot-definition-g-setter-fn slot) nc-setters)
225              (push arg-value nc-arg-values))))
226     (let ((object (g-object-call-constructor (gobject-class-g-type-name class) arg-names arg-values arg-types)))
227       (loop
228          for fn in nc-setters
229          for value in nc-arg-values
230          do (funcall fn object value))
231       object)))
232
233 (defun filter-initargs-by-class (class initargs)
234   (iter (with slots = (class-slots class))
235         (for (arg-name arg-value) on initargs by #'cddr)
236         (for slot = (find arg-name slots :key #'slot-definition-initargs :test 'member))
237         (unless (and slot (typep slot 'gobject-effective-slot-definition))
238           (nconcing (list arg-name arg-value)))))
239
240 (defmethod initialize-instance ((instance g-object) &rest initargs &key &allow-other-keys)
241   (let ((filtered-initargs (filter-initargs-by-class (class-of instance) initargs)))
242     (apply #'call-next-method instance filtered-initargs)))
243
244 (defmethod make-instance ((class gobject-class) &rest initargs &key pointer)
245   (log-for :subclass "(make-instance ~A ~{~A~^ ~})~%" class initargs)
246   (let ((*currently-making-object-p* t))
247     (if pointer
248         (progn
249           (assert (= (length initargs) 2) nil "POINTER can not be combined with other initargs (~A)" initargs)
250           (call-next-method))
251         (let* ((default-initargs (iter (for (arg value) in (class-default-initargs class))
252                                        (nconcing (list arg value))))
253                (effective-initargs (append initargs default-initargs))
254                (pointer (create-gobject-from-class-and-initargs class effective-initargs)))
255           (apply #'call-next-method class :pointer pointer effective-initargs)))))
256
257 (defmethod slot-boundp-using-class ((class gobject-class) object (slot gobject-property-effective-slot-definition))
258   (handler-case
259       (and (slot-boundp object 'pointer)
260            (pointer object)
261            (progn (g-object-property-type (pointer object) (gobject-property-effective-slot-definition-g-property-name slot) :assert-readable t) t))
262     (property-unreadable-error () nil)))
263
264 (defmethod slot-value-using-class ((class gobject-class) object (slot gobject-property-effective-slot-definition))
265   (g-object-call-get-property (pointer object)
266                               (gobject-property-effective-slot-definition-g-property-name slot)
267                               (gobject-effective-slot-definition-g-property-type slot)))
268
269 (defmethod (setf slot-value-using-class) (new-value (class gobject-class) object (slot gobject-property-effective-slot-definition))
270   (g-object-call-set-property (pointer object)
271                               (gobject-property-effective-slot-definition-g-property-name slot)
272                               new-value
273                               (gobject-effective-slot-definition-g-property-type slot))
274   new-value)
275
276 (defmethod slot-boundp-using-class ((class gobject-class) object (slot gobject-fn-effective-slot-definition))
277   (and (slot-boundp object 'pointer)
278        (pointer object)
279        (not (null (gobject-fn-effective-slot-definition-g-getter-fn slot)))))
280
281 (defmethod slot-value-using-class ((class gobject-class) object (slot gobject-fn-effective-slot-definition))
282   (let ((fn (gobject-fn-effective-slot-definition-g-getter-fn slot)))
283     (funcall fn object)))
284
285 (defmethod (setf slot-value-using-class) (new-value (class gobject-class) object (slot gobject-fn-effective-slot-definition))
286   (funcall (gobject-fn-effective-slot-definition-g-setter-fn slot) object new-value)
287   new-value)
288
289 (defmethod slot-boundp-using-class ((class gobject-class) object (slot gobject-effective-slot-definition))
290   (slot-boundp object 'pointer))
291
292 (defmethod slot-makunbound-using-class ((class gobject-class) object (slot gobject-effective-slot-definition))
293   (declare (ignore object))
294   nil)