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