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