1 ;;;; the LOOP iteration macro
3 ;;;; This software is part of the SBCL system. See the README file for
6 ;;;; This code was modified by William Harold Newman beginning
7 ;;;; 19981106, originally to conform to the new SBCL bootstrap package
8 ;;;; system and then subsequently to address other cross-compiling
9 ;;;; bootstrap issues, SBCLification (e.g. DECLARE used to check
10 ;;;; argument types), and other maintenance. Whether or not it then
11 ;;;; supported all the environments implied by the reader conditionals
12 ;;;; in the source code (e.g. #!+CLOE-RUNTIME) before that
13 ;;;; modification, it sure doesn't now. It might perhaps, by blind
14 ;;;; luck, be appropriate for some other CMU-CL-derived system, but
15 ;;;; really it only attempts to be appropriate for SBCL.
17 ;;;; This software is derived from software originally released by the
18 ;;;; Massachusetts Institute of Technology and Symbolics, Inc. Copyright and
19 ;;;; release statements follow. Later modifications to the software are in
20 ;;;; the public domain and are provided with absolutely no warranty. See the
21 ;;;; COPYING and CREDITS files for more information.
23 ;;;; Portions of LOOP are Copyright (c) 1986 by the Massachusetts Institute
24 ;;;; of Technology. All Rights Reserved.
26 ;;;; Permission to use, copy, modify and distribute this software and its
27 ;;;; documentation for any purpose and without fee is hereby granted,
28 ;;;; provided that the M.I.T. copyright notice appear in all copies and that
29 ;;;; both that copyright notice and this permission notice appear in
30 ;;;; supporting documentation. The names "M.I.T." and "Massachusetts
31 ;;;; Institute of Technology" may not be used in advertising or publicity
32 ;;;; pertaining to distribution of the software without specific, written
33 ;;;; prior permission. Notice must be given in supporting documentation that
34 ;;;; copying distribution is by permission of M.I.T. M.I.T. makes no
35 ;;;; representations about the suitability of this software for any purpose.
36 ;;;; It is provided "as is" without express or implied warranty.
38 ;;;; Massachusetts Institute of Technology
39 ;;;; 77 Massachusetts Avenue
40 ;;;; Cambridge, Massachusetts 02139
41 ;;;; United States of America
44 ;;;; Portions of LOOP are Copyright (c) 1989, 1990, 1991, 1992 by Symbolics,
45 ;;;; Inc. All Rights Reserved.
47 ;;;; Permission to use, copy, modify and distribute this software and its
48 ;;;; documentation for any purpose and without fee is hereby granted,
49 ;;;; provided that the Symbolics copyright notice appear in all copies and
50 ;;;; that both that copyright notice and this permission notice appear in
51 ;;;; supporting documentation. The name "Symbolics" may not be used in
52 ;;;; advertising or publicity pertaining to distribution of the software
53 ;;;; without specific, written prior permission. Notice must be given in
54 ;;;; supporting documentation that copying distribution is by permission of
55 ;;;; Symbolics. Symbolics makes no representations about the suitability of
56 ;;;; this software for any purpose. It is provided "as is" without express
57 ;;;; or implied warranty.
59 ;;;; Symbolics, CLOE Runtime, and Minima are trademarks, and CLOE, Genera,
60 ;;;; and Zetalisp are registered trademarks of Symbolics, Inc.
63 ;;;; 8 New England Executive Park, East
64 ;;;; Burlington, Massachusetts 01803
65 ;;;; United States of America
68 (in-package "SB!LOOP")
70 ;;;; The design of this LOOP is intended to permit, using mostly the same
71 ;;;; kernel of code, up to three different "loop" macros:
73 ;;;; (1) The unextended, unextensible ANSI standard LOOP;
75 ;;;; (2) A clean "superset" extension of the ANSI LOOP which provides
76 ;;;; functionality similar to that of the old LOOP, but "in the style of"
77 ;;;; the ANSI LOOP. For instance, user-definable iteration paths, with a
78 ;;;; somewhat cleaned-up interface.
80 ;;;; (3) Extensions provided in another file which can make this LOOP
81 ;;;; kernel behave largely compatibly with the Genera-vintage LOOP macro,
82 ;;;; with only a small addition of code (instead of two whole, separate,
85 ;;;; Each of the above three LOOP variations can coexist in the same LISP
88 ;;;; KLUDGE: In SBCL, we only really use variant (1), and any generality
89 ;;;; for the other variants is wasted. -- WHN 20000121
91 ;;;; FIXME: the STEP-FUNCTION stuff in the code seems to've been
92 ;;;; intended to support code which was conditionalized with
93 ;;;; LOOP-PREFER-POP (not true on CMU CL) and which has since been
94 ;;;; removed. Thus, STEP-FUNCTION stuff could probably be removed too.
96 ;;;; list collection macrology
98 (sb!int:defmacro-mundanely with-loop-list-collection-head
99 ((head-var tail-var &optional user-head-var) &body body)
100 (let ((l (and user-head-var (list (list user-head-var nil)))))
101 `(let* ((,head-var (list nil)) (,tail-var ,head-var) ,@l)
104 (sb!int:defmacro-mundanely loop-collect-rplacd
105 (&environment env (head-var tail-var &optional user-head-var) form)
106 (setq form (sb!xc:macroexpand form env))
107 (flet ((cdr-wrap (form n)
109 (do () ((<= n 4) (setq form `(,(case n
115 (setq form `(cddddr ,form) n (- n 4)))))
116 (let ((tail-form form) (ncdrs nil))
117 ;; Determine whether the form being constructed is a list of known
120 (cond ((eq (car form) 'list)
121 (setq ncdrs (1- (length (cdr form)))))
122 ((member (car form) '(list* cons))
123 (when (and (cddr form) (member (car (last form)) '(nil 'nil)))
124 (setq ncdrs (- (length (cdr form)) 2))))))
127 `(when (setf (cdr ,tail-var) ,tail-form)
128 (setq ,tail-var (last (cdr ,tail-var)))))
129 ((< ncdrs 0) (return-from loop-collect-rplacd nil))
131 ;; @@@@ Here we have a choice of two idioms:
132 ;; (RPLACD TAIL (SETQ TAIL TAIL-FORM))
133 ;; (SETQ TAIL (SETF (CDR TAIL) TAIL-FORM)).
134 ;; Genera and most others I have seen do better with the
136 `(rplacd ,tail-var (setq ,tail-var ,tail-form)))
137 (t `(setq ,tail-var ,(cdr-wrap `(setf (cdr ,tail-var)
140 ;; If not using locatives or something similar to update the
141 ;; user's head variable, we've got to set it... It's harmless
142 ;; to repeatedly set it unconditionally, and probably faster
147 (setq ,user-head-var (cdr ,head-var)))))
150 (sb!int:defmacro-mundanely loop-collect-answer (head-var
151 &optional user-head-var)
155 ;;;; maximization technology
158 The basic idea of all this minimax randomness here is that we have to
159 have constructed all uses of maximize and minimize to a particular
160 "destination" before we can decide how to code them. The goal is to not
161 have to have any kinds of flags, by knowing both that (1) the type is
162 something which we can provide an initial minimum or maximum value for
163 and (2) know that a MAXIMIZE and MINIMIZE are not being combined.
165 SO, we have a datastructure which we annotate with all sorts of things,
166 incrementally updating it as we generate loop body code, and then use
167 a wrapper and internal macros to do the coding when the loop has been
171 (defstruct (loop-minimax
172 (:constructor make-loop-minimax-internal)
182 (defvar *loop-minimax-type-infinities-alist*
183 ;; FIXME: Now that SBCL supports floating point infinities again, we
184 ;; should have floating point infinities here, as cmucl-2.4.8 did.
185 '((fixnum most-positive-fixnum most-negative-fixnum)))
187 (defun make-loop-minimax (answer-variable type)
188 (let ((infinity-data (cdr (assoc type
189 *loop-minimax-type-infinities-alist*
190 :test #'sb!xc:subtypep))))
191 (make-loop-minimax-internal
192 :answer-variable answer-variable
194 :temp-variable (gensym "LOOP-MAXMIN-TEMP-")
195 :flag-variable (and (not infinity-data)
196 (gensym "LOOP-MAXMIN-FLAG-"))
198 :infinity-data infinity-data)))
200 (defun loop-note-minimax-operation (operation minimax)
201 (pushnew (the symbol operation) (loop-minimax-operations minimax))
202 (when (and (cdr (loop-minimax-operations minimax))
203 (not (loop-minimax-flag-variable minimax)))
204 (setf (loop-minimax-flag-variable minimax)
205 (gensym "LOOP-MAXMIN-FLAG-")))
208 (sb!int:defmacro-mundanely with-minimax-value (lm &body body)
209 (let ((init (loop-typed-init (loop-minimax-type lm)))
210 (which (car (loop-minimax-operations lm)))
211 (infinity-data (loop-minimax-infinity-data lm))
212 (answer-var (loop-minimax-answer-variable lm))
213 (temp-var (loop-minimax-temp-variable lm))
214 (flag-var (loop-minimax-flag-variable lm))
215 (type (loop-minimax-type lm)))
217 `(let ((,answer-var ,init) (,temp-var ,init) (,flag-var nil))
218 (declare (type ,type ,answer-var ,temp-var))
220 `(let ((,answer-var ,(if (eq which 'min)
221 (first infinity-data)
222 (second infinity-data)))
224 (declare (type ,type ,answer-var ,temp-var))
227 (sb!int:defmacro-mundanely loop-accumulate-minimax-value (lm operation form)
228 (let* ((answer-var (loop-minimax-answer-variable lm))
229 (temp-var (loop-minimax-temp-variable lm))
230 (flag-var (loop-minimax-flag-variable lm))
231 (test `(,(ecase operation
234 ,temp-var ,answer-var)))
236 (setq ,temp-var ,form)
237 (when ,(if flag-var `(or (not ,flag-var) ,test) test)
238 (setq ,@(and flag-var `(,flag-var t))
239 ,answer-var ,temp-var)))))
241 ;;;; LOOP keyword tables
244 LOOP keyword tables are hash tables string keys and a test of EQUAL.
246 The actual descriptive/dispatch structure used by LOOP is called a "loop
247 universe" contains a few tables and parameterizations. The basic idea is
248 that we can provide a non-extensible ANSI-compatible loop environment,
249 an extensible ANSI-superset loop environment, and (for such environments
250 as CLOE) one which is "sufficiently close" to the old Genera-vintage
251 LOOP for use by old user programs without requiring all of the old LOOP
257 ;;; Compare two "tokens". The first is the frob out of *LOOP-SOURCE-CODE*,
258 ;;; the second a symbol to check against.
259 (defun loop-tequal (x1 x2)
260 (and (symbolp x1) (string= x1 x2)))
262 (defun loop-tassoc (kwd alist)
263 (and (symbolp kwd) (assoc kwd alist :test #'string=)))
265 (defun loop-tmember (kwd list)
266 (and (symbolp kwd) (member kwd list :test #'string=)))
268 (defun loop-lookup-keyword (loop-token table)
269 (and (symbolp loop-token)
270 (values (gethash (symbol-name loop-token) table))))
272 (sb!int:defmacro-mundanely loop-store-table-data (symbol table datum)
273 `(setf (gethash (symbol-name ,symbol) ,table) ,datum))
275 (defstruct (loop-universe
278 keywords ; hash table, value = (fn-name . extra-data)
279 iteration-keywords ; hash table, value = (fn-name . extra-data)
280 for-keywords ; hash table, value = (fn-name . extra-data)
281 path-keywords ; hash table, value = (fn-name . extra-data)
282 type-symbols ; hash table of type SYMBOLS, test EQ,
283 ; value = CL type specifier
284 type-keywords ; hash table of type STRINGS, test EQUAL,
285 ; value = CL type spec
286 ansi ; NIL, T, or :EXTENDED
287 implicit-for-required) ; see loop-hack-iteration
288 (sb!int:def!method print-object ((u loop-universe) stream)
289 (let ((string (case (loop-universe-ansi u)
292 (:extended "extended-ANSI")
293 (t (loop-universe-ansi u)))))
294 (print-unreadable-object (u stream :type t)
295 (write-string string stream))))
297 ;;; This is the "current" loop context in use when we are expanding a
298 ;;; loop. It gets bound on each invocation of LOOP.
299 (defvar *loop-universe*)
301 (defun make-standard-loop-universe (&key keywords for-keywords
302 iteration-keywords path-keywords
303 type-keywords type-symbols ansi)
304 (declare (type (member nil t :extended) ansi))
305 (flet ((maketable (entries)
306 (let* ((size (length entries))
307 (ht (make-hash-table :size (if (< size 10) 10 size)
310 (setf (gethash (symbol-name (car x)) ht) (cadr x)))
313 :keywords (maketable keywords)
314 :for-keywords (maketable for-keywords)
315 :iteration-keywords (maketable iteration-keywords)
316 :path-keywords (maketable path-keywords)
318 :implicit-for-required (not (null ansi))
319 :type-keywords (maketable type-keywords)
320 :type-symbols (let* ((size (length type-symbols))
321 (ht (make-hash-table :size (if (< size 10) 10 size)
323 (dolist (x type-symbols)
325 (setf (gethash x ht) x)
326 (setf (gethash (car x) ht) (cadr x))))
329 ;;;; SETQ hackery, including destructuring ("DESETQ")
331 (defun loop-make-psetq (frobs)
335 (if (null (cddr frobs)) (cadr frobs)
336 `(prog1 ,(cadr frobs)
337 ,(loop-make-psetq (cddr frobs))))))))
339 (defun loop-make-desetq (var-val-pairs)
340 (if (null var-val-pairs)
342 (cons 'loop-really-desetq var-val-pairs)))
344 (defvar *loop-desetq-temporary*
345 (make-symbol "LOOP-DESETQ-TEMP"))
347 (sb!int:defmacro-mundanely loop-really-desetq (&environment env
349 (labels ((find-non-null (var)
350 ;; See whether there's any non-null thing here. Recurse
351 ;; if the list element is itself a list.
352 (do ((tail var)) ((not (consp tail)) tail)
353 (when (find-non-null (pop tail)) (return t))))
354 (loop-desetq-internal (var val &optional temp)
355 ;; returns a list of actions to be performed
359 ;; Don't lose possible side effects.
360 (if (eq (car val) 'prog1)
361 ;; These can come from PSETQ or DESETQ below.
362 ;; Throw away the value, keep the side effects.
363 ;; Special case is for handling an expanded POP.
366 (or (not (eq (car x) 'car))
367 (not (symbolp (cadr x)))
368 (not (symbolp (setq x (sb!xc:macroexpand x env)))))
373 (let* ((car (car var))
375 (car-non-null (find-non-null car))
376 (cdr-non-null (find-non-null cdr)))
377 (when (or car-non-null cdr-non-null)
380 (temp (or temp *loop-desetq-temporary*))
381 (body `(,@(loop-desetq-internal car
383 (setq ,temp (cdr ,temp))
384 ,@(loop-desetq-internal cdr
388 `(,@(unless (eq temp val)
389 `((setq ,temp ,val)))
391 `((let ((,temp ,val))
394 (loop-desetq-internal car `(car ,val) temp)))))
397 `((setq ,var ,val)))))))
399 ((null var-val-pairs)
400 (if (null (cdr actions)) (car actions) `(progn ,@(nreverse actions))))
401 (setq actions (revappend
402 (loop-desetq-internal (pop var-val-pairs)
406 ;;;; LOOP-local variables
408 ;;; This is the "current" pointer into the LOOP source code.
409 (defvar *loop-source-code*)
411 ;;; This is the pointer to the original, for things like NAMED that
412 ;;; insist on being in a particular position
413 (defvar *loop-original-source-code*)
415 ;;; This is *loop-source-code* as of the "last" clause. It is used
416 ;;; primarily for generating error messages (see loop-error, loop-warn).
417 (defvar *loop-source-context*)
419 ;;; list of names for the LOOP, supplied by the NAMED clause
420 (defvar *loop-names*)
422 ;;; The macroexpansion environment given to the macro.
423 (defvar *loop-macro-environment*)
425 ;;; This holds variable names specified with the USING clause.
426 ;;; See LOOP-NAMED-VAR.
427 (defvar *loop-named-vars*)
429 ;;; LETlist-like list being accumulated for one group of parallel bindings.
432 ;;; list of declarations being accumulated in parallel with *LOOP-VARS*
433 (defvar *loop-declarations*)
435 ;;; This is used by LOOP for destructuring binding, if it is doing
436 ;;; that itself. See LOOP-MAKE-VAR.
437 (defvar *loop-desetq-crocks*)
439 ;;; list of wrapping forms, innermost first, which go immediately
440 ;;; inside the current set of parallel bindings being accumulated in
441 ;;; *LOOP-VARS*. The wrappers are appended onto a body. E.g.,
442 ;;; this list could conceivably have as its value
443 ;;; ((WITH-OPEN-FILE (G0001 G0002 ...))),
444 ;;; with G0002 being one of the bindings in *LOOP-VARS* (This is
445 ;;; why the wrappers go inside of the variable bindings).
446 (defvar *loop-wrappers*)
448 ;;; This accumulates lists of previous values of *LOOP-VARS* and
449 ;;; the other lists above, for each new nesting of bindings. See
451 (defvar *loop-bind-stack*)
453 ;;; This is simply a list of LOOP iteration variables, used for
454 ;;; checking for duplications.
455 (defvar *loop-iteration-vars*)
457 ;;; list of prologue forms of the loop, accumulated in reverse order
458 (defvar *loop-prologue*)
460 (defvar *loop-before-loop*)
462 (defvar *loop-after-body*)
464 ;;; This is T if we have emitted any body code, so that iteration
465 ;;; driving clauses can be disallowed. This is not strictly the same
466 ;;; as checking *LOOP-BODY*, because we permit some clauses such as
467 ;;; RETURN to not be considered "real" body (so as to permit the user
468 ;;; to "code" an abnormal return value "in loop").
469 (defvar *loop-emitted-body*)
471 ;;; list of epilogue forms (supplied by FINALLY generally), accumulated
473 (defvar *loop-epilogue*)
475 ;;; list of epilogue forms which are supplied after the above "user"
476 ;;; epilogue. "Normal" termination return values are provide by
477 ;;; putting the return form in here. Normally this is done using
478 ;;; LOOP-EMIT-FINAL-VALUE, q.v.
479 (defvar *loop-after-epilogue*)
481 ;;; the "culprit" responsible for supplying a final value from the
482 ;;; loop. This is so LOOP-EMIT-FINAL-VALUE can moan about multiple
483 ;;; return values being supplied.
484 (defvar *loop-final-value-culprit*)
486 ;;; If this is true, we are in some branch of a conditional. Some
487 ;;; clauses may be disallowed.
488 (defvar *loop-inside-conditional*)
490 ;;; If not NIL, this is a temporary bound around the loop for holding
491 ;;; the temporary value for "it" in things like "when (f) collect it".
492 ;;; It may be used as a supertemporary by some other things.
493 (defvar *loop-when-it-var*)
495 ;;; Sometimes we decide we need to fold together parts of the loop,
496 ;;; but some part of the generated iteration code is different for the
497 ;;; first and remaining iterations. This variable will be the
498 ;;; temporary which is the flag used in the loop to tell whether we
499 ;;; are in the first or remaining iterations.
500 (defvar *loop-never-stepped-var*)
502 ;;; list of all the value-accumulation descriptor structures in the
503 ;;; loop. See LOOP-GET-COLLECTION-INFO.
504 (defvar *loop-collection-cruft*) ; for multiple COLLECTs (etc.)
506 ;;;; code analysis stuff
508 (defun loop-constant-fold-if-possible (form &optional expected-type)
509 (let ((new-form form) (constantp nil) (constant-value nil))
510 (when (setq constantp (constantp new-form))
511 (setq constant-value (eval new-form)))
512 (when (and constantp expected-type)
513 (unless (sb!xc:typep constant-value expected-type)
514 (loop-warn "The form ~S evaluated to ~S, which was not of the anticipated type ~S."
515 form constant-value expected-type)
516 (setq constantp nil constant-value nil)))
517 (values new-form constantp constant-value)))
519 (defun loop-constantp (form)
522 ;;;; LOOP iteration optimization
524 (defvar *loop-duplicate-code*
527 (defvar *loop-iteration-flag-var*
528 (make-symbol "LOOP-NOT-FIRST-TIME"))
530 (defun loop-code-duplication-threshold (env)
531 (declare (ignore env))
532 (let (;; If we could read optimization declaration information (as
533 ;; with the DECLARATION-INFORMATION function (present in
534 ;; CLTL2, removed from ANSI standard) we could set these
535 ;; values flexibly. Without DECLARATION-INFORMATION, we have
536 ;; to set them to constants.
539 (+ 40 (* (- speed space) 10))))
541 (sb!int:defmacro-mundanely loop-body (&environment env
547 &aux rbefore rafter flagvar)
548 (unless (= (length before-loop) (length after-loop))
549 (error "LOOP-BODY called with non-synched before- and after-loop lists"))
550 ;;All our work is done from these copies, working backwards from the end:
551 (setq rbefore (reverse before-loop) rafter (reverse after-loop))
558 (member (car x) '(go return return-from)))
561 (pify (l) (if (null (cdr l)) (car l) `(progn ,@l)))
563 (let ((form `(tagbody
564 ,@(psimp (append prologue (nreverse rbefore)))
566 ,@(psimp (append main-body
570 ,@(psimp epilogue))))
571 (if flagvar `(let ((,flagvar nil)) ,form) form))))
572 (when (or *loop-duplicate-code* (not rbefore))
573 (return-from loop-body (makebody)))
574 ;; This outer loop iterates once for each not-first-time flag test
575 ;; generated plus once more for the forms that don't need a flag test.
576 (do ((threshold (loop-code-duplication-threshold env))) (nil)
577 (declare (fixnum threshold))
578 ;; Go backwards from the ends of before-loop and after-loop
579 ;; merging all the equivalent forms into the body.
580 (do () ((or (null rbefore) (not (equal (car rbefore) (car rafter)))))
581 (push (pop rbefore) main-body)
583 (unless rbefore (return (makebody)))
584 ;; The first forms in RBEFORE & RAFTER (which are the
585 ;; chronologically last forms in the list) differ, therefore
586 ;; they cannot be moved into the main body. If everything that
587 ;; chronologically precedes them either differs or is equal but
588 ;; is okay to duplicate, we can just put all of rbefore in the
589 ;; prologue and all of rafter after the body. Otherwise, there
590 ;; is something that is not okay to duplicate, so it and
591 ;; everything chronologically after it in rbefore and rafter
592 ;; must go into the body, with a flag test to distinguish the
593 ;; first time around the loop from later times. What
594 ;; chronologically precedes the non-duplicatable form will be
595 ;; handled the next time around the outer loop.
596 (do ((bb rbefore (cdr bb))
601 ((null bb) (return-from loop-body (makebody))) ; Did it.
602 (cond ((not (equal (car bb) (car aa))) (setq lastdiff bb count 0))
603 ((or (not (setq inc (estimate-code-size (car bb) env)))
604 (> (incf count inc) threshold))
605 ;; Ok, we have found a non-duplicatable piece of code.
606 ;; Everything chronologically after it must be in the
607 ;; central body. Everything chronologically at and
608 ;; after LASTDIFF goes into the central body under a
610 (let ((then nil) (else nil))
612 (push (pop rbefore) else)
613 (push (pop rafter) then)
614 (when (eq rbefore (cdr lastdiff)) (return)))
616 (push `(setq ,(setq flagvar *loop-iteration-flag-var*)
619 (push `(if ,flagvar ,(pify (psimp then)) ,(pify (psimp else)))
621 ;; Everything chronologically before lastdiff until the
622 ;; non-duplicatable form (CAR BB) is the same in
623 ;; RBEFORE and RAFTER, so just copy it into the body.
626 (push (pop rbefore) main-body)
627 (when (eq rbefore (cdr bb)) (return)))
630 (defun duplicatable-code-p (expr env)
632 (let ((ans (estimate-code-size expr env)))
633 (declare (fixnum ans))
634 ;; @@@@ Use (DECLARATION-INFORMATION 'OPTIMIZE ENV) here to
635 ;; get an alist of optimize quantities back to help quantify
636 ;; how much code we are willing to duplicate.
639 (defvar *special-code-sizes*
640 '((return 0) (progn 0)
641 (null 1) (not 1) (eq 1) (car 1) (cdr 1)
642 (when 1) (unless 1) (if 1)
643 (caar 2) (cadr 2) (cdar 2) (cddr 2)
644 (caaar 3) (caadr 3) (cadar 3) (caddr 3)
645 (cdaar 3) (cdadr 3) (cddar 3) (cdddr 3)
646 (caaaar 4) (caaadr 4) (caadar 4) (caaddr 4)
647 (cadaar 4) (cadadr 4) (caddar 4) (cadddr 4)
648 (cdaaar 4) (cdaadr 4) (cdadar 4) (cdaddr 4)
649 (cddaar 4) (cddadr 4) (cdddar 4) (cddddr 4)))
651 (defvar *estimate-code-size-punt*
655 labels lambda let let* locally
656 macrolet multiple-value-bind
663 (defun destructuring-size (x)
664 (do ((x x (cdr x)) (n 0 (+ (destructuring-size (car x)) n)))
665 ((atom x) (+ n (if (null x) 0 1)))))
667 (defun estimate-code-size (x env)
668 (catch 'estimate-code-size
669 (estimate-code-size-1 x env)))
671 (defun estimate-code-size-1 (x env)
672 (flet ((list-size (l)
675 (dolist (x l n) (incf n (estimate-code-size-1 x env))))))
676 ;;@@@@ ???? (declare (function list-size (list) fixnum))
677 (cond ((constantp x) 1)
678 ((symbolp x) (multiple-value-bind (new-form expanded-p)
679 (sb!xc:macroexpand-1 x env)
681 (estimate-code-size-1 new-form env)
683 ((atom x) 1) ;; ??? self-evaluating???
685 (let ((fn (car x)) (tem nil) (n 0))
686 (declare (symbol fn) (fixnum n))
687 (macrolet ((f (overhead &optional (args nil args-p))
688 `(the fixnum (+ (the fixnum ,overhead)
690 (list-size ,(if args-p
693 (cond ((setq tem (get fn 'estimate-code-size))
696 (t (funcall tem x env))))
697 ((setq tem (assoc fn *special-code-sizes*))
700 (dolist (clause (cdr x) n)
701 (incf n (list-size clause)) (incf n)))
703 (do ((l (cdr x) (cdr l))) ((null l) n)
705 (destructuring-size (car l))
706 (estimate-code-size-1 (cadr l) env)))))
707 ((member fn '(setq psetq))
708 (do ((l (cdr x) (cdr l))) ((null l) n)
709 (setq n (+ n (estimate-code-size-1 (cadr l) env) 1))))
712 (if (sb!int:legal-fun-name-p (cadr x))
714 ;; FIXME: This tag appears not to be present
716 (throw 'duplicatable-code-p nil)))
717 ((eq fn 'multiple-value-setq)
718 (f (length (second x)) (cddr x)))
719 ((eq fn 'return-from)
720 (1+ (estimate-code-size-1 (third x) env)))
721 ((or (special-operator-p fn)
722 (member fn *estimate-code-size-punt*))
723 (throw 'estimate-code-size nil))
724 (t (multiple-value-bind (new-form expanded-p)
725 (sb!xc:macroexpand-1 x env)
727 (estimate-code-size-1 new-form env)
729 (t (throw 'estimate-code-size nil)))))
733 (defun loop-context ()
734 (do ((l *loop-source-context* (cdr l)) (new nil (cons (car l) new)))
735 ((eq l (cdr *loop-source-code*)) (nreverse new))))
737 (defun loop-error (format-string &rest format-args)
738 (error 'sb!int:simple-program-error
739 :format-control "~?~%current LOOP context:~{ ~S~}."
740 :format-arguments (list format-string format-args (loop-context))))
742 (defun loop-warn (format-string &rest format-args)
743 (warn "~?~%current LOOP context:~{ ~S~}."
748 (defun loop-check-data-type (specified-type required-type
749 &optional (default-type required-type))
750 (if (null specified-type)
752 (multiple-value-bind (a b) (sb!xc:subtypep specified-type required-type)
754 (loop-warn "LOOP couldn't verify that ~S is a subtype of the required type ~S."
755 specified-type required-type))
757 (loop-error "The specified data type ~S is not a subtype of ~S."
758 specified-type required-type)))
761 (defun subst-gensyms-for-nil (tree)
762 (declare (special *ignores*))
764 ((null tree) (car (push (gensym "LOOP-IGNORED-VAR-") *ignores*)))
766 (t (cons (subst-gensyms-for-nil (car tree))
767 (subst-gensyms-for-nil (cdr tree))))))
769 (sb!int:defmacro-mundanely loop-destructuring-bind
770 (lambda-list arg-list &rest body)
771 (let ((*ignores* nil))
772 (declare (special *ignores*))
773 (let ((d-var-lambda-list (subst-gensyms-for-nil lambda-list)))
774 `(destructuring-bind ,d-var-lambda-list
776 (declare (ignore ,@*ignores*))
779 (defun loop-build-destructuring-bindings (crocks forms)
781 `((loop-destructuring-bind ,(car crocks) ,(cadr crocks)
782 ,@(loop-build-destructuring-bindings (cddr crocks) forms)))
785 (defun loop-translate (*loop-source-code*
786 *loop-macro-environment*
788 (let ((*loop-original-source-code* *loop-source-code*)
789 (*loop-source-context* nil)
790 (*loop-iteration-vars* nil)
792 (*loop-named-vars* nil)
793 (*loop-declarations* nil)
794 (*loop-desetq-crocks* nil)
795 (*loop-bind-stack* nil)
796 (*loop-prologue* nil)
797 (*loop-wrappers* nil)
798 (*loop-before-loop* nil)
800 (*loop-emitted-body* nil)
801 (*loop-after-body* nil)
802 (*loop-epilogue* nil)
803 (*loop-after-epilogue* nil)
804 (*loop-final-value-culprit* nil)
805 (*loop-inside-conditional* nil)
806 (*loop-when-it-var* nil)
807 (*loop-never-stepped-var* nil)
809 (*loop-collection-cruft* nil))
810 (loop-iteration-driver)
812 (let ((answer `(loop-body
813 ,(nreverse *loop-prologue*)
814 ,(nreverse *loop-before-loop*)
815 ,(nreverse *loop-body*)
816 ,(nreverse *loop-after-body*)
817 ,(nreconc *loop-epilogue*
818 (nreverse *loop-after-epilogue*)))))
819 (dolist (entry *loop-bind-stack*)
820 (let ((vars (first entry))
821 (dcls (second entry))
822 (crocks (third entry))
823 (wrappers (fourth entry)))
825 (setq answer (append w (list answer))))
826 (when (or vars dcls crocks)
827 (let ((forms (list answer)))
828 ;;(when crocks (push crocks forms))
829 (when dcls (push `(declare ,@dcls) forms))
830 (setq answer `(,(if vars 'let 'locally)
832 ,@(loop-build-destructuring-bindings crocks
835 (setq answer `(block ,(pop *loop-names*) ,answer))
836 (unless *loop-names* (return nil)))
839 (defun loop-iteration-driver ()
840 (do () ((null *loop-source-code*))
841 (let ((keyword (car *loop-source-code*)) (tem nil))
842 (cond ((not (symbolp keyword))
843 (loop-error "~S found where LOOP keyword expected" keyword))
844 (t (setq *loop-source-context* *loop-source-code*)
847 (loop-lookup-keyword keyword
848 (loop-universe-keywords
850 ;; It's a "miscellaneous" toplevel LOOP keyword (DO,
851 ;; COLLECT, NAMED, etc.)
852 (apply (symbol-function (first tem)) (rest tem)))
854 (loop-lookup-keyword keyword
855 (loop-universe-iteration-keywords *loop-universe*)))
856 (loop-hack-iteration tem))
857 ((loop-tmember keyword '(and else))
858 ;; The alternative is to ignore it, i.e. let it go
859 ;; around to the next keyword...
860 (loop-error "secondary clause misplaced at top level in LOOP macro: ~S ~S ~S ..."
862 (car *loop-source-code*)
863 (cadr *loop-source-code*)))
864 (t (loop-error "unknown LOOP keyword: ~S" keyword))))))))
866 (defun loop-pop-source ()
867 (if *loop-source-code*
868 (pop *loop-source-code*)
869 (loop-error "LOOP source code ran out when another token was expected.")))
871 (defun loop-get-form ()
872 (if *loop-source-code*
874 (loop-error "LOOP code ran out where a form was expected.")))
876 (defun loop-get-compound-form ()
877 (let ((form (loop-get-form)))
879 (loop-error "A compound form was expected, but ~S found." form))
882 (defun loop-get-progn ()
883 (do ((forms (list (loop-get-compound-form))
884 (cons (loop-get-compound-form) forms))
885 (nextform (car *loop-source-code*)
886 (car *loop-source-code*)))
888 (if (null (cdr forms)) (car forms) (cons 'progn (nreverse forms))))))
890 (defun loop-construct-return (form)
891 `(return-from ,(car *loop-names*) ,form))
893 (defun loop-pseudo-body (form)
894 (cond ((or *loop-emitted-body* *loop-inside-conditional*)
895 (push form *loop-body*))
896 (t (push form *loop-before-loop*) (push form *loop-after-body*))))
898 (defun loop-emit-body (form)
899 (setq *loop-emitted-body* t)
900 (loop-pseudo-body form))
902 (defun loop-emit-final-value (&optional (form nil form-supplied-p))
903 (when form-supplied-p
904 (push (loop-construct-return form) *loop-after-epilogue*))
905 (when *loop-final-value-culprit*
906 (loop-warn "The LOOP clause is providing a value for the iteration;~@
907 however, one was already established by a ~S clause."
908 *loop-final-value-culprit*))
909 (setq *loop-final-value-culprit* (car *loop-source-context*)))
911 (defun loop-disallow-conditional (&optional kwd)
912 (when *loop-inside-conditional*
913 (loop-error "~:[This LOOP~;The LOOP ~:*~S~] clause is not permitted inside a conditional." kwd)))
915 (defun loop-disallow-anonymous-collectors ()
916 (when (find-if-not 'loop-collector-name *loop-collection-cruft*)
917 (loop-error "This LOOP clause is not permitted with anonymous collectors.")))
919 (defun loop-disallow-aggregate-booleans ()
920 (when (loop-tmember *loop-final-value-culprit* '(always never thereis))
921 (loop-error "This anonymous collection LOOP clause is not permitted with aggregate booleans.")))
925 (defun loop-typed-init (data-type)
926 (when (and data-type (sb!xc:subtypep data-type 'number))
927 (if (or (sb!xc:subtypep data-type 'float)
928 (sb!xc:subtypep data-type '(complex float)))
932 (defun loop-optional-type (&optional variable)
933 ;; No variable specified implies that no destructuring is permissible.
934 (and *loop-source-code* ; Don't get confused by NILs..
935 (let ((z (car *loop-source-code*)))
936 (cond ((loop-tequal z 'of-type)
937 ;; This is the syntactically unambigous form in that
938 ;; the form of the type specifier does not matter.
939 ;; Also, it is assumed that the type specifier is
940 ;; unambiguously, and without need of translation, a
941 ;; common lisp type specifier or pattern (matching the
942 ;; variable) thereof.
947 ;; This is the (sort of) "old" syntax, even though we
948 ;; didn't used to support all of these type symbols.
949 (let ((type-spec (or (gethash z
950 (loop-universe-type-symbols
952 (gethash (symbol-name z)
953 (loop-universe-type-keywords
959 ;; This is our sort-of old syntax. But this is only
960 ;; valid for when we are destructuring, so we will be
961 ;; compulsive (should we really be?) and require that
962 ;; we in fact be doing variable destructuring here. We
963 ;; must translate the old keyword pattern typespec
964 ;; into a fully-specified pattern of real type
969 "~S found where a LOOP keyword, LOOP type keyword, or LOOP type pattern expected"
971 (loop-error "~S found where a LOOP keyword or LOOP type keyword expected" z))
973 (labels ((translate (k v)
978 (loop-universe-type-symbols
980 (gethash (symbol-name k)
981 (loop-universe-type-keywords
984 "The destructuring type pattern ~S contains the unrecognized type keyword ~S."
989 "The destructuring type pattern ~S doesn't match the variable pattern ~S."
991 (t (cons (translate (car k) (car v))
992 (translate (cdr k) (cdr v))))))
996 (cons (replicate typ (car v))
997 (replicate typ (cdr v))))))
998 (translate z variable)))))))
1002 (defun loop-bind-block ()
1003 (when (or *loop-vars* *loop-declarations* *loop-wrappers*)
1004 (push (list (nreverse *loop-vars*)
1006 *loop-desetq-crocks*
1009 (setq *loop-vars* nil
1010 *loop-declarations* nil
1011 *loop-desetq-crocks* nil
1012 *loop-wrappers* nil)))
1014 (defun loop-var-p (name)
1015 (do ((entry *loop-bind-stack* (cdr entry)))
1018 ((null entry) (return nil))
1019 ((assoc name (caar entry) :test #'eq) (return t)))))
1021 (defun loop-make-var (name initialization dtype &optional iteration-var-p)
1023 (cond ((not (null initialization))
1024 (push (list (setq name (gensym "LOOP-IGNORE-"))
1027 (push `(ignore ,name) *loop-declarations*))))
1029 (cond (iteration-var-p
1030 (if (member name *loop-iteration-vars*)
1031 (loop-error "duplicated LOOP iteration variable ~S" name)
1032 (push name *loop-iteration-vars*)))
1033 ((assoc name *loop-vars*)
1034 (loop-error "duplicated variable ~S in LOOP parallel binding"
1036 (unless (symbolp name)
1037 (loop-error "bad variable ~S somewhere in LOOP" name))
1038 (loop-declare-var name dtype)
1039 ;; We use ASSOC on this list to check for duplications (above),
1040 ;; so don't optimize out this list:
1041 (push (list name (or initialization (loop-typed-init dtype)))
1044 (let ((newvar (gensym "LOOP-DESTRUCTURE-")))
1045 (loop-declare-var name dtype)
1046 (push (list newvar initialization) *loop-vars*)
1047 ;; *LOOP-DESETQ-CROCKS* gathered in reverse order.
1048 (setq *loop-desetq-crocks*
1049 (list* name newvar *loop-desetq-crocks*))))
1050 (t (let ((tcar nil) (tcdr nil))
1051 (if (atom dtype) (setq tcar (setq tcdr dtype))
1052 (setq tcar (car dtype) tcdr (cdr dtype)))
1053 (loop-make-var (car name) nil tcar iteration-var-p)
1054 (loop-make-var (cdr name) nil tcdr iteration-var-p))))
1057 (defun loop-make-iteration-var (name initialization dtype)
1058 (loop-make-var name initialization dtype t))
1060 (defun loop-declare-var (name dtype)
1061 (cond ((or (null name) (null dtype) (eq dtype t)) nil)
1063 (unless (sb!xc:subtypep t dtype)
1064 (let ((dtype (let ((init (loop-typed-init dtype)))
1065 (if (sb!xc:typep init dtype)
1067 `(or (member ,init) ,dtype)))))
1068 (push `(type ,dtype ,name) *loop-declarations*))))
1070 (cond ((consp dtype)
1071 (loop-declare-var (car name) (car dtype))
1072 (loop-declare-var (cdr name) (cdr dtype)))
1073 (t (loop-declare-var (car name) dtype)
1074 (loop-declare-var (cdr name) dtype))))
1075 (t (error "invalid LOOP variable passed in: ~S" name))))
1077 (defun loop-maybe-bind-form (form data-type)
1078 (if (loop-constantp form)
1080 (loop-make-var (gensym "LOOP-BIND-") form data-type)))
1082 (defun loop-do-if (for negatep)
1083 (let ((form (loop-get-form))
1084 (*loop-inside-conditional* t)
1087 (flet ((get-clause (for)
1088 (do ((body nil)) (nil)
1089 (let ((key (car *loop-source-code*)) (*loop-body* nil) data)
1090 (cond ((not (symbolp key))
1092 "~S found where keyword expected getting LOOP clause after ~S"
1094 (t (setq *loop-source-context* *loop-source-code*)
1096 (when (and (loop-tequal (car *loop-source-code*) 'it)
1098 (setq *loop-source-code*
1101 (loop-when-it-var)))
1102 (cdr *loop-source-code*))))
1103 (cond ((or (not (setq data (loop-lookup-keyword
1104 key (loop-universe-keywords *loop-universe*))))
1105 (progn (apply (symbol-function (car data))
1107 (null *loop-body*)))
1109 "~S does not introduce a LOOP clause that can follow ~S."
1111 (t (setq body (nreconc *loop-body* body)))))))
1112 (setq first-clause-p nil)
1113 (if (loop-tequal (car *loop-source-code*) :and)
1115 (return (if (cdr body)
1116 `(progn ,@(nreverse body))
1118 (let ((then (get-clause for))
1119 (else (when (loop-tequal (car *loop-source-code*) :else)
1121 (list (get-clause :else)))))
1122 (when (loop-tequal (car *loop-source-code*) :end)
1124 (when it-p (setq form `(setq ,it-p ,form)))
1126 `(if ,(if negatep `(not ,form) form)
1130 (defun loop-do-initially ()
1131 (loop-disallow-conditional :initially)
1132 (push (loop-get-progn) *loop-prologue*))
1134 (defun loop-do-finally ()
1135 (loop-disallow-conditional :finally)
1136 (push (loop-get-progn) *loop-epilogue*))
1138 (defun loop-do-do ()
1139 (loop-emit-body (loop-get-progn)))
1141 (defun loop-do-named ()
1142 (let ((name (loop-pop-source)))
1143 (unless (symbolp name)
1144 (loop-error "~S is an invalid name for your LOOP" name))
1145 (when (or *loop-before-loop* *loop-body* *loop-after-epilogue* *loop-inside-conditional*)
1146 (loop-error "The NAMED ~S clause occurs too late." name))
1148 (loop-error "You may only use one NAMED clause in your loop: NAMED ~S ... NAMED ~S."
1149 (car *loop-names*) name))
1150 (setq *loop-names* (list name))))
1152 (defun loop-do-return ()
1153 (loop-pseudo-body (loop-construct-return (loop-get-form))))
1155 ;;;; value accumulation: LIST
1157 (defstruct (loop-collector
1165 (data nil)) ;collector-specific data
1167 (defun loop-get-collection-info (collector class default-type)
1168 (let ((form (loop-get-form))
1169 (dtype (and (not (loop-universe-ansi *loop-universe*)) (loop-optional-type)))
1170 (name (when (loop-tequal (car *loop-source-code*) 'into)
1172 (loop-pop-source))))
1173 (when (not (symbolp name))
1174 (loop-error "The value accumulation recipient name, ~S, is not a symbol." name))
1176 (loop-disallow-aggregate-booleans))
1178 (setq dtype (or (loop-optional-type) default-type)))
1179 (let ((cruft (find (the symbol name) *loop-collection-cruft*
1180 :key #'loop-collector-name)))
1182 (when (and name (loop-var-p name))
1183 (loop-error "Variable ~S in INTO clause is a duplicate" name))
1184 (push (setq cruft (make-loop-collector
1185 :name name :class class
1186 :history (list collector) :dtype dtype))
1187 *loop-collection-cruft*))
1188 (t (unless (eq (loop-collector-class cruft) class)
1190 "incompatible kinds of LOOP value accumulation specified for collecting~@
1191 ~:[as the value of the LOOP~;~:*INTO ~S~]: ~S and ~S"
1192 name (car (loop-collector-history cruft)) collector))
1193 (unless (equal dtype (loop-collector-dtype cruft))
1195 "unequal datatypes specified in different LOOP value accumulations~@
1197 name dtype (loop-collector-dtype cruft))
1198 (when (eq (loop-collector-dtype cruft) t)
1199 (setf (loop-collector-dtype cruft) dtype)))
1200 (push collector (loop-collector-history cruft))))
1201 (values cruft form))))
1203 (defun loop-list-collection (specifically) ; NCONC, LIST, or APPEND
1204 (multiple-value-bind (lc form)
1205 (loop-get-collection-info specifically 'list 'list)
1206 (let ((tempvars (loop-collector-tempvars lc)))
1208 (setf (loop-collector-tempvars lc)
1209 (setq tempvars (list* (gensym "LOOP-LIST-HEAD-")
1210 (gensym "LOOP-LIST-TAIL-")
1211 (and (loop-collector-name lc)
1212 (list (loop-collector-name lc))))))
1213 (push `(with-loop-list-collection-head ,tempvars) *loop-wrappers*)
1214 (unless (loop-collector-name lc)
1215 (loop-emit-final-value `(loop-collect-answer ,(car tempvars)
1216 ,@(cddr tempvars)))))
1218 (list (setq form `(list ,form)))
1220 (append (unless (and (consp form) (eq (car form) 'list))
1221 (setq form `(copy-list ,form)))))
1222 (loop-emit-body `(loop-collect-rplacd ,tempvars ,form)))))
1224 ;;;; value accumulation: MAX, MIN, SUM, COUNT
1226 (defun loop-sum-collection (specifically required-type default-type);SUM, COUNT
1227 (multiple-value-bind (lc form)
1228 (loop-get-collection-info specifically 'sum default-type)
1229 (loop-check-data-type (loop-collector-dtype lc) required-type)
1230 (let ((tempvars (loop-collector-tempvars lc)))
1232 (setf (loop-collector-tempvars lc)
1233 (setq tempvars (list (loop-make-var
1234 (or (loop-collector-name lc)
1235 (gensym "LOOP-SUM-"))
1236 nil (loop-collector-dtype lc)))))
1237 (unless (loop-collector-name lc)
1238 (loop-emit-final-value (car (loop-collector-tempvars lc)))))
1240 (if (eq specifically 'count)
1242 (setq ,(car tempvars)
1243 (1+ ,(car tempvars))))
1244 `(setq ,(car tempvars)
1248 (defun loop-maxmin-collection (specifically)
1249 (multiple-value-bind (lc form)
1250 (loop-get-collection-info specifically 'maxmin 'real)
1251 (loop-check-data-type (loop-collector-dtype lc) 'real)
1252 (let ((data (loop-collector-data lc)))
1254 (setf (loop-collector-data lc)
1255 (setq data (make-loop-minimax
1256 (or (loop-collector-name lc)
1257 (gensym "LOOP-MAXMIN-"))
1258 (loop-collector-dtype lc))))
1259 (unless (loop-collector-name lc)
1260 (loop-emit-final-value (loop-minimax-answer-variable data))))
1261 (loop-note-minimax-operation specifically data)
1262 (push `(with-minimax-value ,data) *loop-wrappers*)
1263 (loop-emit-body `(loop-accumulate-minimax-value ,data
1267 ;;;; value accumulation: aggregate booleans
1269 ;;; handling the ALWAYS and NEVER loop keywords
1271 ;;; Under ANSI these are not permitted to appear under conditionalization.
1272 (defun loop-do-always (restrictive negate)
1273 (let ((form (loop-get-form)))
1274 (when restrictive (loop-disallow-conditional))
1275 (loop-disallow-anonymous-collectors)
1276 (loop-emit-body `(,(if negate 'when 'unless) ,form
1277 ,(loop-construct-return nil)))
1278 (loop-emit-final-value t)))
1280 ;;; handling the THEREIS loop keyword
1282 ;;; Under ANSI this is not permitted to appear under conditionalization.
1283 (defun loop-do-thereis (restrictive)
1284 (when restrictive (loop-disallow-conditional))
1285 (loop-disallow-anonymous-collectors)
1286 (loop-emit-final-value)
1287 (loop-emit-body `(when (setq ,(loop-when-it-var) ,(loop-get-form))
1288 ,(loop-construct-return *loop-when-it-var*))))
1290 (defun loop-do-while (negate kwd &aux (form (loop-get-form)))
1291 (loop-disallow-conditional kwd)
1292 (loop-pseudo-body `(,(if negate 'when 'unless) ,form (go end-loop))))
1294 (defun loop-do-repeat ()
1295 (loop-disallow-conditional :repeat)
1296 (let ((form (loop-get-form))
1298 (let ((var (loop-make-var (gensym "LOOP-REPEAT-") `(ceiling ,form) type)))
1299 (push `(if (<= ,var 0) (go end-loop) (decf ,var)) *loop-before-loop*)
1300 (push `(if (<= ,var 0) (go end-loop) (decf ,var)) *loop-after-body*)
1301 ;; FIXME: What should
1302 ;; (loop count t into a
1305 ;; finally (return (list a b)))
1306 ;; return: (3 3) or (4 3)? PUSHes above are for the former
1307 ;; variant, L-P-B below for the latter.
1308 #+nil (loop-pseudo-body `(when (minusp (decf ,var)) (go end-loop))))))
1310 (defun loop-do-with ()
1311 (loop-disallow-conditional :with)
1312 (do ((var) (val) (dtype)) (nil)
1313 (setq var (loop-pop-source)
1314 dtype (loop-optional-type var)
1315 val (cond ((loop-tequal (car *loop-source-code*) :=)
1319 (when (and var (loop-var-p var))
1320 (loop-error "Variable ~S has already been used" var))
1321 (loop-make-var var val dtype)
1322 (if (loop-tequal (car *loop-source-code*) :and)
1324 (return (loop-bind-block)))))
1326 ;;;; the iteration driver
1328 (defun loop-hack-iteration (entry)
1329 (flet ((make-endtest (list-of-forms)
1330 (cond ((null list-of-forms) nil)
1331 ((member t list-of-forms) '(go end-loop))
1332 (t `(when ,(if (null (cdr (setq list-of-forms
1333 (nreverse list-of-forms))))
1335 (cons 'or list-of-forms))
1337 (do ((pre-step-tests nil)
1339 (post-step-tests nil)
1341 (pre-loop-pre-step-tests nil)
1342 (pre-loop-steps nil)
1343 (pre-loop-post-step-tests nil)
1344 (pre-loop-pseudo-steps nil)
1347 ;; Note that we collect endtests in reverse order, but steps in correct
1348 ;; order. MAKE-ENDTEST does the nreverse for us.
1349 (setq tem (setq data
1350 (apply (symbol-function (first entry)) (rest entry))))
1351 (and (car tem) (push (car tem) pre-step-tests))
1352 (setq steps (nconc steps (copy-list (car (setq tem (cdr tem))))))
1353 (and (car (setq tem (cdr tem))) (push (car tem) post-step-tests))
1355 (nconc pseudo-steps (copy-list (car (setq tem (cdr tem))))))
1356 (setq tem (cdr tem))
1357 (when *loop-emitted-body*
1358 (loop-error "iteration in LOOP follows body code"))
1359 (unless tem (setq tem data))
1360 (when (car tem) (push (car tem) pre-loop-pre-step-tests))
1361 ;; FIXME: This (SETF FOO (NCONC FOO BAR)) idiom appears often enough
1362 ;; that it might be worth making it into an NCONCF macro.
1363 (setq pre-loop-steps
1364 (nconc pre-loop-steps (copy-list (car (setq tem (cdr tem))))))
1365 (when (car (setq tem (cdr tem)))
1366 (push (car tem) pre-loop-post-step-tests))
1367 (setq pre-loop-pseudo-steps
1368 (nconc pre-loop-pseudo-steps (copy-list (cadr tem))))
1369 (unless (loop-tequal (car *loop-source-code*) :and)
1370 (setq *loop-before-loop*
1371 (list* (loop-make-desetq pre-loop-pseudo-steps)
1372 (make-endtest pre-loop-post-step-tests)
1373 (loop-make-psetq pre-loop-steps)
1374 (make-endtest pre-loop-pre-step-tests)
1375 *loop-before-loop*))
1376 (setq *loop-after-body*
1377 (list* (loop-make-desetq pseudo-steps)
1378 (make-endtest post-step-tests)
1379 (loop-make-psetq steps)
1380 (make-endtest pre-step-tests)
1384 (loop-pop-source) ; Flush the "AND".
1385 (when (and (not (loop-universe-implicit-for-required *loop-universe*))
1387 (loop-lookup-keyword
1388 (car *loop-source-code*)
1389 (loop-universe-iteration-keywords *loop-universe*))))
1390 ;; The latest ANSI clarification is that the FOR/AS after the AND must
1393 (setq entry tem)))))
1395 ;;;; main iteration drivers
1397 ;;; FOR variable keyword ..args..
1398 (defun loop-do-for ()
1399 (let* ((var (loop-pop-source))
1400 (data-type (loop-optional-type var))
1401 (keyword (loop-pop-source))
1404 (setq first-arg (loop-get-form))
1405 (unless (and (symbolp keyword)
1406 (setq tem (loop-lookup-keyword
1408 (loop-universe-for-keywords *loop-universe*))))
1409 (loop-error "~S is an unknown keyword in FOR or AS clause in LOOP."
1411 (apply (car tem) var first-arg data-type (cdr tem))))
1413 (defun loop-when-it-var ()
1414 (or *loop-when-it-var*
1415 (setq *loop-when-it-var*
1416 (loop-make-var (gensym "LOOP-IT-") nil nil))))
1418 ;;;; various FOR/AS subdispatches
1420 ;;; ANSI "FOR x = y [THEN z]" is sort of like the old Genera one when
1421 ;;; the THEN is omitted (other than being more stringent in its
1422 ;;; placement), and like the old "FOR x FIRST y THEN z" when the THEN
1423 ;;; is present. I.e., the first initialization occurs in the loop body
1424 ;;; (first-step), not in the variable binding phase.
1425 (defun loop-ansi-for-equals (var val data-type)
1426 (loop-make-iteration-var var nil data-type)
1427 (cond ((loop-tequal (car *loop-source-code*) :then)
1428 ;; Then we are the same as "FOR x FIRST y THEN z".
1430 `(() (,var ,(loop-get-form)) () ()
1431 () (,var ,val) () ()))
1432 (t ;; We are the same as "FOR x = y".
1433 `(() (,var ,val) () ()))))
1435 (defun loop-for-across (var val data-type)
1436 (loop-make-iteration-var var nil data-type)
1437 (let ((vector-var (gensym "LOOP-ACROSS-VECTOR-"))
1438 (index-var (gensym "LOOP-ACROSS-INDEX-")))
1439 (multiple-value-bind (vector-form constantp vector-value)
1440 (loop-constant-fold-if-possible val 'vector)
1442 vector-var vector-form
1443 (if (and (consp vector-form) (eq (car vector-form) 'the))
1446 (loop-make-var index-var 0 'fixnum)
1448 (length-form (cond ((not constantp)
1449 (let ((v (gensym "LOOP-ACROSS-LIMIT-")))
1450 (push `(setq ,v (length ,vector-var))
1452 (loop-make-var v 0 'fixnum)))
1453 (t (setq length (length vector-value)))))
1454 (first-test `(>= ,index-var ,length-form))
1455 (other-test first-test)
1456 (step `(,var (aref ,vector-var ,index-var)))
1457 (pstep `(,index-var (1+ ,index-var))))
1458 (declare (fixnum length))
1460 (setq first-test (= length 0))
1462 (setq other-test t)))
1463 `(,other-test ,step () ,pstep
1464 ,@(and (not (eq first-test other-test))
1465 `(,first-test ,step () ,pstep)))))))
1469 (defun loop-list-step (listvar)
1470 ;; We are not equipped to analyze whether 'FOO is the same as #'FOO
1471 ;; here in any sensible fashion, so let's give an obnoxious warning
1472 ;; whenever 'FOO is used as the stepping function.
1474 ;; While a Discerning Compiler may deal intelligently with
1475 ;; (FUNCALL 'FOO ...), not recognizing FOO may defeat some LOOP
1477 (let ((stepper (cond ((loop-tequal (car *loop-source-code*) :by)
1480 (t '(function cdr)))))
1481 (cond ((and (consp stepper) (eq (car stepper) 'quote))
1482 (loop-warn "Use of QUOTE around stepping function in LOOP will be left verbatim.")
1483 `(funcall ,stepper ,listvar))
1484 ((and (consp stepper) (eq (car stepper) 'function))
1485 (list (cadr stepper) listvar))
1487 `(funcall ,(loop-make-var (gensym "LOOP-FN-") stepper 'function)
1490 (defun loop-for-on (var val data-type)
1491 (multiple-value-bind (list constantp list-value)
1492 (loop-constant-fold-if-possible val)
1493 (let ((listvar var))
1494 (cond ((and var (symbolp var))
1495 (loop-make-iteration-var var list data-type))
1496 (t (loop-make-var (setq listvar (gensym)) list 'list)
1497 (loop-make-iteration-var var nil data-type)))
1498 (let ((list-step (loop-list-step listvar)))
1499 (let* ((first-endtest
1500 ;; mysterious comment from original CMU CL sources:
1501 ;; the following should use `atom' instead of `endp',
1504 (other-endtest first-endtest))
1505 (when (and constantp (listp list-value))
1506 (setq first-endtest (null list-value)))
1507 (cond ((eq var listvar)
1508 ;; The contour of the loop is different because we
1509 ;; use the user's variable...
1510 `(() (,listvar ,list-step)
1511 ,other-endtest () () () ,first-endtest ()))
1512 (t (let ((step `(,var ,listvar))
1513 (pseudo `(,listvar ,list-step)))
1514 `(,other-endtest ,step () ,pseudo
1515 ,@(and (not (eq first-endtest other-endtest))
1516 `(,first-endtest ,step () ,pseudo)))))))))))
1518 (defun loop-for-in (var val data-type)
1519 (multiple-value-bind (list constantp list-value)
1520 (loop-constant-fold-if-possible val)
1521 (let ((listvar (gensym "LOOP-LIST-")))
1522 (loop-make-iteration-var var nil data-type)
1523 (loop-make-var listvar list 'list)
1524 (let ((list-step (loop-list-step listvar)))
1525 (let* ((first-endtest `(endp ,listvar))
1526 (other-endtest first-endtest)
1527 (step `(,var (car ,listvar)))
1528 (pseudo-step `(,listvar ,list-step)))
1529 (when (and constantp (listp list-value))
1530 (setq first-endtest (null list-value)))
1531 `(,other-endtest ,step () ,pseudo-step
1532 ,@(and (not (eq first-endtest other-endtest))
1533 `(,first-endtest ,step () ,pseudo-step))))))))
1535 ;;;; iteration paths
1537 (defstruct (loop-path
1546 (defun add-loop-path (names function universe
1547 &key preposition-groups inclusive-permitted user-data)
1548 (declare (type loop-universe universe))
1549 (unless (listp names)
1550 (setq names (list names)))
1551 (let ((ht (loop-universe-path-keywords universe))
1553 :names (mapcar #'symbol-name names)
1555 :user-data user-data
1556 :preposition-groups (mapcar (lambda (x)
1557 (if (listp x) x (list x)))
1559 :inclusive-permitted inclusive-permitted)))
1560 (dolist (name names)
1561 (setf (gethash (symbol-name name) ht) lp))
1564 ;;; Note: Path functions are allowed to use LOOP-MAKE-VAR, hack
1565 ;;; the prologue, etc.
1566 (defun loop-for-being (var val data-type)
1567 ;; FOR var BEING each/the pathname prep-phrases using-stuff... each/the =
1568 ;; EACH or THE. Not clear if it is optional, so I guess we'll warn.
1573 (initial-prepositions nil))
1574 (cond ((loop-tmember val '(:each :the)) (setq path (loop-pop-source)))
1575 ((loop-tequal (car *loop-source-code*) :and)
1578 (unless (loop-tmember (car *loop-source-code*)
1579 '(:its :each :his :her))
1580 (loop-error "~S was found where ITS or EACH expected in LOOP iteration path syntax."
1581 (car *loop-source-code*)))
1583 (setq path (loop-pop-source))
1584 (setq initial-prepositions `((:in ,val))))
1585 (t (loop-error "unrecognizable LOOP iteration path syntax: missing EACH or THE?")))
1586 (cond ((not (symbolp path))
1588 "~S was found where a LOOP iteration path name was expected."
1590 ((not (setq data (loop-lookup-keyword path (loop-universe-path-keywords *loop-universe*))))
1591 (loop-error "~S is not the name of a LOOP iteration path." path))
1592 ((and inclusive (not (loop-path-inclusive-permitted data)))
1593 (loop-error "\"Inclusive\" iteration is not possible with the ~S LOOP iteration path." path)))
1594 (let ((fun (loop-path-function data))
1595 (preps (nconc initial-prepositions
1596 (loop-collect-prepositional-phrases
1597 (loop-path-preposition-groups data)
1599 (user-data (loop-path-user-data data)))
1600 (when (symbolp fun) (setq fun (symbol-function fun)))
1601 (setq stuff (if inclusive
1602 (apply fun var data-type preps :inclusive t user-data)
1603 (apply fun var data-type preps user-data))))
1604 (when *loop-named-vars*
1605 (loop-error "Unused USING vars: ~S." *loop-named-vars*))
1606 ;; STUFF is now (bindings prologue-forms . stuff-to-pass-back).
1607 ;; Protect the system from the user and the user from himself.
1608 (unless (member (length stuff) '(6 10))
1609 (loop-error "Value passed back by LOOP iteration path function for path ~S has invalid length."
1611 (do ((l (car stuff) (cdr l)) (x)) ((null l))
1612 (if (atom (setq x (car l)))
1613 (loop-make-iteration-var x nil nil)
1614 (loop-make-iteration-var (car x) (cadr x) (caddr x))))
1615 (setq *loop-prologue* (nconc (reverse (cadr stuff)) *loop-prologue*))
1618 (defun loop-named-var (name)
1619 (let ((tem (loop-tassoc name *loop-named-vars*)))
1620 (declare (list tem))
1621 (cond ((null tem) (values (gensym) nil))
1622 (t (setq *loop-named-vars* (delete tem *loop-named-vars*))
1623 (values (cdr tem) t)))))
1625 (defun loop-collect-prepositional-phrases (preposition-groups
1629 (flet ((in-group-p (x group) (car (loop-tmember x group))))
1631 (prepositional-phrases initial-phrases)
1632 (this-group nil nil)
1634 (disallowed-prepositions
1637 (find (car x) preposition-groups :test #'in-group-p)))
1639 (used-prepositions (mapcar #'car initial-phrases)))
1640 ((null *loop-source-code*) (nreverse prepositional-phrases))
1641 (declare (symbol this-prep))
1642 (setq token (car *loop-source-code*))
1643 (dolist (group preposition-groups)
1644 (when (setq this-prep (in-group-p token group))
1645 (return (setq this-group group))))
1647 (when (member this-prep disallowed-prepositions)
1649 (if (member this-prep used-prepositions)
1650 "A ~S prepositional phrase occurs multiply for some LOOP clause."
1651 "Preposition ~S was used when some other preposition has subsumed it.")
1653 (setq used-prepositions (if (listp this-group)
1654 (append this-group used-prepositions)
1655 (cons this-group used-prepositions)))
1657 (push (list this-prep (loop-get-form)) prepositional-phrases))
1658 ((and using-allowed (loop-tequal token 'using))
1660 (do ((z (loop-pop-source) (loop-pop-source)) (tem)) (nil)
1662 (if (setq tem (loop-tassoc (car z) *loop-named-vars*))
1664 "The variable substitution for ~S occurs twice in a USING phrase,~@
1666 (car z) (cadr z) (cadr tem))
1667 (push (cons (car z) (cadr z)) *loop-named-vars*)))
1668 (when (or (null *loop-source-code*)
1669 (symbolp (car *loop-source-code*)))
1671 (t (return (nreverse prepositional-phrases)))))))
1673 ;;;; master sequencer function
1675 (defun loop-sequencer (indexv indexv-type
1676 variable variable-type
1677 sequence-variable sequence-type
1678 step-hack default-top
1680 (let ((endform nil) ; form (constant or variable) with limit value
1681 (sequencep nil) ; T if sequence arg has been provided
1682 (testfn nil) ; endtest function
1683 (test nil) ; endtest form
1684 (stepby (1+ (or (loop-typed-init indexv-type) 0))) ; our increment
1685 (stepby-constantp t)
1686 (step nil) ; step form
1687 (dir nil) ; direction of stepping: NIL, :UP, :DOWN
1688 (inclusive-iteration nil) ; T if include last index
1689 (start-given nil) ; T when prep phrase has specified start
1691 (start-constantp nil)
1692 (limit-given nil) ; T when prep phrase has specified end
1693 (limit-constantp nil)
1696 (when variable (loop-make-iteration-var variable nil variable-type))
1697 (do ((l prep-phrases (cdr l)) (prep) (form) (odir)) ((null l))
1698 (setq prep (caar l) form (cadar l))
1702 (loop-make-var sequence-variable form sequence-type))
1703 ((:from :downfrom :upfrom)
1704 (setq start-given t)
1705 (cond ((eq prep :downfrom) (setq dir ':down))
1706 ((eq prep :upfrom) (setq dir ':up)))
1707 (multiple-value-setq (form start-constantp start-value)
1708 (loop-constant-fold-if-possible form indexv-type))
1709 (loop-make-iteration-var indexv form indexv-type))
1710 ((:upto :to :downto :above :below)
1711 (cond ((loop-tequal prep :upto) (setq inclusive-iteration
1713 ((loop-tequal prep :to) (setq inclusive-iteration t))
1714 ((loop-tequal prep :downto) (setq inclusive-iteration
1716 ((loop-tequal prep :above) (setq dir ':down))
1717 ((loop-tequal prep :below) (setq dir ':up)))
1718 (setq limit-given t)
1719 (multiple-value-setq (form limit-constantp limit-value)
1720 (loop-constant-fold-if-possible form indexv-type))
1721 (setq endform (if limit-constantp
1724 (gensym "LOOP-LIMIT-") form indexv-type))))
1726 (multiple-value-setq (form stepby-constantp stepby)
1727 (loop-constant-fold-if-possible form indexv-type))
1728 (unless stepby-constantp
1729 (loop-make-var (setq stepby (gensym "LOOP-STEP-BY-"))
1733 "~S invalid preposition in sequencing or sequence path;~@
1734 maybe invalid prepositions were specified in iteration path descriptor?"
1736 (when (and odir dir (not (eq dir odir)))
1737 (loop-error "conflicting stepping directions in LOOP sequencing path"))
1739 (when (and sequence-variable (not sequencep))
1740 (loop-error "missing OF or IN phrase in sequence path"))
1741 ;; Now fill in the defaults.
1743 (loop-make-iteration-var
1745 (setq start-constantp t
1746 start-value (or (loop-typed-init indexv-type) 0))
1748 (cond ((member dir '(nil :up))
1749 (when (or limit-given default-top)
1751 (loop-make-var (setq endform (gensym "LOOP-SEQ-LIMIT-"))
1754 (push `(setq ,endform ,default-top) *loop-prologue*))
1755 (setq testfn (if inclusive-iteration '> '>=)))
1756 (setq step (if (eql stepby 1) `(1+ ,indexv) `(+ ,indexv ,stepby))))
1757 (t (unless start-given
1759 (loop-error "don't know where to start stepping"))
1760 (push `(setq ,indexv (1- ,default-top)) *loop-prologue*))
1761 (when (and default-top (not endform))
1762 (setq endform (loop-typed-init indexv-type)
1763 inclusive-iteration t))
1764 (when endform (setq testfn (if inclusive-iteration '< '<=)))
1766 (if (eql stepby 1) `(1- ,indexv) `(- ,indexv ,stepby)))))
1769 `(,testfn ,indexv ,endform)))
1772 `(,variable ,step-hack)))
1773 (let ((first-test test) (remaining-tests test))
1774 (when (and stepby-constantp start-constantp limit-constantp)
1775 (when (setq first-test
1776 (funcall (symbol-function testfn)
1779 (setq remaining-tests t)))
1780 `(() (,indexv ,step)
1781 ,remaining-tests ,step-hack () () ,first-test ,step-hack))))
1783 ;;;; interfaces to the master sequencer
1785 (defun loop-for-arithmetic (var val data-type kwd)
1787 var (loop-check-data-type data-type 'real)
1788 nil nil nil nil nil nil
1789 (loop-collect-prepositional-phrases
1790 '((:from :upfrom :downfrom) (:to :upto :downto :above :below) (:by))
1791 nil (list (list kwd val)))))
1793 (defun loop-sequence-elements-path (variable data-type prep-phrases
1799 (multiple-value-bind (indexv) (loop-named-var 'index)
1800 (let ((sequencev (loop-named-var 'sequence)))
1801 (list* nil nil ; dummy bindings and prologue
1804 variable (or data-type element-type)
1805 sequencev sequence-type
1806 `(,fetch-function ,sequencev ,indexv)
1807 `(,size-function ,sequencev)
1810 ;;;; builtin LOOP iteration paths
1813 (loop for v being the hash-values of ht do (print v))
1814 (loop for k being the hash-keys of ht do (print k))
1815 (loop for v being the hash-values of ht using (hash-key k) do (print (list k v)))
1816 (loop for k being the hash-keys of ht using (hash-value v) do (print (list k v)))
1819 (defun loop-hash-table-iteration-path (variable data-type prep-phrases
1820 &key (which (sb!int:missing-arg)))
1821 (declare (type (member :hash-key :hash-value) which))
1822 (cond ((or (cdr prep-phrases) (not (member (caar prep-phrases) '(:in :of))))
1823 (loop-error "too many prepositions!"))
1824 ((null prep-phrases)
1825 (loop-error "missing OF or IN in ~S iteration path")))
1826 (let ((ht-var (gensym "LOOP-HASHTAB-"))
1827 (next-fn (gensym "LOOP-HASHTAB-NEXT-"))
1828 (dummy-predicate-var nil)
1830 (multiple-value-bind (other-var other-p)
1831 (loop-named-var (ecase which
1832 (:hash-key 'hash-value)
1833 (:hash-value 'hash-key)))
1834 ;; @@@@ LOOP-NAMED-VAR returns a second value of T if the name
1835 ;; was actually specified, so clever code can throw away the
1836 ;; GENSYM'ed-up variable if it isn't really needed. The
1837 ;; following is for those implementations in which we cannot put
1838 ;; dummy NILs into MULTIPLE-VALUE-SETQ variable lists.
1840 dummy-predicate-var (loop-when-it-var))
1841 (let* ((key-var nil)
1843 (variable (or variable (gensym "LOOP-HASH-VAR-TEMP-")))
1844 (bindings `((,variable nil ,data-type)
1845 (,ht-var ,(cadar prep-phrases))
1846 ,@(and other-p other-var `((,other-var nil))))))
1848 (:hash-key (setq key-var variable
1849 val-var (and other-p other-var)))
1850 (:hash-value (setq key-var (and other-p other-var)
1852 (push `(with-hash-table-iterator (,next-fn ,ht-var)) *loop-wrappers*)
1853 (when (or (consp key-var) data-type)
1855 `(,key-var ,(setq key-var (gensym "LOOP-HASH-KEY-TEMP-"))
1857 (push `(,key-var nil) bindings))
1858 (when (or (consp val-var) data-type)
1860 `(,val-var ,(setq val-var (gensym "LOOP-HASH-VAL-TEMP-"))
1862 (push `(,val-var nil) bindings))
1863 `(,bindings ;bindings
1867 (not (multiple-value-setq (,dummy-predicate-var ,key-var ,val-var)
1868 (,next-fn))) ;post-test
1871 (defun loop-package-symbols-iteration-path (variable data-type prep-phrases
1873 (cond ((and prep-phrases (cdr prep-phrases))
1874 (loop-error "Too many prepositions!"))
1875 ((and prep-phrases (not (member (caar prep-phrases) '(:in :of))))
1876 (sb!int:bug "Unknown preposition ~S." (caar prep-phrases))))
1877 (unless (symbolp variable)
1878 (loop-error "Destructuring is not valid for package symbol iteration."))
1879 (let ((pkg-var (gensym "LOOP-PKGSYM-"))
1880 (next-fn (gensym "LOOP-PKGSYM-NEXT-"))
1881 (variable (or variable (gensym "LOOP-PKGSYM-VAR-")))
1882 (package (or (cadar prep-phrases) '*package*)))
1883 (push `(with-package-iterator (,next-fn ,pkg-var ,@symbol-types))
1885 `(((,variable nil ,data-type) (,pkg-var ,package))
1889 (not (multiple-value-setq (,(loop-when-it-var)
1896 (defun make-ansi-loop-universe (extended-p)
1897 (let ((w (make-standard-loop-universe
1898 :keywords '((named (loop-do-named))
1899 (initially (loop-do-initially))
1900 (finally (loop-do-finally))
1902 (doing (loop-do-do))
1903 (return (loop-do-return))
1904 (collect (loop-list-collection list))
1905 (collecting (loop-list-collection list))
1906 (append (loop-list-collection append))
1907 (appending (loop-list-collection append))
1908 (nconc (loop-list-collection nconc))
1909 (nconcing (loop-list-collection nconc))
1910 (count (loop-sum-collection count
1913 (counting (loop-sum-collection count
1916 (sum (loop-sum-collection sum number number))
1917 (summing (loop-sum-collection sum number number))
1918 (maximize (loop-maxmin-collection max))
1919 (minimize (loop-maxmin-collection min))
1920 (maximizing (loop-maxmin-collection max))
1921 (minimizing (loop-maxmin-collection min))
1922 (always (loop-do-always t nil)) ; Normal, do always
1923 (never (loop-do-always t t)) ; Negate test on always.
1924 (thereis (loop-do-thereis t))
1925 (while (loop-do-while nil :while)) ; Normal, do while
1926 (until (loop-do-while t :until)) ;Negate test on while
1927 (when (loop-do-if when nil)) ; Normal, do when
1928 (if (loop-do-if if nil)) ; synonymous
1929 (unless (loop-do-if unless t)) ; Negate test on when
1930 (with (loop-do-with))
1931 (repeat (loop-do-repeat)))
1932 :for-keywords '((= (loop-ansi-for-equals))
1933 (across (loop-for-across))
1936 (from (loop-for-arithmetic :from))
1937 (downfrom (loop-for-arithmetic :downfrom))
1938 (upfrom (loop-for-arithmetic :upfrom))
1939 (below (loop-for-arithmetic :below))
1940 (above (loop-for-arithmetic :above))
1941 (to (loop-for-arithmetic :to))
1942 (upto (loop-for-arithmetic :upto))
1943 (downto (loop-for-arithmetic :downto))
1944 (by (loop-for-arithmetic :by))
1945 (being (loop-for-being)))
1946 :iteration-keywords '((for (loop-do-for))
1948 :type-symbols '(array atom bignum bit bit-vector character
1949 compiled-function complex cons double-float
1950 fixnum float function hash-table integer
1951 keyword list long-float nil null number
1952 package pathname random-state ratio rational
1953 readtable sequence short-float simple-array
1954 simple-bit-vector simple-string simple-vector
1955 single-float standard-char stream string
1956 base-char symbol t vector)
1958 :ansi (if extended-p :extended t))))
1959 (add-loop-path '(hash-key hash-keys) 'loop-hash-table-iteration-path w
1960 :preposition-groups '((:of :in))
1961 :inclusive-permitted nil
1962 :user-data '(:which :hash-key))
1963 (add-loop-path '(hash-value hash-values) 'loop-hash-table-iteration-path w
1964 :preposition-groups '((:of :in))
1965 :inclusive-permitted nil
1966 :user-data '(:which :hash-value))
1967 (add-loop-path '(symbol symbols) 'loop-package-symbols-iteration-path w
1968 :preposition-groups '((:of :in))
1969 :inclusive-permitted nil
1970 :user-data '(:symbol-types (:internal
1973 (add-loop-path '(external-symbol external-symbols)
1974 'loop-package-symbols-iteration-path w
1975 :preposition-groups '((:of :in))
1976 :inclusive-permitted nil
1977 :user-data '(:symbol-types (:external)))
1978 (add-loop-path '(present-symbol present-symbols)
1979 'loop-package-symbols-iteration-path w
1980 :preposition-groups '((:of :in))
1981 :inclusive-permitted nil
1982 :user-data '(:symbol-types (:internal
1986 (defparameter *loop-ansi-universe*
1987 (make-ansi-loop-universe nil))
1989 (defun loop-standard-expansion (keywords-and-forms environment universe)
1990 (if (and keywords-and-forms (symbolp (car keywords-and-forms)))
1991 (loop-translate keywords-and-forms environment universe)
1992 (let ((tag (gensym)))
1993 `(block nil (tagbody ,tag (progn ,@keywords-and-forms) (go ,tag))))))
1995 (sb!int:defmacro-mundanely loop (&environment env &rest keywords-and-forms)
1996 (loop-standard-expansion keywords-and-forms env *loop-ansi-universe*))
1998 (sb!int:defmacro-mundanely loop-finish ()
2000 "Cause the iteration to terminate \"normally\", the same as implicit
2001 termination by an iteration driving clause, or by use of WHILE or
2002 UNTIL -- the epilogue code (if any) will be run, and any implicitly
2003 collected result will be returned as the value of the LOOP."