lib/keyword.c (kw_parseempty): Use correct variable scanning `kwval' list.
[sod] / src / utilities.lisp
CommitLineData
dea4d055
MW
1;;; -*-lisp-*-
2;;;
3;;; Various handy utilities
4;;;
5;;; (c) 2009 Straylight/Edgeware
6;;;
7
8;;;----- Licensing notice ---------------------------------------------------
9;;;
e0808c47 10;;; This file is part of the Sensible Object Design, an object system for C.
dea4d055
MW
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
bb99b695
MW
26(eval-when (:compile-toplevel :load-toplevel :execute)
27 (handler-bind ((warning #'muffle-warning))
28 (cl:defpackage #:sod-utilities
29 (:use #:common-lisp
30
31 ;; MOP from somewhere.
32 #+sbcl #:sb-mop
33 #+(or cmu clisp) #:mop
34 #+ecl #:clos))))
dea4d055
MW
35
36(cl:in-package #:sod-utilities)
37
38;;;--------------------------------------------------------------------------
8e3552b3
MW
39;;; Common symbols.
40;;;
41;;; Sometimes, logically independent packages will want to use the same
42;;; symbol, and these uses (by careful design) don't conflict with each
43;;; other. If we export the symbols here, then the necessary sharing will
44;;; happen automatically.
45
46(export 'int) ; used by c-types and optparse
47
48;;;--------------------------------------------------------------------------
dea4d055
MW
49;;; Macro hacks.
50
51(export 'with-gensyms)
52(defmacro with-gensyms ((&rest binds) &body body)
53 "Evaluate BODY with variables bound to fresh symbols.
54
55 The BINDS are a list of entries (VAR [NAME]), and a singleton list can be
56 replaced by just a symbol; each VAR is bound to a fresh symbol generated
57 by (gensym NAME), where NAME defaults to the symbol-name of VAR."
58 `(let (,@(mapcar (lambda (bind)
59 (multiple-value-bind (var name)
60 (if (atom bind)
61 (values bind (concatenate 'string
62 (symbol-name bind) "-"))
63 (destructuring-bind
64 (var &optional
65 (name (concatenate 'string
66 (symbol-name var) "-")))
67 bind
68 (values var name)))
69 `(,var (gensym ,name))))
70 binds))
71 ,@body))
72
73(eval-when (:compile-toplevel :load-toplevel :execute)
74 (defun strip-quote (form)
75 "If FORM looks like (quote FOO) for self-evaluating FOO, return FOO.
76
77 If FORM is a symbol whose constant value is `nil' then return `nil'.
78 Otherwise return FORM unchanged. This makes it easier to inspect constant
79 things. This is a utility for `once-only'."
80
81 (cond ((and (consp form)
82 (eq (car form) 'quote)
83 (cdr form)
84 (null (cddr form)))
85 (let ((body (cadr form)))
86 (if (or (not (or (consp body) (symbolp body)))
87 (member body '(t nil))
88 (keywordp body))
89 body
90 form)))
91 ((and (symbolp form) (boundp form) (null (symbol-value form)))
92 nil)
93 (t
94 form))))
95
96(export 'once-only)
74ca1bf5 97(defmacro once-only ((&rest binds) &body body)
dea4d055
MW
98 "Macro helper for preventing repeated evaluation.
99
100 The syntax is actually hairier than shown:
101
102 once-only ( [[ :environment ENV ]] { VAR | (VAR [VALUE-FORM]) }* )
103 { FORM }*
104
105 So, the BINDS are a list of entries (VAR [VALUE-FORM]); a singleton list
106 can be replaced by just a symbol VAR, and the VALUE-FORM defaults to VAR.
107 But before them you can have keyword arguments. Only one is defined so
108 far. See below for the crazy things that does.
109
110 The result of evaluating a ONCE-ONLY form is a form with the structure
111
112 (let ((#:GS1 VALUE-FORM1)
113 ...
114 (#:GSn VALUE-FORMn))
115 STUFF)
116
117 where STUFF is the value of the BODY forms, as an implicit progn, in an
118 environment with the VARs bound to the corresponding gensyms.
119
120 As additional magic, if any of the VALUE-FORMs is actually constant (as
121 determined by inspection, and aided by `constantp' if an :environment is
122 supplied, then no gensym is constructed for it, and the VAR is bound
123 directly to the constant form. Moreover, if the constant form looks like
124 (quote FOO) for a self-evaluating FOO then the outer layer of quoting is
125 stripped away."
126
127 ;; We need an extra layer of gensyms in our expansion: we'll want the
128 ;; expansion to examine the various VALUE-FORMs to find out whether they're
129 ;; constant without evaluating them repeatedly. This also helps with
130 ;; another problem: we explicitly encourage the rebinding of a VAR
131 ;; (probably a macro argument) to a gensym which will be bound to the value
132 ;; of the form previously held in VAR itself -- so the gensym and value
133 ;; form must exist at the same time and we need two distinct variables.
134
135 (with-gensyms ((envvar "ENV-") lets sym (bodyfunc "BODY-"))
136 (let ((env nil))
137
138 ;; First things first: let's pick up the keywords.
139 (loop
140 (unless (and binds (keywordp (car binds)))
141 (return))
142 (ecase (pop binds)
143 (:environment (setf env (pop binds)))))
144
145 ;; Now we'll investigate the bindings. Turn each one into a list (VAR
146 ;; VALUE-FORM TEMP) where TEMP is an appropriate gensym -- see the note
147 ;; above.
148 (let ((canon (mapcar (lambda (bind)
149 (multiple-value-bind (var form)
150 (if (atom bind)
151 (values bind bind)
152 (destructuring-bind
153 (var &optional (form var)) bind
154 (values var form)))
155 (list var form
156 (gensym (format nil "T-~A-"
157 (symbol-name var))))))
158 binds)))
159
160 `(let* (,@(and env `((,envvar ,env)))
161 (,lets nil)
162 ,@(mapcar (lambda (bind)
163 (destructuring-bind (var form temp) bind
164 (declare (ignore var))
165 `(,temp ,form)))
166 canon)
167 ,@(mapcar (lambda (bind)
168 (destructuring-bind (var form temp) bind
169 (declare (ignore form))
170 `(,var
171 (cond ((constantp ,temp
172 ,@(and env `(,envvar)))
173 (strip-quote ,temp))
174 ((symbolp ,temp)
175 ,temp)
176 (t
177 (let ((,sym (gensym
178 ,(concatenate 'string
179 (symbol-name var)
180 "-"))))
181 (push (list ,sym ,temp) ,lets)
182 ,sym))))))
183 canon))
184 (flet ((,bodyfunc () ,@body))
185 (if ,lets
186 `(let (,@(nreverse ,lets)) ,(,bodyfunc))
187 (,bodyfunc))))))))
188
189(export 'parse-body)
b8c698ee 190(defun parse-body (body &key (docp t) (declp t))
dea4d055
MW
191 "Parse the BODY into a docstring, declarations and the body forms.
192
193 These are returned as three lists, so that they can be spliced into a
194 macro expansion easily. The declarations are consolidated into a single
b8c698ee
MW
195 `declare' form. If DOCP is nil then a docstring is not permitted; if
196 DECLP is nil, then declarations are not permitted."
dea4d055
MW
197 (let ((decls nil)
198 (doc nil))
199 (loop
200 (cond ((null body) (return))
b8c698ee 201 ((and declp (consp (car body)) (eq (caar body) 'declare))
dea4d055 202 (setf decls (append decls (cdr (pop body)))))
b8c698ee 203 ((and docp (stringp (car body)) (not doc) (cdr body))
dea4d055
MW
204 (setf doc (pop body)))
205 (t (return))))
206 (values (and doc (list doc))
207 (and decls (list (cons 'declare decls)))
208 body)))
209
210;;;--------------------------------------------------------------------------
e8abb286
MW
211;;; Locatives.
212
6efaac65
MW
213(export '(locative locativep))
214(defstruct (locative (:predicate locativep)
215 (:constructor make-locative (reader writer))
216 (:conc-name loc-))
e8abb286
MW
217 "Locative data type. See `locf' and `ref'."
218 (reader nil :type function)
219 (writer nil :type function))
220
221(export 'locf)
222(defmacro locf (place &environment env)
223 "Slightly cheesy locatives.
224
225 (locf PLACE) returns an object which, using the `ref' function, can be
226 used to read or set the value of PLACE. It's cheesy because it uses
227 closures rather than actually taking the address of something. Also,
228 unlike Zetalisp, we don't overload `car' to do our dirty work."
229 (multiple-value-bind
230 (valtmps valforms newtmps setform getform)
231 (get-setf-expansion place env)
232 `(let* (,@(mapcar #'list valtmps valforms))
6efaac65
MW
233 (make-locative (lambda () ,getform)
234 (lambda (,@newtmps) ,setform)))))
e8abb286
MW
235
236(export 'ref)
237(declaim (inline ref (setf ref)))
238(defun ref (loc)
239 "Fetch the value referred to by a locative."
240 (funcall (loc-reader loc)))
241(defun (setf ref) (new loc)
242 "Store a new value in the place referred to by a locative."
243 (funcall (loc-writer loc) new))
244
245(export 'with-locatives)
246(defmacro with-locatives (locs &body body)
247 "Evaluate BODY with implicit locatives.
248
249 LOCS is a list of items of the form (SYM [LOC-EXPR]), where SYM is a
250 symbol and LOC-EXPR evaluates to a locative. If LOC-EXPR is omitted, it
251 defaults to SYM. As an abbreviation for a common case, LOCS may be a
252 symbol instead of a list.
253
254 The BODY is evaluated in an environment where each SYM is a symbol macro
255 which expands to (ref LOC-EXPR) -- or, in fact, something similar which
256 doesn't break if LOC-EXPR has side-effects. Thus, references, including
257 `setf' forms, fetch or modify the thing referred to by the LOC-EXPR.
258 Useful for covering over where something uses a locative."
259 (setf locs (mapcar (lambda (item)
260 (cond ((atom item) (list item item))
261 ((null (cdr item)) (list (car item) (car item)))
262 (t item)))
263 (if (listp locs) locs (list locs))))
264 (let ((tt (mapcar (lambda (l) (declare (ignore l)) (gensym)) locs))
265 (ll (mapcar #'cadr locs))
266 (ss (mapcar #'car locs)))
267 `(let (,@(mapcar (lambda (tmp loc) `(,tmp ,loc)) tt ll))
268 (symbol-macrolet (,@(mapcar (lambda (sym tmp)
269 `(,sym (ref ,tmp))) ss tt))
270 ,@body))))
271
272;;;--------------------------------------------------------------------------
dea4d055
MW
273;;; Anaphorics.
274
275(export 'it)
276
277(export 'aif)
278(defmacro aif (cond cons &optional (alt nil altp))
279 "If COND is not nil, evaluate CONS with `it' bound to the value of COND.
280
281 Otherwise, if given, evaluate ALT; `it' isn't bound in ALT."
282 (once-only (cond)
283 `(if ,cond (let ((it ,cond)) ,cons) ,@(and altp `(,alt)))))
284
285(export 'awhen)
286(defmacro awhen (cond &body body)
287 "If COND, evaluate BODY as a progn with `it' bound to the value of COND."
288 `(let ((it ,cond)) (when it ,@body)))
289
3e166443
MW
290(export 'aand)
291(defmacro aand (&rest forms)
292 "Like `and', but anaphoric.
293
294 Each FORM except the first is evaluated with `it' bound to the value of
295 the previous one. If there are no forms, then the result it `t'; if there
296 is exactly one, then wrapping it in `aand' is pointless."
297 (labels ((doit (first rest)
298 (if (null rest)
299 first
300 `(let ((it ,first))
301 (if it ,(doit (car rest) (cdr rest)) nil)))))
302 (if (null forms)
303 't
304 (doit (car forms) (cdr forms)))))
305
dea4d055 306(export 'acond)
bf090e02 307(defmacro acond (&body clauses &environment env)
dea4d055
MW
308 "Like COND, but with `it' bound to the value of the condition.
309
310 Each of the CLAUSES has the form (CONDITION FORM*); if a CONDITION is
311 non-nil then evaluate the FORMs with `it' bound to the non-nil value, and
312 return the value of the last FORM; if there are no FORMs, then return `it'
313 itself. If the CONDITION is nil then continue with the next clause; if
314 all clauses evaluate to nil then the result is nil."
315 (labels ((walk (clauses)
316 (if (null clauses)
317 `nil
318 (once-only (:environment env (cond (caar clauses)))
319 (if (and (constantp cond)
320 (if (and (consp cond) (eq (car cond) 'quote))
321 (cadr cond) cond))
322 (if (cdar clauses)
323 `(let ((it ,cond))
324 (declare (ignorable it))
325 ,@(cdar clauses))
326 cond)
327 `(if ,cond
328 ,(if (cdar clauses)
329 `(let ((it ,cond))
330 (declare (ignorable it))
331 ,@(cdar clauses))
332 cond)
333 ,(walk (cdr clauses))))))))
334 (walk clauses)))
335
336(export '(acase aecase atypecase aetypecase))
337(defmacro acase (value &body clauses)
338 `(let ((it ,value)) (case it ,@clauses)))
339(defmacro aecase (value &body clauses)
340 `(let ((it ,value)) (ecase it ,@clauses)))
341(defmacro atypecase (value &body clauses)
342 `(let ((it ,value)) (typecase it ,@clauses)))
343(defmacro aetypecase (value &body clauses)
344 `(let ((it ,value)) (etypecase it ,@clauses)))
345
346(export 'asetf)
347(defmacro asetf (&rest places-and-values &environment env)
348 "Anaphoric update of places.
349
350 The PLACES-AND-VALUES are alternating PLACEs and VALUEs. Each VALUE is
351 evaluated with IT bound to the current value stored in the corresponding
352 PLACE."
353 `(progn ,@(loop for (place value) on places-and-values by #'cddr
354 collect (multiple-value-bind
355 (temps inits newtemps setform getform)
356 (get-setf-expansion place env)
357 `(let* (,@(mapcar #'list temps inits)
358 (it ,getform))
359 (multiple-value-bind ,newtemps ,value
360 ,setform))))))
361
362;;;--------------------------------------------------------------------------
363;;; MOP hacks (not terribly demanding).
364
bf090e02
MW
365(export 'instance-initargs)
366(defgeneric instance-initargs (instance)
367 (:documentation
368 "Return a plausble list of initargs for INSTANCE.
369
370 The idea is that you can make a copy of INSTANCE by invoking
371
372 (apply #'make-instance (class-of INSTANCE)
373 (instance-initargs INSTANCE))
374
375 The default implementation works by inspecting the slot definitions and
376 extracting suitable initargs, so this will only succeed if enough slots
377 actually have initargs specified that `initialize-instance' can fill in
378 the rest correctly.
379
380 The list returned is freshly consed, and you can destroy it if you like.")
381 (:method ((instance standard-object))
382 (mapcan (lambda (slot)
383 (aif (slot-definition-initargs slot)
384 (list (car it)
385 (slot-value instance (slot-definition-name slot)))
386 nil))
387 (class-slots (class-of instance)))))
388
dea4d055
MW
389(export '(copy-instance copy-instance-using-class))
390(defgeneric copy-instance-using-class (class instance &rest initargs)
391 (:documentation
392 "Metaobject protocol hook for `copy-instance'.")
393 (:method ((class standard-class) instance &rest initargs)
394 (let ((copy (allocate-instance class)))
395 (dolist (slot (class-slots class))
396 (let ((name (slot-definition-name slot)))
397 (when (slot-boundp instance name)
398 (setf (slot-value copy name) (slot-value instance name)))))
399 (apply #'shared-initialize copy nil initargs))))
400(defun copy-instance (object &rest initargs)
401 "Construct and return a copy of OBJECT.
402
403 The new object has the same class as OBJECT, and the same slot values
404 except where overridden by INITARGS."
405 (apply #'copy-instance-using-class (class-of object) object initargs))
406
684d95c7
MW
407(export 'find-eql-specialized-method)
408(defun find-eql-specialized-method (function arg object)
409 "Return a method defined on FUNCTION whose ARGth argument is
410 `eql'-specialized on OBJECT."
411 (find-if (lambda (method)
412 (let ((spec (nth arg (method-specializers method))))
413 (and spec
414 (typep spec 'eql-specializer)
415 (eq (eql-specializer-object spec) object))))
416 (generic-function-methods function)))
417
9ec578d9
MW
418(export '(generic-function-methods method-specializers
419 eql-specializer eql-specializer-object))
420
dea4d055
MW
421;;;--------------------------------------------------------------------------
422;;; List utilities.
423
424(export 'make-list-builder)
425(defun make-list-builder (&optional initial)
426 "Return a simple list builder."
427
428 ;; The `builder' is just a cons cell whose cdr will be the list that's
429 ;; wanted. Effectively, then, we have a list that's one item longer than
430 ;; we actually want. The car of this extra initial cons cell is always the
431 ;; last cons in the list -- which is now well defined because there's
432 ;; always at least one.
433
434 (let ((builder (cons nil initial)))
435 (setf (car builder) (last builder))
436 builder))
437
438(export 'lbuild-add)
439(defun lbuild-add (builder item)
440 "Add an ITEM to the end of a list BUILDER."
441 (let ((new (cons item nil)))
442 (setf (cdar builder) new
443 (car builder) new))
444 builder)
445
446(export 'lbuild-add-list)
447(defun lbuild-add-list (builder list)
448 "Add a LIST to the end of a list BUILDER. The LIST will be clobbered."
449 (when list
450 (setf (cdar builder) list
451 (car builder) (last list)))
452 builder)
453
454(export 'lbuild-list)
455(defun lbuild-list (builder)
456 "Return the constructed list."
457 (cdr builder))
458
459(export 'mappend)
460(defun mappend (function list &rest more-lists)
69dda0c9 461 "Like a nondestructive `mapcan'.
dea4d055
MW
462
463 Map FUNCTION over the the corresponding elements of LIST and MORE-LISTS,
464 and return the result of appending all of the resulting lists."
465 (reduce #'append (apply #'mapcar function list more-lists) :from-end t))
466
0a8f78ec
MW
467(export 'cross-product)
468(defun cross-product (&rest pieces)
469 "Return the cross product of the PIECES.
470
471 Each arguments may be a list, or a (non-nil) atom, which is equivalent to
472 a singleton list containing just that atom. Return a list of all possible
473 lists which can be constructed by taking one item from each argument list
474 in turn, in an arbitrary order."
475 (reduce (lambda (piece tails)
476 (mapcan (lambda (tail)
477 (mapcar (lambda (head)
478 (cons head tail))
479 (if (listp piece) piece
480 (list piece))))
481 tails))
482 pieces
483 :from-end t
484 :initial-value '(nil)))
485
17c7c784
MW
486(export 'distinguished-point-shortest-paths)
487(defun distinguished-point-shortest-paths (root neighbours-func)
488 "Moderately efficient shortest-paths-from-root computation.
489
490 The ROOT is a distinguished vertex in a graph. The NEIGHBOURS-FUNC
491 accepts a VERTEX as its only argument, and returns a list of conses (V .
492 C) for each of the VERTEX's neighbours, indicating that there is an edge
493 from VERTEX to V, with cost C.
494
495 The return value is a list of entries (COST . REV-PATH) for each vertex
496 reachable from the ROOT; the COST is the total cost of the shortest path,
497 and REV-PATH is the path from the ROOT, in reverse order -- so the first
498 element is the vertex itself and the last element is the ROOT.
499
500 The NEIGHBOURS-FUNC is called at most N times, and may take O(N) time to
501 produce its output list. The computation as a whole takes O(N^2) time,
502 where N is the number of vertices in the graph, assuming there is at most
503 one edge between any pair of vertices."
504
505 ;; This is a listish version of Dijkstra's shortest-path algorithm. It
506 ;; could be made more efficient by using a fancy priority queue rather than
507 ;; a linear search for finding the nearest live element (see below), but it
508 ;; still runs pretty well.
509
510 (let ((map (make-hash-table))
511 (dead nil)
512 (live (list (list 0 root))))
513 (setf (gethash root map) (cons :live (car live)))
514 (loop
515 ;; The dead list contains a record, in output format (COST . PATH), for
516 ;; each vertex whose shortest path has been finally decided. The live
517 ;; list contains a record for the vertices of current interest, also in
518 ;; output format; the COST for a live record shows the best cost for a
519 ;; path using only dead vertices.
520 ;;
521 ;; Each time through here, we pull an item off the live list and
522 ;; push it onto the dead list, so we do at most N iterations total.
523
524 ;; If there are no more live items, then we're done; the remaining
525 ;; vertices, if any, are unreachable from the ROOT.
526 (when (null live) (return))
527
528 ;; Find the closest live vertex to the root. The linear scan through
529 ;; the live list costs at most N time.
530 (let* ((best (reduce (lambda (x y) (if (< (car x) (car y)) x y)) live))
531 (best-cost (car best))
532 (best-path (cdr best))
533 (best-vertex (car best-path)))
534
535 ;; Remove the chosen vertex from the LIVE list, and add the
536 ;; appropriate record to the dead list. We must have the shortest
537 ;; path to this vertex now: we have the shortest path using currently
538 ;; dead vertices; any other path must use at least one live vertex,
539 ;; and, by construction, the path through any such vertex must be
540 ;; further than the path we already have.
541 ;;
542 ;; Removal from the live list uses a linear scan which costs N time.
543 (setf live (delete best live))
544 (push best dead)
545 (setf (car (gethash best-vertex map)) :dead)
546
547 ;; Work through the chosen vertex's neighbours, adding each of them
548 ;; to the live list if they're not already there. If a neighbour is
549 ;; already live, and we find a shorter path to it through our chosen
550 ;; vertex, then update the neighbour's record.
551 ;;
552 ;; The chosen vertex obviously has at most N neighbours. There's no
553 ;; more looping in here, so performance is as claimed.
554 (dolist (neigh (funcall neighbours-func best-vertex))
555 (let* ((neigh-vertex (car neigh))
556 (neigh-cost (+ best-cost (cdr neigh)))
557 (neigh-record (gethash neigh-vertex map)))
558 (cond ((null neigh-record)
559 ;; If the neighbour isn't known, then now's the time to
560 ;; make a fresh live record for it.
561 (let ((new-record (list* :live neigh-cost
562 neigh-vertex best-path)))
563 (push (cdr new-record) live)
564 (setf (gethash neigh-vertex map) new-record)))
565 ((and (eq (car neigh-record) :live)
566 (< neigh-cost (cadr neigh-record)))
567 ;; If the neighbour is live, and we've found a better path
568 ;; to it, then update its record.
569 (setf (cadr neigh-record) neigh-cost
570 (cdddr neigh-record) best-path)))))))
571 dead))
572
38b78e87
MW
573(export '(inconsistent-merge-error
574 merge-error-candidates merge-error-present-function))
dea4d055
MW
575(define-condition inconsistent-merge-error (error)
576 ((candidates :initarg :candidates
38b78e87
MW
577 :reader merge-error-candidates)
578 (present :initarg :present :initform #'identity
579 :reader merge-error-present-function))
dea4d055 580 (:documentation
9fb4a980 581 "Reports an inconsistency in the arguments passed to `merge-lists'.")
dea4d055 582 (:report (lambda (condition stream)
e2838dc5
MW
583 (format stream "Merge inconsistency: failed to decide between ~
584 ~{~#[~;~A~;~A and ~A~:;~
585 ~@{~A, ~#[~;and ~A~]~}~]~}"
38b78e87
MW
586 (mapcar (merge-error-present-function condition)
587 (merge-error-candidates condition))))))
dea4d055
MW
588
589(export 'merge-lists)
e2838dc5 590(defun merge-lists (lists &key pick (test #'eql) (present #'identity))
dea4d055
MW
591 "Return a merge of the given LISTS.
592
e8c5a09e 593 The resulting list contains the items of the given LISTS, with duplicates
dea4d055
MW
594 removed. The order of the resulting list is consistent with the orders of
595 the input LISTS in the sense that if A precedes B in some input list then
596 A will also precede B in the output list. If the lists aren't consistent
597 (e.g., some list contains A followed by B, and another contains B followed
e2838dc5
MW
598 by A) then an error of type `inconsistent-merge-error' is signalled. The
599 offending items are filtered for presentation through the PRESENT function
600 before being attached to the condition, so as to produce a more useful
601 diagnostic message.
dea4d055
MW
602
603 Item equality is determined by TEST.
604
605 If there is an ambiguity at any point -- i.e., a choice between two or
606 more possible next items to emit -- then PICK is called to arbitrate.
607 PICK is called with two arguments: the list of candidate next items, and
e8c5a09e
MW
608 the current output list. It should return one of the candidate items.
609 The order of the candidates in the list given to the PICK function
610 reflects their order in the input LISTS: item A will precede item B in the
611 candidates list if and only if an occurrence of A appears in an earlier
612 input list than any occurrence of item B. (This completely determines the
613 order of the candidates: it is not possible that two candidates appear in
c5ef873a
MW
614 the same input list, since that would resolve the ambiguity between them.)
615 If PICK is omitted then the item chosen is the one appearing in the
616 earliest of the input lists: i.e., effectively, the default PICK function
617 is
e8c5a09e
MW
618
619 (lambda (candidates output-so-far)
620 (declare (ignore output-so-far))
621 (car candidates))
dea4d055
MW
622
623 The primary use of this function is in computing class precedence lists.
624 By building the input lists and selecting the PICK function appropriately,
625 a variety of different CPL algorithms can be implemented."
626
022a3499
MW
627 (do ((lb (make-list-builder)))
628 ((null lists) (lbuild-list lb))
dea4d055
MW
629
630 ;; The candidate items are the ones at the front of the input lists.
631 ;; Gather them up, removing duplicates. If a candidate is somewhere in
632 ;; one of the other lists other than at the front then we reject it. If
633 ;; we've just rejected everything, then we can make no more progress and
634 ;; the input lists were inconsistent.
e8c5a09e
MW
635 (let* ((candidates (delete-duplicates (mapcar #'car lists)
636 :test test :from-end t))
dea4d055
MW
637 (leasts (remove-if (lambda (item)
638 (some (lambda (list)
639 (member item (cdr list) :test test))
640 lists))
641 candidates))
642 (winner (cond ((null leasts)
643 (error 'inconsistent-merge-error
38b78e87
MW
644 :candidates candidates
645 :present present))
dea4d055
MW
646 ((null (cdr leasts))
647 (car leasts))
648 (pick
649 (funcall pick leasts (lbuild-list lb)))
650 (t (car leasts)))))
651
652 ;; Check that the PICK function isn't conning us.
653 (assert (member winner leasts :test test))
654
655 ;; Update the output list and remove the winning item from the input
656 ;; lists. We know that it must be at the front of each input list
657 ;; containing it. At this point, we discard input lists entirely when
658 ;; they run out of entries. The loop ends when there are no more input
659 ;; lists left, i.e., when we've munched all of the input items.
660 (lbuild-add lb winner)
661 (setf lists (delete nil (mapcar (lambda (list)
662 (if (funcall test winner (car list))
663 (cdr list)
664 list))
665 lists))))))
666
667(export 'categorize)
668(defmacro categorize ((itemvar items &key bind) categories &body body)
669 "Categorize ITEMS into lists and invoke BODY.
670
671 The ITEMVAR is a symbol; as the macro iterates over the ITEMS, ITEMVAR
672 will contain the current item. The BIND argument is a list of LET*-like
673 clauses. The CATEGORIES are a list of clauses of the form (SYMBOL
674 PREDICATE).
675
676 The behaviour of the macro is as follows. ITEMVAR is assigned (not
677 bound), in turn, each item in the list ITEMS. The PREDICATEs in the
678 CATEGORIES list are evaluated in turn, in an environment containing
679 ITEMVAR and the BINDings, until one of them evaluates to a non-nil value.
680 At this point, the item is assigned to the category named by the
681 corresponding SYMBOL. If none of the PREDICATEs returns non-nil then an
682 error is signalled; a PREDICATE consisting only of T will (of course)
683 match anything; it is detected specially so as to avoid compiler warnings.
684
685 Once all of the ITEMS have been categorized in this fashion, the BODY is
686 evaluated as an implicit PROGN. For each SYMBOL naming a category, a
687 variable named after that symbol will be bound in the BODY's environment
688 to a list of the items in that category, in the same order in which they
689 were found in the list ITEMS. The final values of the macro are the final
690 values of the BODY."
691
692 (let* ((cat-names (mapcar #'car categories))
693 (cat-match-forms (mapcar #'cadr categories))
694 (cat-vars (mapcar (lambda (name) (gensym (concatenate 'string
695 (symbol-name name) "-")))
696 cat-names))
697 (items-var (gensym "ITEMS-")))
64a7e651
MW
698 `(let (,@(mapcar (lambda (cat-var) (list cat-var nil)) cat-vars))
699 (let ((,items-var ,items))
700 (dolist (,itemvar ,items-var)
701 (let* ,bind
702 (cond ,@(mapcar (lambda (cat-match-form cat-var)
703 `(,cat-match-form
704 (push ,itemvar ,cat-var)))
705 cat-match-forms cat-vars)
706 ,@(and (not (member t cat-match-forms))
707 `((t (error "Failed to categorize ~A"
708 ,itemvar))))))))
dea4d055
MW
709 (let ,(mapcar (lambda (name var)
710 `(,name (nreverse ,var)))
711 cat-names cat-vars)
712 ,@body))))
713
42291726
MW
714(export 'partial-order-minima)
715(defun partial-order-minima (items order)
716 "Return a list of minimal items according to the non-strict partial ORDER.
717
718 The ORDER function describes the partial order: (funcall ORDER X Y) should
719 return true if X precedes or is equal to Y in the order."
720 (reduce (lambda (tops this)
721 (let ((new nil) (keep t))
722 (dolist (top tops)
723 (cond ((funcall order top this)
724 (setf keep nil)
725 (push top new))
726 ((not (funcall order this top))
727 (push top new))))
728 (nreverse (if keep (cons this new) new))))
729 items
730 :initial-value nil))
731
64cbfb65
MW
732(export 'find-duplicates)
733(defun find-duplicates (report sequence &key (key #'identity) (test #'eql))
734 "Call REPORT on each pair of duplicate items in SEQUENCE.
735
736 Duplicates are determined according to the KEY and TEST funcitons."
737 (when (symbolp test) (setf test (symbol-function test)))
738 (cond ((zerop (length sequence)) nil)
739 ((or (eq test #'eq)
740 (eq test #'eql)
741 (eq test #'equal)
742 (eq test #'equalp))
743 (let ((seen (make-hash-table :test test)))
744 (map nil (lambda (item)
745 (let ((k (funcall key item)))
746 (multiple-value-bind (previous matchp)
747 (gethash k seen)
748 (if matchp (funcall report item previous)
749 (setf (gethash k seen) item)))))
750 sequence)))
751 ((listp sequence)
9a3cb461
MW
752 (do ((tail sequence (cdr tail))
753 (i 0 (1+ i)))
754 ((endp tail))
755 (let* ((item (car tail))
756 (match (find (funcall key item) sequence
757 :test test :key key :end i)))
758 (when match (funcall report item match)))))
64cbfb65
MW
759 ((vectorp sequence)
760 (dotimes (i (length sequence))
761 (let* ((item (aref sequence i))
762 (pos (position (funcall key item) sequence
9a3cb461 763 :key key :test test :end i)))
64cbfb65
MW
764 (when pos (funcall report item (aref sequence pos))))))
765 (t
766 (error 'type-error :datum sequence :expected-type 'sequence))))
767
dea4d055
MW
768;;;--------------------------------------------------------------------------
769;;; Strings and characters.
770
771(export 'frob-identifier)
772(defun frob-identifier (string &key (swap-case t) (swap-hyphen t))
773 "Twiddles the case of STRING.
774
775 If all the letters in STRING are uppercase, and SWAP-CASE is true, then
776 switch them to lowercase; if they're all lowercase then switch them to
777 uppercase. If there's a mix then leave them all alone. At the same time,
778 if there are underscores but no hyphens, and SWAP-HYPHEN is true, then
779 switch them to hyphens, if there are hyphens and no underscores, switch
780 them underscores, and if there are both then leave them alone.
781
782 This is an invertible transformation, which turns vaguely plausible Lisp
783 names into vaguely plausible C names and vice versa. Lisp names with
784 `funny characters' like stars and percent signs won't be any use, of
785 course."
786
787 ;; Work out what kind of a job we've got to do. Gather flags: bit 0 means
788 ;; there are upper-case letters; bit 1 means there are lower-case letters;
789 ;; bit 2 means there are hyphens; bit 3 means there are underscores.
790 ;;
791 ;; Consequently, (logxor flags (ash flags 1)) is interesting: bit 1 is set
792 ;; if we have to frob case; bit 3 is set if we have to swap hyphens and
793 ;; underscores. So use this to select functions which do bits of the
794 ;; mapping, and then compose them together.
795 (let* ((flags (reduce (lambda (state ch)
796 (logior state
797 (cond ((upper-case-p ch) 1)
798 ((lower-case-p ch) 2)
799 ((char= ch #\-) 4)
800 ((char= ch #\_) 8)
801 (t 0))))
802 string
803 :initial-value 0))
804 (mask (logxor flags (ash flags 1)))
805 (letter (cond ((or (not swap-case) (not (logbitp 1 mask)))
806 (constantly nil))
807 ((logbitp 0 flags)
808 (lambda (ch)
809 (and (alpha-char-p ch) (char-downcase ch))))
810 (t
811 (lambda (ch)
812 (and (alpha-char-p ch) (char-upcase ch))))))
813 (uscore-hyphen (cond ((or (not (logbitp 3 mask)) (not swap-hyphen))
814 (constantly nil))
815 ((logbitp 2 flags)
816 (lambda (ch) (and (char= ch #\-) #\_)))
817 (t
818 (lambda (ch) (and (char= ch #\_) #\-))))))
819
820 (if (logbitp 3 (logior mask (ash mask 2)))
821 (map 'string (lambda (ch)
822 (or (funcall letter ch)
823 (funcall uscore-hyphen ch)
824 ch))
825 string)
826 string)))
827
828(export 'whitespace-char-p)
829(declaim (inline whitespace-char-p))
830(defun whitespace-char-p (char)
831 "Returns whether CHAR is a whitespace character.
832
833 Whitespaceness is determined relative to the compile-time readtable, which
834 is probably good enough for most purposes."
835 (case char
836 (#.(loop for i below char-code-limit
837 for ch = (code-char i)
838 unless (with-input-from-string (in (string ch))
839 (peek-char t in nil))
840 collect ch) t)
841 (t nil)))
842
843(export 'update-position)
844(declaim (inline update-position))
845(defun update-position (char line column)
846 "Updates LINE and COLUMN appropriately for having read the character CHAR.
847
848 Returns the new LINE and COLUMN numbers."
849 (case char
850 ((#\newline #\vt #\page)
851 (values (1+ line) 0))
852 ((#\tab)
853 (values line (logandc2 (+ column 8) 7)))
854 (t
855 (values line (1+ column)))))
856
857(export 'backtrack-position)
858(declaim (inline backtrack-position))
859(defun backtrack-position (char line column)
860 "Updates LINE and COLUMN appropriately for having unread CHAR.
861
862 Well, actually an approximation for it; it will likely be wrong if the
863 last character was a tab. But when the character is read again, it will
864 be correct."
865
866 ;; This isn't perfect: if the character doesn't actually match what was
867 ;; really read then it might not actually be possible: for example, if we
868 ;; push back a newline while in the middle of a line, or a tab while not at
869 ;; a tab stop. In that case, we'll just lose, but hopefully not too badly.
870 (case char
871
872 ;; In the absence of better ideas, I'll set the column number to zero.
873 ;; This is almost certainly wrong, but with a little luck nobody will ask
874 ;; and it'll be all right soon.
875 ((#\newline #\vt #\page) (values (1- line) 0))
876
877 ;; Winding back a single space is sufficient. If the position is
878 ;; currently on a tab stop then it'll advance back here next time. If
879 ;; not, we're going to lose anyway because the previous character
880 ;; certainly couldn't have been a tab.
881 (#\tab (values line (1- column)))
882
883 ;; Anything else: just decrement the column and cross fingers.
884 (t (values line (1- column)))))
885
886;;;--------------------------------------------------------------------------
887;;; Functions.
888
889(export 'compose)
b0d4e74f 890(defun compose (&rest functions)
dea4d055
MW
891 "Composition of functions. Functions are applied left-to-right.
892
893 This is the reverse order of the usual mathematical notation, but I find
bf090e02
MW
894 it easier to read. It's also slightly easier to work with in programs.
895 That is, (compose F1 F2 ... Fn) is what a category theorist might write as
896 F1 ; F2 ; ... ; Fn, rather than F1 o F2 o ... o Fn."
897
dea4d055
MW
898 (labels ((compose1 (func-a func-b)
899 (lambda (&rest args)
900 (multiple-value-call func-b (apply func-a args)))))
b0d4e74f
MW
901 (if (null functions) #'values
902 (reduce #'compose1 (cdr functions)
903 :initial-value (car functions)))))
dea4d055
MW
904
905;;;--------------------------------------------------------------------------
c34b237d
MW
906;;; Variables.
907
908(export 'defvar-unbound)
909(defmacro defvar-unbound (var doc)
910 "Make VAR a special variable with documentation DOC, but leave it unbound."
911 `(eval-when (:compile-toplevel :load-toplevel :execute)
912 (defvar ,var)
913 (setf (documentation ',var 'variable) ',doc)
914 ',var))
915
916;;;--------------------------------------------------------------------------
dea4d055
MW
917;;; Symbols.
918
919(export 'symbolicate)
920(defun symbolicate (&rest symbols)
921 "Return a symbol named after the concatenation of the names of the SYMBOLS.
922
3109662a 923 The symbol is interned in the current `*package*'. Trad."
dea4d055
MW
924 (intern (apply #'concatenate 'string (mapcar #'symbol-name symbols))))
925
926;;;--------------------------------------------------------------------------
927;;; Object printing.
928
929(export 'maybe-print-unreadable-object)
930(defmacro maybe-print-unreadable-object
931 ((object stream &rest args) &body body)
932 "Print helper for usually-unreadable objects.
933
3109662a 934 If `*print-escape*' is set then print OBJECT unreadably using BODY.
dea4d055
MW
935 Otherwise just print using BODY."
936 (with-gensyms (print)
937 `(flet ((,print () ,@body))
938 (if *print-escape*
939 (print-unreadable-object (,object ,stream ,@args)
940 (,print))
941 (,print)))))
942
08b6e064
MW
943(export 'print-ugly-stuff)
944(defun print-ugly-stuff (stream func)
945 "Print not-pretty things to the stream underlying STREAM.
946
947 The Lisp pretty-printing machinery, notably `pprint-logical-block', may
948 interpose additional streams between its body and the original target
949 stream. This makes it difficult to make use of the underlying stream's
950 special features, whatever they might be."
951
952 ;; This is unpleasant. Hacky hacky.
953 #.(or #+sbcl '(if (typep stream 'sb-pretty:pretty-stream)
954 (let ((target (sb-pretty::pretty-stream-target stream)))
955 (pprint-newline :mandatory stream)
956 (funcall func target))
957 (funcall func stream))
958 #+cmu '(if (typep stream 'pp:pretty-stream)
959 (let ((target (pp::pretty-stream-target stream)))
960 (pprint-newline :mandatory stream)
961 (funcall func target))
962 (funcall func stream))
963 '(funcall func stream)))
964
dea4d055
MW
965;;;--------------------------------------------------------------------------
966;;; Iteration macros.
967
968(export 'dosequence)
969(defmacro dosequence ((var seq &key (start 0) (end nil) indexvar)
970 &body body
971 &environment env)
972 "Macro for iterating over general sequences.
973
974 Iterates over a (sub)sequence SEQ, delimited by START and END (which are
975 evaluated). For each item of SEQ, BODY is invoked with VAR bound to the
976 item, and INDEXVAR (if requested) bound to the item's index. (Note that
977 this is different from most iteration constructs in Common Lisp, which
978 work by mutating the variable.)
979
980 The loop is surrounded by an anonymous BLOCK and the loop body forms an
981 implicit TAGBODY, as is usual. There is no result-form, however."
982
bacaaec3
MW
983 (once-only (:environment env start end)
984 (with-gensyms ((seqvar "SEQ-") (ivar "INDEX-")
985 (endvar "END-") (bodyfunc "BODY-"))
b8c698ee
MW
986 (multiple-value-bind (docs decls body) (parse-body body :docp nil)
987 (declare (ignore docs))
988
989 (flet ((loopguts (indexp listp endvar)
990 ;; Build a DO-loop to do what we want.
991 (let* ((do-vars nil)
992 (end-condition (if endvar
993 `(>= ,ivar ,endvar)
bacaaec3 994 `(endp ,seqvar)))
b8c698ee 995 (item (if listp
bacaaec3
MW
996 `(car ,seqvar)
997 `(aref ,seqvar ,ivar)))
b8c698ee
MW
998 (body-call `(,bodyfunc ,item)))
999 (when listp
bacaaec3 1000 (push `(,seqvar (nthcdr ,start ,seqvar) (cdr ,seqvar))
b8c698ee
MW
1001 do-vars))
1002 (when indexp
1003 (push `(,ivar ,start (1+ ,ivar)) do-vars))
1004 (when indexvar
1005 (setf body-call (append body-call (list ivar))))
1006 `(do ,do-vars (,end-condition) ,body-call))))
1007
1008 `(block nil
bacaaec3
MW
1009 (let ((,seqvar ,seq))
1010 (flet ((,bodyfunc (,var ,@(and indexvar `(,indexvar)))
1011 ,@decls
1012 (tagbody ,@body)))
1013 (etypecase ,seqvar
1014 (vector
1015 (let ((,endvar (or ,end (length ,seqvar))))
1016 ,(loopguts t nil endvar)))
1017 (list
1018 (if ,end
1019 ,(loopguts t t end)
1020 ,(loopguts indexvar t nil))))))))))))
dea4d055
MW
1021
1022;;;--------------------------------------------------------------------------
4b8e5c03
MW
1023;;; Structure accessor hacks.
1024
1025(export 'define-access-wrapper)
1026(defmacro define-access-wrapper (from to &key read-only)
1027 "Make (FROM THING) work like (TO THING).
1028
1029 If not READ-ONLY, then also make (setf (FROM THING) VALUE) work like
1030 (setf (TO THING) VALUE).
1031
1032 This is mostly useful for structure slot accessors where the slot has to
1033 be given an unpleasant name to avoid it being an external symbol."
1034 `(progn
1035 (declaim (inline ,from ,@(and (not read-only) `((setf ,from)))))
1036 (defun ,from (object)
1037 (,to object))
1038 ,@(and (not read-only)
1039 `((defun (setf ,from) (value object)
1040 (setf (,to object) value))))))
1041
1042;;;--------------------------------------------------------------------------
db6c3279
MW
1043;;; Condition and error utilities.
1044
1045(export 'designated-condition)
1046(defun designated-condition (default-type datum arguments
1047 &key allow-pointless-arguments)
1048 "Return the condition designated by DATUM and ARGUMENTS.
1049
1050 DATUM and ARGUMENTS together are a `condition designator' of (some
1051 supertype of) DEFAULT-TYPE; return the condition so designated."
1052 (typecase datum
1053 (condition
1054 (unless (or allow-pointless-arguments (null arguments))
1055 (error "Argument list provided with specific condition"))
1056 datum)
1057 (symbol
1058 (apply #'make-condition datum arguments))
1059 ((or string function)
1060 (make-condition default-type
1061 :format-control datum
1062 :format-arguments arguments))
1063 (t
1064 (error "Unexpected condition designator datum ~S" datum))))
1065
f7b60deb
MW
1066(export 'simple-control-error)
1067(define-condition simple-control-error (control-error simple-error)
1068 ())
1069
1070(export 'invoke-associated-restart)
1071(defun invoke-associated-restart (restart condition &rest arguments)
1072 "Invoke the active RESTART associated with CONDITION, with the ARGUMENTS.
1073
1074 Find an active restart designated by RESTART; if CONDITION is not nil,
1075 then restrict the search to restarts associated with CONDITION, and
1076 restarts not associated with any condition. If no such restart is found
1077 then signal an error of type `control-error'; otherwise invoke the restart
1078 with the given ARGUMENTS."
1079 (apply #'invoke-restart
1080 (or (find-restart restart condition)
1081 (error 'simple-control-error
1082 :format-control "~:[Restart ~S is not active~;~
1083 No active `~(~A~)' restart~]~
1084 ~@[ for condition ~S~]"
1085 :format-arguments (list (symbolp restart)
1086 restart
1087 condition)))
1088 arguments))
1089
c884ec24
MW
1090(export '(enclosing-condition enclosed-condition))
1091(define-condition enclosing-condition (condition)
1092 ((%enclosed-condition :initarg :condition :type condition
1093 :reader enclosed-condition))
1094 (:documentation
1095 "A condition which encloses another condition
1096
1097 This is useful if one wants to attach additional information to an
1098 existing condition. The enclosed condition can be obtained using the
1099 `enclosed-condition' function.")
1100 (:report (lambda (condition stream)
1101 (princ (enclosed-condition condition) stream))))
1102
1103(export 'information)
1104(define-condition information (condition)
1105 ())
1106
1107(export 'simple-information)
1108(define-condition simple-information (simple-condition information)
1109 ())
1110
1111(export 'info)
1112(defun info (datum &rest arguments)
1113 "Report some useful diagnostic information.
1114
1115 Establish a simple restart named `noted', and signal the condition of type
1116 `information' designated by DATUM and ARGUMENTS. Return non-nil if the
1117 restart was invoked, otherwise nil."
1118 (restart-case
1119 (signal (designated-condition 'simple-information datum arguments))
1120 (noted () :report "Noted." t)))
1121
1122(export 'noted)
1123(defun noted (&optional condition)
1124 "Invoke the `noted' restart, possibly associated with the given CONDITION."
1125 (invoke-associated-restart 'noted condition))
1126
1127(export 'promiscuous-cerror)
1128(defun promiscuous-cerror (continue-string datum &rest arguments)
1129 "Like standard `cerror', but robust against sneaky changes of conditions.
1130
1131 It seems that `cerror' (well, at least the version in SBCL) is careful
1132 to limit its restart to the specific condition it signalled. But that's
1133 annoying, because `sod-parser:with-default-error-location' substitutes
1134 different conditions carrying the error-location information."
1135 (restart-case (apply #'error datum arguments)
1136 (continue ()
1137 :report (lambda (stream)
1138 (apply #'format stream continue-string datum arguments))
1139 nil)))
1140
1141(export 'cerror*)
1142(defun cerror* (datum &rest arguments)
1143 (apply #'promiscuous-cerror "Continue" datum arguments))
1144
db6c3279 1145;;;--------------------------------------------------------------------------
dea4d055
MW
1146;;; CLOS hacking.
1147
1148(export 'default-slot)
1149(defmacro default-slot ((instance slot &optional (slot-names t))
1150 &body value
1151 &environment env)
1152 "If INSTANCE's slot named SLOT is unbound, set it to VALUE.
1153
1154 Only set SLOT if it's listed in SLOT-NAMES, or SLOT-NAMES is `t' (i.e., we
1155 obey the `shared-initialize' protocol). SLOT-NAMES defaults to `t', so
1156 you can use it in `initialize-instance' or similar without ill effects.
1157 Both INSTANCE and SLOT are evaluated; VALUE is an implicit progn and only
1158 evaluated if it's needed."
1159
1160 (once-only (:environment env instance slot slot-names)
1161 `(when ,(if (eq slot-names t)
1162 `(not (slot-boundp ,instance ,slot))
1163 `(and (not (slot-boundp ,instance ,slot))
1164 (or (eq ,slot-names t)
1165 (member ,slot ,slot-names))))
1166 (setf (slot-value ,instance ,slot)
1167 (progn ,@value)))))
1168
141283ff
MW
1169(export 'define-on-demand-slot)
1170(defmacro define-on-demand-slot (class slot (instance) &body body)
1171 "Defines a slot which computes its initial value on demand.
1172
1173 Sets up the named SLOT of CLASS to establish its value as the implicit
1174 progn BODY, by defining an appropriate method on `slot-unbound'."
b8c698ee
MW
1175 (multiple-value-bind (docs decls body) (parse-body body)
1176 (with-gensyms (classvar slotvar)
1177 `(defmethod slot-unbound
1178 (,classvar (,instance ,class) (,slotvar (eql ',slot)))
1179 ,@docs ,@decls
1180 (declare (ignore ,classvar))
fc09e191 1181 (setf (slot-value ,instance ',slot) (block ,slot ,@body))))))
141283ff 1182
dea4d055 1183;;;----- That's all, folks --------------------------------------------------