Fix make-array transforms.
[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 \f
91 ;;;; list collection macrology
92
93 (sb!int:defmacro-mundanely with-loop-list-collection-head
94     ((head-var tail-var &optional user-head-var) &body body)
95   (let ((l (and user-head-var (list (list user-head-var nil)))))
96     `(let* ((,head-var (list nil)) (,tail-var ,head-var) ,@l)
97        ,@body)))
98
99 (sb!int:defmacro-mundanely loop-collect-rplacd
100     (&environment env (head-var tail-var &optional user-head-var) form)
101   (setq form (sb!int:%macroexpand form env))
102   (flet ((cdr-wrap (form n)
103            (declare (fixnum n))
104            (do () ((<= n 4) (setq form `(,(case n
105                                             (1 'cdr)
106                                             (2 'cddr)
107                                             (3 'cdddr)
108                                             (4 'cddddr))
109                                          ,form)))
110              (setq form `(cddddr ,form) n (- n 4)))))
111     (let ((tail-form form) (ncdrs nil))
112       ;; Determine whether the form being constructed is a list of known
113       ;; length.
114       (when (consp form)
115         (cond ((eq (car form) 'list)
116                (setq ncdrs (1- (length (cdr form)))))
117               ((member (car form) '(list* cons))
118                (when (and (cddr form) (member (car (last form)) '(nil 'nil)))
119                  (setq ncdrs (- (length (cdr form)) 2))))))
120       (let ((answer
121               (cond ((null ncdrs)
122                      `(when (setf (cdr ,tail-var) ,tail-form)
123                         (setq ,tail-var (last (cdr ,tail-var)))))
124                     ((< ncdrs 0) (return-from loop-collect-rplacd nil))
125                     ((= ncdrs 0)
126                      ;; @@@@ Here we have a choice of two idioms:
127                      ;;   (RPLACD TAIL (SETQ TAIL TAIL-FORM))
128                      ;;   (SETQ TAIL (SETF (CDR TAIL) TAIL-FORM)).
129                      ;; Genera and most others I have seen do better with the
130                      ;; former.
131                      `(rplacd ,tail-var (setq ,tail-var ,tail-form)))
132                     (t `(setq ,tail-var ,(cdr-wrap `(setf (cdr ,tail-var)
133                                                           ,tail-form)
134                                                    ncdrs))))))
135         ;; If not using locatives or something similar to update the
136         ;; user's head variable, we've got to set it... It's harmless
137         ;; to repeatedly set it unconditionally, and probably faster
138         ;; than checking.
139         (when user-head-var
140           (setq answer
141                 `(progn ,answer
142                         (setq ,user-head-var (cdr ,head-var)))))
143         answer))))
144
145 (sb!int:defmacro-mundanely loop-collect-answer (head-var
146                                                    &optional user-head-var)
147   (or user-head-var
148       `(cdr ,head-var)))
149 \f
150 ;;;; maximization technology
151
152 #|
153 The basic idea of all this minimax randomness here is that we have to
154 have constructed all uses of maximize and minimize to a particular
155 "destination" before we can decide how to code them. The goal is to not
156 have to have any kinds of flags, by knowing both that (1) the type is
157 something which we can provide an initial minimum or maximum value for
158 and (2) know that a MAXIMIZE and MINIMIZE are not being combined.
159
160 SO, we have a datastructure which we annotate with all sorts of things,
161 incrementally updating it as we generate loop body code, and then use
162 a wrapper and internal macros to do the coding when the loop has been
163 constructed.
164 |#
165
166 (defstruct (loop-minimax
167              (:constructor make-loop-minimax-internal)
168              (:copier nil)
169              (:predicate nil))
170   answer-variable
171   type
172   temp-variable
173   flag-variable
174   operations
175   infinity-data)
176
177 (defvar *loop-minimax-type-infinities-alist*
178   ;; FIXME: Now that SBCL supports floating point infinities again, we
179   ;; should have floating point infinities here, as cmucl-2.4.8 did.
180   '((fixnum most-positive-fixnum most-negative-fixnum)))
181
182 (defun make-loop-minimax (answer-variable type)
183   (let ((infinity-data (cdr (assoc type
184                                    *loop-minimax-type-infinities-alist*
185                                    :test #'sb!xc:subtypep))))
186     (make-loop-minimax-internal
187       :answer-variable answer-variable
188       :type type
189       :temp-variable (gensym "LOOP-MAXMIN-TEMP-")
190       :flag-variable (and (not infinity-data)
191                           (gensym "LOOP-MAXMIN-FLAG-"))
192       :operations nil
193       :infinity-data infinity-data)))
194
195 (defun loop-note-minimax-operation (operation minimax)
196   (pushnew (the symbol operation) (loop-minimax-operations minimax))
197   (when (and (cdr (loop-minimax-operations minimax))
198              (not (loop-minimax-flag-variable minimax)))
199     (setf (loop-minimax-flag-variable minimax)
200           (gensym "LOOP-MAXMIN-FLAG-")))
201   operation)
202
203 (sb!int:defmacro-mundanely with-minimax-value (lm &body body)
204   (let ((init (loop-typed-init (loop-minimax-type lm)))
205         (which (car (loop-minimax-operations lm)))
206         (infinity-data (loop-minimax-infinity-data lm))
207         (answer-var (loop-minimax-answer-variable lm))
208         (temp-var (loop-minimax-temp-variable lm))
209         (flag-var (loop-minimax-flag-variable lm))
210         (type (loop-minimax-type lm)))
211     (if flag-var
212         `(let ((,answer-var ,init) (,temp-var ,init) (,flag-var nil))
213            (declare (type ,type ,answer-var ,temp-var))
214            ,@body)
215         `(let ((,answer-var ,(if (eq which 'min)
216                                  (first infinity-data)
217                                  (second infinity-data)))
218                (,temp-var ,init))
219            (declare (type ,type ,answer-var ,temp-var))
220            ,@body))))
221
222 (sb!int:defmacro-mundanely loop-accumulate-minimax-value (lm operation form)
223   (let* ((answer-var (loop-minimax-answer-variable lm))
224          (temp-var (loop-minimax-temp-variable lm))
225          (flag-var (loop-minimax-flag-variable lm))
226          (test `(,(ecase operation
227                     (min '<)
228                     (max '>))
229                  ,temp-var ,answer-var)))
230     `(progn
231        (setq ,temp-var ,form)
232        (when ,(if flag-var `(or (not ,flag-var) ,test) test)
233          (setq ,@(and flag-var `(,flag-var t))
234                ,answer-var ,temp-var)))))
235 \f
236 ;;;; LOOP keyword tables
237
238 #|
239 LOOP keyword tables are hash tables string keys and a test of EQUAL.
240
241 The actual descriptive/dispatch structure used by LOOP is called a "loop
242 universe" contains a few tables and parameterizations. The basic idea is
243 that we can provide a non-extensible ANSI-compatible loop environment,
244 an extensible ANSI-superset loop environment, and (for such environments
245 as CLOE) one which is "sufficiently close" to the old Genera-vintage
246 LOOP for use by old user programs without requiring all of the old LOOP
247 code to be loaded.
248 |#
249
250 ;;;; token hackery
251
252 ;;; Compare two "tokens". The first is the frob out of *LOOP-SOURCE-CODE*,
253 ;;; the second a symbol to check against.
254 (defun loop-tequal (x1 x2)
255   (and (symbolp x1) (string= x1 x2)))
256
257 (defun loop-tassoc (kwd alist)
258   (and (symbolp kwd) (assoc kwd alist :test #'string=)))
259
260 (defun loop-tmember (kwd list)
261   (and (symbolp kwd) (member kwd list :test #'string=)))
262
263 (defun loop-lookup-keyword (loop-token table)
264   (and (symbolp loop-token)
265        (values (gethash (symbol-name loop-token) table))))
266
267 (sb!int:defmacro-mundanely loop-store-table-data (symbol table datum)
268   `(setf (gethash (symbol-name ,symbol) ,table) ,datum))
269
270 (defstruct (loop-universe
271              (:copier nil)
272              (:predicate nil))
273   keywords             ; hash table, value = (fn-name . extra-data)
274   iteration-keywords   ; hash table, value = (fn-name . extra-data)
275   for-keywords         ; hash table, value = (fn-name . extra-data)
276   path-keywords        ; hash table, value = (fn-name . extra-data)
277   type-symbols         ; hash table of type SYMBOLS, test EQ,
278                        ; value = CL type specifier
279   type-keywords)       ; hash table of type STRINGS, test EQUAL,
280                        ; value = CL type spec
281 (sb!int:def!method print-object ((u loop-universe) stream)
282   (print-unreadable-object (u stream :type t :identity t)))
283
284 ;;; This is the "current" loop context in use when we are expanding a
285 ;;; loop. It gets bound on each invocation of LOOP.
286 (defvar *loop-universe*)
287
288 (defun make-standard-loop-universe (&key keywords for-keywords
289                                          iteration-keywords path-keywords
290                                          type-keywords type-symbols)
291   (flet ((maketable (entries)
292            (let* ((size (length entries))
293                   (ht (make-hash-table :size (if (< size 10) 10 size)
294                                        :test 'equal)))
295              (dolist (x entries)
296                (setf (gethash (symbol-name (car x)) ht) (cadr x)))
297              ht)))
298     (make-loop-universe
299       :keywords (maketable keywords)
300       :for-keywords (maketable for-keywords)
301       :iteration-keywords (maketable iteration-keywords)
302       :path-keywords (maketable path-keywords)
303       :type-keywords (maketable type-keywords)
304       :type-symbols (let* ((size (length type-symbols))
305                            (ht (make-hash-table :size (if (< size 10) 10 size)
306                                                 :test 'eq)))
307                       (dolist (x type-symbols)
308                         (if (atom x)
309                             (setf (gethash x ht) x)
310                             (setf (gethash (car x) ht) (cadr x))))
311                       ht))))
312 \f
313 ;;;; SETQ hackery, including destructuring ("DESETQ")
314
315 (defun loop-make-psetq (frobs)
316   (and frobs
317        (loop-make-desetq
318          (list (car frobs)
319                (if (null (cddr frobs)) (cadr frobs)
320                    `(prog1 ,(cadr frobs)
321                            ,(loop-make-psetq (cddr frobs))))))))
322
323 (defun loop-make-desetq (var-val-pairs)
324   (if (null var-val-pairs)
325       nil
326       (cons 'loop-really-desetq var-val-pairs)))
327
328 (defvar *loop-desetq-temporary*
329         (make-symbol "LOOP-DESETQ-TEMP"))
330
331 (sb!int:defmacro-mundanely loop-really-desetq (&environment env
332                                                &rest var-val-pairs)
333   (labels ((find-non-null (var)
334              ;; See whether there's any non-null thing here. Recurse
335              ;; if the list element is itself a list.
336              (do ((tail var)) ((not (consp tail)) tail)
337                (when (find-non-null (pop tail)) (return t))))
338            (loop-desetq-internal (var val &optional temp)
339              ;; returns a list of actions to be performed
340              (typecase var
341                (null
342                  (when (consp val)
343                    ;; Don't lose possible side effects.
344                    (if (eq (car val) 'prog1)
345                        ;; These can come from PSETQ or DESETQ below.
346                        ;; Throw away the value, keep the side effects.
347                        ;; Special case is for handling an expanded POP.
348                        (mapcan (lambda (x)
349                                  (and (consp x)
350                                       (or (not (eq (car x) 'car))
351                                           (not (symbolp (cadr x)))
352                                           (not (symbolp (setq x (sb!int:%macroexpand x env)))))
353                                       (cons x nil)))
354                                (cdr val))
355                        `(,val))))
356                (cons
357                  (let* ((car (car var))
358                         (cdr (cdr var))
359                         (car-non-null (find-non-null car))
360                         (cdr-non-null (find-non-null cdr)))
361                    (when (or car-non-null cdr-non-null)
362                      (if cdr-non-null
363                          (let* ((temp-p temp)
364                                 (temp (or temp *loop-desetq-temporary*))
365                                 (body `(,@(loop-desetq-internal car
366                                                                 `(car ,temp))
367                                           (setq ,temp (cdr ,temp))
368                                           ,@(loop-desetq-internal cdr
369                                                                   temp
370                                                                   temp))))
371                            (if temp-p
372                                `(,@(unless (eq temp val)
373                                      `((setq ,temp ,val)))
374                                  ,@body)
375                                `((let ((,temp ,val))
376                                    ,@body))))
377                          ;; no CDRing to do
378                          (loop-desetq-internal car `(car ,val) temp)))))
379                (otherwise
380                  (unless (eq var val)
381                    `((setq ,var ,val)))))))
382     (do ((actions))
383         ((null var-val-pairs)
384          (if (null (cdr actions)) (car actions) `(progn ,@(nreverse actions))))
385       (setq actions (revappend
386                       (loop-desetq-internal (pop var-val-pairs)
387                                             (pop var-val-pairs))
388                       actions)))))
389 \f
390 ;;;; LOOP-local variables
391
392 ;;; This is the "current" pointer into the LOOP source code.
393 (defvar *loop-source-code*)
394
395 ;;; This is the pointer to the original, for things like NAMED that
396 ;;; insist on being in a particular position
397 (defvar *loop-original-source-code*)
398
399 ;;; This is *loop-source-code* as of the "last" clause. It is used
400 ;;; primarily for generating error messages (see loop-error, loop-warn).
401 (defvar *loop-source-context*)
402
403 ;;; list of names for the LOOP, supplied by the NAMED clause
404 (defvar *loop-names*)
405
406 ;;; The macroexpansion environment given to the macro.
407 (defvar *loop-macro-environment*)
408
409 ;;; This holds variable names specified with the USING clause.
410 ;;; See LOOP-NAMED-VAR.
411 (defvar *loop-named-vars*)
412
413 ;;; LETlist-like list being accumulated for current group of bindings.
414 (defvar *loop-vars*)
415
416 ;;; List of declarations being accumulated in parallel with
417 ;;; *LOOP-VARS*.
418 (defvar *loop-declarations*)
419
420 ;;; This is used by LOOP for destructuring binding, if it is doing
421 ;;; that itself. See LOOP-MAKE-VAR.
422 (defvar *loop-desetq-crocks*)
423
424 ;;; list of wrapping forms, innermost first, which go immediately
425 ;;; inside the current set of parallel bindings being accumulated in
426 ;;; *LOOP-VARS*. The wrappers are appended onto a body. E.g., this
427 ;;; list could conceivably have as its value
428 ;;;   ((WITH-OPEN-FILE (G0001 G0002 ...))),
429 ;;; with G0002 being one of the bindings in *LOOP-VARS* (This is why
430 ;;; the wrappers go inside of the variable bindings).
431 (defvar *loop-wrappers*)
432
433 ;;; This accumulates lists of previous values of *LOOP-VARS* and the
434 ;;; other lists above, for each new nesting of bindings. See
435 ;;; LOOP-BIND-BLOCK.
436 (defvar *loop-bind-stack*)
437
438 ;;; list of prologue forms of the loop, accumulated in reverse order
439 (defvar *loop-prologue*)
440
441 (defvar *loop-before-loop*)
442 (defvar *loop-body*)
443 (defvar *loop-after-body*)
444
445 ;;; This is T if we have emitted any body code, so that iteration
446 ;;; driving clauses can be disallowed. This is not strictly the same
447 ;;; as checking *LOOP-BODY*, because we permit some clauses such as
448 ;;; RETURN to not be considered "real" body (so as to permit the user
449 ;;; to "code" an abnormal return value "in loop").
450 (defvar *loop-emitted-body*)
451
452 ;;; list of epilogue forms (supplied by FINALLY generally), accumulated
453 ;;; in reverse order
454 (defvar *loop-epilogue*)
455
456 ;;; list of epilogue forms which are supplied after the above "user"
457 ;;; epilogue. "Normal" termination return values are provide by
458 ;;; putting the return form in here. Normally this is done using
459 ;;; LOOP-EMIT-FINAL-VALUE, q.v.
460 (defvar *loop-after-epilogue*)
461
462 ;;; the "culprit" responsible for supplying a final value from the
463 ;;; loop. This is so LOOP-DISALLOW-AGGREGATE-BOOLEANS can moan about
464 ;;; disallowed anonymous collections.
465 (defvar *loop-final-value-culprit*)
466
467 ;;; If this is true, we are in some branch of a conditional. Some
468 ;;; clauses may be disallowed.
469 (defvar *loop-inside-conditional*)
470
471 ;;; If not NIL, this is a temporary bound around the loop for holding
472 ;;; the temporary value for "it" in things like "when (f) collect it".
473 ;;; It may be used as a supertemporary by some other things.
474 (defvar *loop-when-it-var*)
475
476 ;;; Sometimes we decide we need to fold together parts of the loop,
477 ;;; but some part of the generated iteration code is different for the
478 ;;; first and remaining iterations. This variable will be the
479 ;;; temporary which is the flag used in the loop to tell whether we
480 ;;; are in the first or remaining iterations.
481 (defvar *loop-never-stepped-var*)
482
483 ;;; list of all the value-accumulation descriptor structures in the
484 ;;; loop. See LOOP-GET-COLLECTION-INFO.
485 (defvar *loop-collection-cruft*) ; for multiple COLLECTs (etc.)
486 \f
487 ;;;; code analysis stuff
488
489 (defun loop-constant-fold-if-possible (form &optional expected-type)
490   (let* ((constantp (sb!xc:constantp form))
491          (value (and constantp (sb!int:constant-form-value form))))
492     (when (and constantp expected-type)
493       (unless (sb!xc:typep value expected-type)
494         (loop-warn "~@<The form ~S evaluated to ~S, which was not of ~
495                     the anticipated type ~S.~:@>"
496                    form value expected-type)
497         (setq constantp nil value nil)))
498     (values form constantp value)))
499 \f
500 (sb!int:defmacro-mundanely loop-body (prologue
501                                       before-loop
502                                       main-body
503                                       after-loop
504                                       epilogue)
505   (unless (= (length before-loop) (length after-loop))
506     (error "LOOP-BODY called with non-synched before- and after-loop lists"))
507   ;; All our work is done from these copies, working backwards from the end
508   (let ((rbefore (reverse before-loop))
509         (rafter (reverse after-loop)))
510     ;; Go backwards from the ends of before-loop and after-loop
511     ;; merging all the equivalent forms into the body.
512     (do ()
513         ((or (null rbefore)
514              (not (equal (car rbefore) (car rafter)))))
515       (push (pop rbefore) main-body)
516       (pop rafter))
517     `(tagbody
518         ,@(remove nil prologue)
519         ,@(nreverse (remove nil rbefore))
520       next-loop
521         ,@(remove nil main-body)
522         ,@(nreverse (remove nil rafter))
523         (go next-loop)
524       end-loop
525         ,@(remove nil epilogue))))
526 \f
527 ;;;; loop errors
528
529 (defun loop-context ()
530   (do ((l *loop-source-context* (cdr l)) (new nil (cons (car l) new)))
531       ((eq l (cdr *loop-source-code*)) (nreverse new))))
532
533 (defun loop-error (format-string &rest format-args)
534   (error 'sb!int:simple-program-error
535          :format-control "~?~%current LOOP context:~{ ~S~}."
536          :format-arguments (list format-string format-args (loop-context))))
537
538 (defun loop-warn (format-string &rest format-args)
539   (warn "~?~%current LOOP context:~{ ~S~}."
540         format-string
541         format-args
542         (loop-context)))
543
544 (defun loop-check-data-type (specified-type required-type
545                              &optional (default-type required-type))
546   (if (null specified-type)
547       default-type
548       (multiple-value-bind (a b) (sb!xc:subtypep specified-type required-type)
549         (cond ((not b)
550                (loop-warn "LOOP couldn't verify that ~S is a subtype of the required type ~S."
551                           specified-type required-type))
552               ((not a)
553                (loop-error "The specified data type ~S is not a subtype of ~S."
554                            specified-type required-type)))
555         specified-type)))
556 \f
557 (defun subst-gensyms-for-nil (tree)
558   (declare (special *ignores*))
559   (cond
560     ((null tree) (car (push (gensym "LOOP-IGNORED-VAR-") *ignores*)))
561     ((atom tree) tree)
562     (t (cons (subst-gensyms-for-nil (car tree))
563              (subst-gensyms-for-nil (cdr tree))))))
564
565 (sb!int:defmacro-mundanely loop-destructuring-bind
566     (lambda-list arg-list &rest body)
567   (let ((*ignores* nil))
568     (declare (special *ignores*))
569     (let ((d-var-lambda-list (subst-gensyms-for-nil lambda-list)))
570       `(destructuring-bind ,d-var-lambda-list
571            ,arg-list
572          (declare (ignore ,@*ignores*))
573          ,@body))))
574
575 (defun loop-build-destructuring-bindings (crocks forms)
576   (if crocks
577       `((loop-destructuring-bind ,(car crocks) ,(cadr crocks)
578         ,@(loop-build-destructuring-bindings (cddr crocks) forms)))
579       forms))
580
581 (defun loop-translate (*loop-source-code*
582                        *loop-macro-environment*
583                        *loop-universe*)
584   (let ((*loop-original-source-code* *loop-source-code*)
585         (*loop-source-context* nil)
586         (*loop-vars* nil)
587         (*loop-named-vars* nil)
588         (*loop-declarations* nil)
589         (*loop-desetq-crocks* nil)
590         (*loop-bind-stack* nil)
591         (*loop-prologue* nil)
592         (*loop-wrappers* nil)
593         (*loop-before-loop* nil)
594         (*loop-body* nil)
595         (*loop-emitted-body* nil)
596         (*loop-after-body* nil)
597         (*loop-epilogue* nil)
598         (*loop-after-epilogue* nil)
599         (*loop-final-value-culprit* nil)
600         (*loop-inside-conditional* nil)
601         (*loop-when-it-var* nil)
602         (*loop-never-stepped-var* nil)
603         (*loop-names* nil)
604         (*loop-collection-cruft* nil))
605     (loop-iteration-driver)
606     (loop-bind-block)
607     (let ((answer `(loop-body
608                      ,(nreverse *loop-prologue*)
609                      ,(nreverse *loop-before-loop*)
610                      ,(nreverse *loop-body*)
611                      ,(nreverse *loop-after-body*)
612                      ,(nreconc *loop-epilogue*
613                                (nreverse *loop-after-epilogue*)))))
614       (dolist (entry *loop-bind-stack*)
615         (let ((vars (first entry))
616               (dcls (second entry))
617               (crocks (third entry))
618               (wrappers (fourth entry)))
619           (dolist (w wrappers)
620             (setq answer (append w (list answer))))
621           (when (or vars dcls crocks)
622             (let ((forms (list answer)))
623               ;;(when crocks (push crocks forms))
624               (when dcls (push `(declare ,@dcls) forms))
625               (setq answer `(,(if vars 'let 'locally)
626                              ,vars
627                              ,@(loop-build-destructuring-bindings crocks
628                                                                   forms)))))))
629       (do () (nil)
630         (setq answer `(block ,(pop *loop-names*) ,answer))
631         (unless *loop-names* (return nil)))
632       answer)))
633
634 (defun loop-iteration-driver ()
635   (do ()
636       ((null *loop-source-code*))
637     (let ((keyword (car *loop-source-code*)) (tem nil))
638       (cond ((not (symbolp keyword))
639              (loop-error "~S found where LOOP keyword expected" keyword))
640             (t (setq *loop-source-context* *loop-source-code*)
641                (loop-pop-source)
642                (cond ((setq tem
643                             (loop-lookup-keyword keyword
644                                                  (loop-universe-keywords
645                                                   *loop-universe*)))
646                       ;; It's a "miscellaneous" toplevel LOOP keyword (DO,
647                       ;; COLLECT, NAMED, etc.)
648                       (apply (symbol-function (first tem)) (rest tem)))
649                      ((setq tem
650                             (loop-lookup-keyword keyword
651                                                  (loop-universe-iteration-keywords *loop-universe*)))
652                       (loop-hack-iteration tem))
653                      ((loop-tmember keyword '(and else))
654                       ;; The alternative is to ignore it, i.e. let it go
655                       ;; around to the next keyword...
656                       (loop-error "secondary clause misplaced at top level in LOOP macro: ~S ~S ~S ..."
657                                   keyword
658                                   (car *loop-source-code*)
659                                   (cadr *loop-source-code*)))
660                      (t (loop-error "unknown LOOP keyword: ~S" keyword))))))))
661 \f
662 (defun loop-pop-source ()
663   (if *loop-source-code*
664       (pop *loop-source-code*)
665       (loop-error "LOOP source code ran out when another token was expected.")))
666
667 (defun loop-get-form ()
668   (if *loop-source-code*
669       (loop-pop-source)
670       (loop-error "LOOP code ran out where a form was expected.")))
671
672 (defun loop-get-compound-form ()
673   (let ((form (loop-get-form)))
674     (unless (consp form)
675       (loop-error "A compound form was expected, but ~S found." form))
676     form))
677
678 (defun loop-get-progn ()
679   (do ((forms (list (loop-get-compound-form))
680               (cons (loop-get-compound-form) forms))
681        (nextform (car *loop-source-code*)
682                  (car *loop-source-code*)))
683       ((atom nextform)
684        (if (null (cdr forms)) (car forms) (cons 'progn (nreverse forms))))))
685
686 (defun loop-construct-return (form)
687   `(return-from ,(car *loop-names*) ,form))
688
689 (defun loop-pseudo-body (form)
690   (cond ((or *loop-emitted-body* *loop-inside-conditional*)
691          (push form *loop-body*))
692         (t (push form *loop-before-loop*) (push form *loop-after-body*))))
693
694 (defun loop-emit-body (form)
695   (setq *loop-emitted-body* t)
696   (loop-pseudo-body form))
697
698 (defun loop-emit-final-value (&optional (form nil form-supplied-p))
699   (when form-supplied-p
700     (push (loop-construct-return form) *loop-after-epilogue*))
701   (setq *loop-final-value-culprit* (car *loop-source-context*)))
702
703 (defun loop-disallow-conditional (&optional kwd)
704   (when *loop-inside-conditional*
705     (loop-error "~:[This LOOP~;The LOOP ~:*~S~] clause is not permitted inside a conditional." kwd)))
706
707 (defun loop-disallow-anonymous-collectors ()
708   (when (find-if-not 'loop-collector-name *loop-collection-cruft*)
709     (loop-error "This LOOP clause is not permitted with anonymous collectors.")))
710
711 (defun loop-disallow-aggregate-booleans ()
712   (when (loop-tmember *loop-final-value-culprit* '(always never thereis))
713     (loop-error "This anonymous collection LOOP clause is not permitted with aggregate booleans.")))
714 \f
715 ;;;; loop types
716
717 (defun loop-typed-init (data-type &optional step-var-p)
718   (cond ((null data-type)
719          nil)
720         ((sb!xc:subtypep data-type 'number)
721          (let ((init (if step-var-p 1 0)))
722            (flet ((like (&rest types)
723                     (coerce init (find-if (lambda (type)
724                                             (sb!xc:subtypep data-type type))
725                                           types))))
726              (cond ((sb!xc:subtypep data-type 'float)
727                     (like 'single-float 'double-float
728                           'short-float 'long-float 'float))
729                    ((sb!xc:subtypep data-type '(complex float))
730                     (like '(complex single-float)
731                           '(complex double-float)
732                           '(complex short-float)
733                           '(complex long-float)
734                           '(complex float)))
735                    (t
736                     init)))))
737         ((sb!xc:subtypep data-type 'vector)
738          (let ((ctype (sb!kernel:specifier-type data-type)))
739            (when (sb!kernel:array-type-p ctype)
740              (let ((etype (sb!kernel:type-*-to-t
741                            (sb!kernel:array-type-specialized-element-type ctype))))
742                (make-array 0 :element-type (sb!kernel:type-specifier etype))))))
743         ((sb!xc:typep #\x data-type)
744          #\x)
745         (t
746          nil)))
747
748 (defun loop-optional-type (&optional variable)
749   ;; No variable specified implies that no destructuring is permissible.
750   (and *loop-source-code* ; Don't get confused by NILs..
751        (let ((z (car *loop-source-code*)))
752          (cond ((loop-tequal z 'of-type)
753                 ;; This is the syntactically unambigous form in that
754                 ;; the form of the type specifier does not matter.
755                 ;; Also, it is assumed that the type specifier is
756                 ;; unambiguously, and without need of translation, a
757                 ;; common lisp type specifier or pattern (matching the
758                 ;; variable) thereof.
759                 (loop-pop-source)
760                 (loop-pop-source))
761
762                ((symbolp z)
763                 ;; This is the (sort of) "old" syntax, even though we
764                 ;; didn't used to support all of these type symbols.
765                 (let ((type-spec (or (gethash z
766                                               (loop-universe-type-symbols
767                                                *loop-universe*))
768                                      (gethash (symbol-name z)
769                                               (loop-universe-type-keywords
770                                                *loop-universe*)))))
771                   (when type-spec
772                     (loop-pop-source)
773                     type-spec)))
774                (t
775                 ;; This is our sort-of old syntax. But this is only
776                 ;; valid for when we are destructuring, so we will be
777                 ;; compulsive (should we really be?) and require that
778                 ;; we in fact be doing variable destructuring here. We
779                 ;; must translate the old keyword pattern typespec
780                 ;; into a fully-specified pattern of real type
781                 ;; specifiers here.
782                 (if (consp variable)
783                     (unless (consp z)
784                      (loop-error
785                         "~S found where a LOOP keyword, LOOP type keyword, or LOOP type pattern expected"
786                         z))
787                     (loop-error "~S found where a LOOP keyword or LOOP type keyword expected" z))
788                 (loop-pop-source)
789                 (labels ((translate (k v)
790                            (cond ((null k) nil)
791                                  ((atom k)
792                                   (replicate
793                                     (or (gethash k
794                                                  (loop-universe-type-symbols
795                                                   *loop-universe*))
796                                         (gethash (symbol-name k)
797                                                  (loop-universe-type-keywords
798                                                   *loop-universe*))
799                                         (loop-error
800                                           "The destructuring type pattern ~S contains the unrecognized type keyword ~S."
801                                           z k))
802                                     v))
803                                  ((atom v)
804                                   (loop-error
805                                     "The destructuring type pattern ~S doesn't match the variable pattern ~S."
806                                     z variable))
807                                  (t (cons (translate (car k) (car v))
808                                           (translate (cdr k) (cdr v))))))
809                          (replicate (typ v)
810                            (if (atom v)
811                                typ
812                                (cons (replicate typ (car v))
813                                      (replicate typ (cdr v))))))
814                   (translate z variable)))))))
815 \f
816 ;;;; loop variables
817
818 (defun loop-bind-block ()
819   (when (or *loop-vars* *loop-declarations* *loop-wrappers*)
820     (push (list (nreverse *loop-vars*)
821                 *loop-declarations*
822                 *loop-desetq-crocks*
823                 *loop-wrappers*)
824           *loop-bind-stack*)
825     (setq *loop-vars* nil
826           *loop-declarations* nil
827           *loop-desetq-crocks* nil
828           *loop-wrappers* nil)))
829
830 (defun loop-var-p (name)
831   (do ((entry *loop-bind-stack* (cdr entry)))
832       (nil)
833     (cond
834       ((null entry) (return nil))
835       ((assoc name (caar entry) :test #'eq) (return t)))))
836
837 (defun loop-make-var (name initialization dtype &optional step-var-p)
838   (cond ((null name)
839          (setq name (gensym "LOOP-IGNORE-"))
840          (push (list name initialization) *loop-vars*)
841          (push `(ignore ,name) *loop-declarations*)
842          (loop-declare-var name dtype))
843         ((atom name)
844          (when (or (assoc name *loop-vars*)
845                    (loop-var-p name))
846            (loop-error "duplicated variable ~S in a LOOP binding" name))
847          (unless (symbolp name)
848            (loop-error "bad variable ~S somewhere in LOOP" name))
849          (loop-declare-var name dtype step-var-p initialization)
850          ;; We use ASSOC on this list to check for duplications (above),
851          ;; so don't optimize out this list:
852          (push (list name (or initialization (loop-typed-init dtype step-var-p)))
853                *loop-vars*))
854         (initialization
855          (let ((newvar (gensym "LOOP-DESTRUCTURE-")))
856            (loop-declare-var name dtype)
857            (push (list newvar initialization) *loop-vars*)
858            ;; *LOOP-DESETQ-CROCKS* gathered in reverse order.
859            (setq *loop-desetq-crocks*
860                  (list* name newvar *loop-desetq-crocks*))))
861         (t (let ((tcar nil) (tcdr nil))
862              (if (atom dtype) (setq tcar (setq tcdr dtype))
863                  (setq tcar (car dtype) tcdr (cdr dtype)))
864              (loop-make-var (car name) nil tcar)
865              (loop-make-var (cdr name) nil tcdr))))
866   name)
867
868 (defun loop-declare-var (name dtype &optional step-var-p initialization)
869   (cond ((or (null name) (null dtype) (eq dtype t)) nil)
870         ((symbolp name)
871          (unless (or (sb!xc:subtypep t dtype)
872                      (and (eq (find-package :cl) (symbol-package name))
873                           (eq :special (sb!int:info :variable :kind name))))
874            (let ((dtype (if initialization
875                             dtype
876                             (let ((init (loop-typed-init dtype step-var-p)))
877                               (if (sb!xc:typep init dtype)
878                                   dtype
879                                   `(or ,(type-of init) ,dtype))))))
880              (push `(type ,dtype ,name) *loop-declarations*))))
881         ((consp name)
882          (cond ((consp dtype)
883                 (loop-declare-var (car name) (car dtype))
884                 (loop-declare-var (cdr name) (cdr dtype)))
885                (t (loop-declare-var (car name) dtype)
886                   (loop-declare-var (cdr name) dtype))))
887         (t (error "invalid LOOP variable passed in: ~S" name))))
888
889 (defun loop-maybe-bind-form (form data-type)
890   (if (constantp form)
891       form
892       (loop-make-var (gensym "LOOP-BIND-") form data-type)))
893 \f
894 (defun loop-do-if (for negatep)
895   (let ((form (loop-get-form))
896         (*loop-inside-conditional* t)
897         (it-p nil)
898         (first-clause-p t))
899     (flet ((get-clause (for)
900              (do ((body nil)) (nil)
901                (let ((key (car *loop-source-code*)) (*loop-body* nil) data)
902                  (cond ((not (symbolp key))
903                         (loop-error
904                           "~S found where keyword expected getting LOOP clause after ~S"
905                           key for))
906                        (t (setq *loop-source-context* *loop-source-code*)
907                           (loop-pop-source)
908                           (when (and (loop-tequal (car *loop-source-code*) 'it)
909                                      first-clause-p)
910                             (setq *loop-source-code*
911                                   (cons (or it-p
912                                             (setq it-p
913                                                   (loop-when-it-var)))
914                                         (cdr *loop-source-code*))))
915                           (cond ((or (not (setq data (loop-lookup-keyword
916                                                        key (loop-universe-keywords *loop-universe*))))
917                                      (progn (apply (symbol-function (car data))
918                                                    (cdr data))
919                                             (null *loop-body*)))
920                                  (loop-error
921                                    "~S does not introduce a LOOP clause that can follow ~S."
922                                    key for))
923                                 (t (setq body (nreconc *loop-body* body)))))))
924                (setq first-clause-p nil)
925                (if (loop-tequal (car *loop-source-code*) :and)
926                    (loop-pop-source)
927                    (return (if (cdr body)
928                                `(progn ,@(nreverse body))
929                                (car body)))))))
930       (let ((then (get-clause for))
931             (else (when (loop-tequal (car *loop-source-code*) :else)
932                     (loop-pop-source)
933                     (list (get-clause :else)))))
934         (when (loop-tequal (car *loop-source-code*) :end)
935           (loop-pop-source))
936         (when it-p (setq form `(setq ,it-p ,form)))
937         (loop-pseudo-body
938           `(if ,(if negatep `(not ,form) form)
939                ,then
940                ,@else))))))
941
942 (defun loop-do-initially ()
943   (loop-disallow-conditional :initially)
944   (push (loop-get-progn) *loop-prologue*))
945
946 (defun loop-do-finally ()
947   (loop-disallow-conditional :finally)
948   (push (loop-get-progn) *loop-epilogue*))
949
950 (defun loop-do-do ()
951   (loop-emit-body (loop-get-progn)))
952
953 (defun loop-do-named ()
954   (let ((name (loop-pop-source)))
955     (unless (symbolp name)
956       (loop-error "~S is an invalid name for your LOOP" name))
957     (when (or *loop-before-loop* *loop-body* *loop-after-epilogue* *loop-inside-conditional*)
958       (loop-error "The NAMED ~S clause occurs too late." name))
959     (when *loop-names*
960       (loop-error "You may only use one NAMED clause in your loop: NAMED ~S ... NAMED ~S."
961                   (car *loop-names*) name))
962     (setq *loop-names* (list name))))
963
964 (defun loop-do-return ()
965   (loop-emit-body (loop-construct-return (loop-get-form))))
966 \f
967 ;;;; value accumulation: LIST
968
969 (defstruct (loop-collector
970             (:copier nil)
971             (:predicate nil))
972   name
973   class
974   (history nil)
975   (tempvars nil)
976   dtype
977   (data nil)) ;collector-specific data
978
979 (defun loop-get-collection-info (collector class default-type)
980   (let ((form (loop-get-form))
981         (name (when (loop-tequal (car *loop-source-code*) 'into)
982                 (loop-pop-source)
983                 (loop-pop-source))))
984     (when (not (symbolp name))
985       (loop-error "The value accumulation recipient name, ~S, is not a symbol." name))
986     (unless name
987       (loop-disallow-aggregate-booleans))
988     (let ((dtype (or (loop-optional-type) default-type))
989           (cruft (find (the symbol name) *loop-collection-cruft*
990                        :key #'loop-collector-name)))
991       (cond ((not cruft)
992              (when (and name (loop-var-p name))
993                (loop-error "Variable ~S in INTO clause is a duplicate" name))
994              (push (setq cruft (make-loop-collector
995                                  :name name :class class
996                                  :history (list collector) :dtype dtype))
997                    *loop-collection-cruft*))
998             (t (unless (eq (loop-collector-class cruft) class)
999                  (loop-error
1000                    "incompatible kinds of LOOP value accumulation specified for collecting~@
1001                     ~:[as the value of the LOOP~;~:*INTO ~S~]: ~S and ~S"
1002                    name (car (loop-collector-history cruft)) collector))
1003                (unless (equal dtype (loop-collector-dtype cruft))
1004                  (loop-warn
1005                    "unequal datatypes specified in different LOOP value accumulations~@
1006                    into ~S: ~S and ~S"
1007                    name dtype (loop-collector-dtype cruft))
1008                  (when (eq (loop-collector-dtype cruft) t)
1009                    (setf (loop-collector-dtype cruft) dtype)))
1010                (push collector (loop-collector-history cruft))))
1011       (values cruft form))))
1012
1013 (defun loop-list-collection (specifically)      ; NCONC, LIST, or APPEND
1014   (multiple-value-bind (lc form)
1015       (loop-get-collection-info specifically 'list 'list)
1016     (let ((tempvars (loop-collector-tempvars lc)))
1017       (unless tempvars
1018         (setf (loop-collector-tempvars lc)
1019               (setq tempvars (list* (gensym "LOOP-LIST-HEAD-")
1020                                     (gensym "LOOP-LIST-TAIL-")
1021                                     (and (loop-collector-name lc)
1022                                          (list (loop-collector-name lc))))))
1023         (push `(with-loop-list-collection-head ,tempvars) *loop-wrappers*)
1024         (unless (loop-collector-name lc)
1025           (loop-emit-final-value `(loop-collect-answer ,(car tempvars)
1026                                                        ,@(cddr tempvars)))))
1027       (ecase specifically
1028         (list (setq form `(list ,form)))
1029         (nconc nil)
1030         (append (unless (and (consp form) (eq (car form) 'list))
1031                   (setq form `(copy-list ,form)))))
1032       (loop-emit-body `(loop-collect-rplacd ,tempvars ,form)))))
1033 \f
1034 ;;;; value accumulation: MAX, MIN, SUM, COUNT
1035
1036 (defun loop-sum-collection (specifically required-type default-type);SUM, COUNT
1037   (multiple-value-bind (lc form)
1038       (loop-get-collection-info specifically 'sum default-type)
1039     (loop-check-data-type (loop-collector-dtype lc) required-type)
1040     (let ((tempvars (loop-collector-tempvars lc)))
1041       (unless tempvars
1042         (setf (loop-collector-tempvars lc)
1043               (setq tempvars (list (loop-make-var
1044                                      (or (loop-collector-name lc)
1045                                          (gensym "LOOP-SUM-"))
1046                                      nil (loop-collector-dtype lc)))))
1047         (unless (loop-collector-name lc)
1048           (loop-emit-final-value (car (loop-collector-tempvars lc)))))
1049       (loop-emit-body
1050         (if (eq specifically 'count)
1051             `(when ,form
1052                (setq ,(car tempvars)
1053                      (1+ ,(car tempvars))))
1054             `(setq ,(car tempvars)
1055                    (+ ,(car tempvars)
1056                       ,form)))))))
1057
1058 (defun loop-maxmin-collection (specifically)
1059   (multiple-value-bind (lc form)
1060       (loop-get-collection-info specifically 'maxmin 'real)
1061     (loop-check-data-type (loop-collector-dtype lc) 'real)
1062     (let ((data (loop-collector-data lc)))
1063       (unless data
1064         (setf (loop-collector-data lc)
1065               (setq data (make-loop-minimax
1066                            (or (loop-collector-name lc)
1067                                (gensym "LOOP-MAXMIN-"))
1068                            (loop-collector-dtype lc))))
1069         (unless (loop-collector-name lc)
1070           (loop-emit-final-value (loop-minimax-answer-variable data))))
1071       (loop-note-minimax-operation specifically data)
1072       (push `(with-minimax-value ,data) *loop-wrappers*)
1073       (loop-emit-body `(loop-accumulate-minimax-value ,data
1074                                                       ,specifically
1075                                                       ,form)))))
1076 \f
1077 ;;;; value accumulation: aggregate booleans
1078
1079 ;;; handling the ALWAYS and NEVER loop keywords
1080 ;;;
1081 ;;; Under ANSI these are not permitted to appear under conditionalization.
1082 (defun loop-do-always (restrictive negate)
1083   (let ((form (loop-get-form)))
1084     (when restrictive (loop-disallow-conditional))
1085     (loop-disallow-anonymous-collectors)
1086     (loop-emit-body `(,(if negate 'when 'unless) ,form
1087                       ,(loop-construct-return nil)))
1088     (loop-emit-final-value t)))
1089
1090 ;;; handling the THEREIS loop keyword
1091 ;;;
1092 ;;; Under ANSI this is not permitted to appear under conditionalization.
1093 (defun loop-do-thereis (restrictive)
1094   (when restrictive (loop-disallow-conditional))
1095   (loop-disallow-anonymous-collectors)
1096   (loop-emit-final-value)
1097   (loop-emit-body `(when (setq ,(loop-when-it-var) ,(loop-get-form))
1098                     ,(loop-construct-return *loop-when-it-var*))))
1099 \f
1100 (defun loop-do-while (negate kwd &aux (form (loop-get-form)))
1101   (loop-disallow-conditional kwd)
1102   (loop-pseudo-body `(,(if negate 'when 'unless) ,form (go end-loop))))
1103
1104 (defun loop-do-repeat ()
1105   (loop-disallow-conditional :repeat)
1106   (let ((form (loop-get-form))
1107         (type 'integer))
1108     (let ((var (loop-make-var (gensym "LOOP-REPEAT-") `(ceiling ,form) type)))
1109       (push `(if (<= ,var 0) (go end-loop) (decf ,var)) *loop-before-loop*)
1110       (push `(if (<= ,var 0) (go end-loop) (decf ,var)) *loop-after-body*)
1111       ;; FIXME: What should
1112       ;;   (loop count t into a
1113       ;;         repeat 3
1114       ;;         count t into b
1115       ;;         finally (return (list a b)))
1116       ;; return: (3 3) or (4 3)? PUSHes above are for the former
1117       ;; variant, L-P-B below for the latter.
1118       #+nil (loop-pseudo-body `(when (minusp (decf ,var)) (go end-loop))))))
1119
1120 (defun loop-do-with ()
1121   (loop-disallow-conditional :with)
1122   (do ((var) (val) (dtype))
1123       (nil)
1124     (setq var (loop-pop-source)
1125           dtype (loop-optional-type var)
1126           val (cond ((loop-tequal (car *loop-source-code*) :=)
1127                      (loop-pop-source)
1128                      (loop-get-form))
1129                     (t nil)))
1130     (when (and var (loop-var-p var))
1131       (loop-error "Variable ~S has already been used" var))
1132     (loop-make-var var val dtype)
1133     (if (loop-tequal (car *loop-source-code*) :and)
1134         (loop-pop-source)
1135         (return (loop-bind-block)))))
1136 \f
1137 ;;;; the iteration driver
1138
1139 (defun loop-hack-iteration (entry)
1140   (flet ((make-endtest (list-of-forms)
1141            (cond ((null list-of-forms) nil)
1142                  ((member t list-of-forms) '(go end-loop))
1143                  (t `(when ,(if (null (cdr (setq list-of-forms
1144                                                  (nreverse list-of-forms))))
1145                                 (car list-of-forms)
1146                                 (cons 'or list-of-forms))
1147                        (go end-loop))))))
1148     (do ((pre-step-tests nil)
1149          (steps nil)
1150          (post-step-tests nil)
1151          (pseudo-steps nil)
1152          (pre-loop-pre-step-tests nil)
1153          (pre-loop-steps nil)
1154          (pre-loop-post-step-tests nil)
1155          (pre-loop-pseudo-steps nil)
1156          (tem) (data))
1157         (nil)
1158       ;; Note that we collect endtests in reverse order, but steps in correct
1159       ;; order. MAKE-ENDTEST does the nreverse for us.
1160       (setq tem (setq data
1161                       (apply (symbol-function (first entry)) (rest entry))))
1162       (and (car tem) (push (car tem) pre-step-tests))
1163       (setq steps (nconc steps (copy-list (car (setq tem (cdr tem))))))
1164       (and (car (setq tem (cdr tem))) (push (car tem) post-step-tests))
1165       (setq pseudo-steps
1166             (nconc pseudo-steps (copy-list (car (setq tem (cdr tem))))))
1167       (setq tem (cdr tem))
1168       (when *loop-emitted-body*
1169         (loop-error "iteration in LOOP follows body code"))
1170       (unless tem (setq tem data))
1171       (when (car tem) (push (car tem) pre-loop-pre-step-tests))
1172       ;; FIXME: This (SETF FOO (NCONC FOO BAR)) idiom appears often enough
1173       ;; that it might be worth making it into an NCONCF macro.
1174       (setq pre-loop-steps
1175             (nconc pre-loop-steps (copy-list (car (setq tem (cdr tem))))))
1176       (when (car (setq tem (cdr tem)))
1177         (push (car tem) pre-loop-post-step-tests))
1178       (setq pre-loop-pseudo-steps
1179             (nconc pre-loop-pseudo-steps (copy-list (cadr tem))))
1180       (unless (loop-tequal (car *loop-source-code*) :and)
1181         (setq *loop-before-loop*
1182               (list* (loop-make-desetq pre-loop-pseudo-steps)
1183                      (make-endtest pre-loop-post-step-tests)
1184                      (loop-make-psetq pre-loop-steps)
1185                      (make-endtest pre-loop-pre-step-tests)
1186                      *loop-before-loop*))
1187         (setq *loop-after-body*
1188               (list* (loop-make-desetq pseudo-steps)
1189                      (make-endtest post-step-tests)
1190                      (loop-make-psetq steps)
1191                      (make-endtest pre-step-tests)
1192                      *loop-after-body*))
1193         (loop-bind-block)
1194         (return nil))
1195       (loop-pop-source)))) ; Flush the "AND".
1196 \f
1197 ;;;; main iteration drivers
1198
1199 ;;; FOR variable keyword ..args..
1200 (defun loop-do-for ()
1201   (let* ((var (loop-pop-source))
1202          (data-type (loop-optional-type var))
1203          (keyword (loop-pop-source))
1204          (first-arg nil)
1205          (tem nil))
1206     (setq first-arg (loop-get-form))
1207     (unless (and (symbolp keyword)
1208                  (setq tem (loop-lookup-keyword
1209                              keyword
1210                              (loop-universe-for-keywords *loop-universe*))))
1211       (loop-error "~S is an unknown keyword in FOR or AS clause in LOOP."
1212                   keyword))
1213     (apply (car tem) var first-arg data-type (cdr tem))))
1214
1215 (defun loop-when-it-var ()
1216   (or *loop-when-it-var*
1217       (setq *loop-when-it-var*
1218             (loop-make-var (gensym "LOOP-IT-") nil nil))))
1219 \f
1220 ;;;; various FOR/AS subdispatches
1221
1222 ;;; ANSI "FOR x = y [THEN z]" is sort of like the old Genera one when
1223 ;;; the THEN is omitted (other than being more stringent in its
1224 ;;; placement), and like the old "FOR x FIRST y THEN z" when the THEN
1225 ;;; is present. I.e., the first initialization occurs in the loop body
1226 ;;; (first-step), not in the variable binding phase.
1227 (defun loop-ansi-for-equals (var val data-type)
1228   (loop-make-var var nil data-type)
1229   (cond ((loop-tequal (car *loop-source-code*) :then)
1230          ;; Then we are the same as "FOR x FIRST y THEN z".
1231          (loop-pop-source)
1232          `(() (,var ,(loop-get-form)) () ()
1233            () (,var ,val) () ()))
1234         (t ;; We are the same as "FOR x = y".
1235          `(() (,var ,val) () ()))))
1236
1237 (defun loop-for-across (var val data-type)
1238   (loop-make-var var nil data-type)
1239   (let ((vector-var (gensym "LOOP-ACROSS-VECTOR-"))
1240         (index-var (gensym "LOOP-ACROSS-INDEX-")))
1241     (multiple-value-bind (vector-form constantp vector-value)
1242         (loop-constant-fold-if-possible val 'vector)
1243       (loop-make-var
1244         vector-var vector-form
1245         (if (and (consp vector-form) (eq (car vector-form) 'the))
1246             (cadr vector-form)
1247             'vector))
1248       (loop-make-var index-var 0 'fixnum)
1249       (let* ((length 0)
1250              (length-form (cond ((not constantp)
1251                                  (let ((v (gensym "LOOP-ACROSS-LIMIT-")))
1252                                    (push `(setq ,v (length ,vector-var))
1253                                          *loop-prologue*)
1254                                    (loop-make-var v 0 'fixnum)))
1255                                 (t (setq length (length vector-value)))))
1256              (first-test `(>= ,index-var ,length-form))
1257              (other-test first-test)
1258              (step `(,var (aref ,vector-var ,index-var)))
1259              (pstep `(,index-var (1+ ,index-var))))
1260         (declare (fixnum length))
1261         (when constantp
1262           (setq first-test (= length 0))
1263           (when (<= length 1)
1264             (setq other-test t)))
1265         `(,other-test ,step () ,pstep
1266           ,@(and (not (eq first-test other-test))
1267                  `(,first-test ,step () ,pstep)))))))
1268 \f
1269 ;;;; list iteration
1270
1271 (defun loop-list-step (listvar)
1272   ;; We are not equipped to analyze whether 'FOO is the same as #'FOO
1273   ;; here in any sensible fashion, so let's give an obnoxious warning
1274   ;; whenever 'FOO is used as the stepping function.
1275   ;;
1276   ;; While a Discerning Compiler may deal intelligently with
1277   ;; (FUNCALL 'FOO ...), not recognizing FOO may defeat some LOOP
1278   ;; optimizations.
1279   (let ((stepper (cond ((loop-tequal (car *loop-source-code*) :by)
1280                         (loop-pop-source)
1281                         (loop-get-form))
1282                        (t '(function cdr)))))
1283     (cond ((and (consp stepper) (eq (car stepper) 'quote))
1284            (loop-warn "Use of QUOTE around stepping function in LOOP will be left verbatim.")
1285            `(funcall ,stepper ,listvar))
1286           ((and (consp stepper) (eq (car stepper) 'function))
1287            (list (cadr stepper) listvar))
1288           (t
1289            `(funcall ,(loop-make-var (gensym "LOOP-FN-") stepper 'function)
1290                      ,listvar)))))
1291
1292 (defun loop-for-on (var val data-type)
1293   (multiple-value-bind (list constantp list-value)
1294       (loop-constant-fold-if-possible val)
1295     (let ((listvar var))
1296       (cond ((and var (symbolp var))
1297              (loop-make-var var list data-type))
1298             (t
1299              (loop-make-var (setq listvar (gensym)) list 't)
1300              (loop-make-var var nil data-type)))
1301       (let ((list-step (loop-list-step listvar)))
1302         (let* ((first-endtest
1303                 ;; mysterious comment from original CMU CL sources:
1304                 ;;   the following should use `atom' instead of `endp',
1305                 ;;   per [bug2428]
1306                 `(atom ,listvar))
1307                (other-endtest first-endtest))
1308           (when (and constantp (listp list-value))
1309             (setq first-endtest (null list-value)))
1310           (cond ((eq var listvar)
1311                  ;; The contour of the loop is different because we
1312                  ;; use the user's variable...
1313                  `(() (,listvar ,list-step)
1314                    ,other-endtest () () () ,first-endtest ()))
1315                 (t (let ((step `(,var ,listvar))
1316                          (pseudo `(,listvar ,list-step)))
1317                      `(,other-endtest ,step () ,pseudo
1318                        ,@(and (not (eq first-endtest other-endtest))
1319                               `(,first-endtest ,step () ,pseudo)))))))))))
1320
1321 (defun loop-for-in (var val data-type)
1322   (multiple-value-bind (list constantp list-value)
1323       (loop-constant-fold-if-possible val)
1324     (let ((listvar (gensym "LOOP-LIST-")))
1325       (loop-make-var var nil data-type)
1326       (loop-make-var listvar list 'list)
1327       (let ((list-step (loop-list-step listvar)))
1328         (let* ((first-endtest `(endp ,listvar))
1329                (other-endtest first-endtest)
1330                (step `(,var (car ,listvar)))
1331                (pseudo-step `(,listvar ,list-step)))
1332           (when (and constantp (listp list-value))
1333             (setq first-endtest (null list-value)))
1334           `(,other-endtest ,step () ,pseudo-step
1335             ,@(and (not (eq first-endtest other-endtest))
1336                    `(,first-endtest ,step () ,pseudo-step))))))))
1337 \f
1338 ;;;; iteration paths
1339
1340 (defstruct (loop-path
1341             (:copier nil)
1342             (:predicate nil))
1343   names
1344   preposition-groups
1345   inclusive-permitted
1346   function
1347   user-data)
1348
1349 (defun add-loop-path (names function universe
1350                       &key preposition-groups inclusive-permitted user-data)
1351   (declare (type loop-universe universe))
1352   (unless (listp names)
1353     (setq names (list names)))
1354   (let ((ht (loop-universe-path-keywords universe))
1355         (lp (make-loop-path
1356               :names (mapcar #'symbol-name names)
1357               :function function
1358               :user-data user-data
1359               :preposition-groups (mapcar (lambda (x)
1360                                             (if (listp x) x (list x)))
1361                                           preposition-groups)
1362               :inclusive-permitted inclusive-permitted)))
1363     (dolist (name names)
1364       (setf (gethash (symbol-name name) ht) lp))
1365     lp))
1366 \f
1367 ;;; Note: Path functions are allowed to use LOOP-MAKE-VAR, hack
1368 ;;; the prologue, etc.
1369 (defun loop-for-being (var val data-type)
1370   ;; FOR var BEING each/the pathname prep-phrases using-stuff... each/the =
1371   ;; EACH or THE. Not clear if it is optional, so I guess we'll warn.
1372   (let ((path nil)
1373         (data nil)
1374         (inclusive nil)
1375         (stuff nil)
1376         (initial-prepositions nil))
1377     (cond ((loop-tmember val '(:each :the)) (setq path (loop-pop-source)))
1378           ((loop-tequal (car *loop-source-code*) :and)
1379            (loop-pop-source)
1380            (setq inclusive t)
1381            (unless (loop-tmember (car *loop-source-code*)
1382                                  '(:its :each :his :her))
1383              (loop-error "~S was found where ITS or EACH expected in LOOP iteration path syntax."
1384                          (car *loop-source-code*)))
1385            (loop-pop-source)
1386            (setq path (loop-pop-source))
1387            (setq initial-prepositions `((:in ,val))))
1388           (t (loop-error "unrecognizable LOOP iteration path syntax: missing EACH or THE?")))
1389     (cond ((not (symbolp path))
1390            (loop-error
1391             "~S was found where a LOOP iteration path name was expected."
1392             path))
1393           ((not (setq data (loop-lookup-keyword path (loop-universe-path-keywords *loop-universe*))))
1394            (loop-error "~S is not the name of a LOOP iteration path." path))
1395           ((and inclusive (not (loop-path-inclusive-permitted data)))
1396            (loop-error "\"Inclusive\" iteration is not possible with the ~S LOOP iteration path." path)))
1397     (let ((fun (loop-path-function data))
1398           (preps (nconc initial-prepositions
1399                         (loop-collect-prepositional-phrases
1400                          (loop-path-preposition-groups data)
1401                          t)))
1402           (user-data (loop-path-user-data data)))
1403       (when (symbolp fun) (setq fun (symbol-function fun)))
1404       (setq stuff (if inclusive
1405                       (apply fun var data-type preps :inclusive t user-data)
1406                       (apply fun var data-type preps user-data))))
1407     (when *loop-named-vars*
1408       (loop-error "Unused USING vars: ~S." *loop-named-vars*))
1409     ;; STUFF is now (bindings prologue-forms . stuff-to-pass-back).
1410     ;; Protect the system from the user and the user from himself.
1411     (unless (member (length stuff) '(6 10))
1412       (loop-error "Value passed back by LOOP iteration path function for path ~S has invalid length."
1413                   path))
1414     (do ((l (car stuff) (cdr l)) (x)) ((null l))
1415       (if (atom (setq x (car l)))
1416           (loop-make-var x nil nil)
1417           (loop-make-var (car x) (cadr x) (caddr x))))
1418     (setq *loop-prologue* (nconc (reverse (cadr stuff)) *loop-prologue*))
1419     (cddr stuff)))
1420 \f
1421 (defun loop-named-var (name)
1422   (let ((tem (loop-tassoc name *loop-named-vars*)))
1423     (declare (list tem))
1424     (cond ((null tem) (values (gensym) nil))
1425           (t (setq *loop-named-vars* (delete tem *loop-named-vars*))
1426              (values (cdr tem) t)))))
1427
1428 (defun loop-collect-prepositional-phrases (preposition-groups
1429                                            &optional
1430                                            using-allowed
1431                                            initial-phrases)
1432   (flet ((in-group-p (x group) (car (loop-tmember x group))))
1433     (do ((token nil)
1434          (prepositional-phrases initial-phrases)
1435          (this-group nil nil)
1436          (this-prep nil nil)
1437          (disallowed-prepositions
1438            (mapcan (lambda (x)
1439                      (copy-list
1440                       (find (car x) preposition-groups :test #'in-group-p)))
1441                    initial-phrases))
1442          (used-prepositions (mapcar #'car initial-phrases)))
1443         ((null *loop-source-code*) (nreverse prepositional-phrases))
1444       (declare (symbol this-prep))
1445       (setq token (car *loop-source-code*))
1446       (dolist (group preposition-groups)
1447         (when (setq this-prep (in-group-p token group))
1448           (return (setq this-group group))))
1449       (cond (this-group
1450              (when (member this-prep disallowed-prepositions)
1451                (loop-error
1452                  (if (member this-prep used-prepositions)
1453                      "A ~S prepositional phrase occurs multiply for some LOOP clause."
1454                      "Preposition ~S was used when some other preposition has subsumed it.")
1455                  token))
1456              (setq used-prepositions (if (listp this-group)
1457                                          (append this-group used-prepositions)
1458                                          (cons this-group used-prepositions)))
1459              (loop-pop-source)
1460              (push (list this-prep (loop-get-form)) prepositional-phrases))
1461             ((and using-allowed (loop-tequal token 'using))
1462              (loop-pop-source)
1463              (do ((z (loop-pop-source) (loop-pop-source)) (tem)) (nil)
1464                (when (cadr z)
1465                  (if (setq tem (loop-tassoc (car z) *loop-named-vars*))
1466                      (loop-error
1467                        "The variable substitution for ~S occurs twice in a USING phrase,~@
1468                         with ~S and ~S."
1469                        (car z) (cadr z) (cadr tem))
1470                      (push (cons (car z) (cadr z)) *loop-named-vars*)))
1471                (when (or (null *loop-source-code*)
1472                          (symbolp (car *loop-source-code*)))
1473                  (return nil))))
1474             (t (return (nreverse prepositional-phrases)))))))
1475 \f
1476 ;;;; master sequencer function
1477
1478 (defun loop-sequencer (indexv indexv-type
1479                        variable variable-type
1480                        sequence-variable sequence-type
1481                        step-hack default-top
1482                        prep-phrases)
1483    (let ((endform nil) ; form (constant or variable) with limit value
1484          (sequencep nil) ; T if sequence arg has been provided
1485          (testfn nil) ; endtest function
1486          (test nil) ; endtest form
1487          (stepby (1+ (or (loop-typed-init indexv-type) 0))) ; our increment
1488          (stepby-constantp t)
1489          (step nil) ; step form
1490          (dir nil) ; direction of stepping: NIL, :UP, :DOWN
1491          (inclusive-iteration nil) ; T if include last index
1492          (start-given nil) ; T when prep phrase has specified start
1493          (start-value nil)
1494          (start-constantp nil)
1495          (limit-given nil) ; T when prep phrase has specified end
1496          (limit-constantp nil)
1497          (limit-value nil)
1498          )
1499      (flet ((assert-index-for-arithmetic (index)
1500               (unless (atom index)
1501                 (loop-error "Arithmetic index must be an atom."))))
1502        (when variable (loop-make-var variable nil variable-type))
1503        (do ((l prep-phrases (cdr l)) (prep) (form) (odir)) ((null l))
1504          (setq prep (caar l) form (cadar l))
1505          (case prep
1506            ((:of :in)
1507             (setq sequencep t)
1508             (loop-make-var sequence-variable form sequence-type))
1509            ((:from :downfrom :upfrom)
1510             (setq start-given t)
1511             (cond ((eq prep :downfrom) (setq dir ':down))
1512                   ((eq prep :upfrom) (setq dir ':up)))
1513             (multiple-value-setq (form start-constantp start-value)
1514               (loop-constant-fold-if-possible form indexv-type))
1515             (assert-index-for-arithmetic indexv)
1516             ;; KLUDGE: loop-make-var generates a temporary symbol for
1517             ;; indexv if it is NIL. We have to use it to have the index
1518             ;; actually count
1519             (setq indexv (loop-make-var indexv form indexv-type)))
1520            ((:upto :to :downto :above :below)
1521             (cond ((loop-tequal prep :upto) (setq inclusive-iteration
1522                                                   (setq dir ':up)))
1523                   ((loop-tequal prep :to) (setq inclusive-iteration t))
1524                   ((loop-tequal prep :downto) (setq inclusive-iteration
1525                                                     (setq dir ':down)))
1526                   ((loop-tequal prep :above) (setq dir ':down))
1527                   ((loop-tequal prep :below) (setq dir ':up)))
1528             (setq limit-given t)
1529             (multiple-value-setq (form limit-constantp limit-value)
1530               (loop-constant-fold-if-possible form `(and ,indexv-type real)))
1531             (setq endform (if limit-constantp
1532                               `',limit-value
1533                               (loop-make-var
1534                                  (gensym "LOOP-LIMIT-") form
1535                                  `(and ,indexv-type real)))))
1536            (:by
1537             (multiple-value-setq (form stepby-constantp stepby)
1538               (loop-constant-fold-if-possible form
1539                                               `(and ,indexv-type (real (0)))))
1540             (unless stepby-constantp
1541               (loop-make-var (setq stepby (gensym "LOOP-STEP-BY-"))
1542                  form
1543                  `(and ,indexv-type (real (0)))
1544                  t)))
1545            (t (loop-error
1546                  "~S invalid preposition in sequencing or sequence path;~@
1547               maybe invalid prepositions were specified in iteration path descriptor?"
1548                  prep)))
1549          (when (and odir dir (not (eq dir odir)))
1550            (loop-error
1551              "conflicting stepping directions in LOOP sequencing path"))
1552          (setq odir dir))
1553        (when (and sequence-variable (not sequencep))
1554          (loop-error "missing OF or IN phrase in sequence path"))
1555        ;; Now fill in the defaults.
1556        (if start-given
1557            (when limit-given
1558              ;; if both start and limit are given, they had better both
1559              ;; be REAL.  We already enforce the REALness of LIMIT,
1560              ;; above; here's the KLUDGE to enforce the type of START.
1561              (flet ((type-declaration-of (x)
1562                       (and (eq (car x) 'type) (caddr x))))
1563                (let ((decl (find indexv *loop-declarations*
1564                                  :key #'type-declaration-of))
1565                      (%decl (find indexv *loop-declarations*
1566                                   :key #'type-declaration-of
1567                                   :from-end t)))
1568                  (sb!int:aver (eq decl %decl))
1569                  (when decl
1570                    (setf (cadr decl)
1571                          `(and real ,(cadr decl)))))))
1572            ;; default start
1573            ;; DUPLICATE KLUDGE: loop-make-var generates a temporary
1574            ;; symbol for indexv if it is NIL. See also the comment in
1575            ;; the (:from :downfrom :upfrom) case
1576            (progn
1577              (assert-index-for-arithmetic indexv)
1578              (setq indexv
1579                    (loop-make-var
1580                       indexv
1581                       (setq start-constantp t
1582                             start-value (or (loop-typed-init indexv-type) 0))
1583                       `(and ,indexv-type real)))))
1584        (cond ((member dir '(nil :up))
1585               (when (or limit-given default-top)
1586                 (unless limit-given
1587                   (loop-make-var (setq endform (gensym "LOOP-SEQ-LIMIT-"))
1588                      nil
1589                      indexv-type)
1590                   (push `(setq ,endform ,default-top) *loop-prologue*))
1591                 (setq testfn (if inclusive-iteration '> '>=)))
1592               (setq step (if (eql stepby 1) `(1+ ,indexv) `(+ ,indexv ,stepby))))
1593              (t (unless start-given
1594                   (unless default-top
1595                     (loop-error "don't know where to start stepping"))
1596                   (push `(setq ,indexv (1- ,default-top)) *loop-prologue*))
1597                 (when (and default-top (not endform))
1598                   (setq endform (loop-typed-init indexv-type)
1599                         inclusive-iteration t))
1600                 (when endform (setq testfn (if inclusive-iteration  '< '<=)))
1601                 (setq step
1602                       (if (eql stepby 1) `(1- ,indexv) `(- ,indexv ,stepby)))))
1603        (when testfn
1604          (setq test
1605                `(,testfn ,indexv ,endform)))
1606        (when step-hack
1607          (setq step-hack
1608                `(,variable ,step-hack)))
1609        (let ((first-test test) (remaining-tests test))
1610          ;; As far as I can tell, the effect of the following code is
1611          ;; to detect cases where we know statically whether the first
1612          ;; iteration of the loop will be executed. Depending on the
1613          ;; situation, we can either:
1614          ;;  a) save one jump and one comparison per loop (not per iteration)
1615          ;;     when it will get executed
1616          ;;  b) remove the loop body completely when it won't be executed
1617          ;;
1618          ;; Noble goals. However, the code generated in case a) will
1619          ;; fool the loop induction variable detection, and cause
1620          ;; code like (LOOP FOR I TO 10 ...) to use generic addition
1621          ;; (bug #278a).
1622          ;;
1623          ;; Since the gain in case a) is rather minimal and Python is
1624          ;; generally smart enough to handle b) without any extra
1625          ;; support from the loop macro, I've disabled this code for
1626          ;; now. The code and the comment left here in case somebody
1627          ;; extends the induction variable bound detection to work
1628          ;; with code where the stepping precedes the test.
1629          ;; -- JES 2005-11-30
1630          #+nil
1631          (when (and stepby-constantp start-constantp limit-constantp
1632                     (realp start-value) (realp limit-value))
1633            (when (setq first-test
1634                        (funcall (symbol-function testfn)
1635                                 start-value
1636                                 limit-value))
1637              (setq remaining-tests t)))
1638          `(() (,indexv ,step)
1639            ,remaining-tests ,step-hack () () ,first-test ,step-hack)))))
1640 \f
1641 ;;;; interfaces to the master sequencer
1642
1643 (defun loop-for-arithmetic (var val data-type kwd)
1644   (loop-sequencer
1645    var (loop-check-data-type data-type 'number)
1646    nil nil nil nil nil nil
1647    (loop-collect-prepositional-phrases
1648     '((:from :upfrom :downfrom) (:to :upto :downto :above :below) (:by))
1649     nil (list (list kwd val)))))
1650
1651 \f
1652 ;;;; builtin LOOP iteration paths
1653
1654 #||
1655 (loop for v being the hash-values of ht do (print v))
1656 (loop for k being the hash-keys of ht do (print k))
1657 (loop for v being the hash-values of ht using (hash-key k) do (print (list k v)))
1658 (loop for k being the hash-keys of ht using (hash-value v) do (print (list k v)))
1659 ||#
1660
1661 (defun loop-hash-table-iteration-path (variable data-type prep-phrases
1662                                        &key (which (sb!int:missing-arg)))
1663   (declare (type (member :hash-key :hash-value) which))
1664   (cond ((or (cdr prep-phrases) (not (member (caar prep-phrases) '(:in :of))))
1665          (loop-error "too many prepositions!"))
1666         ((null prep-phrases)
1667          (loop-error "missing OF or IN in ~S iteration path")))
1668   (let ((ht-var (gensym "LOOP-HASHTAB-"))
1669         (next-fn (gensym "LOOP-HASHTAB-NEXT-"))
1670         (dummy-predicate-var nil)
1671         (post-steps nil))
1672     (multiple-value-bind (other-var other-p)
1673         (loop-named-var (ecase which
1674                           (:hash-key 'hash-value)
1675                           (:hash-value 'hash-key)))
1676       ;; @@@@ LOOP-NAMED-VAR returns a second value of T if the name
1677       ;; was actually specified, so clever code can throw away the
1678       ;; GENSYM'ed-up variable if it isn't really needed. The
1679       ;; following is for those implementations in which we cannot put
1680       ;; dummy NILs into MULTIPLE-VALUE-SETQ variable lists.
1681       (setq other-p t
1682             dummy-predicate-var (loop-when-it-var))
1683       (let* ((key-var nil)
1684              (val-var nil)
1685              (variable (or variable (gensym "LOOP-HASH-VAR-TEMP-")))
1686              (bindings `((,variable nil ,data-type)
1687                          (,ht-var ,(cadar prep-phrases))
1688                          ,@(and other-p other-var `((,other-var nil))))))
1689         (ecase which
1690           (:hash-key (setq key-var variable
1691                            val-var (and other-p other-var)))
1692           (:hash-value (setq key-var (and other-p other-var)
1693                              val-var variable)))
1694         (push `(with-hash-table-iterator (,next-fn ,ht-var)) *loop-wrappers*)
1695         (when (or (consp key-var) data-type)
1696           (setq post-steps
1697                 `(,key-var ,(setq key-var (gensym "LOOP-HASH-KEY-TEMP-"))
1698                            ,@post-steps))
1699           (push `(,key-var nil) bindings))
1700         (when (or (consp val-var) data-type)
1701           (setq post-steps
1702                 `(,val-var ,(setq val-var (gensym "LOOP-HASH-VAL-TEMP-"))
1703                            ,@post-steps))
1704           (push `(,val-var nil) bindings))
1705         `(,bindings                     ;bindings
1706           ()                            ;prologue
1707           ()                            ;pre-test
1708           ()                            ;parallel steps
1709           (not (multiple-value-setq (,dummy-predicate-var ,key-var ,val-var)
1710                  (,next-fn)))           ;post-test
1711           ,post-steps)))))
1712
1713 (defun loop-package-symbols-iteration-path (variable data-type prep-phrases
1714                                             &key symbol-types)
1715   (cond ((and prep-phrases (cdr prep-phrases))
1716          (loop-error "Too many prepositions!"))
1717         ((and prep-phrases (not (member (caar prep-phrases) '(:in :of))))
1718          (sb!int:bug "Unknown preposition ~S." (caar prep-phrases))))
1719   (unless (symbolp variable)
1720     (loop-error "Destructuring is not valid for package symbol iteration."))
1721   (let ((pkg-var (gensym "LOOP-PKGSYM-"))
1722         (next-fn (gensym "LOOP-PKGSYM-NEXT-"))
1723         (variable (or variable (gensym "LOOP-PKGSYM-VAR-")))
1724         (package (or (cadar prep-phrases) '*package*)))
1725     (push `(with-package-iterator (,next-fn ,pkg-var ,@symbol-types))
1726           *loop-wrappers*)
1727     `(((,variable nil ,data-type) (,pkg-var ,package))
1728       ()
1729       ()
1730       ()
1731       (not (multiple-value-setq (,(loop-when-it-var)
1732                                  ,variable)
1733              (,next-fn)))
1734       ())))
1735 \f
1736 ;;;; ANSI LOOP
1737
1738 (defun make-ansi-loop-universe ()
1739   (let ((w (make-standard-loop-universe
1740              :keywords '((named (loop-do-named))
1741                          (initially (loop-do-initially))
1742                          (finally (loop-do-finally))
1743                          (do (loop-do-do))
1744                          (doing (loop-do-do))
1745                          (return (loop-do-return))
1746                          (collect (loop-list-collection list))
1747                          (collecting (loop-list-collection list))
1748                          (append (loop-list-collection append))
1749                          (appending (loop-list-collection append))
1750                          (nconc (loop-list-collection nconc))
1751                          (nconcing (loop-list-collection nconc))
1752                          (count (loop-sum-collection count
1753                                                      real
1754                                                      fixnum))
1755                          (counting (loop-sum-collection count
1756                                                         real
1757                                                         fixnum))
1758                          (sum (loop-sum-collection sum number number))
1759                          (summing (loop-sum-collection sum number number))
1760                          (maximize (loop-maxmin-collection max))
1761                          (minimize (loop-maxmin-collection min))
1762                          (maximizing (loop-maxmin-collection max))
1763                          (minimizing (loop-maxmin-collection min))
1764                          (always (loop-do-always t nil)) ; Normal, do always
1765                          (never (loop-do-always t t)) ; Negate test on always.
1766                          (thereis (loop-do-thereis t))
1767                          (while (loop-do-while nil :while)) ; Normal, do while
1768                          (until (loop-do-while t :until)) ;Negate test on while
1769                          (when (loop-do-if when nil))   ; Normal, do when
1770                          (if (loop-do-if if nil))       ; synonymous
1771                          (unless (loop-do-if unless t)) ; Negate test on when
1772                          (with (loop-do-with))
1773                          (repeat (loop-do-repeat)))
1774              :for-keywords '((= (loop-ansi-for-equals))
1775                              (across (loop-for-across))
1776                              (in (loop-for-in))
1777                              (on (loop-for-on))
1778                              (from (loop-for-arithmetic :from))
1779                              (downfrom (loop-for-arithmetic :downfrom))
1780                              (upfrom (loop-for-arithmetic :upfrom))
1781                              (below (loop-for-arithmetic :below))
1782                              (above (loop-for-arithmetic :above))
1783                              (to (loop-for-arithmetic :to))
1784                              (upto (loop-for-arithmetic :upto))
1785                              (downto (loop-for-arithmetic :downto))
1786                              (by (loop-for-arithmetic :by))
1787                              (being (loop-for-being)))
1788              :iteration-keywords '((for (loop-do-for))
1789                                    (as (loop-do-for)))
1790              :type-symbols '(array atom bignum bit bit-vector character
1791                              compiled-function complex cons double-float
1792                              fixnum float function hash-table integer
1793                              keyword list long-float nil null number
1794                              package pathname random-state ratio rational
1795                              readtable sequence short-float simple-array
1796                              simple-bit-vector simple-string simple-vector
1797                              single-float standard-char stream string
1798                              base-char symbol t vector)
1799              :type-keywords nil)))
1800     (add-loop-path '(hash-key hash-keys) 'loop-hash-table-iteration-path w
1801                    :preposition-groups '((:of :in))
1802                    :inclusive-permitted nil
1803                    :user-data '(:which :hash-key))
1804     (add-loop-path '(hash-value hash-values) 'loop-hash-table-iteration-path w
1805                    :preposition-groups '((:of :in))
1806                    :inclusive-permitted nil
1807                    :user-data '(:which :hash-value))
1808     (add-loop-path '(symbol symbols) 'loop-package-symbols-iteration-path w
1809                    :preposition-groups '((:of :in))
1810                    :inclusive-permitted nil
1811                    :user-data '(:symbol-types (:internal
1812                                                :external
1813                                                :inherited)))
1814     (add-loop-path '(external-symbol external-symbols)
1815                    'loop-package-symbols-iteration-path w
1816                    :preposition-groups '((:of :in))
1817                    :inclusive-permitted nil
1818                    :user-data '(:symbol-types (:external)))
1819     (add-loop-path '(present-symbol present-symbols)
1820                    'loop-package-symbols-iteration-path w
1821                    :preposition-groups '((:of :in))
1822                    :inclusive-permitted nil
1823                    :user-data '(:symbol-types (:internal
1824                                                :external)))
1825     w))
1826
1827 (defparameter *loop-ansi-universe*
1828   (make-ansi-loop-universe))
1829
1830 (defun loop-standard-expansion (keywords-and-forms environment universe)
1831   (if (and keywords-and-forms (symbolp (car keywords-and-forms)))
1832       (loop-translate keywords-and-forms environment universe)
1833       (let ((tag (gensym)))
1834         `(block nil (tagbody ,tag (progn ,@keywords-and-forms) (go ,tag))))))
1835
1836 (sb!int:defmacro-mundanely loop (&environment env &rest keywords-and-forms)
1837   (loop-standard-expansion keywords-and-forms env *loop-ansi-universe*))
1838
1839 (sb!int:defmacro-mundanely loop-finish ()
1840   #!+sb-doc
1841   "Cause the iteration to terminate \"normally\", the same as implicit
1842 termination by an iteration driving clause, or by use of WHILE or
1843 UNTIL -- the epilogue code (if any) will be run, and any implicitly
1844 collected result will be returned as the value of the LOOP."
1845   '(go end-loop))