fix force-output/finish-output thinko in io.lisp
[alexandria.git] / macros.lisp
blob309788b3ae9d7709457798964c6f773932034808
1 (in-package :alexandria)
3 (defmacro with-gensyms (names &body forms)
4 "Binds each variable named by a symbol in NAMES to a unique symbol around
5 FORMS. Each of NAMES must either be either a symbol, or of the form:
7 (symbol string-designator)
9 Bare symbols appearing in NAMES are equivalent to:
11 (symbol symbol)
13 The string-designator is used as the argument to GENSYM when constructing the
14 unique symbol the named variable will be bound to."
15 `(let ,(mapcar (lambda (name)
16 (multiple-value-bind (symbol string)
17 (etypecase name
18 (symbol
19 (values name (symbol-name name)))
20 ((cons symbol (cons string-designator null))
21 (values (first name) (string (second name)))))
22 `(,symbol (gensym ,string))))
23 names)
24 ,@forms))
26 (defmacro with-unique-names (names &body forms)
27 "Alias for WITH-GENSYMS."
28 `(with-gensyms ,names ,@forms))
30 (defmacro once-only (specs &body forms)
31 "Each SPEC must be either a NAME, or a (NAME INITFORM), with plain
32 NAME using the named variable as initform.
34 Evaluates FORMS with names rebound to temporary variables, ensuring
35 that each is evaluated only once.
37 Example:
38 (defmacro cons1 (x) (once-only (x) `(cons ,x ,x)))
39 (let ((y 0)) (cons1 (incf y))) => (1 . 1)"
40 (let ((gensyms (make-gensym-list (length specs) "ONCE-ONLY"))
41 (names-and-forms (mapcar (lambda (spec)
42 (etypecase spec
43 (list
44 (destructuring-bind (name form) spec
45 (cons name form)))
46 (symbol
47 (cons spec spec))))
48 specs)))
49 ;; bind in user-macro
50 `(let ,(mapcar (lambda (g n) (list g `(gensym ,(string (car n)))))
51 gensyms names-and-forms)
52 ;; bind in final expansion
53 `(let (,,@(mapcar (lambda (g n)
54 ``(,,g ,,(cdr n)))
55 gensyms names-and-forms))
56 ;; bind in user-macro
57 ,(let ,(mapcar (lambda (n g) (list (car n) g))
58 names-and-forms gensyms)
59 ,@forms)))))
61 (defun parse-body (body &key documentation whole)
62 "Parses BODY into (values remaining-forms declarations doc-string).
63 Documentation strings are recognized only if DOCUMENTATION is true.
64 Syntax errors in body are signalled and WHOLE is used in the signal
65 arguments when given."
66 (let ((doc nil)
67 (decls nil)
68 (current nil))
69 (tagbody
70 :declarations
71 (setf current (car body))
72 (when (and documentation (stringp current) (cdr body))
73 (if doc
74 (error "Too many documentation strings in ~S." (or whole body))
75 (setf doc (pop body)))
76 (go :declarations))
77 (when (and (listp current) (eql (first current) 'declare))
78 (push (pop body) decls)
79 (go :declarations)))
80 (values body (nreverse decls) doc)))
82 (defun parse-ordinary-lambda-list (lambda-list)
83 "Parses an ordinary lambda-list, returning as multiple values:
85 1. Required parameters.
86 2. Optional parameter specifications, normalized into form (NAME INIT SUPPLIEDP)
87 where SUPPLIEDP is NIL if not present.
88 3. Name of the rest parameter, or NIL.
89 4. Keyword parameter specifications, normalized into form ((KEYWORD-NAME NAME) INIT SUPPLIEDP)
90 where SUPPLIEDP is NIL if not present.
91 5. Boolean indicating &ALLOW-OTHER-KEYS presence.
92 6. &AUX parameter specifications, normalized into form (NAME INIT).
94 Signals a PROGRAM-ERROR is the lambda-list is malformed."
95 (let ((state :required)
96 (allow-other-keys nil)
97 (auxp nil)
98 (required nil)
99 (optional nil)
100 (rest nil)
101 (keys nil)
102 (aux nil))
103 (labels ((fail (elt)
104 (simple-program-error "Misplaced ~S in ordinary lambda-list:~% ~S"
105 elt lambda-list))
106 (check-variable (elt what)
107 (unless (and (symbolp elt) (not (constantp elt)))
108 (simple-program-error "Invalid ~A ~S in ordinary lambda-list:~% ~S"
109 what elt lambda-list)))
110 (check-spec (spec what)
111 (destructuring-bind (init suppliedp) spec
112 (declare (ignore init))
113 (check-variable suppliedp what))))
114 (dolist (elt lambda-list)
115 (case elt
116 (&optional
117 (if (eq state :required)
118 (setf state elt)
119 (fail elt)))
120 (&rest
121 (if (member state '(:required &optional))
122 (setf state elt)
123 (progn
124 (break "state=~S" state)
125 (fail elt))))
126 (&key
127 (if (member state '(:required &optional :after-rest))
128 (setf state elt)
129 (fail elt)))
130 (&allow-other-keys
131 (if (eq state '&key)
132 (setf allow-other-keys t
133 state elt)
134 (fail elt)))
135 (&aux
136 (cond ((eq state '&rest)
137 (fail elt))
138 (auxp
139 (simple-program-error "Multiple ~S in ordinary lambda-list:~% ~S"
140 elt lambda-list))
142 (setf auxp t
143 state elt))
145 (otherwise
146 (when (member elt '#.(set-difference lambda-list-keywords
147 '(&optional &rest &key &allow-other-keys &aux)))
148 (simple-program-error
149 "Bad lambda-list keyword ~S in ordinary lambda-list:~% ~S"
150 elt lambda-list))
151 (case state
152 (:required
153 (check-variable elt "required parameter")
154 (push elt required))
155 (&optional
156 (cond ((consp elt)
157 (destructuring-bind (name &rest tail) elt
158 (check-variable name "optional parameter")
159 (if (cdr tail)
160 (check-spec tail "optional-supplied-p parameter")
161 (setf elt (append elt '(nil))))))
163 (check-variable elt "optional parameter")
164 (setf elt (cons elt '(nil nil)))))
165 (push elt optional))
166 (&rest
167 (check-variable elt "rest parameter")
168 (setf rest elt
169 state :after-rest))
170 (&key
171 (cond ((consp elt)
172 (destructuring-bind (var-or-kv &rest tail) elt
173 (cond ((consp var-or-kv)
174 (destructuring-bind (keyword var) var-or-kv
175 (unless (symbolp keyword)
176 (simple-program-error "Invalid keyword name ~S in ordinary ~
177 lambda-list:~% ~S"
178 keyword lambda-list))
179 (check-variable var "keyword parameter")))
181 (check-variable var-or-kv "keyword parameter")
182 (setf var-or-kv (list (make-keyword var-or-kv) var-or-kv))))
183 (if (cdr tail)
184 (check-spec tail "keyword-supplied-p parameter")
185 (setf tail (append tail '(nil))))
186 (setf elt (cons var-or-kv tail))))
188 (check-variable elt "keyword parameter")
189 (setf elt (list (list (make-keyword elt) elt) nil nil))))
190 (push elt keys))
191 (&aux
192 (if (consp elt)
193 (destructuring-bind (var &optional init) elt
194 (declare (ignore init))
195 (check-variable var "&aux parameter"))
196 (check-variable elt "&aux parameter"))
197 (push elt aux))
199 (simple-program-error "Invalid ordinary lambda-list:~% ~S" lambda-list)))))))
200 (values (nreverse required) (nreverse optional) rest (nreverse keys)
201 allow-other-keys (nreverse aux))))