chiark / gitweb /
src/pset-proto.lisp: Fix export of `check-unused-properties'.
[sod] / src / pset-proto.lisp
1 ;;; -*-lisp-*-
2 ;;;
3 ;;; Protocol for property sets
4 ;;;
5 ;;; (c) 2009 Straylight/Edgeware
6 ;;;
7
8 ;;;----- Licensing notice ---------------------------------------------------
9 ;;;
10 ;;; This file is part of the Sensble Object Design, an object system for C.
11 ;;;
12 ;;; SOD is free software; you can redistribute it and/or modify
13 ;;; it under the terms of the GNU General Public License as published by
14 ;;; the Free Software Foundation; either version 2 of the License, or
15 ;;; (at your option) any later version.
16 ;;;
17 ;;; SOD is distributed in the hope that it will be useful,
18 ;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
19 ;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
20 ;;; GNU General Public License for more details.
21 ;;;
22 ;;; You should have received a copy of the GNU General Public License
23 ;;; along with SOD; if not, write to the Free Software Foundation,
24 ;;; Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
25
26 (cl:in-package #:sod)
27
28 ;;;--------------------------------------------------------------------------
29 ;;; Property representation.
30
31 (export 'property-key)
32 (defun property-key (name)
33   "Convert NAME into a keyword.
34
35    If NAME isn't a symbol already, then flip its case (using
36    `frob-identifier'), and intern into the `keyword' package."
37   (etypecase name
38     (symbol name)
39     (string (intern (frob-identifier name) :keyword))))
40
41 (export '(property propertyp p-name p-value p-type p-key p-seenp))
42 (defstruct (property
43              (:predicate propertyp)
44              (:conc-name p-)
45              (:constructor %make-property
46                            (name value
47                             &key type location seenp
48                             &aux (key (property-key name)) (%type type))))
49   "A simple structure for holding a property in a property set.
50
51    The main useful feature is the ability to tick off properties which have
52    been used, so that we can complain about unrecognized properties.
53
54    An explicit type tag is necessary because we need to be able to talk
55    distinctly about identifiers, strings and symbols, and we've only got two
56    obvious Lisp types to play with.  Sad, but true."
57
58   (name nil :type (or string symbol))
59   (value nil :type t)
60   (%type nil :type symbol)
61   (location (file-location nil) :type file-location)
62   (key nil :type symbol)
63   (seenp nil :type boolean))
64 (define-access-wrapper p-type p-%type)
65
66 (export 'decode-property)
67 (defgeneric decode-property (raw)
68   (:documentation "Decode a RAW value into a TYPE, VALUE pair.")
69   (:method ((raw symbol)) (values :symbol raw))
70   (:method ((raw integer)) (values :int raw))
71   (:method ((raw string)) (values :string raw))
72   (:method ((raw character)) (values :char raw))
73   (:method ((raw property)) (values (p-type raw) (p-value raw)))
74   (:method ((raw cons)) (values (car raw) (cdr raw)))
75   (:method ((raw function)) (values :func raw)))
76
77 (export 'make-property)
78 (defun make-property (name raw-value &key type location seenp)
79   (multiple-value-bind (type value)
80       (if type
81           (values type raw-value)
82           (decode-property raw-value))
83     (%make-property name value
84                     :type type
85                     :location (file-location location)
86                     :seenp seenp)))
87
88 (defun string-to-symbol
89     (string &key (package *package*) (swap-case t) (swap-hyphen t))
90   "Convert STRING to a symbol in PACKAGE.
91
92    Parse off a `PACKAGE:' prefix from STRING if necessary, to identify the
93    package; PACKAGE is used if there isn't a prefix.  A doubled colon allows
94    access to internal symbols, and will intern if necessary.  Note that
95    escape characters are /not/ processed; don't put colons in package names
96    if you want to use them from SOD property sets.
97
98    The portions of the string are modified by `frob-identifier'; the
99    arguments SWAP-CASE and SWAP-HYPHEN are passed to `frob-identifier' to
100    control this process."
101
102   (let* ((length (length string))
103          (colon (position #\: string)))
104     (multiple-value-bind (start internalp)
105         (cond ((not colon) (values 0 t))
106               ((and (< (1+ colon) length)
107                     (char= (char string (1+ colon)) #\:))
108                (values (+ colon 2) t))
109               (t
110                (values (1+ colon) nil)))
111       (when colon
112         (let* ((package-name (if (zerop colon) "KEYWORD"
113                                  (frob-identifier (subseq string 0 colon)
114                                                   :swap-case swap-case
115                                                   :swap-hyphen swap-hyphen)))
116                (found (find-package package-name)))
117           (unless found
118             (error "Unknown package `~A'" package-name))
119           (setf package found)))
120       (let ((name (frob-identifier (subseq string start)
121                                    :swap-case swap-case
122                                    :swap-hyphen swap-hyphen)))
123         (multiple-value-bind (symbol status)
124             (funcall (if internalp #'intern #'find-symbol) name package)
125           (cond ((or internalp (eq status :external))
126                  symbol)
127                 ((not status)
128                  (error "Symbol `~A' not found in package `~A'"
129                         name (package-name package)))
130                 (t
131                  (error "Symbol `~A' not external in package `~A'"
132                         name (package-name package)))))))))
133
134 (export 'coerce-property-value)
135 (defgeneric coerce-property-value (value type wanted)
136   (:documentation
137    "Convert VALUE, a property of type TYPE, to be of type WANTED.
138
139    It's sensible to add additional methods to this function, but there are
140    all the ones we need.")
141
142   ;; If TYPE matches WANTED, we'll assume that VALUE already has the right
143   ;; form.  Otherwise, if nothing else matched, then I guess we'll have to
144   ;; say it didn't work.
145   (:method (value type wanted)
146     (if (eql type wanted) value
147         (error "Incorrect type: expected ~A but found ~A" wanted type)))
148
149   ;; If the caller asks for type T then give him the raw thing.
150   (:method (value type (wanted (eql t)))
151     (declare (ignore type))
152     value))
153
154 ;;;--------------------------------------------------------------------------
155 ;;; Property set representation.
156
157 (export '(pset psetp))
158 (defstruct (pset (:predicate psetp)
159                  (:constructor %make-pset)
160                  (:conc-name %pset-))
161   "A property set.
162
163    Wrapped up in a structure so that we can define a print function."
164   (hash (make-hash-table) :type hash-table))
165
166 (export '(make-pset pset-get pset-store pset-map))
167 (declaim (inline make-pset pset-get pset-store pset-map))
168
169 (defun make-pset ()
170   "Constructor for property sets."
171   (%make-pset))
172
173 (defun pset-get (pset key)
174   "Look KEY up in PSET and return what we find.
175
176    If there's no property by that name, return nil."
177   (values (gethash key (%pset-hash pset))))
178
179 (defun pset-store (pset prop)
180   "Store property PROP in PSET.
181
182    Overwrite or replace any previous property with the same name.  Mutates
183    the property set."
184   (setf (gethash (p-key prop) (%pset-hash pset)) prop))
185
186 (defun pset-map (func pset)
187   "Call FUNC for each property in PSET."
188   (maphash (lambda (key value) (declare (ignore key)) (funcall func value))
189            (%pset-hash pset)))
190
191 (export 'with-pset-iterator)
192 (defmacro with-pset-iterator ((name pset) &body body)
193   "Evaluate BODY with NAME bound to a macro returning properties from PSET.
194
195    Evaluating (NAME) returns a property object or nil if all properties have
196    been read."
197   (with-gensyms (next win key value)
198     `(with-hash-table-iterator (,next (%pset-hash ,pset))
199        (macrolet ((,name ()
200                     `(multiple-value-bind (,',win ,',key ,',value) (,',next)
201                       (declare (ignore ,',key))
202                       (and ,',win ,',value))))
203          ,@body))))
204
205 ;;;--------------------------------------------------------------------------
206 ;;; `Cooked' property set operations.
207
208 (export 'store-property)
209 (defun store-property
210     (pset name value &key type location)
211   "Store a property in PSET."
212   (pset-store pset
213               (make-property name value :type type :location location)))
214
215 (export 'get-property)
216 (defun get-property (pset name type &optional default)
217   "Fetch a property from a property set.
218
219    If a property NAME is not found in PSET, or if a property is found, but
220    its type doesn't match TYPE, then return DEFAULT and nil; otherwise return
221    the value and its file location.  In the latter case, mark the property as
222    having been used.
223
224    The value returned depends on the TYPE argument provided.  If you pass
225    `nil' then you get back the entire `property' object.  If you pass `t',
226    then you get whatever was left in the property set, uninterpreted.
227    Otherwise the value is coerced to the right kind of thing (where possible)
228    and returned.
229
230    The file location at which the property was defined is returned as a
231    second value.
232
233    If PSET is nil, then return DEFAULT and nil."
234
235   (let ((prop (and pset (pset-get pset (property-key name)))))
236     (with-default-error-location ((and prop (p-location prop)))
237       (cond ((not prop)
238              (values default nil))
239             ((not type)
240              (setf (p-seenp prop) t)
241              (values prop (p-location prop)))
242             (t
243              (setf (p-seenp prop) t)
244              (values (coerce-property-value (p-value prop)
245                                             (p-type prop)
246                                             type)
247                      (p-location prop)))))))
248
249 (export 'add-property)
250 (defun add-property (pset name value &key type location)
251   "Add a property to PSET.
252
253    If a property with the same NAME already exists, report an error."
254
255   (with-default-error-location (location)
256     (let ((existing (get-property pset name nil)))
257       (when existing
258         (error "Property ~S already defined~@[ at ~A~]"
259                name (p-location existing)))
260       (store-property pset name value :type type :location location))))
261
262 (export 'make-property-set)
263 (defun make-property-set (&rest plist)
264   "Make a new property set, with given properties.
265
266    This isn't the way to make properties when parsing, but it works well for
267    programmatic generation.  The arguments should form a property list
268    (alternating keywords and values is good).
269
270    An attempt is made to guess property types from the Lisp types of the
271    values.  This isn't always successful but it's not too bad.  The
272    alternative is manufacturing a `property-value' object by hand and
273    stuffing it into the set."
274
275   (property-set plist))
276
277 (export 'property-set)
278 (defgeneric property-set (thing)
279   (:documentation
280    "Convert THING into a property set.")
281   (:method ((pset pset)) pset)
282   (:method ((list list))
283     "Convert a list into a property set.  This works for alists and plists."
284     (multiple-value-bind (next name value)
285         (if (and list (consp (car list)))
286             (values #'cdr #'caar #'cdar)
287             (values #'cddr #'car #'cadr))
288       (do ((pset (make-pset))
289            (list list (funcall next list)))
290           ((endp list) pset)
291         (add-property pset (funcall name list) (funcall value list))))))
292
293 (export 'check-unused-properties)
294 (defun check-unused-properties (pset)
295   "Issue errors about unused properties in PSET."
296   (when pset
297     (pset-map (lambda (prop)
298                 (unless (p-seenp prop)
299                   (cerror*-with-location (p-location prop)
300                                          "Unknown property `~A'"
301                                          (p-name prop))
302                   (setf (p-seenp prop) t)))
303               pset)))
304
305 ;;;--------------------------------------------------------------------------
306 ;;; Utility macros.
307
308 (defmacro default-slot-from-property
309     ((instance slot slot-names)
310      (pset property type
311       &optional (pvar (gensym "PROP-"))
312       &rest convert-forms)
313      &body default-forms)
314   "Initialize a slot from a property.
315
316    We initialize SLOT in INSTANCE.  In full: if PSET contains a property
317    called NAME, then convert it to TYPE, bind the value to PVAR and evaluate
318    CONVERT-FORMS -- these default to just using the property value.  If
319    there's no property, and the slot is named in SLOT-NAMES and currently
320    unbound, then evaluate DEFAULT-FORMS and use their value to compute the
321    slot value."
322
323   (once-only (instance slot slot-names pset property type)
324     (with-gensyms (floc)
325       `(multiple-value-bind (,pvar ,floc)
326            (get-property ,pset ,property ,type)
327          (if ,floc
328              (setf (slot-value ,instance ,slot)
329                    (with-default-error-location (,floc)
330                      ,@(or convert-forms `(,pvar))))
331              (default-slot (,instance ,slot ,slot-names)
332                ,@default-forms))))))
333
334 ;;;----- That's all, folks --------------------------------------------------