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