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