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. Whether or not it then supported all the
10 ;;;; environments implied by the reader conditionals in the source
11 ;;;; code (e.g. #!+CLOE-RUNTIME) before that modification, it sure
12 ;;;; doesn't now: it might be appropriate for CMU-CL-derived systems
13 ;;;; in general but only claims to be appropriate for the particular
14 ;;;; branch I was working on.
16 ;;;; This software is derived from software originally released by the
17 ;;;; Massachusetts Institute of Technology and Symbolics, Inc. Copyright and
18 ;;;; release statements follow. Later modifications to the software are in
19 ;;;; the public domain and are provided with absolutely no warranty. See the
20 ;;;; COPYING and CREDITS files for more information.
22 ;;;; Portions of LOOP are Copyright (c) 1986 by the Massachusetts Institute
23 ;;;; of Technology. All Rights Reserved.
25 ;;;; Permission to use, copy, modify and distribute this software and its
26 ;;;; documentation for any purpose and without fee is hereby granted,
27 ;;;; provided that the M.I.T. copyright notice appear in all copies and that
28 ;;;; both that copyright notice and this permission notice appear in
29 ;;;; supporting documentation. The names "M.I.T." and "Massachusetts
30 ;;;; Institute of Technology" may not be used in advertising or publicity
31 ;;;; pertaining to distribution of the software without specific, written
32 ;;;; prior permission. Notice must be given in supporting documentation that
33 ;;;; copying distribution is by permission of M.I.T. M.I.T. makes no
34 ;;;; representations about the suitability of this software for any purpose.
35 ;;;; It is provided "as is" without express or implied warranty.
37 ;;;; Massachusetts Institute of Technology
38 ;;;; 77 Massachusetts Avenue
39 ;;;; Cambridge, Massachusetts 02139
40 ;;;; United States of America
43 ;;;; Portions of LOOP are Copyright (c) 1989, 1990, 1991, 1992 by Symbolics,
44 ;;;; Inc. All Rights Reserved.
46 ;;;; Permission to use, copy, modify and distribute this software and its
47 ;;;; documentation for any purpose and without fee is hereby granted,
48 ;;;; provided that the Symbolics copyright notice appear in all copies and
49 ;;;; that both that copyright notice and this permission notice appear in
50 ;;;; supporting documentation. The name "Symbolics" may not be used in
51 ;;;; advertising or publicity pertaining to distribution of the software
52 ;;;; without specific, written prior permission. Notice must be given in
53 ;;;; supporting documentation that copying distribution is by permission of
54 ;;;; Symbolics. Symbolics makes no representations about the suitability of
55 ;;;; this software for any purpose. It is provided "as is" without express
56 ;;;; or implied warranty.
58 ;;;; Symbolics, CLOE Runtime, and Minima are trademarks, and CLOE, Genera,
59 ;;;; and Zetalisp are registered trademarks of Symbolics, Inc.
62 ;;;; 8 New England Executive Park, East
63 ;;;; Burlington, Massachusetts 01803
64 ;;;; United States of America
67 (in-package "SB!LOOP")
69 ;;;; The design of this LOOP is intended to permit, using mostly the same
70 ;;;; kernel of code, up to three different "loop" macros:
72 ;;;; (1) The unextended, unextensible ANSI standard LOOP;
74 ;;;; (2) A clean "superset" extension of the ANSI LOOP which provides
75 ;;;; functionality similar to that of the old LOOP, but "in the style of"
76 ;;;; the ANSI LOOP. For instance, user-definable iteration paths, with a
77 ;;;; somewhat cleaned-up interface.
79 ;;;; (3) Extensions provided in another file which can make this LOOP
80 ;;;; kernel behave largely compatibly with the Genera-vintage LOOP macro,
81 ;;;; with only a small addition of code (instead of two whole, separate,
84 ;;;; Each of the above three LOOP variations can coexist in the same LISP
87 ;;;; KLUDGE: In SBCL, we only really use variant (1), and any generality
88 ;;;; for the other variants is wasted. -- WHN 20000121
90 ;;;; FIXME: the STEP-FUNCTION stuff in the code seems to've been
91 ;;;; intended to support code which was conditionalized with
92 ;;;; LOOP-PREFER-POP (not true on CMU CL) and which has since been
93 ;;;; removed. Thus, STEP-FUNCTION stuff could probably be removed too.
95 ;;;; miscellaneous environment things
97 (eval-when (:compile-toplevel :load-toplevel :execute)
98 (defvar *loop-real-data-type* 'real))
100 (eval-when (:compile-toplevel :load-toplevel :execute)
101 (defvar *loop-gentemp* nil)
102 (defun loop-gentemp (&optional (pref 'loopvar-))
104 (gentemp (string pref))
107 ;;; @@@@ The following form takes a list of variables and a form which
108 ;;; presumably references those variables, and wraps it somehow so that the
109 ;;; compiler does not consider those variables have been referenced. The intent
110 ;;; of this is that iteration variables can be flagged as unused by the
111 ;;; compiler, e.g. I in (loop for i from 1 to 10 do (print t)), since we will
112 ;;; tell it when a usage of it is "invisible" or "not to be considered".
114 ;;; We implicitly assume that a setq does not count as a reference. That is,
115 ;;; the kind of form generated for the above loop construct to step I,
117 ;;; `(SETQ I ,(HIDE-VARIABLE-REFERENCES '(I) '(1+ I))).
119 ;;; FIXME: This is a no-op except for Genera, now obsolete, so it
121 (defun hide-variable-references (variable-list form)
122 (declare (ignore variable-list))
125 ;;; @@@@ The following function takes a flag, a variable, and a form which
126 ;;; presumably references that variable, and wraps it somehow so that the
127 ;;; compiler does not consider that variable to have been referenced. The
128 ;;; intent of this is that iteration variables can be flagged as unused by the
129 ;;; compiler, e.g. I in (loop for i from 1 to 10 do (print t)), since we will
130 ;;; tell it when a usage of it is "invisible" or "not to be considered".
132 ;;; We implicitly assume that a setq does not count as a reference. That is,
133 ;;; the kind of form generated for the above loop construct to step I,
135 ;;; `(SETQ I ,(HIDE-VARIABLE-REFERENCES T 'I '(1+ I))).
137 ;;; Certain cases require that the "invisibility" of the reference be
138 ;;; conditional upon something. This occurs in cases of "named" variables (the
139 ;;; USING clause). For instance, we want IDX in (LOOP FOR E BEING THE
140 ;;; VECTOR-ELEMENTS OF V USING (INDEX IDX) ...) to be "invisible" when it is
141 ;;; stepped, so that the user gets informed if IDX is not referenced. However,
142 ;;; if no USING clause is present, we definitely do not want to be informed
143 ;;; that some gensym or other is not used.
145 ;;; It is easier for the caller to do this conditionally by passing a flag
146 ;;; (which happens to be the second value of NAMED-VARIABLE, q.v.) to this
147 ;;; function than for all callers to contain the conditional invisibility
150 ;;; FIXME: This is a no-op except for Genera, now obsolete, so it
152 (defun hide-variable-reference (really-hide variable form)
153 (declare (ignore really-hide variable))
156 ;;;; list collection macrology
158 (sb!kernel:defmacro-mundanely with-loop-list-collection-head
159 ((head-var tail-var &optional user-head-var) &body body)
160 (let ((l (and user-head-var (list (list user-head-var nil)))))
161 `(let* ((,head-var (list nil)) (,tail-var ,head-var) ,@l)
164 (sb!kernel:defmacro-mundanely loop-collect-rplacd
165 (&environment env (head-var tail-var &optional user-head-var) form)
166 (setq form (sb!xc:macroexpand form env))
167 (flet ((cdr-wrap (form n)
169 (do () ((<= n 4) (setq form `(,(case n
175 (setq form `(cddddr ,form) n (- n 4)))))
176 (let ((tail-form form) (ncdrs nil))
177 ;; Determine whether the form being constructed is a list of known
180 (cond ((eq (car form) 'list)
181 (setq ncdrs (1- (length (cdr form)))))
182 ((member (car form) '(list* cons))
183 (when (and (cddr form) (member (car (last form)) '(nil 'nil)))
184 (setq ncdrs (- (length (cdr form)) 2))))))
187 `(when (setf (cdr ,tail-var) ,tail-form)
188 (setq ,tail-var (last (cdr ,tail-var)))))
189 ((< ncdrs 0) (return-from loop-collect-rplacd nil))
191 ;; @@@@ Here we have a choice of two idioms:
192 ;; (RPLACD TAIL (SETQ TAIL TAIL-FORM))
193 ;; (SETQ TAIL (SETF (CDR TAIL) TAIL-FORM)).
194 ;; Genera and most others I have seen do better with the
196 `(rplacd ,tail-var (setq ,tail-var ,tail-form)))
197 (t `(setq ,tail-var ,(cdr-wrap `(setf (cdr ,tail-var)
200 ;; If not using locatives or something similar to update the
201 ;; user's head variable, we've got to set it... It's harmless
202 ;; to repeatedly set it unconditionally, and probably faster
207 (setq ,user-head-var (cdr ,head-var)))))
210 (sb!kernel:defmacro-mundanely loop-collect-answer (head-var
211 &optional user-head-var)
215 ;;;; maximization technology
218 The basic idea of all this minimax randomness here is that we have to
219 have constructed all uses of maximize and minimize to a particular
220 "destination" before we can decide how to code them. The goal is to not
221 have to have any kinds of flags, by knowing both that (1) the type is
222 something which we can provide an initial minimum or maximum value for
223 and (2) know that a MAXIMIZE and MINIMIZE are not being combined.
225 SO, we have a datastructure which we annotate with all sorts of things,
226 incrementally updating it as we generate loop body code, and then use
227 a wrapper and internal macros to do the coding when the loop has been
231 (defstruct (loop-minimax
232 (:constructor make-loop-minimax-internal)
242 (defvar *loop-minimax-type-infinities-alist*
243 ;; Note: In the portable loop.lisp, this had various
244 ;; conditional-on-*FEATURES* cases to support machines which had true
245 ;; floating infinity. Now that we're limited to CMU CL, this is irrelevant.
246 ;; FIXME: Or is it? What if we ever support infinity? Perhaps we should
247 ;; put in something conditional on SB-INFINITY or something?
248 '((fixnum most-positive-fixnum most-negative-fixnum)))
250 (defun make-loop-minimax (answer-variable type)
251 (let ((infinity-data (cdr (assoc type
252 *loop-minimax-type-infinities-alist*
254 (make-loop-minimax-internal
255 :answer-variable answer-variable
257 :temp-variable (loop-gentemp 'loop-maxmin-temp-)
258 :flag-variable (and (not infinity-data)
259 (loop-gentemp 'loop-maxmin-flag-))
261 :infinity-data infinity-data)))
263 (defun loop-note-minimax-operation (operation minimax)
264 (pushnew (the symbol operation) (loop-minimax-operations minimax))
265 (when (and (cdr (loop-minimax-operations minimax))
266 (not (loop-minimax-flag-variable minimax)))
267 (setf (loop-minimax-flag-variable minimax)
268 (loop-gentemp 'loop-maxmin-flag-)))
271 (sb!kernel:defmacro-mundanely with-minimax-value (lm &body body)
272 (let ((init (loop-typed-init (loop-minimax-type lm)))
273 (which (car (loop-minimax-operations lm)))
274 (infinity-data (loop-minimax-infinity-data lm))
275 (answer-var (loop-minimax-answer-variable lm))
276 (temp-var (loop-minimax-temp-variable lm))
277 (flag-var (loop-minimax-flag-variable lm))
278 (type (loop-minimax-type lm)))
280 `(let ((,answer-var ,init) (,temp-var ,init) (,flag-var nil))
281 (declare (type ,type ,answer-var ,temp-var))
283 `(let ((,answer-var ,(if (eq which 'min)
284 (first infinity-data)
285 (second infinity-data)))
287 (declare (type ,type ,answer-var ,temp-var))
290 (sb!kernel:defmacro-mundanely loop-accumulate-minimax-value (lm
293 (let* ((answer-var (loop-minimax-answer-variable lm))
294 (temp-var (loop-minimax-temp-variable lm))
295 (flag-var (loop-minimax-flag-variable lm))
297 (hide-variable-reference
298 t (loop-minimax-answer-variable lm)
302 ,temp-var ,answer-var))))
304 (setq ,temp-var ,form)
305 (when ,(if flag-var `(or (not ,flag-var) ,test) test)
306 (setq ,@(and flag-var `(,flag-var t))
307 ,answer-var ,temp-var)))))
309 ;;;; LOOP keyword tables
312 LOOP keyword tables are hash tables string keys and a test of EQUAL.
314 The actual descriptive/dispatch structure used by LOOP is called a "loop
315 universe" contains a few tables and parameterizations. The basic idea is
316 that we can provide a non-extensible ANSI-compatible loop environment,
317 an extensible ANSI-superset loop environment, and (for such environments
318 as CLOE) one which is "sufficiently close" to the old Genera-vintage
319 LOOP for use by old user programs without requiring all of the old LOOP
325 ;;; Compare two "tokens". The first is the frob out of *LOOP-SOURCE-CODE*,
326 ;;; the second a symbol to check against.
327 (defun loop-tequal (x1 x2)
328 (and (symbolp x1) (string= x1 x2)))
330 (defun loop-tassoc (kwd alist)
331 (and (symbolp kwd) (assoc kwd alist :test #'string=)))
333 (defun loop-tmember (kwd list)
334 (and (symbolp kwd) (member kwd list :test #'string=)))
336 (defun loop-lookup-keyword (loop-token table)
337 (and (symbolp loop-token)
338 (values (gethash (symbol-name loop-token) table))))
340 (sb!kernel:defmacro-mundanely loop-store-table-data (symbol table datum)
341 `(setf (gethash (symbol-name ,symbol) ,table) ,datum))
343 (defstruct (loop-universe
346 keywords ; hash table, value = (fn-name . extra-data)
347 iteration-keywords ; hash table, value = (fn-name . extra-data)
348 for-keywords ; hash table, value = (fn-name . extra-data)
349 path-keywords ; hash table, value = (fn-name . extra-data)
350 type-symbols ; hash table of type SYMBOLS, test EQ,
351 ; value = CL type specifier
352 type-keywords ; hash table of type STRINGS, test EQUAL,
353 ; value = CL type spec
354 ansi ; NIL, T, or :EXTENDED
355 implicit-for-required) ; see loop-hack-iteration
356 (sb!int:def!method print-object ((u loop-universe) stream)
357 (let ((string (case (loop-universe-ansi u)
360 (:extended "Extended-ANSI")
361 (t (loop-universe-ansi u)))))
362 (print-unreadable-object (u stream :type t)
363 (write-string string stream))))
365 ;;; This is the "current" loop context in use when we are expanding a
366 ;;; loop. It gets bound on each invocation of LOOP.
367 (defvar *loop-universe*)
369 (defun make-standard-loop-universe (&key keywords for-keywords
370 iteration-keywords path-keywords
371 type-keywords type-symbols ansi)
372 (check-type ansi (member nil t :extended))
373 (flet ((maketable (entries)
374 (let* ((size (length entries))
375 (ht (make-hash-table :size (if (< size 10) 10 size)
378 (setf (gethash (symbol-name (car x)) ht) (cadr x)))
381 :keywords (maketable keywords)
382 :for-keywords (maketable for-keywords)
383 :iteration-keywords (maketable iteration-keywords)
384 :path-keywords (maketable path-keywords)
386 :implicit-for-required (not (null ansi))
387 :type-keywords (maketable type-keywords)
388 :type-symbols (let* ((size (length type-symbols))
389 (ht (make-hash-table :size (if (< size 10) 10 size)
391 (dolist (x type-symbols)
393 (setf (gethash x ht) x)
394 (setf (gethash (car x) ht) (cadr x))))
399 (defvar *loop-destructuring-hooks*
402 "If not NIL, this must be a list of two things:
403 a LET-like macro, and a SETQ-like macro, which perform LOOP-style destructuring.")
405 (defun loop-make-psetq (frobs)
409 (if (null (cddr frobs)) (cadr frobs)
410 `(prog1 ,(cadr frobs)
411 ,(loop-make-psetq (cddr frobs))))))))
413 (defun loop-make-desetq (var-val-pairs)
414 (if (null var-val-pairs)
416 (cons (if *loop-destructuring-hooks*
417 (cadr *loop-destructuring-hooks*)
421 (defvar *loop-desetq-temporary*
422 (make-symbol "LOOP-DESETQ-TEMP"))
424 (sb!kernel:defmacro-mundanely loop-really-desetq (&environment env
426 (labels ((find-non-null (var)
427 ;; see whether there's any non-null thing here
428 ;; recurse if the list element is itself a list
429 (do ((tail var)) ((not (consp tail)) tail)
430 (when (find-non-null (pop tail)) (return t))))
431 (loop-desetq-internal (var val &optional temp)
432 ;; returns a list of actions to be performed
436 ;; don't lose possible side-effects
437 (if (eq (car val) 'prog1)
438 ;; these can come from psetq or desetq below.
439 ;; throw away the value, keep the side-effects.
440 ;;Special case is for handling an expanded POP.
441 (mapcan #'(lambda (x)
443 (or (not (eq (car x) 'car))
444 (not (symbolp (cadr x)))
445 (not (symbolp (setq x (sb!xc:macroexpand x env)))))
450 (let* ((car (car var))
452 (car-non-null (find-non-null car))
453 (cdr-non-null (find-non-null cdr)))
454 (when (or car-non-null cdr-non-null)
457 (temp (or temp *loop-desetq-temporary*))
458 (body `(,@(loop-desetq-internal car
460 (setq ,temp (cdr ,temp))
461 ,@(loop-desetq-internal cdr
465 `(,@(unless (eq temp val)
466 `((setq ,temp ,val)))
468 `((let ((,temp ,val))
471 (loop-desetq-internal car `(car ,val) temp)))))
474 `((setq ,var ,val)))))))
476 ((null var-val-pairs)
477 (if (null (cdr actions)) (car actions) `(progn ,@(nreverse actions))))
478 (setq actions (revappend
479 (loop-desetq-internal (pop var-val-pairs)
483 ;;;; LOOP-local variables
485 ;;;This is the "current" pointer into the LOOP source code.
486 (defvar *loop-source-code*)
488 ;;;This is the pointer to the original, for things like NAMED that
489 ;;;insist on being in a particular position
490 (defvar *loop-original-source-code*)
492 ;;;This is *loop-source-code* as of the "last" clause. It is used
493 ;;;primarily for generating error messages (see loop-error, loop-warn).
494 (defvar *loop-source-context*)
496 ;;;List of names for the LOOP, supplied by the NAMED clause.
497 (defvar *loop-names*)
499 ;;;The macroexpansion environment given to the macro.
500 (defvar *loop-macro-environment*)
502 ;;;This holds variable names specified with the USING clause.
503 ;;; See LOOP-NAMED-VARIABLE.
504 (defvar *loop-named-variables*)
506 ;;; LETlist-like list being accumulated for one group of parallel bindings.
507 (defvar *loop-variables*)
509 ;;;List of declarations being accumulated in parallel with
511 (defvar *loop-declarations*)
513 ;;;Used by LOOP for destructuring binding, if it is doing that itself.
514 ;;; See loop-make-variable.
515 (defvar *loop-desetq-crocks*)
517 ;;; List of wrapping forms, innermost first, which go immediately inside
518 ;;; the current set of parallel bindings being accumulated in
519 ;;; *loop-variables*. The wrappers are appended onto a body. E.g.,
520 ;;; this list could conceivably has as its value ((with-open-file (g0001
521 ;;; g0002 ...))), with g0002 being one of the bindings in
522 ;;; *loop-variables* (this is why the wrappers go inside of the variable
524 (defvar *loop-wrappers*)
526 ;;;This accumulates lists of previous values of *loop-variables* and the
527 ;;;other lists above, for each new nesting of bindings. See
529 (defvar *loop-bind-stack*)
531 ;;;This is a LOOP-global variable for the (obsolete) NODECLARE clause
532 ;;;which inhibits LOOP from actually outputting a type declaration for
533 ;;;an iteration (or any) variable.
534 (defvar *loop-nodeclare*)
536 ;;;This is simply a list of LOOP iteration variables, used for checking
538 (defvar *loop-iteration-variables*)
540 ;;;List of prologue forms of the loop, accumulated in reverse order.
541 (defvar *loop-prologue*)
543 (defvar *loop-before-loop*)
545 (defvar *loop-after-body*)
547 ;;;This is T if we have emitted any body code, so that iteration driving
548 ;;;clauses can be disallowed. This is not strictly the same as
549 ;;;checking *loop-body*, because we permit some clauses such as RETURN
550 ;;;to not be considered "real" body (so as to permit the user to "code"
551 ;;;an abnormal return value "in loop").
552 (defvar *loop-emitted-body*)
554 ;;;List of epilogue forms (supplied by FINALLY generally), accumulated
555 ;;; in reverse order.
556 (defvar *loop-epilogue*)
558 ;;;List of epilogue forms which are supplied after the above "user"
559 ;;;epilogue. "normal" termination return values are provide by putting
560 ;;;the return form in here. Normally this is done using
561 ;;;loop-emit-final-value, q.v.
562 (defvar *loop-after-epilogue*)
564 ;;;The "culprit" responsible for supplying a final value from the loop.
565 ;;;This is so loop-emit-final-value can moan about multiple return
566 ;;;values being supplied.
567 (defvar *loop-final-value-culprit*)
569 ;;;If not NIL, we are in some branch of a conditional. Some clauses may
571 (defvar *loop-inside-conditional*)
573 ;;;If not NIL, this is a temporary bound around the loop for holding the
574 ;;;temporary value for "it" in things like "when (f) collect it". It
575 ;;;may be used as a supertemporary by some other things.
576 (defvar *loop-when-it-variable*)
578 ;;;Sometimes we decide we need to fold together parts of the loop, but
579 ;;;some part of the generated iteration code is different for the first
580 ;;;and remaining iterations. This variable will be the temporary which
581 ;;;is the flag used in the loop to tell whether we are in the first or
582 ;;;remaining iterations.
583 (defvar *loop-never-stepped-variable*)
585 ;;;List of all the value-accumulation descriptor structures in the loop.
586 ;;; See loop-get-collection-info.
587 (defvar *loop-collection-cruft*) ; for multiple COLLECTs (etc)
589 ;;;; code analysis stuff
591 (defun loop-constant-fold-if-possible (form &optional expected-type)
592 (let ((new-form form) (constantp nil) (constant-value nil))
593 (when (setq constantp (constantp new-form))
594 (setq constant-value (eval new-form)))
595 (when (and constantp expected-type)
596 (unless (typep constant-value expected-type)
597 (loop-warn "The form ~S evaluated to ~S, which was not of the anticipated type ~S."
598 form constant-value expected-type)
599 (setq constantp nil constant-value nil)))
600 (values new-form constantp constant-value)))
602 (defun loop-constantp (form)
605 ;;;; LOOP iteration optimization
607 (defvar *loop-duplicate-code*
610 (defvar *loop-iteration-flag-variable*
611 (make-symbol "LOOP-NOT-FIRST-TIME"))
613 (defun loop-code-duplication-threshold (env)
614 (declare (ignore env))
615 (let (;; If we could read optimization declaration information (as with
616 ;; the DECLARATION-INFORMATION function (present in CLTL2, removed
617 ;; from ANSI standard) we could set these values flexibly. Without
618 ;; DECLARATION-INFORMATION, we have to set them to constants.
621 (+ 40 (* (- speed space) 10))))
623 (sb!kernel:defmacro-mundanely loop-body (&environment env
629 &aux rbefore rafter flagvar)
630 (unless (= (length before-loop) (length after-loop))
631 (error "LOOP-BODY called with non-synched before- and after-loop lists"))
632 ;;All our work is done from these copies, working backwards from the end:
633 (setq rbefore (reverse before-loop) rafter (reverse after-loop))
640 (member (car x) '(go return return-from)))
643 (pify (l) (if (null (cdr l)) (car l) `(progn ,@l)))
645 (let ((form `(tagbody
646 ,@(psimp (append prologue (nreverse rbefore)))
648 ,@(psimp (append main-body
652 ,@(psimp epilogue))))
653 (if flagvar `(let ((,flagvar nil)) ,form) form))))
654 (when (or *loop-duplicate-code* (not rbefore))
655 (return-from loop-body (makebody)))
656 ;; This outer loop iterates once for each not-first-time flag test
657 ;; generated plus once more for the forms that don't need a flag test
658 (do ((threshold (loop-code-duplication-threshold env))) (nil)
659 (declare (fixnum threshold))
660 ;; Go backwards from the ends of before-loop and after-loop merging all
661 ;; the equivalent forms into the body.
662 (do () ((or (null rbefore) (not (equal (car rbefore) (car rafter)))))
663 (push (pop rbefore) main-body)
665 (unless rbefore (return (makebody)))
666 ;; The first forms in rbefore & rafter (which are the chronologically
667 ;; last forms in the list) differ, therefore they cannot be moved
668 ;; into the main body. If everything that chronologically precedes
669 ;; them either differs or is equal but is okay to duplicate, we can
670 ;; just put all of rbefore in the prologue and all of rafter after
671 ;; the body. Otherwise, there is something that is not okay to
672 ;; duplicate, so it and everything chronologically after it in
673 ;; rbefore and rafter must go into the body, with a flag test to
674 ;; distinguish the first time around the loop from later times.
675 ;; What chronologically precedes the non-duplicatable form will
676 ;; be handled the next time around the outer loop.
677 (do ((bb rbefore (cdr bb))
682 ((null bb) (return-from loop-body (makebody))) ; Did it.
683 (cond ((not (equal (car bb) (car aa))) (setq lastdiff bb count 0))
684 ((or (not (setq inc (estimate-code-size (car bb) env)))
685 (> (incf count inc) threshold))
686 ;; Ok, we have found a non-duplicatable piece of code.
687 ;; Everything chronologically after it must be in the central
688 ;; body. Everything chronologically at and after lastdiff goes
689 ;; into the central body under a flag test.
690 (let ((then nil) (else nil))
692 (push (pop rbefore) else)
693 (push (pop rafter) then)
694 (when (eq rbefore (cdr lastdiff)) (return)))
696 (push `(setq ,(setq flagvar *loop-iteration-flag-variable*)
699 (push `(if ,flagvar ,(pify (psimp then)) ,(pify (psimp else)))
701 ;; Everything chronologically before lastdiff until the
702 ;; non-duplicatable form (car bb) is the same in rbefore and
703 ;; rafter so just copy it into the body
706 (push (pop rbefore) main-body)
707 (when (eq rbefore (cdr bb)) (return)))
710 (defun duplicatable-code-p (expr env)
712 (let ((ans (estimate-code-size expr env)))
713 (declare (fixnum ans))
714 ;; @@@@ Use (DECLARATION-INFORMATION 'OPTIMIZE ENV) here to get an
715 ;; alist of optimize quantities back to help quantify how much code we
716 ;; are willing to duplicate.
719 (defvar *special-code-sizes*
720 '((return 0) (progn 0)
721 (null 1) (not 1) (eq 1) (car 1) (cdr 1)
722 (when 1) (unless 1) (if 1)
723 (caar 2) (cadr 2) (cdar 2) (cddr 2)
724 (caaar 3) (caadr 3) (cadar 3) (caddr 3)
725 (cdaar 3) (cdadr 3) (cddar 3) (cdddr 3)
726 (caaaar 4) (caaadr 4) (caadar 4) (caaddr 4)
727 (cadaar 4) (cadadr 4) (caddar 4) (cadddr 4)
728 (cdaaar 4) (cdaadr 4) (cdadar 4) (cdaddr 4)
729 (cddaar 4) (cddadr 4) (cdddar 4) (cddddr 4)))
731 (defvar *estimate-code-size-punt*
735 labels lambda let let* locally
736 macrolet multiple-value-bind
743 (defun destructuring-size (x)
744 (do ((x x (cdr x)) (n 0 (+ (destructuring-size (car x)) n)))
745 ((atom x) (+ n (if (null x) 0 1)))))
747 (defun estimate-code-size (x env)
748 (catch 'estimate-code-size
749 (estimate-code-size-1 x env)))
751 (defun estimate-code-size-1 (x env)
752 (flet ((list-size (l)
755 (dolist (x l n) (incf n (estimate-code-size-1 x env))))))
756 ;;@@@@ ???? (declare (function list-size (list) fixnum))
757 (cond ((constantp x) 1)
758 ((symbolp x) (multiple-value-bind (new-form expanded-p)
759 (sb!xc:macroexpand-1 x env)
761 (estimate-code-size-1 new-form env)
763 ((atom x) 1) ;; ??? self-evaluating???
765 (let ((fn (car x)) (tem nil) (n 0))
766 (declare (symbol fn) (fixnum n))
767 (macrolet ((f (overhead &optional (args nil args-p))
768 `(the fixnum (+ (the fixnum ,overhead)
770 (list-size ,(if args-p
773 (cond ((setq tem (get fn 'estimate-code-size))
776 (t (funcall tem x env))))
777 ((setq tem (assoc fn *special-code-sizes*))
780 (dolist (clause (cdr x) n)
781 (incf n (list-size clause)) (incf n)))
783 (do ((l (cdr x) (cdr l))) ((null l) n)
785 (destructuring-size (car l))
786 (estimate-code-size-1 (cadr l) env)))))
787 ((member fn '(setq psetq))
788 (do ((l (cdr x) (cdr l))) ((null l) n)
789 (setq n (+ n (estimate-code-size-1 (cadr l) env) 1))))
792 ;; This skirts the issue of implementationally-defined
793 ;; lambda macros by recognizing CL function names and
795 (if (or (symbolp (cadr x))
796 (and (consp (cadr x)) (eq (caadr x) 'setf)))
798 (throw 'duplicatable-code-p nil)))
799 ((eq fn 'multiple-value-setq)
800 (f (length (second x)) (cddr x)))
801 ((eq fn 'return-from)
802 (1+ (estimate-code-size-1 (third x) env)))
803 ((or (special-operator-p fn)
804 (member fn *estimate-code-size-punt*))
805 (throw 'estimate-code-size nil))
806 (t (multiple-value-bind (new-form expanded-p)
807 (sb!xc:macroexpand-1 x env)
809 (estimate-code-size-1 new-form env)
811 (t (throw 'estimate-code-size nil)))))
815 (defun loop-context ()
816 (do ((l *loop-source-context* (cdr l)) (new nil (cons (car l) new)))
817 ((eq l (cdr *loop-source-code*)) (nreverse new))))
819 (defun loop-error (format-string &rest format-args)
820 (error "~?~%current LOOP context:~{ ~S~}."
825 (defun loop-warn (format-string &rest format-args)
826 (warn "~?~%current LOOP context:~{ ~S~}."
831 (defun loop-check-data-type (specified-type required-type
832 &optional (default-type required-type))
833 (if (null specified-type)
835 (multiple-value-bind (a b) (subtypep specified-type required-type)
837 (loop-warn "LOOP couldn't verify that ~S is a subtype of the required type ~S."
838 specified-type required-type))
840 (loop-error "The specified data type ~S is not a subtype of ~S."
841 specified-type required-type)))
844 (defun loop-translate (*loop-source-code*
845 *loop-macro-environment*
847 (let ((*loop-original-source-code* *loop-source-code*)
848 (*loop-source-context* nil)
849 (*loop-iteration-variables* nil)
850 (*loop-variables* nil)
851 (*loop-nodeclare* nil)
852 (*loop-named-variables* nil)
853 (*loop-declarations* nil)
854 (*loop-desetq-crocks* nil)
855 (*loop-bind-stack* nil)
856 (*loop-prologue* nil)
857 (*loop-wrappers* nil)
858 (*loop-before-loop* nil)
860 (*loop-emitted-body* nil)
861 (*loop-after-body* nil)
862 (*loop-epilogue* nil)
863 (*loop-after-epilogue* nil)
864 (*loop-final-value-culprit* nil)
865 (*loop-inside-conditional* nil)
866 (*loop-when-it-variable* nil)
867 (*loop-never-stepped-variable* nil)
869 (*loop-collection-cruft* nil))
870 (loop-iteration-driver)
872 (let ((answer `(loop-body
873 ,(nreverse *loop-prologue*)
874 ,(nreverse *loop-before-loop*)
875 ,(nreverse *loop-body*)
876 ,(nreverse *loop-after-body*)
877 ,(nreconc *loop-epilogue*
878 (nreverse *loop-after-epilogue*)))))
880 (setq answer `(block ,(pop *loop-names*) ,answer))
881 (unless *loop-names* (return nil)))
882 (dolist (entry *loop-bind-stack*)
883 (let ((vars (first entry))
884 (dcls (second entry))
885 (crocks (third entry))
886 (wrappers (fourth entry)))
888 (setq answer (append w (list answer))))
889 (when (or vars dcls crocks)
890 (let ((forms (list answer)))
891 ;;(when crocks (push crocks forms))
892 (when dcls (push `(declare ,@dcls) forms))
893 (setq answer `(,(cond ((not vars) 'locally)
894 (*loop-destructuring-hooks*
895 (first *loop-destructuring-hooks*))
900 `((destructuring-bind ,@crocks
905 (defun loop-iteration-driver ()
906 (do () ((null *loop-source-code*))
907 (let ((keyword (car *loop-source-code*)) (tem nil))
908 (cond ((not (symbolp keyword))
909 (loop-error "~S found where LOOP keyword expected" keyword))
910 (t (setq *loop-source-context* *loop-source-code*)
913 (loop-lookup-keyword keyword
914 (loop-universe-keywords
916 ;; It's a "miscellaneous" toplevel LOOP keyword (DO,
917 ;; COLLECT, NAMED, etc.)
918 (apply (symbol-function (first tem)) (rest tem)))
920 (loop-lookup-keyword keyword
921 (loop-universe-iteration-keywords *loop-universe*)))
922 (loop-hack-iteration tem))
923 ((loop-tmember keyword '(and else))
924 ;; The alternative is to ignore it, i.e. let it go
925 ;; around to the next keyword...
926 (loop-error "secondary clause misplaced at top level in LOOP macro: ~S ~S ~S ..."
928 (car *loop-source-code*)
929 (cadr *loop-source-code*)))
930 (t (loop-error "unknown LOOP keyword: ~S" keyword))))))))
932 (defun loop-pop-source ()
933 (if *loop-source-code*
934 (pop *loop-source-code*)
935 (loop-error "LOOP source code ran out when another token was expected.")))
937 (defun loop-get-progn ()
938 (do ((forms (list (loop-pop-source)) (cons (loop-pop-source) forms))
939 (nextform (car *loop-source-code*) (car *loop-source-code*)))
941 (if (null (cdr forms)) (car forms) (cons 'progn (nreverse forms))))))
943 (defun loop-get-form ()
944 (if *loop-source-code*
946 (loop-error "LOOP code ran out where a form was expected.")))
948 (defun loop-construct-return (form)
949 `(return-from ,(car *loop-names*) ,form))
951 (defun loop-pseudo-body (form)
952 (cond ((or *loop-emitted-body* *loop-inside-conditional*)
953 (push form *loop-body*))
954 (t (push form *loop-before-loop*) (push form *loop-after-body*))))
956 (defun loop-emit-body (form)
957 (setq *loop-emitted-body* t)
958 (loop-pseudo-body form))
960 (defun loop-emit-final-value (form)
961 (push (loop-construct-return form) *loop-after-epilogue*)
962 (when *loop-final-value-culprit*
963 (loop-warn "The LOOP clause is providing a value for the iteration,~@
964 however one was already established by a ~S clause."
965 *loop-final-value-culprit*))
966 (setq *loop-final-value-culprit* (car *loop-source-context*)))
968 (defun loop-disallow-conditional (&optional kwd)
969 (when *loop-inside-conditional*
970 (loop-error "~:[This LOOP~;The LOOP ~:*~S~] clause is not permitted inside a conditional." kwd)))
974 (defun loop-typed-init (data-type)
975 (when (and data-type (subtypep data-type 'number))
976 (if (or (subtypep data-type 'float) (subtypep data-type '(complex float)))
980 (defun loop-optional-type (&optional variable)
981 ;; No variable specified implies that no destructuring is permissible.
982 (and *loop-source-code* ; Don't get confused by NILs..
983 (let ((z (car *loop-source-code*)))
984 (cond ((loop-tequal z 'of-type)
985 ;; This is the syntactically unambigous form in that the form
986 ;; of the type specifier does not matter. Also, it is assumed
987 ;; that the type specifier is unambiguously, and without need
988 ;; of translation, a common lisp type specifier or pattern
989 ;; (matching the variable) thereof.
994 ;; This is the (sort of) "old" syntax, even though we didn't
995 ;; used to support all of these type symbols.
996 (let ((type-spec (or (gethash z
997 (loop-universe-type-symbols
999 (gethash (symbol-name z)
1000 (loop-universe-type-keywords
1001 *loop-universe*)))))
1006 ;; This is our sort-of old syntax. But this is only valid for
1007 ;; when we are destructuring, so we will be compulsive (should
1008 ;; we really be?) and require that we in fact be doing variable
1009 ;; destructuring here. We must translate the old keyword
1010 ;; pattern typespec into a fully-specified pattern of real type
1012 (if (consp variable)
1015 "~S found where a LOOP keyword, LOOP type keyword, or LOOP type pattern expected"
1017 (loop-error "~S found where a LOOP keyword or LOOP type keyword expected" z))
1019 (labels ((translate (k v)
1020 (cond ((null k) nil)
1024 (loop-universe-type-symbols
1026 (gethash (symbol-name k)
1027 (loop-universe-type-keywords
1030 "The destructuring type pattern ~S contains the unrecognized type keyword ~S."
1035 "The destructuring type pattern ~S doesn't match the variable pattern ~S."
1037 (t (cons (translate (car k) (car v))
1038 (translate (cdr k) (cdr v))))))
1042 (cons (replicate typ (car v))
1043 (replicate typ (cdr v))))))
1044 (translate z variable)))))))
1048 (defun loop-bind-block ()
1049 (when (or *loop-variables* *loop-declarations* *loop-wrappers*)
1050 (push (list (nreverse *loop-variables*)
1052 *loop-desetq-crocks*
1055 (setq *loop-variables* nil
1056 *loop-declarations* nil
1057 *loop-desetq-crocks* nil
1058 *loop-wrappers* nil)))
1060 (defun loop-make-variable (name initialization dtype
1061 &optional iteration-variable-p)
1063 (cond ((not (null initialization))
1064 (push (list (setq name (loop-gentemp 'loop-ignore-))
1067 (push `(ignore ,name) *loop-declarations*))))
1069 (cond (iteration-variable-p
1070 (if (member name *loop-iteration-variables*)
1071 (loop-error "duplicated LOOP iteration variable ~S" name)
1072 (push name *loop-iteration-variables*)))
1073 ((assoc name *loop-variables*)
1074 (loop-error "duplicated variable ~S in LOOP parallel binding"
1076 (unless (symbolp name)
1077 (loop-error "bad variable ~S somewhere in LOOP" name))
1078 (loop-declare-variable name dtype)
1079 ;; We use ASSOC on this list to check for duplications (above),
1080 ;; so don't optimize out this list:
1081 (push (list name (or initialization (loop-typed-init dtype)))
1084 (cond (*loop-destructuring-hooks*
1085 (loop-declare-variable name dtype)
1086 (push (list name initialization) *loop-variables*))
1087 (t (let ((newvar (loop-gentemp 'loop-destructure-)))
1088 (push (list newvar initialization) *loop-variables*)
1089 ;; *LOOP-DESETQ-CROCKS* gathered in reverse order.
1090 (setq *loop-desetq-crocks*
1091 (list* name newvar *loop-desetq-crocks*))
1092 ;; FIXME: We can delete this, right?
1094 (loop-make-variable name
1097 iteration-variable-p)))))
1098 (t (let ((tcar nil) (tcdr nil))
1099 (if (atom dtype) (setq tcar (setq tcdr dtype))
1100 (setq tcar (car dtype) tcdr (cdr dtype)))
1101 (loop-make-variable (car name) nil tcar iteration-variable-p)
1102 (loop-make-variable (cdr name) nil tcdr iteration-variable-p))))
1105 (defun loop-make-iteration-variable (name initialization dtype)
1106 (loop-make-variable name initialization dtype t))
1108 (defun loop-declare-variable (name dtype)
1109 (cond ((or (null name) (null dtype) (eq dtype t)) nil)
1111 (unless (or (eq dtype t) (member (the symbol name) *loop-nodeclare*))
1112 (let ((dtype (let ((init (loop-typed-init dtype)))
1113 (if (typep init dtype)
1115 `(or (member ,init) ,dtype)))))
1116 (push `(type ,dtype ,name) *loop-declarations*))))
1118 (cond ((consp dtype)
1119 (loop-declare-variable (car name) (car dtype))
1120 (loop-declare-variable (cdr name) (cdr dtype)))
1121 (t (loop-declare-variable (car name) dtype)
1122 (loop-declare-variable (cdr name) dtype))))
1123 (t (error "invalid LOOP variable passed in: ~S" name))))
1125 (defun loop-maybe-bind-form (form data-type)
1126 (if (loop-constantp form)
1128 (loop-make-variable (loop-gentemp 'loop-bind-) form data-type)))
1130 (defun loop-do-if (for negatep)
1131 (let ((form (loop-get-form)) (*loop-inside-conditional* t) (it-p nil))
1132 (flet ((get-clause (for)
1133 (do ((body nil)) (nil)
1134 (let ((key (car *loop-source-code*)) (*loop-body* nil) data)
1135 (cond ((not (symbolp key))
1137 "~S found where keyword expected getting LOOP clause after ~S"
1139 (t (setq *loop-source-context* *loop-source-code*)
1141 (when (loop-tequal (car *loop-source-code*) 'it)
1142 (setq *loop-source-code*
1145 (loop-when-it-variable)))
1146 (cdr *loop-source-code*))))
1147 (cond ((or (not (setq data (loop-lookup-keyword
1148 key (loop-universe-keywords *loop-universe*))))
1149 (progn (apply (symbol-function (car data))
1151 (null *loop-body*)))
1153 "~S does not introduce a LOOP clause that can follow ~S."
1155 (t (setq body (nreconc *loop-body* body)))))))
1156 (if (loop-tequal (car *loop-source-code*) :and)
1158 (return (if (cdr body)
1159 `(progn ,@(nreverse body))
1161 (let ((then (get-clause for))
1162 (else (when (loop-tequal (car *loop-source-code*) :else)
1164 (list (get-clause :else)))))
1165 (when (loop-tequal (car *loop-source-code*) :end)
1167 (when it-p (setq form `(setq ,it-p ,form)))
1169 `(if ,(if negatep `(not ,form) form)
1173 (defun loop-do-initially ()
1174 (loop-disallow-conditional :initially)
1175 (push (loop-get-progn) *loop-prologue*))
1177 (defun loop-do-finally ()
1178 (loop-disallow-conditional :finally)
1179 (push (loop-get-progn) *loop-epilogue*))
1181 (defun loop-do-do ()
1182 (loop-emit-body (loop-get-progn)))
1184 (defun loop-do-named ()
1185 (let ((name (loop-pop-source)))
1186 (unless (symbolp name)
1187 (loop-error "~S is an invalid name for your LOOP" name))
1188 (when (or *loop-before-loop* *loop-body* *loop-after-epilogue* *loop-inside-conditional*)
1189 (loop-error "The NAMED ~S clause occurs too late." name))
1191 (loop-error "You may only use one NAMED clause in your loop: NAMED ~S ... NAMED ~S."
1192 (car *loop-names*) name))
1193 (setq *loop-names* (list name nil))))
1195 (defun loop-do-return ()
1196 (loop-pseudo-body (loop-construct-return (loop-get-form))))
1198 ;;;; value accumulation: LIST
1200 (defstruct (loop-collector
1208 (data nil)) ;collector-specific data
1210 (defun loop-get-collection-info (collector class default-type)
1211 (let ((form (loop-get-form))
1212 (dtype (and (not (loop-universe-ansi *loop-universe*)) (loop-optional-type)))
1213 (name (when (loop-tequal (car *loop-source-code*) 'into)
1215 (loop-pop-source))))
1216 (when (not (symbolp name))
1217 (loop-error "The value accumulation recipient name, ~S, is not a symbol." name))
1219 (setq dtype (or (loop-optional-type) default-type)))
1220 (let ((cruft (find (the symbol name) *loop-collection-cruft*
1221 :key #'loop-collector-name)))
1223 (push (setq cruft (make-loop-collector
1224 :name name :class class
1225 :history (list collector) :dtype dtype))
1226 *loop-collection-cruft*))
1227 (t (unless (eq (loop-collector-class cruft) class)
1229 "incompatible kinds of LOOP value accumulation specified for collecting~@
1230 ~:[as the value of the LOOP~;~:*INTO ~S~]: ~S and ~S"
1231 name (car (loop-collector-history cruft)) collector))
1232 (unless (equal dtype (loop-collector-dtype cruft))
1234 "unequal datatypes specified in different LOOP value accumulations~@
1236 name dtype (loop-collector-dtype cruft))
1237 (when (eq (loop-collector-dtype cruft) t)
1238 (setf (loop-collector-dtype cruft) dtype)))
1239 (push collector (loop-collector-history cruft))))
1240 (values cruft form))))
1242 (defun loop-list-collection (specifically) ; NCONC, LIST, or APPEND
1243 (multiple-value-bind (lc form)
1244 (loop-get-collection-info specifically 'list 'list)
1245 (let ((tempvars (loop-collector-tempvars lc)))
1247 (setf (loop-collector-tempvars lc)
1248 (setq tempvars (list* (loop-gentemp 'loop-list-head-)
1249 (loop-gentemp 'loop-list-tail-)
1250 (and (loop-collector-name lc)
1251 (list (loop-collector-name lc))))))
1252 (push `(with-loop-list-collection-head ,tempvars) *loop-wrappers*)
1253 (unless (loop-collector-name lc)
1254 (loop-emit-final-value `(loop-collect-answer ,(car tempvars)
1255 ,@(cddr tempvars)))))
1257 (list (setq form `(list ,form)))
1259 (append (unless (and (consp form) (eq (car form) 'list))
1260 (setq form `(copy-list ,form)))))
1261 (loop-emit-body `(loop-collect-rplacd ,tempvars ,form)))))
1263 ;;;; value accumulation: MAX, MIN, SUM, COUNT
1265 (defun loop-sum-collection (specifically required-type default-type);SUM, COUNT
1266 (multiple-value-bind (lc form)
1267 (loop-get-collection-info specifically 'sum default-type)
1268 (loop-check-data-type (loop-collector-dtype lc) required-type)
1269 (let ((tempvars (loop-collector-tempvars lc)))
1271 (setf (loop-collector-tempvars lc)
1272 (setq tempvars (list (loop-make-variable
1273 (or (loop-collector-name lc)
1274 (loop-gentemp 'loop-sum-))
1275 nil (loop-collector-dtype lc)))))
1276 (unless (loop-collector-name lc)
1277 (loop-emit-final-value (car (loop-collector-tempvars lc)))))
1279 (if (eq specifically 'count)
1281 (setq ,(car tempvars)
1282 ,(hide-variable-reference t
1284 `(1+ ,(car tempvars)))))
1285 `(setq ,(car tempvars)
1286 (+ ,(hide-variable-reference t
1291 (defun loop-maxmin-collection (specifically)
1292 (multiple-value-bind (lc form)
1293 (loop-get-collection-info specifically 'maxmin *loop-real-data-type*)
1294 (loop-check-data-type (loop-collector-dtype lc) *loop-real-data-type*)
1295 (let ((data (loop-collector-data lc)))
1297 (setf (loop-collector-data lc)
1298 (setq data (make-loop-minimax
1299 (or (loop-collector-name lc)
1300 (loop-gentemp 'loop-maxmin-))
1301 (loop-collector-dtype lc))))
1302 (unless (loop-collector-name lc)
1303 (loop-emit-final-value (loop-minimax-answer-variable data))))
1304 (loop-note-minimax-operation specifically data)
1305 (push `(with-minimax-value ,data) *loop-wrappers*)
1306 (loop-emit-body `(loop-accumulate-minimax-value ,data
1310 ;;;; value accumulation: aggregate booleans
1312 ;;; ALWAYS and NEVER
1314 ;;; Under ANSI these are not permitted to appear under conditionalization.
1315 (defun loop-do-always (restrictive negate)
1316 (let ((form (loop-get-form)))
1317 (when restrictive (loop-disallow-conditional))
1318 (loop-emit-body `(,(if negate 'when 'unless) ,form
1319 ,(loop-construct-return nil)))
1320 (loop-emit-final-value t)))
1324 ;;; Under ANSI this is not permitted to appear under conditionalization.
1325 (defun loop-do-thereis (restrictive)
1326 (when restrictive (loop-disallow-conditional))
1327 (loop-emit-body `(when (setq ,(loop-when-it-variable) ,(loop-get-form))
1328 ,(loop-construct-return *loop-when-it-variable*))))
1330 (defun loop-do-while (negate kwd &aux (form (loop-get-form)))
1331 (loop-disallow-conditional kwd)
1332 (loop-pseudo-body `(,(if negate 'when 'unless) ,form (go end-loop))))
1334 (defun loop-do-with ()
1335 (loop-disallow-conditional :with)
1336 (do ((var) (val) (dtype)) (nil)
1337 (setq var (loop-pop-source)
1338 dtype (loop-optional-type var)
1339 val (cond ((loop-tequal (car *loop-source-code*) :=)
1343 (loop-make-variable var val dtype)
1344 (if (loop-tequal (car *loop-source-code*) :and)
1346 (return (loop-bind-block)))))
1348 ;;;; the iteration driver
1350 (defun loop-hack-iteration (entry)
1351 (flet ((make-endtest (list-of-forms)
1352 (cond ((null list-of-forms) nil)
1353 ((member t list-of-forms) '(go end-loop))
1354 (t `(when ,(if (null (cdr (setq list-of-forms
1355 (nreverse list-of-forms))))
1357 (cons 'or list-of-forms))
1359 (do ((pre-step-tests nil)
1361 (post-step-tests nil)
1363 (pre-loop-pre-step-tests nil)
1364 (pre-loop-steps nil)
1365 (pre-loop-post-step-tests nil)
1366 (pre-loop-pseudo-steps nil)
1369 ;; Note that we collect endtests in reverse order, but steps in correct
1370 ;; order. MAKE-ENDTEST does the nreverse for us.
1371 (setq tem (setq data
1372 (apply (symbol-function (first entry)) (rest entry))))
1373 (and (car tem) (push (car tem) pre-step-tests))
1374 (setq steps (nconc steps (copy-list (car (setq tem (cdr tem))))))
1375 (and (car (setq tem (cdr tem))) (push (car tem) post-step-tests))
1377 (nconc pseudo-steps (copy-list (car (setq tem (cdr tem))))))
1378 (setq tem (cdr tem))
1379 (when *loop-emitted-body*
1380 (loop-error "iteration in LOOP follows body code"))
1381 (unless tem (setq tem data))
1382 (when (car tem) (push (car tem) pre-loop-pre-step-tests))
1383 ;; FIXME: This (SETF FOO (NCONC FOO BAR)) idiom appears often enough
1384 ;; that it might be worth making it into an NCONCF macro.
1385 (setq pre-loop-steps
1386 (nconc pre-loop-steps (copy-list (car (setq tem (cdr tem))))))
1387 (when (car (setq tem (cdr tem)))
1388 (push (car tem) pre-loop-post-step-tests))
1389 (setq pre-loop-pseudo-steps
1390 (nconc pre-loop-pseudo-steps (copy-list (cadr tem))))
1391 (unless (loop-tequal (car *loop-source-code*) :and)
1392 (setq *loop-before-loop*
1393 (list* (loop-make-desetq pre-loop-pseudo-steps)
1394 (make-endtest pre-loop-post-step-tests)
1395 (loop-make-psetq pre-loop-steps)
1396 (make-endtest pre-loop-pre-step-tests)
1397 *loop-before-loop*))
1398 (setq *loop-after-body*
1399 (list* (loop-make-desetq pseudo-steps)
1400 (make-endtest post-step-tests)
1401 (loop-make-psetq steps)
1402 (make-endtest pre-step-tests)
1406 (loop-pop-source) ; Flush the "AND".
1407 (when (and (not (loop-universe-implicit-for-required *loop-universe*))
1409 (loop-lookup-keyword
1410 (car *loop-source-code*)
1411 (loop-universe-iteration-keywords *loop-universe*))))
1412 ;; The latest ANSI clarification is that the FOR/AS after the AND must
1415 (setq entry tem)))))
1417 ;;;; main iteration drivers
1419 ;;; FOR variable keyword ..args..
1420 (defun loop-do-for ()
1421 (let* ((var (loop-pop-source))
1422 (data-type (loop-optional-type var))
1423 (keyword (loop-pop-source))
1426 (setq first-arg (loop-get-form))
1427 (unless (and (symbolp keyword)
1428 (setq tem (loop-lookup-keyword
1430 (loop-universe-for-keywords *loop-universe*))))
1431 (loop-error "~S is an unknown keyword in FOR or AS clause in LOOP."
1433 (apply (car tem) var first-arg data-type (cdr tem))))
1435 (defun loop-do-repeat ()
1436 (let ((form (loop-get-form))
1437 (type (loop-check-data-type (loop-optional-type)
1438 *loop-real-data-type*)))
1439 (when (and (consp form) (eq (car form) 'the) (subtypep (second form) type))
1440 (setq type (second form)))
1441 (multiple-value-bind (number constantp value)
1442 (loop-constant-fold-if-possible form type)
1443 (cond ((and constantp (<= value 1)) `(t () () () ,(<= value 0) () () ()))
1444 (t (let ((var (loop-make-variable (loop-gentemp 'loop-repeat-)
1448 `((not (plusp (setq ,var (1- ,var))))
1449 () () () () () () ())
1450 `((minusp (setq ,var (1- ,var)))
1453 (defun loop-when-it-variable ()
1454 (or *loop-when-it-variable*
1455 (setq *loop-when-it-variable*
1456 (loop-make-variable (loop-gentemp 'loop-it-) nil nil))))
1458 ;;;; various FOR/AS subdispatches
1460 ;;; ANSI "FOR x = y [THEN z]" is sort of like the old Genera one when the THEN
1461 ;;; is omitted (other than being more stringent in its placement), and like the
1462 ;;; old "FOR x FIRST y THEN z" when the THEN is present. I.e., the first
1463 ;;; initialization occurs in the loop body (first-step), not in the variable
1465 (defun loop-ansi-for-equals (var val data-type)
1466 (loop-make-iteration-variable var nil data-type)
1467 (cond ((loop-tequal (car *loop-source-code*) :then)
1468 ;; Then we are the same as "FOR x FIRST y THEN z".
1470 `(() (,var ,(loop-get-form)) () ()
1471 () (,var ,val) () ()))
1472 (t ;; We are the same as "FOR x = y".
1473 `(() (,var ,val) () ()))))
1475 (defun loop-for-across (var val data-type)
1476 (loop-make-iteration-variable var nil data-type)
1477 (let ((vector-var (loop-gentemp 'loop-across-vector-))
1478 (index-var (loop-gentemp 'loop-across-index-)))
1479 (multiple-value-bind (vector-form constantp vector-value)
1480 (loop-constant-fold-if-possible val 'vector)
1482 vector-var vector-form
1483 (if (and (consp vector-form) (eq (car vector-form) 'the))
1486 (loop-make-variable index-var 0 'fixnum)
1488 (length-form (cond ((not constantp)
1489 (let ((v (loop-gentemp 'loop-across-limit-)))
1490 (push `(setq ,v (length ,vector-var))
1492 (loop-make-variable v 0 'fixnum)))
1493 (t (setq length (length vector-value)))))
1494 (first-test `(>= ,index-var ,length-form))
1495 (other-test first-test)
1496 (step `(,var (aref ,vector-var ,index-var)))
1497 (pstep `(,index-var (1+ ,index-var))))
1498 (declare (fixnum length))
1500 (setq first-test (= length 0))
1502 (setq other-test t)))
1503 `(,other-test ,step () ,pstep
1504 ,@(and (not (eq first-test other-test))
1505 `(,first-test ,step () ,pstep)))))))
1509 (defun loop-list-step (listvar)
1510 ;; We are not equipped to analyze whether 'FOO is the same as #'FOO here in
1511 ;; any sensible fashion, so let's give an obnoxious warning whenever 'FOO is
1512 ;; used as the stepping function.
1514 ;; While a Discerning Compiler may deal intelligently with
1515 ;; (FUNCALL 'FOO ...), not recognizing FOO may defeat some LOOP
1517 (let ((stepper (cond ((loop-tequal (car *loop-source-code*) :by)
1520 (t '(function cdr)))))
1521 (cond ((and (consp stepper) (eq (car stepper) 'quote))
1522 (loop-warn "Use of QUOTE around stepping function in LOOP will be left verbatim.")
1523 `(funcall ,stepper ,listvar))
1524 ((and (consp stepper) (eq (car stepper) 'function))
1525 (list (cadr stepper) listvar))
1527 `(funcall ,(loop-make-variable (loop-gentemp 'loop-fn-)
1532 (defun loop-for-on (var val data-type)
1533 (multiple-value-bind (list constantp list-value)
1534 (loop-constant-fold-if-possible val)
1535 (let ((listvar var))
1536 (cond ((and var (symbolp var))
1537 (loop-make-iteration-variable var list data-type))
1538 (t (loop-make-variable (setq listvar (loop-gentemp)) list 'list)
1539 (loop-make-iteration-variable var nil data-type)))
1540 (let ((list-step (loop-list-step listvar)))
1541 (let* ((first-endtest
1542 (hide-variable-reference
1545 ;; the following should use `atom' instead of `endp', per
1548 (other-endtest first-endtest))
1549 (when (and constantp (listp list-value))
1550 (setq first-endtest (null list-value)))
1551 (cond ((eq var listvar)
1552 ;; Contour of the loop is different because we use the user's
1554 `(() (,listvar ,(hide-variable-reference t listvar list-step))
1555 ,other-endtest () () () ,first-endtest ()))
1556 (t (let ((step `(,var ,listvar))
1557 (pseudo `(,listvar ,list-step)))
1558 `(,other-endtest ,step () ,pseudo
1559 ,@(and (not (eq first-endtest other-endtest))
1560 `(,first-endtest ,step () ,pseudo)))))))))))
1562 (defun loop-for-in (var val data-type)
1563 (multiple-value-bind (list constantp list-value)
1564 (loop-constant-fold-if-possible val)
1565 (let ((listvar (loop-gentemp 'loop-list-)))
1566 (loop-make-iteration-variable var nil data-type)
1567 (loop-make-variable listvar list 'list)
1568 (let ((list-step (loop-list-step listvar)))
1569 (let* ((first-endtest `(endp ,listvar))
1570 (other-endtest first-endtest)
1571 (step `(,var (car ,listvar)))
1572 (pseudo-step `(,listvar ,list-step)))
1573 (when (and constantp (listp list-value))
1574 (setq first-endtest (null list-value)))
1575 `(,other-endtest ,step () ,pseudo-step
1576 ,@(and (not (eq first-endtest other-endtest))
1577 `(,first-endtest ,step () ,pseudo-step))))))))
1579 ;;;; iteration paths
1581 (defstruct (loop-path
1590 (defun add-loop-path (names function universe
1591 &key preposition-groups inclusive-permitted user-data)
1592 (unless (listp names) (setq names (list names)))
1593 (check-type universe loop-universe)
1594 (let ((ht (loop-universe-path-keywords universe))
1596 :names (mapcar #'symbol-name names)
1598 :user-data user-data
1599 :preposition-groups (mapcar (lambda (x)
1600 (if (listp x) x (list x)))
1602 :inclusive-permitted inclusive-permitted)))
1603 (dolist (name names)
1604 (setf (gethash (symbol-name name) ht) lp))
1607 ;;; Note: path functions are allowed to use loop-make-variable, hack
1608 ;;; the prologue, etc.
1609 (defun loop-for-being (var val data-type)
1610 ;; FOR var BEING each/the pathname prep-phrases using-stuff... each/the =
1611 ;; EACH or THE. Not clear if it is optional, so I guess we'll warn.
1616 (initial-prepositions nil))
1617 (cond ((loop-tmember val '(:each :the)) (setq path (loop-pop-source)))
1618 ((loop-tequal (car *loop-source-code*) :and)
1621 (unless (loop-tmember (car *loop-source-code*)
1622 '(:its :each :his :her))
1623 (loop-error "~S was found where ITS or EACH expected in LOOP iteration path syntax."
1624 (car *loop-source-code*)))
1626 (setq path (loop-pop-source))
1627 (setq initial-prepositions `((:in ,val))))
1628 (t (loop-error "unrecognizable LOOP iteration path syntax: missing EACH or THE?")))
1629 (cond ((not (symbolp path))
1631 "~S was found where a LOOP iteration path name was expected."
1633 ((not (setq data (loop-lookup-keyword path (loop-universe-path-keywords *loop-universe*))))
1634 (loop-error "~S is not the name of a LOOP iteration path." path))
1635 ((and inclusive (not (loop-path-inclusive-permitted data)))
1636 (loop-error "\"Inclusive\" iteration is not possible with the ~S LOOP iteration path." path)))
1637 (let ((fun (loop-path-function data))
1638 (preps (nconc initial-prepositions
1639 (loop-collect-prepositional-phrases
1640 (loop-path-preposition-groups data)
1642 (user-data (loop-path-user-data data)))
1643 (when (symbolp fun) (setq fun (symbol-function fun)))
1644 (setq stuff (if inclusive
1645 (apply fun var data-type preps :inclusive t user-data)
1646 (apply fun var data-type preps user-data))))
1647 (when *loop-named-variables*
1648 (loop-error "Unused USING variables: ~S." *loop-named-variables*))
1649 ;; STUFF is now (bindings prologue-forms . stuff-to-pass-back). Protect the
1650 ;; system from the user and the user from himself.
1651 (unless (member (length stuff) '(6 10))
1652 (loop-error "Value passed back by LOOP iteration path function for path ~S has invalid length."
1654 (do ((l (car stuff) (cdr l)) (x)) ((null l))
1655 (if (atom (setq x (car l)))
1656 (loop-make-iteration-variable x nil nil)
1657 (loop-make-iteration-variable (car x) (cadr x) (caddr x))))
1658 (setq *loop-prologue* (nconc (reverse (cadr stuff)) *loop-prologue*))
1661 (defun named-variable (name)
1662 (let ((tem (loop-tassoc name *loop-named-variables*)))
1663 (declare (list tem))
1664 (cond ((null tem) (values (loop-gentemp) nil))
1665 (t (setq *loop-named-variables* (delete tem *loop-named-variables*))
1666 (values (cdr tem) t)))))
1668 (defun loop-collect-prepositional-phrases (preposition-groups
1672 (flet ((in-group-p (x group) (car (loop-tmember x group))))
1674 (prepositional-phrases initial-phrases)
1675 (this-group nil nil)
1677 (disallowed-prepositions
1678 (mapcan #'(lambda (x)
1680 (find (car x) preposition-groups :test #'in-group-p)))
1682 (used-prepositions (mapcar #'car initial-phrases)))
1683 ((null *loop-source-code*) (nreverse prepositional-phrases))
1684 (declare (symbol this-prep))
1685 (setq token (car *loop-source-code*))
1686 (dolist (group preposition-groups)
1687 (when (setq this-prep (in-group-p token group))
1688 (return (setq this-group group))))
1690 (when (member this-prep disallowed-prepositions)
1692 (if (member this-prep used-prepositions)
1693 "A ~S prepositional phrase occurs multiply for some LOOP clause."
1694 "Preposition ~S was used when some other preposition has subsumed it.")
1696 (setq used-prepositions (if (listp this-group)
1697 (append this-group used-prepositions)
1698 (cons this-group used-prepositions)))
1700 (push (list this-prep (loop-get-form)) prepositional-phrases))
1701 ((and USING-allowed (loop-tequal token 'using))
1703 (do ((z (loop-pop-source) (loop-pop-source)) (tem)) (nil)
1706 (not (null (cddr z)))
1707 (not (symbolp (car z)))
1708 (and (cadr z) (not (symbolp (cadr z)))))
1709 (loop-error "~S bad variable pair in path USING phrase" z))
1711 (if (setq tem (loop-tassoc (car z) *loop-named-variables*))
1713 "The variable substitution for ~S occurs twice in a USING phrase,~@
1715 (car z) (cadr z) (cadr tem))
1716 (push (cons (car z) (cadr z)) *loop-named-variables*)))
1717 (when (or (null *loop-source-code*)
1718 (symbolp (car *loop-source-code*)))
1720 (t (return (nreverse prepositional-phrases)))))))
1722 ;;;; master sequencer function
1724 (defun loop-sequencer (indexv indexv-type indexv-user-specified-p
1725 variable variable-type
1726 sequence-variable sequence-type
1727 step-hack default-top
1729 (let ((endform nil) ; Form (constant or variable) with limit value
1730 (sequencep nil) ; T if sequence arg has been provided
1731 (testfn nil) ; endtest function
1732 (test nil) ; endtest form
1733 (stepby (1+ (or (loop-typed-init indexv-type) 0))) ; our increment
1734 (stepby-constantp t)
1735 (step nil) ; step form
1736 (dir nil) ; direction of stepping: NIL, :UP, :DOWN
1737 (inclusive-iteration nil) ; T if include last index
1738 (start-given nil) ; T when prep phrase has specified start
1740 (start-constantp nil)
1741 (limit-given nil) ; T when prep phrase has specified end
1742 (limit-constantp nil)
1745 (when variable (loop-make-iteration-variable variable nil variable-type))
1746 (do ((l prep-phrases (cdr l)) (prep) (form) (odir)) ((null l))
1747 (setq prep (caar l) form (cadar l))
1751 (loop-make-variable sequence-variable form sequence-type))
1752 ((:from :downfrom :upfrom)
1753 (setq start-given t)
1754 (cond ((eq prep :downfrom) (setq dir ':down))
1755 ((eq prep :upfrom) (setq dir ':up)))
1756 (multiple-value-setq (form start-constantp start-value)
1757 (loop-constant-fold-if-possible form indexv-type))
1758 (loop-make-iteration-variable indexv form indexv-type))
1759 ((:upto :to :downto :above :below)
1760 (cond ((loop-tequal prep :upto) (setq inclusive-iteration
1762 ((loop-tequal prep :to) (setq inclusive-iteration t))
1763 ((loop-tequal prep :downto) (setq inclusive-iteration
1765 ((loop-tequal prep :above) (setq dir ':down))
1766 ((loop-tequal prep :below) (setq dir ':up)))
1767 (setq limit-given t)
1768 (multiple-value-setq (form limit-constantp limit-value)
1769 (loop-constant-fold-if-possible form indexv-type))
1770 (setq endform (if limit-constantp
1773 (loop-gentemp 'loop-limit-) form indexv-type))))
1775 (multiple-value-setq (form stepby-constantp stepby)
1776 (loop-constant-fold-if-possible form indexv-type))
1777 (unless stepby-constantp
1778 (loop-make-variable (setq stepby (loop-gentemp 'loop-step-by-))
1782 "~S invalid preposition in sequencing or sequence path;~@
1783 maybe invalid prepositions were specified in iteration path descriptor?"
1785 (when (and odir dir (not (eq dir odir)))
1786 (loop-error "conflicting stepping directions in LOOP sequencing path"))
1788 (when (and sequence-variable (not sequencep))
1789 (loop-error "missing OF or IN phrase in sequence path"))
1790 ;; Now fill in the defaults.
1792 (loop-make-iteration-variable
1794 (setq start-constantp t
1795 start-value (or (loop-typed-init indexv-type) 0))
1797 (cond ((member dir '(nil :up))
1798 (when (or limit-given default-top)
1800 (loop-make-variable (setq endform
1801 (loop-gentemp 'loop-seq-limit-))
1803 (push `(setq ,endform ,default-top) *loop-prologue*))
1804 (setq testfn (if inclusive-iteration '> '>=)))
1805 (setq step (if (eql stepby 1) `(1+ ,indexv) `(+ ,indexv ,stepby))))
1806 (t (unless start-given
1808 (loop-error "don't know where to start stepping"))
1809 (push `(setq ,indexv (1- ,default-top)) *loop-prologue*))
1810 (when (and default-top (not endform))
1811 (setq endform (loop-typed-init indexv-type)
1812 inclusive-iteration t))
1813 (when endform (setq testfn (if inclusive-iteration '< '<=)))
1815 (if (eql stepby 1) `(1- ,indexv) `(- ,indexv ,stepby)))))
1818 (hide-variable-reference t indexv `(,testfn ,indexv ,endform))))
1821 `(,variable ,(hide-variable-reference indexv-user-specified-p
1824 (let ((first-test test) (remaining-tests test))
1825 (when (and stepby-constantp start-constantp limit-constantp)
1826 (when (setq first-test
1827 (funcall (symbol-function testfn)
1830 (setq remaining-tests t)))
1831 `(() (,indexv ,(hide-variable-reference t indexv step))
1832 ,remaining-tests ,step-hack () () ,first-test ,step-hack))))
1834 ;;;; interfaces to the master sequencer
1836 (defun loop-for-arithmetic (var val data-type kwd)
1838 var (loop-check-data-type data-type *loop-real-data-type*) t
1839 nil nil nil nil nil nil
1840 (loop-collect-prepositional-phrases
1841 '((:from :upfrom :downfrom) (:to :upto :downto :above :below) (:by))
1842 nil (list (list kwd val)))))
1844 (defun loop-sequence-elements-path (variable data-type prep-phrases
1850 (multiple-value-bind (indexv indexv-user-specified-p) (named-variable 'index)
1851 (let ((sequencev (named-variable 'sequence)))
1852 (list* nil nil ; dummy bindings and prologue
1854 indexv 'fixnum indexv-user-specified-p
1855 variable (or data-type element-type)
1856 sequencev sequence-type
1857 `(,fetch-function ,sequencev ,indexv)
1858 `(,size-function ,sequencev)
1861 ;;;; builtin LOOP iteration paths
1864 (loop for v being the hash-values of ht do (print v))
1865 (loop for k being the hash-keys of ht do (print k))
1866 (loop for v being the hash-values of ht using (hash-key k) do (print (list k v)))
1867 (loop for k being the hash-keys of ht using (hash-value v) do (print (list k v)))
1870 (defun loop-hash-table-iteration-path (variable data-type prep-phrases
1872 (check-type which (member hash-key hash-value))
1873 (cond ((or (cdr prep-phrases) (not (member (caar prep-phrases) '(:in :of))))
1874 (loop-error "Too many prepositions!"))
1875 ((null prep-phrases)
1876 (loop-error "missing OF or IN in ~S iteration path")))
1877 (let ((ht-var (loop-gentemp 'loop-hashtab-))
1878 (next-fn (loop-gentemp 'loop-hashtab-next-))
1879 (dummy-predicate-var nil)
1881 (multiple-value-bind (other-var other-p)
1882 (named-variable (if (eq which 'hash-key) 'hash-value 'hash-key))
1883 ;; @@@@ named-variable returns a second value of T if the name was
1884 ;; actually specified, so clever code can throw away the gensym'ed up
1885 ;; variable if it isn't really needed. The following is for those
1886 ;; implementations in which we cannot put dummy NILs into
1887 ;; multiple-value-setq variable lists.
1889 dummy-predicate-var (loop-when-it-variable))
1892 (bindings `((,variable nil ,data-type)
1893 (,ht-var ,(cadar prep-phrases))
1894 ,@(and other-p other-var `((,other-var nil))))))
1895 (if (eq which 'hash-key)
1896 (setq key-var variable val-var (and other-p other-var))
1897 (setq key-var (and other-p other-var) val-var variable))
1898 (push `(with-hash-table-iterator (,next-fn ,ht-var)) *loop-wrappers*)
1899 (when (consp key-var)
1901 `(,key-var ,(setq key-var (loop-gentemp 'loop-hash-key-temp-))
1903 (push `(,key-var nil) bindings))
1904 (when (consp val-var)
1906 `(,val-var ,(setq val-var (loop-gentemp 'loop-hash-val-temp-))
1908 (push `(,val-var nil) bindings))
1909 `(,bindings ;bindings
1913 (not (multiple-value-setq (,dummy-predicate-var ,key-var ,val-var)
1914 (,next-fn))) ;post-test
1917 (defun loop-package-symbols-iteration-path (variable data-type prep-phrases
1919 (cond ((or (cdr prep-phrases) (not (member (caar prep-phrases) '(:in :of))))
1920 (loop-error "Too many prepositions!"))
1921 ((null prep-phrases)
1922 (loop-error "missing OF or IN in ~S iteration path")))
1923 (unless (symbolp variable)
1924 (loop-error "Destructuring is not valid for package symbol iteration."))
1925 (let ((pkg-var (loop-gentemp 'loop-pkgsym-))
1926 (next-fn (loop-gentemp 'loop-pkgsym-next-)))
1927 (push `(with-package-iterator (,next-fn ,pkg-var ,@symbol-types))
1929 `(((,variable nil ,data-type) (,pkg-var ,(cadar prep-phrases)))
1933 (not (multiple-value-setq (,(loop-when-it-variable)
1940 (defun make-ansi-loop-universe (extended-p)
1941 (let ((w (make-standard-loop-universe
1942 :keywords `((named (loop-do-named))
1943 (initially (loop-do-initially))
1944 (finally (loop-do-finally))
1946 (doing (loop-do-do))
1947 (return (loop-do-return))
1948 (collect (loop-list-collection list))
1949 (collecting (loop-list-collection list))
1950 (append (loop-list-collection append))
1951 (appending (loop-list-collection append))
1952 (nconc (loop-list-collection nconc))
1953 (nconcing (loop-list-collection nconc))
1954 (count (loop-sum-collection count
1955 ,*loop-real-data-type*
1957 (counting (loop-sum-collection count
1958 ,*loop-real-data-type*
1960 (sum (loop-sum-collection sum number number))
1961 (summing (loop-sum-collection sum number number))
1962 (maximize (loop-maxmin-collection max))
1963 (minimize (loop-maxmin-collection min))
1964 (maximizing (loop-maxmin-collection max))
1965 (minimizing (loop-maxmin-collection min))
1966 (always (loop-do-always t nil)) ; Normal, do always
1967 (never (loop-do-always t t)) ; Negate test on always.
1968 (thereis (loop-do-thereis t))
1969 (while (loop-do-while nil :while)) ; Normal, do while
1970 (until (loop-do-while t :until)) ;Negate test on while
1971 (when (loop-do-if when nil)) ; Normal, do when
1972 (if (loop-do-if if nil)) ; synonymous
1973 (unless (loop-do-if unless t)) ; Negate test on when
1974 (with (loop-do-with)))
1975 :for-keywords '((= (loop-ansi-for-equals))
1976 (across (loop-for-across))
1979 (from (loop-for-arithmetic :from))
1980 (downfrom (loop-for-arithmetic :downfrom))
1981 (upfrom (loop-for-arithmetic :upfrom))
1982 (below (loop-for-arithmetic :below))
1983 (to (loop-for-arithmetic :to))
1984 (upto (loop-for-arithmetic :upto))
1985 (being (loop-for-being)))
1986 :iteration-keywords '((for (loop-do-for))
1988 (repeat (loop-do-repeat)))
1989 :type-symbols '(array atom bignum bit bit-vector character
1990 compiled-function complex cons double-float
1991 fixnum float function hash-table integer
1992 keyword list long-float nil null number
1993 package pathname random-state ratio rational
1994 readtable sequence short-float simple-array
1995 simple-bit-vector simple-string simple-vector
1996 single-float standard-char stream string
1997 base-char symbol t vector)
1999 :ansi (if extended-p :extended t))))
2000 (add-loop-path '(hash-key hash-keys) 'loop-hash-table-iteration-path w
2001 :preposition-groups '((:of :in))
2002 :inclusive-permitted nil
2003 :user-data '(:which hash-key))
2004 (add-loop-path '(hash-value hash-values) 'loop-hash-table-iteration-path w
2005 :preposition-groups '((:of :in))
2006 :inclusive-permitted nil
2007 :user-data '(:which hash-value))
2008 (add-loop-path '(symbol symbols) 'loop-package-symbols-iteration-path w
2009 :preposition-groups '((:of :in))
2010 :inclusive-permitted nil
2011 :user-data '(:symbol-types (:internal
2014 (add-loop-path '(external-symbol external-symbols)
2015 'loop-package-symbols-iteration-path w
2016 :preposition-groups '((:of :in))
2017 :inclusive-permitted nil
2018 :user-data '(:symbol-types (:external)))
2019 (add-loop-path '(present-symbol present-symbols)
2020 'loop-package-symbols-iteration-path w
2021 :preposition-groups '((:of :in))
2022 :inclusive-permitted nil
2023 :user-data '(:symbol-types (:internal)))
2026 (defparameter *loop-ansi-universe*
2027 (make-ansi-loop-universe nil))
2029 (defun loop-standard-expansion (keywords-and-forms environment universe)
2030 (if (and keywords-and-forms (symbolp (car keywords-and-forms)))
2031 (loop-translate keywords-and-forms environment universe)
2032 (let ((tag (gensym)))
2033 `(block nil (tagbody ,tag (progn ,@keywords-and-forms) (go ,tag))))))
2035 (sb!kernel:defmacro-mundanely loop (&environment env &rest keywords-and-forms)
2036 (loop-standard-expansion keywords-and-forms env *loop-ansi-universe*))
2038 (sb!kernel:defmacro-mundanely loop-finish ()
2040 "Causes the iteration to terminate \"normally\", the same as implicit
2041 termination by an iteration driving clause, or by use of WHILE or
2042 UNTIL -- the epilogue code (if any) will be run, and any implicitly
2043 collected result will be returned as the value of the LOOP."