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