1.0.36.26: bug using OF-TYPE VECTOR in LOOP
[sbcl.git] / src / code / loop.lisp
1 ;;;; the LOOP iteration macro
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5
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.
16
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.
22
23 ;;;; Portions of LOOP are Copyright (c) 1986 by the Massachusetts Institute
24 ;;;; of Technology. All Rights Reserved.
25 ;;;;
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.
37 ;;;;
38 ;;;;      Massachusetts Institute of Technology
39 ;;;;      77 Massachusetts Avenue
40 ;;;;      Cambridge, Massachusetts  02139
41 ;;;;      United States of America
42 ;;;;      +1-617-253-1000
43
44 ;;;; Portions of LOOP are Copyright (c) 1989, 1990, 1991, 1992 by Symbolics,
45 ;;;; Inc. All Rights Reserved.
46 ;;;;
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.
58 ;;;;
59 ;;;; Symbolics, CLOE Runtime, and Minima are trademarks, and CLOE, Genera,
60 ;;;; and Zetalisp are registered trademarks of Symbolics, Inc.
61 ;;;;
62 ;;;;      Symbolics, Inc.
63 ;;;;      8 New England Executive Park, East
64 ;;;;      Burlington, Massachusetts  01803
65 ;;;;      United States of America
66 ;;;;      +1-617-221-1000
67
68 (in-package "SB!LOOP")
69
70 ;;;; The design of this LOOP is intended to permit, using mostly the same
71 ;;;; kernel of code, up to three different "loop" macros:
72 ;;;;
73 ;;;; (1) The unextended, unextensible ANSI standard LOOP;
74 ;;;;
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.
79 ;;;;
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,
83 ;;;; LOOP macros).
84 ;;;;
85 ;;;; Each of the above three LOOP variations can coexist in the same LISP
86 ;;;; environment.
87 ;;;;
88 ;;;; KLUDGE: In SBCL, we only really use variant (1), and any generality
89 ;;;; for the other variants is wasted. -- WHN 20000121
90
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.
95 \f
96 ;;;; list collection macrology
97
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)
102        ,@body)))
103
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)
108            (declare (fixnum n))
109            (do () ((<= n 4) (setq form `(,(case n
110                                             (1 'cdr)
111                                             (2 'cddr)
112                                             (3 'cdddr)
113                                             (4 'cddddr))
114                                          ,form)))
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
118       ;; length.
119       (when (consp form)
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))))))
125       (let ((answer
126               (cond ((null ncdrs)
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))
130                     ((= ncdrs 0)
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
135                      ;; former.
136                      `(rplacd ,tail-var (setq ,tail-var ,tail-form)))
137                     (t `(setq ,tail-var ,(cdr-wrap `(setf (cdr ,tail-var)
138                                                           ,tail-form)
139                                                    ncdrs))))))
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
143         ;; than checking.
144         (when user-head-var
145           (setq answer
146                 `(progn ,answer
147                         (setq ,user-head-var (cdr ,head-var)))))
148         answer))))
149
150 (sb!int:defmacro-mundanely loop-collect-answer (head-var
151                                                    &optional user-head-var)
152   (or user-head-var
153       `(cdr ,head-var)))
154 \f
155 ;;;; maximization technology
156
157 #|
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.
164
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
168 constructed.
169 |#
170
171 (defstruct (loop-minimax
172              (:constructor make-loop-minimax-internal)
173              (:copier nil)
174              (:predicate nil))
175   answer-variable
176   type
177   temp-variable
178   flag-variable
179   operations
180   infinity-data)
181
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)))
186
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
193       :type type
194       :temp-variable (gensym "LOOP-MAXMIN-TEMP-")
195       :flag-variable (and (not infinity-data)
196                           (gensym "LOOP-MAXMIN-FLAG-"))
197       :operations nil
198       :infinity-data infinity-data)))
199
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-")))
206   operation)
207
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)))
216     (if flag-var
217         `(let ((,answer-var ,init) (,temp-var ,init) (,flag-var nil))
218            (declare (type ,type ,answer-var ,temp-var))
219            ,@body)
220         `(let ((,answer-var ,(if (eq which 'min)
221                                  (first infinity-data)
222                                  (second infinity-data)))
223                (,temp-var ,init))
224            (declare (type ,type ,answer-var ,temp-var))
225            ,@body))))
226
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
232                     (min '<)
233                     (max '>))
234                  ,temp-var ,answer-var)))
235     `(progn
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)))))
240 \f
241 ;;;; LOOP keyword tables
242
243 #|
244 LOOP keyword tables are hash tables string keys and a test of EQUAL.
245
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
252 code to be loaded.
253 |#
254
255 ;;;; token hackery
256
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)))
261
262 (defun loop-tassoc (kwd alist)
263   (and (symbolp kwd) (assoc kwd alist :test #'string=)))
264
265 (defun loop-tmember (kwd list)
266   (and (symbolp kwd) (member kwd list :test #'string=)))
267
268 (defun loop-lookup-keyword (loop-token table)
269   (and (symbolp loop-token)
270        (values (gethash (symbol-name loop-token) table))))
271
272 (sb!int:defmacro-mundanely loop-store-table-data (symbol table datum)
273   `(setf (gethash (symbol-name ,symbol) ,table) ,datum))
274
275 (defstruct (loop-universe
276              (:copier nil)
277              (:predicate nil))
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)
290                   ((nil) "non-ANSI")
291                   ((t) "ANSI")
292                   (:extended "extended-ANSI")
293                   (t (loop-universe-ansi u)))))
294     (print-unreadable-object (u stream :type t)
295       (write-string string stream))))
296
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*)
300
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)
308                                        :test 'equal)))
309              (dolist (x entries)
310                (setf (gethash (symbol-name (car x)) ht) (cadr x)))
311              ht)))
312     (make-loop-universe
313       :keywords (maketable keywords)
314       :for-keywords (maketable for-keywords)
315       :iteration-keywords (maketable iteration-keywords)
316       :path-keywords (maketable path-keywords)
317       :ansi ansi
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)
322                                                 :test 'eq)))
323                       (dolist (x type-symbols)
324                         (if (atom x)
325                             (setf (gethash x ht) x)
326                             (setf (gethash (car x) ht) (cadr x))))
327                       ht))))
328 \f
329 ;;;; SETQ hackery, including destructuring ("DESETQ")
330
331 (defun loop-make-psetq (frobs)
332   (and frobs
333        (loop-make-desetq
334          (list (car frobs)
335                (if (null (cddr frobs)) (cadr frobs)
336                    `(prog1 ,(cadr frobs)
337                            ,(loop-make-psetq (cddr frobs))))))))
338
339 (defun loop-make-desetq (var-val-pairs)
340   (if (null var-val-pairs)
341       nil
342       (cons 'loop-really-desetq var-val-pairs)))
343
344 (defvar *loop-desetq-temporary*
345         (make-symbol "LOOP-DESETQ-TEMP"))
346
347 (sb!int:defmacro-mundanely loop-really-desetq (&environment env
348                                                &rest var-val-pairs)
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
356              (typecase var
357                (null
358                  (when (consp val)
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.
364                        (mapcan (lambda (x)
365                                  (and (consp x)
366                                       (or (not (eq (car x) 'car))
367                                           (not (symbolp (cadr x)))
368                                           (not (symbolp (setq x (sb!xc:macroexpand x env)))))
369                                       (cons x nil)))
370                                (cdr val))
371                        `(,val))))
372                (cons
373                  (let* ((car (car var))
374                         (cdr (cdr 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)
378                      (if cdr-non-null
379                          (let* ((temp-p temp)
380                                 (temp (or temp *loop-desetq-temporary*))
381                                 (body `(,@(loop-desetq-internal car
382                                                                 `(car ,temp))
383                                           (setq ,temp (cdr ,temp))
384                                           ,@(loop-desetq-internal cdr
385                                                                   temp
386                                                                   temp))))
387                            (if temp-p
388                                `(,@(unless (eq temp val)
389                                      `((setq ,temp ,val)))
390                                  ,@body)
391                                `((let ((,temp ,val))
392                                    ,@body))))
393                          ;; no CDRing to do
394                          (loop-desetq-internal car `(car ,val) temp)))))
395                (otherwise
396                  (unless (eq var val)
397                    `((setq ,var ,val)))))))
398     (do ((actions))
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)
403                                             (pop var-val-pairs))
404                       actions)))))
405 \f
406 ;;;; LOOP-local variables
407
408 ;;; This is the "current" pointer into the LOOP source code.
409 (defvar *loop-source-code*)
410
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*)
414
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*)
418
419 ;;; list of names for the LOOP, supplied by the NAMED clause
420 (defvar *loop-names*)
421
422 ;;; The macroexpansion environment given to the macro.
423 (defvar *loop-macro-environment*)
424
425 ;;; This holds variable names specified with the USING clause.
426 ;;; See LOOP-NAMED-VAR.
427 (defvar *loop-named-vars*)
428
429 ;;; LETlist-like list being accumulated for current group of bindings.
430 (defvar *loop-vars*)
431
432 ;;; List of declarations being accumulated in parallel with
433 ;;; *LOOP-VARS*.
434 (defvar *loop-declarations*)
435
436 ;;; This is used by LOOP for destructuring binding, if it is doing
437 ;;; that itself. See LOOP-MAKE-VAR.
438 (defvar *loop-desetq-crocks*)
439
440 ;;; list of wrapping forms, innermost first, which go immediately
441 ;;; inside the current set of parallel bindings being accumulated in
442 ;;; *LOOP-VARS*. The wrappers are appended onto a body. E.g., this
443 ;;; list could conceivably have as its value
444 ;;;   ((WITH-OPEN-FILE (G0001 G0002 ...))),
445 ;;; with G0002 being one of the bindings in *LOOP-VARS* (This is why
446 ;;; the wrappers go inside of the variable bindings).
447 (defvar *loop-wrappers*)
448
449 ;;; This accumulates lists of previous values of *LOOP-VARS* and the
450 ;;; other lists above, for each new nesting of bindings. See
451 ;;; LOOP-BIND-BLOCK.
452 (defvar *loop-bind-stack*)
453
454 ;;; list of prologue forms of the loop, accumulated in reverse order
455 (defvar *loop-prologue*)
456
457 (defvar *loop-before-loop*)
458 (defvar *loop-body*)
459 (defvar *loop-after-body*)
460
461 ;;; This is T if we have emitted any body code, so that iteration
462 ;;; driving clauses can be disallowed. This is not strictly the same
463 ;;; as checking *LOOP-BODY*, because we permit some clauses such as
464 ;;; RETURN to not be considered "real" body (so as to permit the user
465 ;;; to "code" an abnormal return value "in loop").
466 (defvar *loop-emitted-body*)
467
468 ;;; list of epilogue forms (supplied by FINALLY generally), accumulated
469 ;;; in reverse order
470 (defvar *loop-epilogue*)
471
472 ;;; list of epilogue forms which are supplied after the above "user"
473 ;;; epilogue. "Normal" termination return values are provide by
474 ;;; putting the return form in here. Normally this is done using
475 ;;; LOOP-EMIT-FINAL-VALUE, q.v.
476 (defvar *loop-after-epilogue*)
477
478 ;;; the "culprit" responsible for supplying a final value from the
479 ;;; loop. This is so LOOP-DISALLOW-AGGREGATE-BOOLEANS can moan about
480 ;;; disallowed anonymous collections.
481 (defvar *loop-final-value-culprit*)
482
483 ;;; If this is true, we are in some branch of a conditional. Some
484 ;;; clauses may be disallowed.
485 (defvar *loop-inside-conditional*)
486
487 ;;; If not NIL, this is a temporary bound around the loop for holding
488 ;;; the temporary value for "it" in things like "when (f) collect it".
489 ;;; It may be used as a supertemporary by some other things.
490 (defvar *loop-when-it-var*)
491
492 ;;; Sometimes we decide we need to fold together parts of the loop,
493 ;;; but some part of the generated iteration code is different for the
494 ;;; first and remaining iterations. This variable will be the
495 ;;; temporary which is the flag used in the loop to tell whether we
496 ;;; are in the first or remaining iterations.
497 (defvar *loop-never-stepped-var*)
498
499 ;;; list of all the value-accumulation descriptor structures in the
500 ;;; loop. See LOOP-GET-COLLECTION-INFO.
501 (defvar *loop-collection-cruft*) ; for multiple COLLECTs (etc.)
502 \f
503 ;;;; code analysis stuff
504
505 (defun loop-constant-fold-if-possible (form &optional expected-type)
506   (let* ((constantp (sb!xc:constantp form))
507          (value (and constantp (sb!int:constant-form-value form))))
508     (when (and constantp expected-type)
509       (unless (sb!xc:typep value expected-type)
510         (loop-warn "~@<The form ~S evaluated to ~S, which was not of ~
511                     the anticipated type ~S.~:@>"
512                    form value expected-type)
513         (setq constantp nil value nil)))
514     (values form constantp value)))
515 \f
516 ;;;; LOOP iteration optimization
517
518 (defvar *loop-duplicate-code* nil)
519
520 (defvar *loop-iteration-flag-var* (make-symbol "LOOP-NOT-FIRST-TIME"))
521
522 (defun loop-code-duplication-threshold (env)
523   (declare (ignore env))
524   (let (;; If we could read optimization declaration information (as
525         ;; with the DECLARATION-INFORMATION function (present in
526         ;; CLTL2, removed from ANSI standard) we could set these
527         ;; values flexibly. Without DECLARATION-INFORMATION, we have
528         ;; to set them to constants.
529         ;;
530         ;; except FIXME: we've lost all pretence of portability,
531         ;; considering this instead an internal implementation, so
532         ;; we're free to couple to our own representation of the
533         ;; environment.
534         (speed 1)
535         (space 1))
536     (+ 40 (* (- speed space) 10))))
537
538 (sb!int:defmacro-mundanely loop-body (&environment env
539                                          prologue
540                                          before-loop
541                                          main-body
542                                          after-loop
543                                          epilogue
544                                          &aux rbefore rafter flagvar)
545   (unless (= (length before-loop) (length after-loop))
546     (error "LOOP-BODY called with non-synched before- and after-loop lists"))
547   ;;All our work is done from these copies, working backwards from the end:
548   (setq rbefore (reverse before-loop) rafter (reverse after-loop))
549   (labels ((psimp (l)
550              (let ((ans nil))
551                (dolist (x l)
552                  (when x
553                    (push x ans)
554                    (when (and (consp x)
555                               (member (car x) '(go return return-from)))
556                      (return nil))))
557                (nreverse ans)))
558            (pify (l) (if (null (cdr l)) (car l) `(progn ,@l)))
559            (makebody ()
560              (let ((form `(tagbody
561                             ,@(psimp (append prologue (nreverse rbefore)))
562                          next-loop
563                             ,@(psimp (append main-body
564                                              (nreconc rafter
565                                                       `((go next-loop)))))
566                          end-loop
567                             ,@(psimp epilogue))))
568                (if flagvar `(let ((,flagvar nil)) ,form) form))))
569     (when (or *loop-duplicate-code* (not rbefore))
570       (return-from loop-body (makebody)))
571     ;; This outer loop iterates once for each not-first-time flag test
572     ;; generated plus once more for the forms that don't need a flag test.
573     (do ((threshold (loop-code-duplication-threshold env))) (nil)
574       (declare (fixnum threshold))
575       ;; Go backwards from the ends of before-loop and after-loop
576       ;; merging all the equivalent forms into the body.
577       (do () ((or (null rbefore) (not (equal (car rbefore) (car rafter)))))
578         (push (pop rbefore) main-body)
579         (pop rafter))
580       (unless rbefore (return (makebody)))
581       ;; The first forms in RBEFORE & RAFTER (which are the
582       ;; chronologically last forms in the list) differ, therefore
583       ;; they cannot be moved into the main body. If everything that
584       ;; chronologically precedes them either differs or is equal but
585       ;; is okay to duplicate, we can just put all of rbefore in the
586       ;; prologue and all of rafter after the body. Otherwise, there
587       ;; is something that is not okay to duplicate, so it and
588       ;; everything chronologically after it in rbefore and rafter
589       ;; must go into the body, with a flag test to distinguish the
590       ;; first time around the loop from later times. What
591       ;; chronologically precedes the non-duplicatable form will be
592       ;; handled the next time around the outer loop.
593       (do ((bb rbefore (cdr bb))
594            (aa rafter (cdr aa))
595            (lastdiff nil)
596            (count 0)
597            (inc nil))
598           ((null bb) (return-from loop-body (makebody)))        ; Did it.
599         (cond ((not (equal (car bb) (car aa))) (setq lastdiff bb count 0))
600               ((or (not (setq inc (estimate-code-size (car bb) env)))
601                    (> (incf count inc) threshold))
602                ;; Ok, we have found a non-duplicatable piece of code.
603                ;; Everything chronologically after it must be in the
604                ;; central body. Everything chronologically at and
605                ;; after LASTDIFF goes into the central body under a
606                ;; flag test.
607                (let ((then nil) (else nil))
608                  (do () (nil)
609                    (push (pop rbefore) else)
610                    (push (pop rafter) then)
611                    (when (eq rbefore (cdr lastdiff)) (return)))
612                  (unless flagvar
613                    (push `(setq ,(setq flagvar *loop-iteration-flag-var*)
614                                 t)
615                          else))
616                  (push `(if ,flagvar ,(pify (psimp then)) ,(pify (psimp else)))
617                        main-body))
618                ;; Everything chronologically before lastdiff until the
619                ;; non-duplicatable form (CAR BB) is the same in
620                ;; RBEFORE and RAFTER, so just copy it into the body.
621                (do () (nil)
622                  (pop rafter)
623                  (push (pop rbefore) main-body)
624                  (when (eq rbefore (cdr bb)) (return)))
625                (return)))))))
626 \f
627 (defun duplicatable-code-p (expr env)
628   (if (null expr) 0
629       (let ((ans (estimate-code-size expr env)))
630         (declare (fixnum ans))
631         ;; @@@@ Use (DECLARATION-INFORMATION 'OPTIMIZE ENV) here to
632         ;; get an alist of optimize quantities back to help quantify
633         ;; how much code we are willing to duplicate.
634         ans)))
635
636 (defvar *special-code-sizes*
637         '((return 0) (progn 0)
638           (null 1) (not 1) (eq 1) (car 1) (cdr 1)
639           (when 1) (unless 1) (if 1)
640           (caar 2) (cadr 2) (cdar 2) (cddr 2)
641           (caaar 3) (caadr 3) (cadar 3) (caddr 3)
642           (cdaar 3) (cdadr 3) (cddar 3) (cdddr 3)
643           (caaaar 4) (caaadr 4) (caadar 4) (caaddr 4)
644           (cadaar 4) (cadadr 4) (caddar 4) (cadddr 4)
645           (cdaaar 4) (cdaadr 4) (cdadar 4) (cdaddr 4)
646           (cddaar 4) (cddadr 4) (cdddar 4) (cddddr 4)))
647
648 (defvar *estimate-code-size-punt*
649         '(block
650            do do* dolist
651            flet
652            labels lambda let let* locally
653            macrolet multiple-value-bind
654            prog prog*
655            symbol-macrolet
656            tagbody
657            unwind-protect
658            with-open-file))
659
660 (defun destructuring-size (x)
661   (do ((x x (cdr x)) (n 0 (+ (destructuring-size (car x)) n)))
662       ((atom x) (+ n (if (null x) 0 1)))))
663
664 (defun estimate-code-size (x env)
665   (catch 'estimate-code-size
666     (estimate-code-size-1 x env)))
667
668 (defun estimate-code-size-1 (x env)
669   (flet ((list-size (l)
670            (let ((n 0))
671              (declare (fixnum n))
672              (dolist (x l n) (incf n (estimate-code-size-1 x env))))))
673     ;;@@@@ ???? (declare (function list-size (list) fixnum))
674     (cond ((constantp x) 1)
675           ((symbolp x) (multiple-value-bind (new-form expanded-p)
676                            (sb!xc:macroexpand-1 x env)
677                          (if expanded-p
678                              (estimate-code-size-1 new-form env)
679                              1)))
680           ((atom x) 1) ;; ??? self-evaluating???
681           ((symbolp (car x))
682            (let ((fn (car x)) (tem nil) (n 0))
683              (declare (symbol fn) (fixnum n))
684              (macrolet ((f (overhead &optional (args nil args-p))
685                           `(the fixnum (+ (the fixnum ,overhead)
686                                           (the fixnum
687                                                (list-size ,(if args-p
688                                                                args
689                                                              '(cdr x))))))))
690                (cond ((setq tem (get fn 'estimate-code-size))
691                       (typecase tem
692                         (fixnum (f tem))
693                         (t (funcall tem x env))))
694                      ((setq tem (assoc fn *special-code-sizes*))
695                       (f (second tem)))
696                      ((eq fn 'cond)
697                       (dolist (clause (cdr x) n)
698                         (incf n (list-size clause)) (incf n)))
699                      ((eq fn 'desetq)
700                       (do ((l (cdr x) (cdr l))) ((null l) n)
701                         (setq n (+ n
702                                    (destructuring-size (car l))
703                                    (estimate-code-size-1 (cadr l) env)))))
704                      ((member fn '(setq psetq))
705                       (do ((l (cdr x) (cdr l))) ((null l) n)
706                         (setq n (+ n (estimate-code-size-1 (cadr l) env) 1))))
707                      ((eq fn 'go) 1)
708                      ((eq fn 'function)
709                       (if (sb!int:legal-fun-name-p (cadr x))
710                           1
711                           ;; FIXME: This tag appears not to be present
712                           ;; anywhere.
713                           (throw 'duplicatable-code-p nil)))
714                      ((eq fn 'multiple-value-setq)
715                       (f (length (second x)) (cddr x)))
716                      ((eq fn 'return-from)
717                       (1+ (estimate-code-size-1 (third x) env)))
718                      ((or (special-operator-p fn)
719                           (member fn *estimate-code-size-punt*))
720                       (throw 'estimate-code-size nil))
721                      (t (multiple-value-bind (new-form expanded-p)
722                             (sb!xc:macroexpand-1 x env)
723                           (if expanded-p
724                               (estimate-code-size-1 new-form env)
725                               (f 3))))))))
726           (t (throw 'estimate-code-size nil)))))
727 \f
728 ;;;; loop errors
729
730 (defun loop-context ()
731   (do ((l *loop-source-context* (cdr l)) (new nil (cons (car l) new)))
732       ((eq l (cdr *loop-source-code*)) (nreverse new))))
733
734 (defun loop-error (format-string &rest format-args)
735   (error 'sb!int:simple-program-error
736          :format-control "~?~%current LOOP context:~{ ~S~}."
737          :format-arguments (list format-string format-args (loop-context))))
738
739 (defun loop-warn (format-string &rest format-args)
740   (warn "~?~%current LOOP context:~{ ~S~}."
741         format-string
742         format-args
743         (loop-context)))
744
745 (defun loop-check-data-type (specified-type required-type
746                              &optional (default-type required-type))
747   (if (null specified-type)
748       default-type
749       (multiple-value-bind (a b) (sb!xc:subtypep specified-type required-type)
750         (cond ((not b)
751                (loop-warn "LOOP couldn't verify that ~S is a subtype of the required type ~S."
752                           specified-type required-type))
753               ((not a)
754                (loop-error "The specified data type ~S is not a subtype of ~S."
755                            specified-type required-type)))
756         specified-type)))
757 \f
758 (defun subst-gensyms-for-nil (tree)
759   (declare (special *ignores*))
760   (cond
761     ((null tree) (car (push (gensym "LOOP-IGNORED-VAR-") *ignores*)))
762     ((atom tree) tree)
763     (t (cons (subst-gensyms-for-nil (car tree))
764              (subst-gensyms-for-nil (cdr tree))))))
765
766 (sb!int:defmacro-mundanely loop-destructuring-bind
767     (lambda-list arg-list &rest body)
768   (let ((*ignores* nil))
769     (declare (special *ignores*))
770     (let ((d-var-lambda-list (subst-gensyms-for-nil lambda-list)))
771       `(destructuring-bind ,d-var-lambda-list
772            ,arg-list
773          (declare (ignore ,@*ignores*))
774          ,@body))))
775
776 (defun loop-build-destructuring-bindings (crocks forms)
777   (if crocks
778       `((loop-destructuring-bind ,(car crocks) ,(cadr crocks)
779         ,@(loop-build-destructuring-bindings (cddr crocks) forms)))
780       forms))
781
782 (defun loop-translate (*loop-source-code*
783                        *loop-macro-environment*
784                        *loop-universe*)
785   (let ((*loop-original-source-code* *loop-source-code*)
786         (*loop-source-context* nil)
787         (*loop-vars* nil)
788         (*loop-named-vars* nil)
789         (*loop-declarations* nil)
790         (*loop-desetq-crocks* nil)
791         (*loop-bind-stack* nil)
792         (*loop-prologue* nil)
793         (*loop-wrappers* nil)
794         (*loop-before-loop* nil)
795         (*loop-body* nil)
796         (*loop-emitted-body* nil)
797         (*loop-after-body* nil)
798         (*loop-epilogue* nil)
799         (*loop-after-epilogue* nil)
800         (*loop-final-value-culprit* nil)
801         (*loop-inside-conditional* nil)
802         (*loop-when-it-var* nil)
803         (*loop-never-stepped-var* nil)
804         (*loop-names* nil)
805         (*loop-collection-cruft* nil))
806     (loop-iteration-driver)
807     (loop-bind-block)
808     (let ((answer `(loop-body
809                      ,(nreverse *loop-prologue*)
810                      ,(nreverse *loop-before-loop*)
811                      ,(nreverse *loop-body*)
812                      ,(nreverse *loop-after-body*)
813                      ,(nreconc *loop-epilogue*
814                                (nreverse *loop-after-epilogue*)))))
815       (dolist (entry *loop-bind-stack*)
816         (let ((vars (first entry))
817               (dcls (second entry))
818               (crocks (third entry))
819               (wrappers (fourth entry)))
820           (dolist (w wrappers)
821             (setq answer (append w (list answer))))
822           (when (or vars dcls crocks)
823             (let ((forms (list answer)))
824               ;;(when crocks (push crocks forms))
825               (when dcls (push `(declare ,@dcls) forms))
826               (setq answer `(,(if vars 'let 'locally)
827                              ,vars
828                              ,@(loop-build-destructuring-bindings crocks
829                                                                   forms)))))))
830       (do () (nil)
831         (setq answer `(block ,(pop *loop-names*) ,answer))
832         (unless *loop-names* (return nil)))
833       answer)))
834
835 (defun loop-iteration-driver ()
836   (do ()
837       ((null *loop-source-code*))
838     (let ((keyword (car *loop-source-code*)) (tem nil))
839       (cond ((not (symbolp keyword))
840              (loop-error "~S found where LOOP keyword expected" keyword))
841             (t (setq *loop-source-context* *loop-source-code*)
842                (loop-pop-source)
843                (cond ((setq tem
844                             (loop-lookup-keyword keyword
845                                                  (loop-universe-keywords
846                                                   *loop-universe*)))
847                       ;; It's a "miscellaneous" toplevel LOOP keyword (DO,
848                       ;; COLLECT, NAMED, etc.)
849                       (apply (symbol-function (first tem)) (rest tem)))
850                      ((setq tem
851                             (loop-lookup-keyword keyword
852                                                  (loop-universe-iteration-keywords *loop-universe*)))
853                       (loop-hack-iteration tem))
854                      ((loop-tmember keyword '(and else))
855                       ;; The alternative is to ignore it, i.e. let it go
856                       ;; around to the next keyword...
857                       (loop-error "secondary clause misplaced at top level in LOOP macro: ~S ~S ~S ..."
858                                   keyword
859                                   (car *loop-source-code*)
860                                   (cadr *loop-source-code*)))
861                      (t (loop-error "unknown LOOP keyword: ~S" keyword))))))))
862 \f
863 (defun loop-pop-source ()
864   (if *loop-source-code*
865       (pop *loop-source-code*)
866       (loop-error "LOOP source code ran out when another token was expected.")))
867
868 (defun loop-get-form ()
869   (if *loop-source-code*
870       (loop-pop-source)
871       (loop-error "LOOP code ran out where a form was expected.")))
872
873 (defun loop-get-compound-form ()
874   (let ((form (loop-get-form)))
875     (unless (consp form)
876       (loop-error "A compound form was expected, but ~S found." form))
877     form))
878
879 (defun loop-get-progn ()
880   (do ((forms (list (loop-get-compound-form))
881               (cons (loop-get-compound-form) forms))
882        (nextform (car *loop-source-code*)
883                  (car *loop-source-code*)))
884       ((atom nextform)
885        (if (null (cdr forms)) (car forms) (cons 'progn (nreverse forms))))))
886
887 (defun loop-construct-return (form)
888   `(return-from ,(car *loop-names*) ,form))
889
890 (defun loop-pseudo-body (form)
891   (cond ((or *loop-emitted-body* *loop-inside-conditional*)
892          (push form *loop-body*))
893         (t (push form *loop-before-loop*) (push form *loop-after-body*))))
894
895 (defun loop-emit-body (form)
896   (setq *loop-emitted-body* t)
897   (loop-pseudo-body form))
898
899 (defun loop-emit-final-value (&optional (form nil form-supplied-p))
900   (when form-supplied-p
901     (push (loop-construct-return form) *loop-after-epilogue*))
902   (setq *loop-final-value-culprit* (car *loop-source-context*)))
903
904 (defun loop-disallow-conditional (&optional kwd)
905   (when *loop-inside-conditional*
906     (loop-error "~:[This LOOP~;The LOOP ~:*~S~] clause is not permitted inside a conditional." kwd)))
907
908 (defun loop-disallow-anonymous-collectors ()
909   (when (find-if-not 'loop-collector-name *loop-collection-cruft*)
910     (loop-error "This LOOP clause is not permitted with anonymous collectors.")))
911
912 (defun loop-disallow-aggregate-booleans ()
913   (when (loop-tmember *loop-final-value-culprit* '(always never thereis))
914     (loop-error "This anonymous collection LOOP clause is not permitted with aggregate booleans.")))
915 \f
916 ;;;; loop types
917
918 (defun loop-typed-init (data-type &optional step-var-p)
919   (cond ((null data-type)
920          nil)
921         ((sb!xc:subtypep data-type 'number)
922          (let ((init (if step-var-p 1 0)))
923            (flet ((like (&rest types)
924                     (coerce init (find-if (lambda (type)
925                                             (sb!xc:subtypep data-type type))
926                                           types))))
927              (cond ((sb!xc:subtypep data-type 'float)
928                     (like 'single-float 'double-float
929                           'short-float 'long-float 'float))
930                    ((sb!xc:subtypep data-type '(complex float))
931                     (like '(complex single-float)
932                           '(complex double-float)
933                           '(complex short-float)
934                           '(complex long-float)
935                           '(complex float)))
936                    (t
937                     init)))))
938         ((sb!xc:subtypep data-type 'vector)
939          (let ((ctype (sb!kernel:specifier-type data-type)))
940            (when (sb!kernel:array-type-p ctype)
941              (let ((etype (sb!kernel:type-*-to-t
942                            (sb!kernel:array-type-specialized-element-type ctype))))
943                (make-array 0 :element-type (sb!kernel:type-specifier etype))))))
944         (t
945          nil)))
946
947 (defun loop-optional-type (&optional variable)
948   ;; No variable specified implies that no destructuring is permissible.
949   (and *loop-source-code* ; Don't get confused by NILs..
950        (let ((z (car *loop-source-code*)))
951          (cond ((loop-tequal z 'of-type)
952                 ;; This is the syntactically unambigous form in that
953                 ;; the form of the type specifier does not matter.
954                 ;; Also, it is assumed that the type specifier is
955                 ;; unambiguously, and without need of translation, a
956                 ;; common lisp type specifier or pattern (matching the
957                 ;; variable) thereof.
958                 (loop-pop-source)
959                 (loop-pop-source))
960
961                ((symbolp z)
962                 ;; This is the (sort of) "old" syntax, even though we
963                 ;; didn't used to support all of these type symbols.
964                 (let ((type-spec (or (gethash z
965                                               (loop-universe-type-symbols
966                                                *loop-universe*))
967                                      (gethash (symbol-name z)
968                                               (loop-universe-type-keywords
969                                                *loop-universe*)))))
970                   (when type-spec
971                     (loop-pop-source)
972                     type-spec)))
973                (t
974                 ;; This is our sort-of old syntax. But this is only
975                 ;; valid for when we are destructuring, so we will be
976                 ;; compulsive (should we really be?) and require that
977                 ;; we in fact be doing variable destructuring here. We
978                 ;; must translate the old keyword pattern typespec
979                 ;; into a fully-specified pattern of real type
980                 ;; specifiers here.
981                 (if (consp variable)
982                     (unless (consp z)
983                      (loop-error
984                         "~S found where a LOOP keyword, LOOP type keyword, or LOOP type pattern expected"
985                         z))
986                     (loop-error "~S found where a LOOP keyword or LOOP type keyword expected" z))
987                 (loop-pop-source)
988                 (labels ((translate (k v)
989                            (cond ((null k) nil)
990                                  ((atom k)
991                                   (replicate
992                                     (or (gethash k
993                                                  (loop-universe-type-symbols
994                                                   *loop-universe*))
995                                         (gethash (symbol-name k)
996                                                  (loop-universe-type-keywords
997                                                   *loop-universe*))
998                                         (loop-error
999                                           "The destructuring type pattern ~S contains the unrecognized type keyword ~S."
1000                                           z k))
1001                                     v))
1002                                  ((atom v)
1003                                   (loop-error
1004                                     "The destructuring type pattern ~S doesn't match the variable pattern ~S."
1005                                     z variable))
1006                                  (t (cons (translate (car k) (car v))
1007                                           (translate (cdr k) (cdr v))))))
1008                          (replicate (typ v)
1009                            (if (atom v)
1010                                typ
1011                                (cons (replicate typ (car v))
1012                                      (replicate typ (cdr v))))))
1013                   (translate z variable)))))))
1014 \f
1015 ;;;; loop variables
1016
1017 (defun loop-bind-block ()
1018   (when (or *loop-vars* *loop-declarations* *loop-wrappers*)
1019     (push (list (nreverse *loop-vars*)
1020                 *loop-declarations*
1021                 *loop-desetq-crocks*
1022                 *loop-wrappers*)
1023           *loop-bind-stack*)
1024     (setq *loop-vars* nil
1025           *loop-declarations* nil
1026           *loop-desetq-crocks* nil
1027           *loop-wrappers* nil)))
1028
1029 (defun loop-var-p (name)
1030   (do ((entry *loop-bind-stack* (cdr entry)))
1031       (nil)
1032     (cond
1033       ((null entry) (return nil))
1034       ((assoc name (caar entry) :test #'eq) (return t)))))
1035
1036 (defun loop-make-var (name initialization dtype &optional step-var-p)
1037   (cond ((null name)
1038          (setq name (gensym "LOOP-IGNORE-"))
1039          (push (list name initialization) *loop-vars*)
1040          (if (null initialization)
1041              (push `(ignore ,name) *loop-declarations*)
1042              (loop-declare-var name dtype)))
1043         ((atom name)
1044          (when (or (assoc name *loop-vars*)
1045                    (loop-var-p name))
1046            (loop-error "duplicated variable ~S in a LOOP binding" name))
1047          (unless (symbolp name)
1048            (loop-error "bad variable ~S somewhere in LOOP" name))
1049          (loop-declare-var name dtype step-var-p initialization)
1050          ;; We use ASSOC on this list to check for duplications (above),
1051          ;; so don't optimize out this list:
1052          (push (list name (or initialization (loop-typed-init dtype step-var-p)))
1053                *loop-vars*))
1054         (initialization
1055          (let ((newvar (gensym "LOOP-DESTRUCTURE-")))
1056            (loop-declare-var name dtype)
1057            (push (list newvar initialization) *loop-vars*)
1058            ;; *LOOP-DESETQ-CROCKS* gathered in reverse order.
1059            (setq *loop-desetq-crocks*
1060                  (list* name newvar *loop-desetq-crocks*))))
1061         (t (let ((tcar nil) (tcdr nil))
1062              (if (atom dtype) (setq tcar (setq tcdr dtype))
1063                  (setq tcar (car dtype) tcdr (cdr dtype)))
1064              (loop-make-var (car name) nil tcar)
1065              (loop-make-var (cdr name) nil tcdr))))
1066   name)
1067
1068 (defun loop-declare-var (name dtype &optional step-var-p initialization)
1069   (cond ((or (null name) (null dtype) (eq dtype t)) nil)
1070         ((symbolp name)
1071          (unless (or (sb!xc:subtypep t dtype)
1072                      (and (eq (find-package :cl) (symbol-package name))
1073                           (eq :special (sb!int:info :variable :kind name))))
1074            (let ((dtype (if initialization
1075                             dtype
1076                             (let ((init (loop-typed-init dtype step-var-p)))
1077                               (if (sb!xc:typep init dtype)
1078                                   dtype
1079                                   `(or ,(type-of init) ,dtype))))))
1080              (push `(type ,dtype ,name) *loop-declarations*))))
1081         ((consp name)
1082          (cond ((consp dtype)
1083                 (loop-declare-var (car name) (car dtype))
1084                 (loop-declare-var (cdr name) (cdr dtype)))
1085                (t (loop-declare-var (car name) dtype)
1086                   (loop-declare-var (cdr name) dtype))))
1087         (t (error "invalid LOOP variable passed in: ~S" name))))
1088
1089 (defun loop-maybe-bind-form (form data-type)
1090   (if (constantp form)
1091       form
1092       (loop-make-var (gensym "LOOP-BIND-") form data-type)))
1093 \f
1094 (defun loop-do-if (for negatep)
1095   (let ((form (loop-get-form))
1096         (*loop-inside-conditional* t)
1097         (it-p nil)
1098         (first-clause-p t))
1099     (flet ((get-clause (for)
1100              (do ((body nil)) (nil)
1101                (let ((key (car *loop-source-code*)) (*loop-body* nil) data)
1102                  (cond ((not (symbolp key))
1103                         (loop-error
1104                           "~S found where keyword expected getting LOOP clause after ~S"
1105                           key for))
1106                        (t (setq *loop-source-context* *loop-source-code*)
1107                           (loop-pop-source)
1108                           (when (and (loop-tequal (car *loop-source-code*) 'it)
1109                                      first-clause-p)
1110                             (setq *loop-source-code*
1111                                   (cons (or it-p
1112                                             (setq it-p
1113                                                   (loop-when-it-var)))
1114                                         (cdr *loop-source-code*))))
1115                           (cond ((or (not (setq data (loop-lookup-keyword
1116                                                        key (loop-universe-keywords *loop-universe*))))
1117                                      (progn (apply (symbol-function (car data))
1118                                                    (cdr data))
1119                                             (null *loop-body*)))
1120                                  (loop-error
1121                                    "~S does not introduce a LOOP clause that can follow ~S."
1122                                    key for))
1123                                 (t (setq body (nreconc *loop-body* body)))))))
1124                (setq first-clause-p nil)
1125                (if (loop-tequal (car *loop-source-code*) :and)
1126                    (loop-pop-source)
1127                    (return (if (cdr body)
1128                                `(progn ,@(nreverse body))
1129                                (car body)))))))
1130       (let ((then (get-clause for))
1131             (else (when (loop-tequal (car *loop-source-code*) :else)
1132                     (loop-pop-source)
1133                     (list (get-clause :else)))))
1134         (when (loop-tequal (car *loop-source-code*) :end)
1135           (loop-pop-source))
1136         (when it-p (setq form `(setq ,it-p ,form)))
1137         (loop-pseudo-body
1138           `(if ,(if negatep `(not ,form) form)
1139                ,then
1140                ,@else))))))
1141
1142 (defun loop-do-initially ()
1143   (loop-disallow-conditional :initially)
1144   (push (loop-get-progn) *loop-prologue*))
1145
1146 (defun loop-do-finally ()
1147   (loop-disallow-conditional :finally)
1148   (push (loop-get-progn) *loop-epilogue*))
1149
1150 (defun loop-do-do ()
1151   (loop-emit-body (loop-get-progn)))
1152
1153 (defun loop-do-named ()
1154   (let ((name (loop-pop-source)))
1155     (unless (symbolp name)
1156       (loop-error "~S is an invalid name for your LOOP" name))
1157     (when (or *loop-before-loop* *loop-body* *loop-after-epilogue* *loop-inside-conditional*)
1158       (loop-error "The NAMED ~S clause occurs too late." name))
1159     (when *loop-names*
1160       (loop-error "You may only use one NAMED clause in your loop: NAMED ~S ... NAMED ~S."
1161                   (car *loop-names*) name))
1162     (setq *loop-names* (list name))))
1163
1164 (defun loop-do-return ()
1165   (loop-emit-body (loop-construct-return (loop-get-form))))
1166 \f
1167 ;;;; value accumulation: LIST
1168
1169 (defstruct (loop-collector
1170             (:copier nil)
1171             (:predicate nil))
1172   name
1173   class
1174   (history nil)
1175   (tempvars nil)
1176   dtype
1177   (data nil)) ;collector-specific data
1178
1179 (defun loop-get-collection-info (collector class default-type)
1180   (let ((form (loop-get-form))
1181         (dtype (and (not (loop-universe-ansi *loop-universe*)) (loop-optional-type)))
1182         (name (when (loop-tequal (car *loop-source-code*) 'into)
1183                 (loop-pop-source)
1184                 (loop-pop-source))))
1185     (when (not (symbolp name))
1186       (loop-error "The value accumulation recipient name, ~S, is not a symbol." name))
1187     (unless name
1188       (loop-disallow-aggregate-booleans))
1189     (unless dtype
1190       (setq dtype (or (loop-optional-type) default-type)))
1191     (let ((cruft (find (the symbol name) *loop-collection-cruft*
1192                        :key #'loop-collector-name)))
1193       (cond ((not cruft)
1194              (when (and name (loop-var-p name))
1195                (loop-error "Variable ~S in INTO clause is a duplicate" name))
1196              (push (setq cruft (make-loop-collector
1197                                  :name name :class class
1198                                  :history (list collector) :dtype dtype))
1199                    *loop-collection-cruft*))
1200             (t (unless (eq (loop-collector-class cruft) class)
1201                  (loop-error
1202                    "incompatible kinds of LOOP value accumulation specified for collecting~@
1203                     ~:[as the value of the LOOP~;~:*INTO ~S~]: ~S and ~S"
1204                    name (car (loop-collector-history cruft)) collector))
1205                (unless (equal dtype (loop-collector-dtype cruft))
1206                  (loop-warn
1207                    "unequal datatypes specified in different LOOP value accumulations~@
1208                    into ~S: ~S and ~S"
1209                    name dtype (loop-collector-dtype cruft))
1210                  (when (eq (loop-collector-dtype cruft) t)
1211                    (setf (loop-collector-dtype cruft) dtype)))
1212                (push collector (loop-collector-history cruft))))
1213       (values cruft form))))
1214
1215 (defun loop-list-collection (specifically)      ; NCONC, LIST, or APPEND
1216   (multiple-value-bind (lc form)
1217       (loop-get-collection-info specifically 'list 'list)
1218     (let ((tempvars (loop-collector-tempvars lc)))
1219       (unless tempvars
1220         (setf (loop-collector-tempvars lc)
1221               (setq tempvars (list* (gensym "LOOP-LIST-HEAD-")
1222                                     (gensym "LOOP-LIST-TAIL-")
1223                                     (and (loop-collector-name lc)
1224                                          (list (loop-collector-name lc))))))
1225         (push `(with-loop-list-collection-head ,tempvars) *loop-wrappers*)
1226         (unless (loop-collector-name lc)
1227           (loop-emit-final-value `(loop-collect-answer ,(car tempvars)
1228                                                        ,@(cddr tempvars)))))
1229       (ecase specifically
1230         (list (setq form `(list ,form)))
1231         (nconc nil)
1232         (append (unless (and (consp form) (eq (car form) 'list))
1233                   (setq form `(copy-list ,form)))))
1234       (loop-emit-body `(loop-collect-rplacd ,tempvars ,form)))))
1235 \f
1236 ;;;; value accumulation: MAX, MIN, SUM, COUNT
1237
1238 (defun loop-sum-collection (specifically required-type default-type);SUM, COUNT
1239   (multiple-value-bind (lc form)
1240       (loop-get-collection-info specifically 'sum default-type)
1241     (loop-check-data-type (loop-collector-dtype lc) required-type)
1242     (let ((tempvars (loop-collector-tempvars lc)))
1243       (unless tempvars
1244         (setf (loop-collector-tempvars lc)
1245               (setq tempvars (list (loop-make-var
1246                                      (or (loop-collector-name lc)
1247                                          (gensym "LOOP-SUM-"))
1248                                      nil (loop-collector-dtype lc)))))
1249         (unless (loop-collector-name lc)
1250           (loop-emit-final-value (car (loop-collector-tempvars lc)))))
1251       (loop-emit-body
1252         (if (eq specifically 'count)
1253             `(when ,form
1254                (setq ,(car tempvars)
1255                      (1+ ,(car tempvars))))
1256             `(setq ,(car tempvars)
1257                    (+ ,(car tempvars)
1258                       ,form)))))))
1259
1260 (defun loop-maxmin-collection (specifically)
1261   (multiple-value-bind (lc form)
1262       (loop-get-collection-info specifically 'maxmin 'real)
1263     (loop-check-data-type (loop-collector-dtype lc) 'real)
1264     (let ((data (loop-collector-data lc)))
1265       (unless data
1266         (setf (loop-collector-data lc)
1267               (setq data (make-loop-minimax
1268                            (or (loop-collector-name lc)
1269                                (gensym "LOOP-MAXMIN-"))
1270                            (loop-collector-dtype lc))))
1271         (unless (loop-collector-name lc)
1272           (loop-emit-final-value (loop-minimax-answer-variable data))))
1273       (loop-note-minimax-operation specifically data)
1274       (push `(with-minimax-value ,data) *loop-wrappers*)
1275       (loop-emit-body `(loop-accumulate-minimax-value ,data
1276                                                       ,specifically
1277                                                       ,form)))))
1278 \f
1279 ;;;; value accumulation: aggregate booleans
1280
1281 ;;; handling the ALWAYS and NEVER loop keywords
1282 ;;;
1283 ;;; Under ANSI these are not permitted to appear under conditionalization.
1284 (defun loop-do-always (restrictive negate)
1285   (let ((form (loop-get-form)))
1286     (when restrictive (loop-disallow-conditional))
1287     (loop-disallow-anonymous-collectors)
1288     (loop-emit-body `(,(if negate 'when 'unless) ,form
1289                       ,(loop-construct-return nil)))
1290     (loop-emit-final-value t)))
1291
1292 ;;; handling the THEREIS loop keyword
1293 ;;;
1294 ;;; Under ANSI this is not permitted to appear under conditionalization.
1295 (defun loop-do-thereis (restrictive)
1296   (when restrictive (loop-disallow-conditional))
1297   (loop-disallow-anonymous-collectors)
1298   (loop-emit-final-value)
1299   (loop-emit-body `(when (setq ,(loop-when-it-var) ,(loop-get-form))
1300                     ,(loop-construct-return *loop-when-it-var*))))
1301 \f
1302 (defun loop-do-while (negate kwd &aux (form (loop-get-form)))
1303   (loop-disallow-conditional kwd)
1304   (loop-pseudo-body `(,(if negate 'when 'unless) ,form (go end-loop))))
1305
1306 (defun loop-do-repeat ()
1307   (loop-disallow-conditional :repeat)
1308   (let ((form (loop-get-form))
1309         (type 'integer))
1310     (let ((var (loop-make-var (gensym "LOOP-REPEAT-") `(ceiling ,form) type)))
1311       (push `(if (<= ,var 0) (go end-loop) (decf ,var)) *loop-before-loop*)
1312       (push `(if (<= ,var 0) (go end-loop) (decf ,var)) *loop-after-body*)
1313       ;; FIXME: What should
1314       ;;   (loop count t into a
1315       ;;         repeat 3
1316       ;;         count t into b
1317       ;;         finally (return (list a b)))
1318       ;; return: (3 3) or (4 3)? PUSHes above are for the former
1319       ;; variant, L-P-B below for the latter.
1320       #+nil (loop-pseudo-body `(when (minusp (decf ,var)) (go end-loop))))))
1321
1322 (defun loop-do-with ()
1323   (loop-disallow-conditional :with)
1324   (do ((var) (val) (dtype))
1325       (nil)
1326     (setq var (loop-pop-source)
1327           dtype (loop-optional-type var)
1328           val (cond ((loop-tequal (car *loop-source-code*) :=)
1329                      (loop-pop-source)
1330                      (loop-get-form))
1331                     (t nil)))
1332     (when (and var (loop-var-p var))
1333       (loop-error "Variable ~S has already been used" var))
1334     (loop-make-var var val dtype)
1335     (if (loop-tequal (car *loop-source-code*) :and)
1336         (loop-pop-source)
1337         (return (loop-bind-block)))))
1338 \f
1339 ;;;; the iteration driver
1340
1341 (defun loop-hack-iteration (entry)
1342   (flet ((make-endtest (list-of-forms)
1343            (cond ((null list-of-forms) nil)
1344                  ((member t list-of-forms) '(go end-loop))
1345                  (t `(when ,(if (null (cdr (setq list-of-forms
1346                                                  (nreverse list-of-forms))))
1347                                 (car list-of-forms)
1348                                 (cons 'or list-of-forms))
1349                        (go end-loop))))))
1350     (do ((pre-step-tests nil)
1351          (steps nil)
1352          (post-step-tests nil)
1353          (pseudo-steps nil)
1354          (pre-loop-pre-step-tests nil)
1355          (pre-loop-steps nil)
1356          (pre-loop-post-step-tests nil)
1357          (pre-loop-pseudo-steps nil)
1358          (tem) (data))
1359         (nil)
1360       ;; Note that we collect endtests in reverse order, but steps in correct
1361       ;; order. MAKE-ENDTEST does the nreverse for us.
1362       (setq tem (setq data
1363                       (apply (symbol-function (first entry)) (rest entry))))
1364       (and (car tem) (push (car tem) pre-step-tests))
1365       (setq steps (nconc steps (copy-list (car (setq tem (cdr tem))))))
1366       (and (car (setq tem (cdr tem))) (push (car tem) post-step-tests))
1367       (setq pseudo-steps
1368             (nconc pseudo-steps (copy-list (car (setq tem (cdr tem))))))
1369       (setq tem (cdr tem))
1370       (when *loop-emitted-body*
1371         (loop-error "iteration in LOOP follows body code"))
1372       (unless tem (setq tem data))
1373       (when (car tem) (push (car tem) pre-loop-pre-step-tests))
1374       ;; FIXME: This (SETF FOO (NCONC FOO BAR)) idiom appears often enough
1375       ;; that it might be worth making it into an NCONCF macro.
1376       (setq pre-loop-steps
1377             (nconc pre-loop-steps (copy-list (car (setq tem (cdr tem))))))
1378       (when (car (setq tem (cdr tem)))
1379         (push (car tem) pre-loop-post-step-tests))
1380       (setq pre-loop-pseudo-steps
1381             (nconc pre-loop-pseudo-steps (copy-list (cadr tem))))
1382       (unless (loop-tequal (car *loop-source-code*) :and)
1383         (setq *loop-before-loop*
1384               (list* (loop-make-desetq pre-loop-pseudo-steps)
1385                      (make-endtest pre-loop-post-step-tests)
1386                      (loop-make-psetq pre-loop-steps)
1387                      (make-endtest pre-loop-pre-step-tests)
1388                      *loop-before-loop*))
1389         (setq *loop-after-body*
1390               (list* (loop-make-desetq pseudo-steps)
1391                      (make-endtest post-step-tests)
1392                      (loop-make-psetq steps)
1393                      (make-endtest pre-step-tests)
1394                      *loop-after-body*))
1395         (loop-bind-block)
1396         (return nil))
1397       (loop-pop-source)                         ; Flush the "AND".
1398       (when (and (not (loop-universe-implicit-for-required *loop-universe*))
1399                  (setq tem
1400                        (loop-lookup-keyword
1401                         (car *loop-source-code*)
1402                         (loop-universe-iteration-keywords *loop-universe*))))
1403         ;; The latest ANSI clarification is that the FOR/AS after the AND must
1404         ;; NOT be supplied.
1405         (loop-pop-source)
1406         (setq entry tem)))))
1407 \f
1408 ;;;; main iteration drivers
1409
1410 ;;; FOR variable keyword ..args..
1411 (defun loop-do-for ()
1412   (let* ((var (loop-pop-source))
1413          (data-type (loop-optional-type var))
1414          (keyword (loop-pop-source))
1415          (first-arg nil)
1416          (tem nil))
1417     (setq first-arg (loop-get-form))
1418     (unless (and (symbolp keyword)
1419                  (setq tem (loop-lookup-keyword
1420                              keyword
1421                              (loop-universe-for-keywords *loop-universe*))))
1422       (loop-error "~S is an unknown keyword in FOR or AS clause in LOOP."
1423                   keyword))
1424     (apply (car tem) var first-arg data-type (cdr tem))))
1425
1426 (defun loop-when-it-var ()
1427   (or *loop-when-it-var*
1428       (setq *loop-when-it-var*
1429             (loop-make-var (gensym "LOOP-IT-") nil nil))))
1430 \f
1431 ;;;; various FOR/AS subdispatches
1432
1433 ;;; ANSI "FOR x = y [THEN z]" is sort of like the old Genera one when
1434 ;;; the THEN is omitted (other than being more stringent in its
1435 ;;; placement), and like the old "FOR x FIRST y THEN z" when the THEN
1436 ;;; is present. I.e., the first initialization occurs in the loop body
1437 ;;; (first-step), not in the variable binding phase.
1438 (defun loop-ansi-for-equals (var val data-type)
1439   (loop-make-var var nil data-type)
1440   (cond ((loop-tequal (car *loop-source-code*) :then)
1441          ;; Then we are the same as "FOR x FIRST y THEN z".
1442          (loop-pop-source)
1443          `(() (,var ,(loop-get-form)) () ()
1444            () (,var ,val) () ()))
1445         (t ;; We are the same as "FOR x = y".
1446          `(() (,var ,val) () ()))))
1447
1448 (defun loop-for-across (var val data-type)
1449   (loop-make-var var nil data-type)
1450   (let ((vector-var (gensym "LOOP-ACROSS-VECTOR-"))
1451         (index-var (gensym "LOOP-ACROSS-INDEX-")))
1452     (multiple-value-bind (vector-form constantp vector-value)
1453         (loop-constant-fold-if-possible val 'vector)
1454       (loop-make-var
1455         vector-var vector-form
1456         (if (and (consp vector-form) (eq (car vector-form) 'the))
1457             (cadr vector-form)
1458             'vector))
1459       (loop-make-var index-var 0 'fixnum)
1460       (let* ((length 0)
1461              (length-form (cond ((not constantp)
1462                                  (let ((v (gensym "LOOP-ACROSS-LIMIT-")))
1463                                    (push `(setq ,v (length ,vector-var))
1464                                          *loop-prologue*)
1465                                    (loop-make-var v 0 'fixnum)))
1466                                 (t (setq length (length vector-value)))))
1467              (first-test `(>= ,index-var ,length-form))
1468              (other-test first-test)
1469              (step `(,var (aref ,vector-var ,index-var)))
1470              (pstep `(,index-var (1+ ,index-var))))
1471         (declare (fixnum length))
1472         (when constantp
1473           (setq first-test (= length 0))
1474           (when (<= length 1)
1475             (setq other-test t)))
1476         `(,other-test ,step () ,pstep
1477           ,@(and (not (eq first-test other-test))
1478                  `(,first-test ,step () ,pstep)))))))
1479 \f
1480 ;;;; list iteration
1481
1482 (defun loop-list-step (listvar)
1483   ;; We are not equipped to analyze whether 'FOO is the same as #'FOO
1484   ;; here in any sensible fashion, so let's give an obnoxious warning
1485   ;; whenever 'FOO is used as the stepping function.
1486   ;;
1487   ;; While a Discerning Compiler may deal intelligently with
1488   ;; (FUNCALL 'FOO ...), not recognizing FOO may defeat some LOOP
1489   ;; optimizations.
1490   (let ((stepper (cond ((loop-tequal (car *loop-source-code*) :by)
1491                         (loop-pop-source)
1492                         (loop-get-form))
1493                        (t '(function cdr)))))
1494     (cond ((and (consp stepper) (eq (car stepper) 'quote))
1495            (loop-warn "Use of QUOTE around stepping function in LOOP will be left verbatim.")
1496            `(funcall ,stepper ,listvar))
1497           ((and (consp stepper) (eq (car stepper) 'function))
1498            (list (cadr stepper) listvar))
1499           (t
1500            `(funcall ,(loop-make-var (gensym "LOOP-FN-") stepper 'function)
1501                      ,listvar)))))
1502
1503 (defun loop-for-on (var val data-type)
1504   (multiple-value-bind (list constantp list-value)
1505       (loop-constant-fold-if-possible val)
1506     (let ((listvar var))
1507       (cond ((and var (symbolp var))
1508              (loop-make-var var list data-type))
1509             (t
1510              (loop-make-var (setq listvar (gensym)) list 't)
1511              (loop-make-var var nil data-type)))
1512       (let ((list-step (loop-list-step listvar)))
1513         (let* ((first-endtest
1514                 ;; mysterious comment from original CMU CL sources:
1515                 ;;   the following should use `atom' instead of `endp',
1516                 ;;   per [bug2428]
1517                 `(atom ,listvar))
1518                (other-endtest first-endtest))
1519           (when (and constantp (listp list-value))
1520             (setq first-endtest (null list-value)))
1521           (cond ((eq var listvar)
1522                  ;; The contour of the loop is different because we
1523                  ;; use the user's variable...
1524                  `(() (,listvar ,list-step)
1525                    ,other-endtest () () () ,first-endtest ()))
1526                 (t (let ((step `(,var ,listvar))
1527                          (pseudo `(,listvar ,list-step)))
1528                      `(,other-endtest ,step () ,pseudo
1529                        ,@(and (not (eq first-endtest other-endtest))
1530                               `(,first-endtest ,step () ,pseudo)))))))))))
1531
1532 (defun loop-for-in (var val data-type)
1533   (multiple-value-bind (list constantp list-value)
1534       (loop-constant-fold-if-possible val)
1535     (let ((listvar (gensym "LOOP-LIST-")))
1536       (loop-make-var var nil data-type)
1537       (loop-make-var listvar list 'list)
1538       (let ((list-step (loop-list-step listvar)))
1539         (let* ((first-endtest `(endp ,listvar))
1540                (other-endtest first-endtest)
1541                (step `(,var (car ,listvar)))
1542                (pseudo-step `(,listvar ,list-step)))
1543           (when (and constantp (listp list-value))
1544             (setq first-endtest (null list-value)))
1545           `(,other-endtest ,step () ,pseudo-step
1546             ,@(and (not (eq first-endtest other-endtest))
1547                    `(,first-endtest ,step () ,pseudo-step))))))))
1548 \f
1549 ;;;; iteration paths
1550
1551 (defstruct (loop-path
1552             (:copier nil)
1553             (:predicate nil))
1554   names
1555   preposition-groups
1556   inclusive-permitted
1557   function
1558   user-data)
1559
1560 (defun add-loop-path (names function universe
1561                       &key preposition-groups inclusive-permitted user-data)
1562   (declare (type loop-universe universe))
1563   (unless (listp names)
1564     (setq names (list names)))
1565   (let ((ht (loop-universe-path-keywords universe))
1566         (lp (make-loop-path
1567               :names (mapcar #'symbol-name names)
1568               :function function
1569               :user-data user-data
1570               :preposition-groups (mapcar (lambda (x)
1571                                             (if (listp x) x (list x)))
1572                                           preposition-groups)
1573               :inclusive-permitted inclusive-permitted)))
1574     (dolist (name names)
1575       (setf (gethash (symbol-name name) ht) lp))
1576     lp))
1577 \f
1578 ;;; Note: Path functions are allowed to use LOOP-MAKE-VAR, hack
1579 ;;; the prologue, etc.
1580 (defun loop-for-being (var val data-type)
1581   ;; FOR var BEING each/the pathname prep-phrases using-stuff... each/the =
1582   ;; EACH or THE. Not clear if it is optional, so I guess we'll warn.
1583   (let ((path nil)
1584         (data nil)
1585         (inclusive nil)
1586         (stuff nil)
1587         (initial-prepositions nil))
1588     (cond ((loop-tmember val '(:each :the)) (setq path (loop-pop-source)))
1589           ((loop-tequal (car *loop-source-code*) :and)
1590            (loop-pop-source)
1591            (setq inclusive t)
1592            (unless (loop-tmember (car *loop-source-code*)
1593                                  '(:its :each :his :her))
1594              (loop-error "~S was found where ITS or EACH expected in LOOP iteration path syntax."
1595                          (car *loop-source-code*)))
1596            (loop-pop-source)
1597            (setq path (loop-pop-source))
1598            (setq initial-prepositions `((:in ,val))))
1599           (t (loop-error "unrecognizable LOOP iteration path syntax: missing EACH or THE?")))
1600     (cond ((not (symbolp path))
1601            (loop-error
1602             "~S was found where a LOOP iteration path name was expected."
1603             path))
1604           ((not (setq data (loop-lookup-keyword path (loop-universe-path-keywords *loop-universe*))))
1605            (loop-error "~S is not the name of a LOOP iteration path." path))
1606           ((and inclusive (not (loop-path-inclusive-permitted data)))
1607            (loop-error "\"Inclusive\" iteration is not possible with the ~S LOOP iteration path." path)))
1608     (let ((fun (loop-path-function data))
1609           (preps (nconc initial-prepositions
1610                         (loop-collect-prepositional-phrases
1611                          (loop-path-preposition-groups data)
1612                          t)))
1613           (user-data (loop-path-user-data data)))
1614       (when (symbolp fun) (setq fun (symbol-function fun)))
1615       (setq stuff (if inclusive
1616                       (apply fun var data-type preps :inclusive t user-data)
1617                       (apply fun var data-type preps user-data))))
1618     (when *loop-named-vars*
1619       (loop-error "Unused USING vars: ~S." *loop-named-vars*))
1620     ;; STUFF is now (bindings prologue-forms . stuff-to-pass-back).
1621     ;; Protect the system from the user and the user from himself.
1622     (unless (member (length stuff) '(6 10))
1623       (loop-error "Value passed back by LOOP iteration path function for path ~S has invalid length."
1624                   path))
1625     (do ((l (car stuff) (cdr l)) (x)) ((null l))
1626       (if (atom (setq x (car l)))
1627           (loop-make-var x nil nil)
1628           (loop-make-var (car x) (cadr x) (caddr x))))
1629     (setq *loop-prologue* (nconc (reverse (cadr stuff)) *loop-prologue*))
1630     (cddr stuff)))
1631 \f
1632 (defun loop-named-var (name)
1633   (let ((tem (loop-tassoc name *loop-named-vars*)))
1634     (declare (list tem))
1635     (cond ((null tem) (values (gensym) nil))
1636           (t (setq *loop-named-vars* (delete tem *loop-named-vars*))
1637              (values (cdr tem) t)))))
1638
1639 (defun loop-collect-prepositional-phrases (preposition-groups
1640                                            &optional
1641                                            using-allowed
1642                                            initial-phrases)
1643   (flet ((in-group-p (x group) (car (loop-tmember x group))))
1644     (do ((token nil)
1645          (prepositional-phrases initial-phrases)
1646          (this-group nil nil)
1647          (this-prep nil nil)
1648          (disallowed-prepositions
1649            (mapcan (lambda (x)
1650                      (copy-list
1651                       (find (car x) preposition-groups :test #'in-group-p)))
1652                    initial-phrases))
1653          (used-prepositions (mapcar #'car initial-phrases)))
1654         ((null *loop-source-code*) (nreverse prepositional-phrases))
1655       (declare (symbol this-prep))
1656       (setq token (car *loop-source-code*))
1657       (dolist (group preposition-groups)
1658         (when (setq this-prep (in-group-p token group))
1659           (return (setq this-group group))))
1660       (cond (this-group
1661              (when (member this-prep disallowed-prepositions)
1662                (loop-error
1663                  (if (member this-prep used-prepositions)
1664                      "A ~S prepositional phrase occurs multiply for some LOOP clause."
1665                      "Preposition ~S was used when some other preposition has subsumed it.")
1666                  token))
1667              (setq used-prepositions (if (listp this-group)
1668                                          (append this-group used-prepositions)
1669                                          (cons this-group used-prepositions)))
1670              (loop-pop-source)
1671              (push (list this-prep (loop-get-form)) prepositional-phrases))
1672             ((and using-allowed (loop-tequal token 'using))
1673              (loop-pop-source)
1674              (do ((z (loop-pop-source) (loop-pop-source)) (tem)) (nil)
1675                (when (cadr z)
1676                  (if (setq tem (loop-tassoc (car z) *loop-named-vars*))
1677                      (loop-error
1678                        "The variable substitution for ~S occurs twice in a USING phrase,~@
1679                         with ~S and ~S."
1680                        (car z) (cadr z) (cadr tem))
1681                      (push (cons (car z) (cadr z)) *loop-named-vars*)))
1682                (when (or (null *loop-source-code*)
1683                          (symbolp (car *loop-source-code*)))
1684                  (return nil))))
1685             (t (return (nreverse prepositional-phrases)))))))
1686 \f
1687 ;;;; master sequencer function
1688
1689 (defun loop-sequencer (indexv indexv-type
1690                        variable variable-type
1691                        sequence-variable sequence-type
1692                        step-hack default-top
1693                        prep-phrases)
1694    (let ((endform nil) ; form (constant or variable) with limit value
1695          (sequencep nil) ; T if sequence arg has been provided
1696          (testfn nil) ; endtest function
1697          (test nil) ; endtest form
1698          (stepby (1+ (or (loop-typed-init indexv-type) 0))) ; our increment
1699          (stepby-constantp t)
1700          (step nil) ; step form
1701          (dir nil) ; direction of stepping: NIL, :UP, :DOWN
1702          (inclusive-iteration nil) ; T if include last index
1703          (start-given nil) ; T when prep phrase has specified start
1704          (start-value nil)
1705          (start-constantp nil)
1706          (limit-given nil) ; T when prep phrase has specified end
1707          (limit-constantp nil)
1708          (limit-value nil)
1709          )
1710      (flet ((assert-index-for-arithmetic (index)
1711               (unless (atom index)
1712                 (loop-error "Arithmetic index must be an atom."))))
1713        (when variable (loop-make-var variable nil variable-type))
1714        (do ((l prep-phrases (cdr l)) (prep) (form) (odir)) ((null l))
1715          (setq prep (caar l) form (cadar l))
1716          (case prep
1717            ((:of :in)
1718             (setq sequencep t)
1719             (loop-make-var sequence-variable form sequence-type))
1720            ((:from :downfrom :upfrom)
1721             (setq start-given t)
1722             (cond ((eq prep :downfrom) (setq dir ':down))
1723                   ((eq prep :upfrom) (setq dir ':up)))
1724             (multiple-value-setq (form start-constantp start-value)
1725               (loop-constant-fold-if-possible form indexv-type))
1726             (assert-index-for-arithmetic indexv)
1727             ;; KLUDGE: loop-make-var generates a temporary symbol for
1728             ;; indexv if it is NIL. We have to use it to have the index
1729             ;; actually count
1730             (setq indexv (loop-make-var indexv form indexv-type)))
1731            ((:upto :to :downto :above :below)
1732             (cond ((loop-tequal prep :upto) (setq inclusive-iteration
1733                                                   (setq dir ':up)))
1734                   ((loop-tequal prep :to) (setq inclusive-iteration t))
1735                   ((loop-tequal prep :downto) (setq inclusive-iteration
1736                                                     (setq dir ':down)))
1737                   ((loop-tequal prep :above) (setq dir ':down))
1738                   ((loop-tequal prep :below) (setq dir ':up)))
1739             (setq limit-given t)
1740             (multiple-value-setq (form limit-constantp limit-value)
1741               (loop-constant-fold-if-possible form `(and ,indexv-type real)))
1742             (setq endform (if limit-constantp
1743                               `',limit-value
1744                               (loop-make-var
1745                                  (gensym "LOOP-LIMIT-") form
1746                                  `(and ,indexv-type real)))))
1747            (:by
1748             (multiple-value-setq (form stepby-constantp stepby)
1749               (loop-constant-fold-if-possible form
1750                                               `(and ,indexv-type (real (0)))))
1751             (unless stepby-constantp
1752               (loop-make-var (setq stepby (gensym "LOOP-STEP-BY-"))
1753                  form
1754                  `(and ,indexv-type (real (0)))
1755                  t)))
1756            (t (loop-error
1757                  "~S invalid preposition in sequencing or sequence path;~@
1758               maybe invalid prepositions were specified in iteration path descriptor?"
1759                  prep)))
1760          (when (and odir dir (not (eq dir odir)))
1761            (loop-error
1762              "conflicting stepping directions in LOOP sequencing path"))
1763          (setq odir dir))
1764        (when (and sequence-variable (not sequencep))
1765          (loop-error "missing OF or IN phrase in sequence path"))
1766        ;; Now fill in the defaults.
1767        (if start-given
1768            (when limit-given
1769              ;; if both start and limit are given, they had better both
1770              ;; be REAL.  We already enforce the REALness of LIMIT,
1771              ;; above; here's the KLUDGE to enforce the type of START.
1772              (flet ((type-declaration-of (x)
1773                       (and (eq (car x) 'type) (caddr x))))
1774                (let ((decl (find indexv *loop-declarations*
1775                                  :key #'type-declaration-of))
1776                      (%decl (find indexv *loop-declarations*
1777                                   :key #'type-declaration-of
1778                                   :from-end t)))
1779                  (sb!int:aver (eq decl %decl))
1780                  (when decl
1781                    (setf (cadr decl)
1782                          `(and real ,(cadr decl)))))))
1783            ;; default start
1784            ;; DUPLICATE KLUDGE: loop-make-var generates a temporary
1785            ;; symbol for indexv if it is NIL. See also the comment in
1786            ;; the (:from :downfrom :upfrom) case
1787            (progn
1788              (assert-index-for-arithmetic indexv)
1789              (setq indexv
1790                    (loop-make-var
1791                       indexv
1792                       (setq start-constantp t
1793                             start-value (or (loop-typed-init indexv-type) 0))
1794                       `(and ,indexv-type real)))))
1795        (cond ((member dir '(nil :up))
1796               (when (or limit-given default-top)
1797                 (unless limit-given
1798                   (loop-make-var (setq endform (gensym "LOOP-SEQ-LIMIT-"))
1799                      nil
1800                      indexv-type)
1801                   (push `(setq ,endform ,default-top) *loop-prologue*))
1802                 (setq testfn (if inclusive-iteration '> '>=)))
1803               (setq step (if (eql stepby 1) `(1+ ,indexv) `(+ ,indexv ,stepby))))
1804              (t (unless start-given
1805                   (unless default-top
1806                     (loop-error "don't know where to start stepping"))
1807                   (push `(setq ,indexv (1- ,default-top)) *loop-prologue*))
1808                 (when (and default-top (not endform))
1809                   (setq endform (loop-typed-init indexv-type)
1810                         inclusive-iteration t))
1811                 (when endform (setq testfn (if inclusive-iteration  '< '<=)))
1812                 (setq step
1813                       (if (eql stepby 1) `(1- ,indexv) `(- ,indexv ,stepby)))))
1814        (when testfn
1815          (setq test
1816                `(,testfn ,indexv ,endform)))
1817        (when step-hack
1818          (setq step-hack
1819                `(,variable ,step-hack)))
1820        (let ((first-test test) (remaining-tests test))
1821          ;; As far as I can tell, the effect of the following code is
1822          ;; to detect cases where we know statically whether the first
1823          ;; iteration of the loop will be executed. Depending on the
1824          ;; situation, we can either:
1825          ;;  a) save one jump and one comparison per loop (not per iteration)
1826          ;;     when it will get executed
1827          ;;  b) remove the loop body completely when it won't be executed
1828          ;;
1829          ;; Noble goals. However, the code generated in case a) will
1830          ;; fool the loop induction variable detection, and cause
1831          ;; code like (LOOP FOR I TO 10 ...) to use generic addition
1832          ;; (bug #278a).
1833          ;;
1834          ;; Since the gain in case a) is rather minimal and Python is
1835          ;; generally smart enough to handle b) without any extra
1836          ;; support from the loop macro, I've disabled this code for
1837          ;; now. The code and the comment left here in case somebody
1838          ;; extends the induction variable bound detection to work
1839          ;; with code where the stepping precedes the test.
1840          ;; -- JES 2005-11-30
1841          #+nil
1842          (when (and stepby-constantp start-constantp limit-constantp
1843                     (realp start-value) (realp limit-value))
1844            (when (setq first-test
1845                        (funcall (symbol-function testfn)
1846                                 start-value
1847                                 limit-value))
1848              (setq remaining-tests t)))
1849          `(() (,indexv ,step)
1850            ,remaining-tests ,step-hack () () ,first-test ,step-hack)))))
1851 \f
1852 ;;;; interfaces to the master sequencer
1853
1854 (defun loop-for-arithmetic (var val data-type kwd)
1855   (loop-sequencer
1856    var (loop-check-data-type data-type 'number)
1857    nil nil nil nil nil nil
1858    (loop-collect-prepositional-phrases
1859     '((:from :upfrom :downfrom) (:to :upto :downto :above :below) (:by))
1860     nil (list (list kwd val)))))
1861
1862 \f
1863 ;;;; builtin LOOP iteration paths
1864
1865 #||
1866 (loop for v being the hash-values of ht do (print v))
1867 (loop for k being the hash-keys of ht do (print k))
1868 (loop for v being the hash-values of ht using (hash-key k) do (print (list k v)))
1869 (loop for k being the hash-keys of ht using (hash-value v) do (print (list k v)))
1870 ||#
1871
1872 (defun loop-hash-table-iteration-path (variable data-type prep-phrases
1873                                        &key (which (sb!int:missing-arg)))
1874   (declare (type (member :hash-key :hash-value) which))
1875   (cond ((or (cdr prep-phrases) (not (member (caar prep-phrases) '(:in :of))))
1876          (loop-error "too many prepositions!"))
1877         ((null prep-phrases)
1878          (loop-error "missing OF or IN in ~S iteration path")))
1879   (let ((ht-var (gensym "LOOP-HASHTAB-"))
1880         (next-fn (gensym "LOOP-HASHTAB-NEXT-"))
1881         (dummy-predicate-var nil)
1882         (post-steps nil))
1883     (multiple-value-bind (other-var other-p)
1884         (loop-named-var (ecase which
1885                           (:hash-key 'hash-value)
1886                           (:hash-value 'hash-key)))
1887       ;; @@@@ LOOP-NAMED-VAR returns a second value of T if the name
1888       ;; was actually specified, so clever code can throw away the
1889       ;; GENSYM'ed-up variable if it isn't really needed. The
1890       ;; following is for those implementations in which we cannot put
1891       ;; dummy NILs into MULTIPLE-VALUE-SETQ variable lists.
1892       (setq other-p t
1893             dummy-predicate-var (loop-when-it-var))
1894       (let* ((key-var nil)
1895              (val-var nil)
1896              (variable (or variable (gensym "LOOP-HASH-VAR-TEMP-")))
1897              (bindings `((,variable nil ,data-type)
1898                          (,ht-var ,(cadar prep-phrases))
1899                          ,@(and other-p other-var `((,other-var nil))))))
1900         (ecase which
1901           (:hash-key (setq key-var variable
1902                            val-var (and other-p other-var)))
1903           (:hash-value (setq key-var (and other-p other-var)
1904                              val-var variable)))
1905         (push `(with-hash-table-iterator (,next-fn ,ht-var)) *loop-wrappers*)
1906         (when (or (consp key-var) data-type)
1907           (setq post-steps
1908                 `(,key-var ,(setq key-var (gensym "LOOP-HASH-KEY-TEMP-"))
1909                            ,@post-steps))
1910           (push `(,key-var nil) bindings))
1911         (when (or (consp val-var) data-type)
1912           (setq post-steps
1913                 `(,val-var ,(setq val-var (gensym "LOOP-HASH-VAL-TEMP-"))
1914                            ,@post-steps))
1915           (push `(,val-var nil) bindings))
1916         `(,bindings                     ;bindings
1917           ()                            ;prologue
1918           ()                            ;pre-test
1919           ()                            ;parallel steps
1920           (not (multiple-value-setq (,dummy-predicate-var ,key-var ,val-var)
1921                  (,next-fn)))           ;post-test
1922           ,post-steps)))))
1923
1924 (defun loop-package-symbols-iteration-path (variable data-type prep-phrases
1925                                             &key symbol-types)
1926   (cond ((and prep-phrases (cdr prep-phrases))
1927          (loop-error "Too many prepositions!"))
1928         ((and prep-phrases (not (member (caar prep-phrases) '(:in :of))))
1929          (sb!int:bug "Unknown preposition ~S." (caar prep-phrases))))
1930   (unless (symbolp variable)
1931     (loop-error "Destructuring is not valid for package symbol iteration."))
1932   (let ((pkg-var (gensym "LOOP-PKGSYM-"))
1933         (next-fn (gensym "LOOP-PKGSYM-NEXT-"))
1934         (variable (or variable (gensym "LOOP-PKGSYM-VAR-")))
1935         (package (or (cadar prep-phrases) '*package*)))
1936     (push `(with-package-iterator (,next-fn ,pkg-var ,@symbol-types))
1937           *loop-wrappers*)
1938     `(((,variable nil ,data-type) (,pkg-var ,package))
1939       ()
1940       ()
1941       ()
1942       (not (multiple-value-setq (,(loop-when-it-var)
1943                                  ,variable)
1944              (,next-fn)))
1945       ())))
1946 \f
1947 ;;;; ANSI LOOP
1948
1949 (defun make-ansi-loop-universe (extended-p)
1950   (let ((w (make-standard-loop-universe
1951              :keywords '((named (loop-do-named))
1952                          (initially (loop-do-initially))
1953                          (finally (loop-do-finally))
1954                          (do (loop-do-do))
1955                          (doing (loop-do-do))
1956                          (return (loop-do-return))
1957                          (collect (loop-list-collection list))
1958                          (collecting (loop-list-collection list))
1959                          (append (loop-list-collection append))
1960                          (appending (loop-list-collection append))
1961                          (nconc (loop-list-collection nconc))
1962                          (nconcing (loop-list-collection nconc))
1963                          (count (loop-sum-collection count
1964                                                      real
1965                                                      fixnum))
1966                          (counting (loop-sum-collection count
1967                                                         real
1968                                                         fixnum))
1969                          (sum (loop-sum-collection sum number number))
1970                          (summing (loop-sum-collection sum number number))
1971                          (maximize (loop-maxmin-collection max))
1972                          (minimize (loop-maxmin-collection min))
1973                          (maximizing (loop-maxmin-collection max))
1974                          (minimizing (loop-maxmin-collection min))
1975                          (always (loop-do-always t nil)) ; Normal, do always
1976                          (never (loop-do-always t t)) ; Negate test on always.
1977                          (thereis (loop-do-thereis t))
1978                          (while (loop-do-while nil :while)) ; Normal, do while
1979                          (until (loop-do-while t :until)) ;Negate test on while
1980                          (when (loop-do-if when nil))   ; Normal, do when
1981                          (if (loop-do-if if nil))       ; synonymous
1982                          (unless (loop-do-if unless t)) ; Negate test on when
1983                          (with (loop-do-with))
1984                          (repeat (loop-do-repeat)))
1985              :for-keywords '((= (loop-ansi-for-equals))
1986                              (across (loop-for-across))
1987                              (in (loop-for-in))
1988                              (on (loop-for-on))
1989                              (from (loop-for-arithmetic :from))
1990                              (downfrom (loop-for-arithmetic :downfrom))
1991                              (upfrom (loop-for-arithmetic :upfrom))
1992                              (below (loop-for-arithmetic :below))
1993                              (above (loop-for-arithmetic :above))
1994                              (to (loop-for-arithmetic :to))
1995                              (upto (loop-for-arithmetic :upto))
1996                              (downto (loop-for-arithmetic :downto))
1997                              (by (loop-for-arithmetic :by))
1998                              (being (loop-for-being)))
1999              :iteration-keywords '((for (loop-do-for))
2000                                    (as (loop-do-for)))
2001              :type-symbols '(array atom bignum bit bit-vector character
2002                              compiled-function complex cons double-float
2003                              fixnum float function hash-table integer
2004                              keyword list long-float nil null number
2005                              package pathname random-state ratio rational
2006                              readtable sequence short-float simple-array
2007                              simple-bit-vector simple-string simple-vector
2008                              single-float standard-char stream string
2009                              base-char symbol t vector)
2010              :type-keywords nil
2011              :ansi (if extended-p :extended t))))
2012     (add-loop-path '(hash-key hash-keys) 'loop-hash-table-iteration-path w
2013                    :preposition-groups '((:of :in))
2014                    :inclusive-permitted nil
2015                    :user-data '(:which :hash-key))
2016     (add-loop-path '(hash-value hash-values) 'loop-hash-table-iteration-path w
2017                    :preposition-groups '((:of :in))
2018                    :inclusive-permitted nil
2019                    :user-data '(:which :hash-value))
2020     (add-loop-path '(symbol symbols) 'loop-package-symbols-iteration-path w
2021                    :preposition-groups '((:of :in))
2022                    :inclusive-permitted nil
2023                    :user-data '(:symbol-types (:internal
2024                                                :external
2025                                                :inherited)))
2026     (add-loop-path '(external-symbol external-symbols)
2027                    'loop-package-symbols-iteration-path w
2028                    :preposition-groups '((:of :in))
2029                    :inclusive-permitted nil
2030                    :user-data '(:symbol-types (:external)))
2031     (add-loop-path '(present-symbol present-symbols)
2032                    'loop-package-symbols-iteration-path w
2033                    :preposition-groups '((:of :in))
2034                    :inclusive-permitted nil
2035                    :user-data '(:symbol-types (:internal
2036                                                :external)))
2037     w))
2038
2039 (defparameter *loop-ansi-universe*
2040   (make-ansi-loop-universe nil))
2041
2042 (defun loop-standard-expansion (keywords-and-forms environment universe)
2043   (if (and keywords-and-forms (symbolp (car keywords-and-forms)))
2044       (loop-translate keywords-and-forms environment universe)
2045       (let ((tag (gensym)))
2046         `(block nil (tagbody ,tag (progn ,@keywords-and-forms) (go ,tag))))))
2047
2048 (sb!int:defmacro-mundanely loop (&environment env &rest keywords-and-forms)
2049   (loop-standard-expansion keywords-and-forms env *loop-ansi-universe*))
2050
2051 (sb!int:defmacro-mundanely loop-finish ()
2052   #!+sb-doc
2053   "Cause the iteration to terminate \"normally\", the same as implicit
2054 termination by an iteration driving clause, or by use of WHILE or
2055 UNTIL -- the epilogue code (if any) will be run, and any implicitly
2056 collected result will be returned as the value of the LOOP."
2057   '(go end-loop))