source: trunk/abcl/src/org/armedbear/lisp/loop.lisp

Last change on this file was 15569, checked in by Mark Evenson, 2 years ago

Untabify en masse

Results of running style.org source blocks on tree

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