primarily intending to integrate Colin Walter's O(N) map code and
authorWilliam Harold Newman <william.newman@airmail.net>
Fri, 22 Sep 2000 15:04:39 +0000 (15:04 +0000)
committerWilliam Harold Newman <william.newman@airmail.net>
Fri, 22 Sep 2000 15:04:39 +0000 (15:04 +0000)
fixing BUTLAST (but doing some other stuff too, since achieving the
primary objective involved a lot of inspecting other code):

another revision of MAP stuff, part I:
  * I switched over to code inspired by Colin Walters' O(N) MAP
    code (from the cmucl-imp mailing list 2000 Sep 02) for the
    general non-DEFTRANSFORM case.
  * HIGH-SECURITY-SUPPORT error checking logic goes away, pending
    part II
  * I made some  miscellaneous cleanups of old arity-1 code too.
  * The old MAP-FOR-EFFECT, MAP-TO-LIST, and MAP-TO-SIMPLE macros,
    and the old functions MAP-WITHOUT-ERRORCHECKING, and
    GET-MINIMUM-LENGTH-SEQUENCES go away.
  * The old #+!HIGH-SECURITY length-checking logic goes
    away, to be replaced by stuff in part II.
  * New O(N) functions %MAP-FOR-EFFECT, %MAP-TO-LIST, and
    %MAP-TO-VECTOR are added, and MAP is redefined in terms of them.
  * Add a note pointing out that since MAP-INTO has not been
    rewritten to take advantage of all the new mapping technology,
    it's still slow.
  * Delete no-longer-used ELT-SLICE macro.

another revision of MAP stuff, part II: Peter Van Eynde might go into
a killing frenzy, or at least his ansi-test suite will gnaw SBCL to
death, unless we raise type errors on length mismatches like
  (MAP '(SIMPLE-VECTOR 128) #'+ #(1 2) #(1 1)).
How to do this without clobbering efficiency? More DEFTRANSFORMs, I
think..
  * MAP becomes a wrapper around %MAP. %MAP doesn't do this
    kind of length checking, MAP does. The old DEFUN MAP,
    DEFKNOWN MAP, and DEFTRANSFORM MAP stuff all turns into
    corresponding definitions for %MAP. The wrapper is
    implemented both as a DEFUN MAP and a DEFTRANSFORM MAP.
  * Now make DEFTRANSFORM MAP smarter:
    ** If necessary, check at runtime that ARRAY-DIMENSION
       matches what we pull out of SPECIFIER-TYPE.
    ** No test is done when SPEED > SAFETY.
    ** No test is needed when we can tell at compile time that
       the result type doesn't specify the length of the result.
  * Also add the same kind of ARRAY-DIMENSION/SPECIFIER-TYPE runtime
    check to DEFUN MAP.
  * While I'm at it, since DEFTRANSFORM MAP needs to think hard about
    the type of the result anyway, it might as well declare what
    it's figured out (TRULY-THE) to benefit any code downstream.

Start playing with MAP regression tests. Add tests/assertoid.lisp to
support future regression tests.

Once I started using the QUIT :UNIX-CODE keyword argument in my test
cases, I could see that it isn't very mnemonic. So I changed it to the
more-descriptive name :UNIX-STATUS, leaving the old name supported but
deprecated.

Oops! The old DEFTRANSFORM MAP (now DEFTRANSFORM %MAP) should really
only be done when (>= SPEED SPACE), but it wasn't declared that way.

While looking for an example of a DEFTRANSFORM with &REST arguments
to use as a model for the code in the new DEFTRANSFORM from MAP to
%MAP, I noticed that the problem of taking a list of names and
generating a corresponding list of gensyms is solved in many different
places in the code, in several ways. Also, the related problem of just
creating a list of N gensyms is solved in several places in in the
code. This seems unnecessarily error-prone and wasteful, so I went
looking for such cases and turned them into calls to MAKE-GENSYM-LIST.

another revision of MAP stuff, part III:
  * Search for 'map' in the output from clocc ansi-tests/tests.lisp,
    to check that the new MAP code isn't too obviously broken.
  * Add some regression tests in test/map.impure.lisp.

Oops! The various %MAP-..-ARITY-1 helper functions expect a function
argument, but DEFTRANSFORM MAP can call them passing them a function
name instead.
  * Change the helper functions so that they can handle
    function names as arguments.
  * Define %COERCE-CALLABLE-TO-FUNCTION to help with this. Note that
    this seems to be what %COERCE-NAME-TO-FUNCTION meant long ago,
    judging from DEFTRANSFORM %COERCE-NAME-TO-FUNCTION; so
    appropriate that DEFTRANSFORM for %COERCE-CALLABLE-TO-FUNCTION.
  * Use %COERCE-CALLABLE-TO-FUNCTION elsewhere that expressions
    involving %COERCE-NAME-TO-FUNCTION were used previously.

deleted the old commented-out version of DEFMACRO HANDLER-CASE
(since it was marked "Delete this when the system is stable.":-)

deleted the old commented-out version of GEN-FORMAT-DEF-FORM,
since it was supposed to be safe to do so after sbcl-0.6.4

I removed the apology for not using PRINT-OBJECT everywhere in the
printer from the bugs list in the man page, since it seems to be
rather tricky to construct a test case which exposes the system's
non-PRINT-OBJECT-ness without the test case itself violating the ANSI
spec.

I updated, cleaned up, or removed outright some other outdated or
confusing entries in the BUGS file and from the bugs list on the man
page.

Now that BUTLAST no longer blows up on the new problem cases a la
(BUTLAST NIL -1), I wonder whether I could stop it from blowing
up on the old problem cases a la (BUTLAST NIL)? It looks like
a compiler problem, since the interpreted definition of BUTLAST works,
even though the compiled one doesn't. In fact, it's a declaration
problem, since LENGTH is set to -1 when LIST=NIL, but is declared
as an INDEX. (Of course it's likely also a compiler problem, since
the compiler is supposed to signal type errors for this kind of
declaration error.) I fixed the misdeclaration, and noted the
possible compiler bug in BUGS.

After writing the new revised weird type declarations for the
not-necessarily positive LENGTH, and writing explanatory comments,
  ;; (Despite the name, LENGTH can be -1 when when LIST is an ATOM.)
for each of the cut-and-pasted (LET ((LENGTH ..)) ..) forms in BUTLAST
and NBUTLAST, I said "screw it" -- no, that's not it, I quoted Martin
Fowler and Kent Beck: "If you see the same code structure in more than
one place, you can be sure that your program will be better if you
find a way to unify them," and "It's surprising how often you look at
thickly commented code and notice that the comments are there because
the code is bad." So I just rewrote BUTLAST and NBUTLAST. Hopefully
the new versions will be better-behaved than the old ones.

Now that the INDEX type is used in DEFUN MAKE-GENSYM-LIST, which
belongs in early-extensions.lisp, INDEX should be defined before
early-extensions.lisp, i.e. earlier than its current definition in
early-c.lisp. Move it to early-extensions.lisp. Then to make that
work, since DEF!TYPE is used to define INDEX, defbangtype.lisp needs
to precede early-extensions.lisp in stems-and-flags.lisp-expr; so move
it. Also, INDEX is defined in terms of SB!XC:ARRAY-DIMENSION-LIMIT, so
early-array.lisp needs to move before the new location of
defbangtype.lisp. And then early-vm.lisp needs to move before that, so
I might as well move the rest of the early-vm-ish stuff back too. And
then DEFTYPE is used before deftype.lisp, so I need to change DEFMACRO
DEF!TYPE to DEF!MACRO DEF!TYPE, so I need to move defbangmacro.lisp
before deftype.lisp. (This is like a trip down memory lane to the
endless tweaks and recompiles it took me to find and unravel the
twisted order dependencies which make CMU CL unbootstrappable. Ah,
those were the days..:-)

The DEFTYPEs for INDEX and POSN in early-assem.lisp duplicate
the functionality of the SB-KERNEL:INDEX type.
  * Change uses of the SB-ASSEM::POSN type to uses of the INDEX type.
  * Delete the SB-ASSEM::POSN type and the SB-ASSEM::MAX-POSN constant.
  * Move SB-KERNEL:INDEX into SB-INT, since it's not really
    just a kernel-level thing, but makes sense for implementing
    user-level stuff in SB-INT and SB-EXT and SB-C (and SB-ASSEM).
  * Grep for all '[a-z]:+index[^-a-z]' and rename them (or just
    remove prefixes) to match new SB-INT-ness of INDEX.
  * Make the SB-ASSEM package use the SB-INT package; delete
    the SB-ASSEM::INDEX type and SB-ASSEM::MAX-INDEX constant.
    And since as a rule anything which can see SB-INT deserves
    to see SB-EXT too, make SB-ASSEM use SB-EXT as well.

14 files changed:
src/compiler/aliencomp.lisp
src/compiler/assem.lisp
src/compiler/checkgen.lisp
src/compiler/deftype.lisp
src/compiler/disassem.lisp
src/compiler/early-assem.lisp
src/compiler/early-c.lisp
src/compiler/fndb.lisp
src/compiler/ir1opt.lisp
src/compiler/ir1tran.lisp
src/compiler/locall.lisp
src/compiler/macros.lisp
src/compiler/seqtran.lisp
src/compiler/srctran.lisp

index be61a41..ce65019 100644 (file)
 (deftransform alien-funcall ((function &rest args)
                             ((alien (* t)) &rest *) *
                             :important t)
-  (let ((names (loop repeat (length args) collect (gensym))))
+  (let ((names (make-gensym-list (length args))))
     (/noshow "entering first DEFTRANSFORM ALIEN-FUNCALL" function args)
     `(lambda (function ,@names)
        (alien-funcall (deref function) ,@names))))
index 0d1710b..e3cb3c7 100644 (file)
 (defstruct segment
   ;; the name of this segment (for debugging output and stuff)
   (name "Unnamed" :type simple-base-string)
-  ;; Ordinarily this is a vector where instructions are written. If the segment
-  ;; is made invalid (e.g. by APPEND-SEGMENT) then the vector can be
-  ;; replaced by NIL.
+  ;; Ordinarily this is a vector where instructions are written. If
+  ;; the segment is made invalid (e.g. by APPEND-SEGMENT) then the
+  ;; vector can be replaced by NIL.
   (buffer (make-array 0
                      :fill-pointer 0
                      :adjustable t
                      :element-type 'assembly-unit)
          :type (or null (vector assembly-unit)))
-  ;; whether or not to run the scheduler. Note: if the instruction definitions
-  ;; were not compiled with the scheduler turned on, this has no effect.
+  ;; whether or not to run the scheduler. Note: if the instruction
+  ;; definitions were not compiled with the scheduler turned on, this
+  ;; has no effect.
   (run-scheduler nil)
-  ;; If a function, then this is funcalled for each inst emitted with the
-  ;; segment, the VOP, the name of the inst (as a string), and the inst
-  ;; arguments.
+  ;; If a function, then this is funcalled for each inst emitted with
+  ;; the segment, the VOP, the name of the inst (as a string), and the
+  ;; inst arguments.
   (inst-hook nil :type (or function null))
-  ;; what position does this correspond to? Initially, positions and indexes
-  ;; are the same, but after we start collapsing choosers, positions can change
-  ;; while indexes stay the same.
-  (current-posn 0 :type posn)
+  ;; what position does this correspond to? Initially, positions and
+  ;; indexes are the same, but after we start collapsing choosers,
+  ;; positions can change while indexes stay the same.
+  (current-posn 0 :type index)
   ;; a list of all the annotations that have been output to this segment
   (annotations nil :type list)
   ;; a pointer to the last cons cell in the annotations list. This is
   ;; the number of bits of alignment at the last time we synchronized
   (alignment max-alignment :type alignment)
   ;; the position the last time we synchronized
-  (sync-posn 0 :type posn)
-  ;; The posn and index everything ends at. This is not maintained while the
-  ;; data is being generated, but is filled in after. Basically, we copy
-  ;; current-posn and current-index so that we can trash them while processing
-  ;; choosers and back-patches.
-  (final-posn 0 :type posn)
+  (sync-posn 0 :type index)
+  ;; The posn and index everything ends at. This is not maintained
+  ;; while the data is being generated, but is filled in after.
+  ;; Basically, we copy current-posn and current-index so that we can
+  ;; trash them while processing choosers and back-patches.
+  (final-posn 0 :type index)
   (final-index 0 :type index)
   ;; *** State used by the scheduler during instruction queueing.
   ;;
           :type simple-vector)
   (writers (make-array *assem-max-locations* :initial-element nil)
           :type simple-vector)
-  ;; The number of additional cycles before the next control transfer, or NIL
-  ;; if a control transfer hasn't been queued. When a delayed branch is
-  ;; queued, this slot is set to the delay count.
+  ;; The number of additional cycles before the next control transfer,
+  ;; or NIL if a control transfer hasn't been queued. When a delayed
+  ;; branch is queued, this slot is set to the delay count.
   (branch-countdown nil :type (or null (and fixnum unsigned-byte)))
   ;; *** These two slots are used both by the queuing noise and the
   ;; scheduling noise.
   ;;
-  ;; All the instructions that are pending and don't have any unresolved
-  ;; dependents. We don't list branches here even if they would otherwise
-  ;; qualify. They are listed above.
+  ;; All the instructions that are pending and don't have any
+  ;; unresolved dependents. We don't list branches here even if they
+  ;; would otherwise qualify. They are listed above.
   (emittable-insts-sset (make-sset) :type sset)
-  ;; list of queued branches. We handle these specially, because they have to
-  ;; be emitted at a specific place (e.g. one slot before the end of the
-  ;; block).
+  ;; list of queued branches. We handle these specially, because they
+  ;; have to be emitted at a specific place (e.g. one slot before the
+  ;; end of the block).
   (queued-branches nil :type list)
   ;; *** state used by the scheduler during instruction scheduling.
   ;;
-  ;; the instructions who would have had a read dependent removed if it were
-  ;; not for a delay slot. This is a list of lists. Each element in the
-  ;; top level list corresponds to yet another cycle of delay. Each element
-  ;; in the second level lists is a dotted pair, holding the dependency
-  ;; instruction and the dependent to remove.
+  ;; the instructions who would have had a read dependent removed if
+  ;; it were not for a delay slot. This is a list of lists. Each
+  ;; element in the top level list corresponds to yet another cycle of
+  ;; delay. Each element in the second level lists is a dotted pair,
+  ;; holding the dependency instruction and the dependent to remove.
   (delayed nil :type list)
   ;; The emittable insts again, except this time as a list sorted by depth.
   (emittable-insts-queue nil :type list)
     ;; Make sure that the array is big enough.
     (do ()
        ((>= (array-dimension buffer 0) new-value))
-      ;; When we have to increase the size of the array, we want to roughly
-      ;; double the vector length: that way growing the array to size N conses
-      ;; only O(N) bytes in total. But just doubling the length would leave a
-      ;; zero-length vector unchanged. Hence, take the MAX with 1..
+      ;; When we have to increase the size of the array, we want to
+      ;; roughly double the vector length: that way growing the array
+      ;; to size N conses only O(N) bytes in total. But just doubling
+      ;; the length would leave a zero-length vector unchanged. Hence,
+      ;; take the MAX with 1..
       (adjust-array buffer (max 1 (* 2 (array-dimension buffer 0)))))
     ;; Now that the array has the intended next free byte, we can point to it.
     (setf (fill-pointer buffer) new-value)))
 ;;;; structures/types used by the scheduler
 
 (sb!c:def-boolean-attribute instruction
-  ;; This attribute is set if the scheduler can freely flush this instruction
-  ;; if it thinks it is not needed. Examples are NOP and instructions that
-  ;; have no side effect not described by the writes.
+  ;; This attribute is set if the scheduler can freely flush this
+  ;; instruction if it thinks it is not needed. Examples are NOP and
+  ;; instructions that have no side effect not described by the
+  ;; writes.
   flushable
-  ;; This attribute is set when an instruction can cause a control transfer.
-  ;; For test instructions, the delay is used to determine how many
-  ;; instructions follow the branch.
+  ;; This attribute is set when an instruction can cause a control
+  ;; transfer. For test instructions, the delay is used to determine
+  ;; how many instructions follow the branch.
   branch
-  ;; This attribute indicates that this ``instruction'' can be variable length,
-  ;; and therefore better never be used in a branch delay slot.
+  ;; This attribute indicates that this ``instruction'' can be
+  ;; variable length, and therefore better never be used in a branch
+  ;; delay slot.
   variable-length)
 
 (defstruct (instruction
   (emitter (required-argument) :type (or null function))
   ;; The attributes of this instruction.
   (attributes (instruction-attributes) :type sb!c:attributes)
-  ;; Number of instructions or cycles of delay before additional instructions
-  ;; can read our writes.
+  ;; Number of instructions or cycles of delay before additional
+  ;; instructions can read our writes.
   (delay 0 :type (and fixnum unsigned-byte))
-  ;; the maximum number of instructions in the longest dependency chain from
-  ;; this instruction to one of the independent instructions. This is used
-  ;; as a heuristic at to which instructions should be scheduled first.
+  ;; the maximum number of instructions in the longest dependency
+  ;; chain from this instruction to one of the independent
+  ;; instructions. This is used as a heuristic at to which
+  ;; instructions should be scheduled first.
   (depth nil :type (or null (and fixnum unsigned-byte)))
-  ;; ** When trying remember which of the next four is which, note that the
-  ;; ``read'' or ``write'' always refers to the dependent (second)
-  ;; instruction.
+  ;; Note: When trying remember which of the next four is which, note
+  ;; that the ``read'' or ``write'' always refers to the dependent
+  ;; (second) instruction.
   ;;
   ;; instructions whose writes this instruction tries to read
   (read-dependencies (make-sset) :type sset)
        (push inst (svref (segment-writers segment) index)))))
   (values))
 
-;;; This routine is called by due to uses of the INST macro when the scheduler
-;;; is turned on. The change to the dependency graph has already been computed,
-;;; so we just have to check to see whether the basic block is terminated.
+;;; This routine is called by due to uses of the INST macro when the
+;;; scheduler is turned on. The change to the dependency graph has
+;;; already been computed, so we just have to check to see whether the
+;;; basic block is terminated.
 (defun queue-inst (segment inst)
   #!+sb-show-assem (format *trace-output* "~&queuing ~S~%" inst)
   #!+sb-show-assem (format *trace-output*
        (schedule-pending-instructions segment))))
   (values))
 
-;;; Emit all the pending instructions, and reset any state. This is called
-;;; whenever we hit a label (i.e. an entry point of some kind) and when the
-;;; user turns the scheduler off (otherwise, the queued instructions would
-;;; sit there until the scheduler was turned back on, and emitted in the
-;;; wrong place).
+;;; Emit all the pending instructions, and reset any state. This is
+;;; called whenever we hit a label (i.e. an entry point of some kind)
+;;; and when the user turns the scheduler off (otherwise, the queued
+;;; instructions would sit there until the scheduler was turned back
+;;; on, and emitted in the wrong place).
 (defun schedule-pending-instructions (segment)
   (assert (segment-run-scheduler segment))
 
   #!+sb-show-assem (format *trace-output*
                           "~&scheduling pending instructions..~%")
 
-  ;; Note that any values live at the end of the block have to be computed
-  ;; last.
+  ;; Note that any values live at the end of the block have to be
+  ;; computed last.
   (let ((emittable-insts (segment-emittable-insts-sset segment))
        (writers (segment-writers segment)))
     (dotimes (index (length writers))
          (setf (instruction-attributep (inst-attributes inst) flushable)
                nil)))))
 
-  ;; Grovel through the entire graph in the forward direction finding all
-  ;; the leaf instructions.
+  ;; Grovel through the entire graph in the forward direction finding
+  ;; all the leaf instructions.
   (labels ((grovel-inst (inst)
             (let ((max 0))
               (do-sset-elements (dep (inst-write-dependencies inst))
                           "initially delayed: ~S~%"
                           (segment-delayed segment))
 
-  ;; Accumulate the results in reverse order. Well, actually, this list will
-  ;; be in forward order, because we are generating the reverse order in
-  ;; reverse.
+  ;; Accumulate the results in reverse order. Well, actually, this
+  ;; list will be in forward order, because we are generating the
+  ;; reverse order in reverse.
   (let ((results nil))
 
     ;; Schedule all the branches in their exact locations.
       (dolist (branch (segment-queued-branches segment))
        (let ((inst (cdr branch)))
          (dotimes (i (- (car branch) insts-from-end))
-           ;; Each time through this loop we need to emit another instruction.
-           ;; First, we check to see whether there is any instruction that
-           ;; must be emitted before (i.e. must come after) the branch inst.
-           ;; If so, emit it. Otherwise, just pick one of the emittable
-           ;; insts. If there is nothing to do, then emit a nop.
-           ;; ### Note: despite the fact that this is a loop, it really won't
-           ;; work for repetitions other then zero and one. For example, if
-           ;; the branch has two dependents and one of them dpends on the
-           ;; other, then the stuff that grabs a dependent could easily
-           ;; grab the wrong one. But I don't feel like fixing this because
-           ;; it doesn't matter for any of the architectures we are using
-           ;; or plan on using.
+           ;; Each time through this loop we need to emit another
+           ;; instruction. First, we check to see whether there is
+           ;; any instruction that must be emitted before (i.e. must
+           ;; come after) the branch inst. If so, emit it. Otherwise,
+           ;; just pick one of the emittable insts. If there is
+           ;; nothing to do, then emit a nop. ### Note: despite the
+           ;; fact that this is a loop, it really won't work for
+           ;; repetitions other then zero and one. For example, if
+p          ;; the branch has two dependents and one of them dpends on
+           ;; the other, then the stuff that grabs a dependent could
+           ;; easily grab the wrong one. But I don't feel like fixing
+           ;; this because it doesn't matter for any of the
+           ;; architectures we are using or plan on using.
            (flet ((maybe-schedule-dependent (dependents)
                     (do-sset-elements (inst dependents)
                       ;; If do-sset-elements enters the body, then there is a
   ;; That's all, folks.
   (values))
 
-;;; Utility for maintaining the segment-delayed list. We cdr down list
-;;; n times (extending it if necessary) and then push thing on into the car
-;;; of that cons cell.
+;;; a utility for maintaining the segment-delayed list. We cdr down
+;;; list n times (extending it if necessary) and then push thing on
+;;; into the car of that cons cell.
 (defun add-to-nth-list (list thing n)
   (do ((cell (or list (setf list (list nil)))
             (or (cdr cell) (setf (cdr cell) (list nil))))
 
 ;;; Find the next instruction to schedule and return it after updating
 ;;; any dependency information. If we can't do anything useful right
-;;; now, but there is more work to be done, return :NOP to indicate that
-;;; a nop must be emitted. If we are all done, return NIL.
+;;; now, but there is more work to be done, return :NOP to indicate
+;;; that a nop must be emitted. If we are all done, return NIL.
 (defun schedule-one-inst (segment delay-slot-p)
   (do ((prev nil remaining)
        (remaining (segment-emittable-insts-queue segment) (cdr remaining)))
                     (if (inst-emitter inst)
                         ;; Nope, it's still a go. So return it.
                         inst
-                        ;; Yes, so pick a new one. We have to start over,
-                        ;; because note-resolved-dependencies might have
-                        ;; changed the emittable-insts-queue.
+                        ;; Yes, so pick a new one. We have to start
+                        ;; over, because note-resolved-dependencies
+                        ;; might have changed the emittable-insts-queue.
                         (schedule-one-inst segment delay-slot-p))))))
   ;; Nothing to do, so make something up.
   (cond ((segment-delayed segment)
         ;; All done.
         nil)))
 
-;;; This function is called whenever an instruction has been scheduled, and we
-;;; want to know what possibilities that opens up. So look at all the
-;;; instructions that this one depends on, and remove this instruction from
-;;; their dependents list. If we were the last dependent, then that
-;;; dependency can be emitted now.
+;;; This function is called whenever an instruction has been
+;;; scheduled, and we want to know what possibilities that opens up.
+;;; So look at all the instructions that this one depends on, and
+;;; remove this instruction from their dependents list. If we were the
+;;; last dependent, then that dependency can be emitted now.
 (defun note-resolved-dependencies (segment inst)
   (assert (sset-empty (inst-read-dependents inst)))
   (assert (sset-empty (inst-write-dependents inst)))
                               (inst-delay dep)))))
   (values))
 
-;;; Process the next entry in segment-delayed. This is called whenever anyone
-;;; emits an instruction.
+;;; Process the next entry in segment-delayed. This is called whenever
+;;; anyone emits an instruction.
 (defun advance-one-inst (segment)
   (let ((delayed-stuff (pop (segment-delayed segment))))
     (dolist (stuff delayed-stuff)
              (insert-emittable-inst segment dependency)))
          (insert-emittable-inst segment stuff)))))
 
-;;; Note that inst is emittable by sticking it in the SEGMENT-EMITTABLE-INSTS-
-;;; QUEUE list. We keep the emittable-insts sorted with the largest ``depths''
-;;; first. Except that if INST is a branch, don't bother. It will be handled
-;;; correctly by the branch emitting code in SCHEDULE-PENDING-INSTRUCTIONS.
+;;; Note that inst is emittable by sticking it in the
+;;; SEGMENT-EMITTABLE-INSTS-QUEUE list. We keep the emittable-insts
+;;; sorted with the largest ``depths'' first. Except that if INST is a
+;;; branch, don't bother. It will be handled correctly by the branch
+;;; emitting code in SCHEDULE-PENDING-INSTRUCTIONS.
 (defun insert-emittable-inst (segment inst)
   (unless (instruction-attributep (inst-attributes inst) branch)
     #!+sb-show-assem (format *trace-output* "now emittable: ~S~%" inst)
   ;; The function to use to generate the real data
   (function nil :type function))
 
-;;; This is similar to a BACK-PATCH, but also an indication that the amount
-;;; of stuff output depends on label-positions, etc. Back-patches can't change
-;;; their mind about how much stuff to emit, but choosers can.
+;;; This is similar to a BACK-PATCH, but also an indication that the
+;;; amount of stuff output depends on label-positions, etc.
+;;; Back-patches can't change their mind about how much stuff to emit,
+;;; but choosers can.
 (defstruct (chooser
            (:include annotation)
            (:constructor make-chooser
 ;;; interface: Emit the supplied BYTE to SEGMENT, growing SEGMENT if necessary.
 (defun emit-byte (segment byte)
   (declare (type segment segment))
-  ;; We could use DECLARE instead of CHECK-TYPE here, but (1) CMU CL's inspired
-  ;; decision to treat DECLARE as ASSERT by default has not been copied by
-  ;; other compilers, and this code runs in the cross-compilation host Common
-  ;; Lisp, not just CMU CL, and (2) classic CMU CL allowed more things here
-  ;; than this, and I haven't tried to proof-read all the calls to EMIT-BYTE to
-  ;; ensure that they're passing appropriate. -- WHN 19990323
+  ;; We could use DECLARE instead of CHECK-TYPE here, but (1) CMU CL's
+  ;; inspired decision to treat DECLARE as ASSERT by default has not
+  ;; been copied by other compilers, and this code runs in the
+  ;; cross-compilation host Common Lisp, not just CMU CL, and (2)
+  ;; classic CMU CL allowed more things here than this, and I haven't
+  ;; tried to proof-read all the calls to EMIT-BYTE to ensure that
+  ;; they're passing appropriate. -- WHN 19990323
   (check-type byte possibly-signed-assembly-unit)
   (vector-push-extend (logand byte assembly-unit-mask)
                      (segment-buffer segment))
   (values))
 
 ;;; Used to handle the common parts of annotation emision. We just
-;;; assign the posn and index of the note and tack it on to the end
-;;; of the segment's annotations list.
+;;; assign the posn and index of the note and tack it on to the end of
+;;; the segment's annotations list.
 (defun emit-annotation (segment note)
   (declare (type segment segment)
           (type annotation note))
     (emit-skip segment size)
     (adjust-alignment-after-chooser segment chooser)))
 
-;;; Called in EMIT-CHOOSER and COMPRESS-SEGMENT in order to recompute the
-;;; current alignment information in light of this chooser. If the alignment
-;;; guaranteed byte the chooser is less then the segments current alignment,
-;;; we have to adjust the segments notion of the current alignment.
+;;; Called in EMIT-CHOOSER and COMPRESS-SEGMENT in order to recompute
+;;; the current alignment information in light of this chooser. If the
+;;; alignment guaranteed byte the chooser is less then the segments
+;;; current alignment, we have to adjust the segments notion of the
+;;; current alignment.
 ;;;
-;;; The hard part is recomputing the sync posn, because it's not just the
-;;; choosers posn. Consider a chooser that emits either one or three words.
-;;; It preserves 8-byte (3 bit) alignments, because the difference between
-;;; the two choices is 8 bytes.
+;;; The hard part is recomputing the sync posn, because it's not just
+;;; the choosers posn. Consider a chooser that emits either one or
+;;; three words. It preserves 8-byte (3 bit) alignments, because the
+;;; difference between the two choices is 8 bytes.
 (defun adjust-alignment-after-chooser (segment chooser)
   (declare (type segment segment) (type chooser chooser))
   (let ((alignment (chooser-alignment chooser))
        (seg-alignment (segment-alignment segment)))
     (when (< alignment seg-alignment)
-      ;; The chooser might change the alignment of the output. So we have
-      ;; to figure out what the worst case alignment could be.
+      ;; The chooser might change the alignment of the output. So we
+      ;; have to figure out what the worst case alignment could be.
       (setf (segment-alignment segment) alignment)
       (let* ((posn (chooser-posn chooser))
             (sync-posn (segment-sync-posn segment))
        (setf (segment-sync-posn segment) (- posn delta)))))
   (values))
 
-;;; Used internally whenever a chooser or alignment decides it doesn't need
-;;; as much space as it originally thought.
+;;; Used internally whenever a chooser or alignment decides it doesn't
+;;; need as much space as it originally thought.
 (defun emit-filler (segment bytes)
   (let ((last (segment-last-annotation segment)))
     (cond ((and last (filler-p (car last)))
   (incf (segment-current-index segment) bytes)
   (values))
 
-;;; EMIT-LABEL (the interface) basically just expands into this, supplying
-;;; the segment and vop.
+;;; EMIT-LABEL (the interface) basically just expands into this,
+;;; supplying the segment and vop.
 (defun %emit-label (segment vop label)
   (when (segment-run-scheduler segment)
     (schedule-pending-instructions segment))
       (funcall hook segment vop :label label)))
   (emit-annotation segment label))
 
-;;; Called by the ALIGN macro to emit an alignment note. We check to see
-;;; if we can guarantee the alignment restriction by just outputting a fixed
-;;; number of bytes. If so, we do so. Otherwise, we create and emit
-;;; an alignment note.
+;;; Called by the ALIGN macro to emit an alignment note. We check to
+;;; see if we can guarantee the alignment restriction by just
+;;; outputting a fixed number of bytes. If so, we do so. Otherwise, we
+;;; create and emit an alignment note.
 (defun emit-alignment (segment vop bits &optional (fill-byte 0))
   (when (segment-run-scheduler segment)
     (schedule-pending-instructions segment))
                   (segment-sync-posn segment))))
     (cond ((> bits alignment)
           ;; We need more bits of alignment. First emit enough noise
-          ;; to get back in sync with alignment, and then emit an alignment
-          ;; note to cover the rest.
+          ;; to get back in sync with alignment, and then emit an
+          ;; alignment note to cover the rest.
           (let ((slop (logand offset (1- (ash 1 alignment)))))
             (unless (zerop slop)
               (emit-skip segment (- (ash 1 alignment) slop) fill-byte)))
           (setf (segment-sync-posn segment) (segment-current-posn segment)))
          (t
           ;; The last alignment was more restrictive then this one.
-          ;; So we can just figure out how much noise to emit assuming
-          ;; the last alignment was met.
+          ;; So we can just figure out how much noise to emit
+          ;; assuming the last alignment was met.
           (let* ((mask (1- (ash 1 bits)))
                  (new-offset (logand (+ offset mask) (lognot mask))))
             (emit-skip segment (- new-offset offset) fill-byte))
           (emit-annotation segment (make-alignment bits 0 fill-byte)))))
   (values))
 
-;;; Used to find how ``aligned'' different offsets are. Returns the number
-;;; of low-order 0 bits, up to MAX-ALIGNMENT.
+;;; Used to find how ``aligned'' different offsets are. Returns the
+;;; number of low-order 0 bits, up to MAX-ALIGNMENT.
 (defun find-alignment (offset)
   (dotimes (i max-alignment max-alignment)
     (when (logbitp i offset)
       (return i))))
 
-;;; Emit a postit. The function will be called as a back-patch with the
-;;; position the following instruction is finally emitted. Postits do not
-;;; interfere at all with scheduling.
+;;; Emit a postit. The function will be called as a back-patch with
+;;; the position the following instruction is finally emitted. Postits
+;;; do not interfere at all with scheduling.
 (defun %emit-postit (segment function)
   (push function (segment-postits segment))
   (values))
 \f
 ;;;; output compression/position assignment stuff
 
-;;; Grovel though all the annotations looking for choosers. When we find
-;;; a chooser, invoke the maybe-shrink function. If it returns T, it output
-;;; some other byte sequence.
+;;; Grovel though all the annotations looking for choosers. When we
+;;; find a chooser, invoke the maybe-shrink function. If it returns T,
+;;; it output some other byte sequence.
 (defun compress-output (segment)
   (dotimes (i 5) ; it better not take more than one or two passes.
     (let ((delta 0))
              (setf prev remaining))))
           ((alignment-p note)
            (unless (zerop (alignment-size note))
-             ;; Re-emit the alignment, letting it collapse if we know anything
-             ;; more about the alignment guarantees of the segment.
+             ;; Re-emit the alignment, letting it collapse if we know
+             ;; anything more about the alignment guarantees of the
+             ;; segment.
              (let ((index (alignment-index note)))
                (setf (segment-current-index segment) index)
                (setf (segment-current-posn segment) posn)
       (decf (segment-final-posn segment) delta)))
   (values))
 
-;;; Grovel over segment, filling in any backpatches. If any choosers are left
-;;; over, we need to emit their worst case varient.
+;;; Grovel over segment, filling in any backpatches. If any choosers
+;;; are left over, we need to emit their worst case varient.
 (defun process-back-patches (segment)
   (do* ((prev nil)
        (remaining (segment-annotations segment) next)
 \f
 ;;;; interface to the rest of the compiler
 
-;;; This holds the current segment while assembling. Use ASSEMBLE to change
-;;; it.
+;;; This holds the current segment while assembling. Use ASSEMBLE to
+;;; change it.
 ;;;
 ;;; The double asterisks in the name are intended to suggest that this
-;;; isn't just any old special variable, it's an extra-special variable,
-;;; because sometimes MACROLET is used to bind it. So be careful out there..
+;;; isn't just any old special variable, it's an extra-special
+;;; variable, because sometimes MACROLET is used to bind it. So be
+;;; careful out there..
 (defvar **current-segment**)
 
-;;; Just like **CURRENT-SEGMENT**, except this holds the current vop. Used only
-;;; to keep track of which vops emit which insts.
+;;; Just like **CURRENT-SEGMENT**, except this holds the current vop.
+;;; Used only to keep track of which vops emit which insts.
 ;;;
 ;;; The double asterisks in the name are intended to suggest that this
-;;; isn't just any old special variable, it's an extra-special variable,
-;;; because sometimes MACROLET is used to bind it. So be careful out there..
+;;; isn't just any old special variable, it's an extra-special
+;;; variable, because sometimes MACROLET is used to bind it. So be
+;;; careful out there..
 (defvar **current-vop** nil)
 
-;;; We also symbol-macrolet **CURRENT-SEGMENT** to a local holding the segment
-;;; so uses of **CURRENT-SEGMENT** inside the body don't have to keep
-;;; dereferencing the symbol. Given that ASSEMBLE is the only interface to
-;;; **CURRENT-SEGMENT**, we don't have to worry about the special value
-;;; becomming out of sync with the lexical value. Unless some bozo closes over
-;;; it, but nobody does anything like that...
+;;; We also SYMBOL-MACROLET **CURRENT-SEGMENT** to a local holding the
+;;; segment so uses of **CURRENT-SEGMENT** inside the body don't have
+;;; to keep dereferencing the symbol. Given that ASSEMBLE is the only
+;;; interface to **CURRENT-SEGMENT**, we don't have to worry about the
+;;; special value becomming out of sync with the lexical value. Unless
+;;; some bozo closes over it, but nobody does anything like that...
 ;;;
-;;; FIXME: The way this macro uses MACROEXPAND internally breaks my old
-;;; assumptions about macros which are needed both in the host and the target.
-;;; (This is more or less the same way that PUSH-IN, DELETEF-IN, and
-;;; DEF-BOOLEAN-ATTRIBUTE break my old assumptions, except that they used
-;;; GET-SETF-EXPANSION instead of MACROEXPAND to do the dirty deed.) The
-;;; quick and dirty "solution" here is the same as there: use cut and
-;;; paste to duplicate the defmacro in a
-;;;   (SB!INT:DEF!MACRO FOO (..) .. CL:MACROEXPAND ..)
-;;;   #+SB-XC-HOST
-;;;   (DEFMACRO FOO (..) .. SB!XC:MACROEXPAND ..)
-;;; idiom. This is disgusting and unmaintainable, and there are obviously
-;;; better solutions and maybe even good solutions, but I'm disinclined to
+;;; FIXME: The way this macro uses MACROEXPAND internally breaks my
+;;; old assumptions about macros which are needed both in the host and
+;;; the target. (This is more or less the same way that PUSH-IN,
+;;; DELETEF-IN, and DEF-BOOLEAN-ATTRIBUTE break my old assumptions,
+;;; except that they used GET-SETF-EXPANSION instead of MACROEXPAND to
+;;; do the dirty deed.) The quick and dirty "solution" here is the
+;;; same as there: use cut and paste to duplicate the defmacro in a
+;;; (SB!INT:DEF!MACRO FOO (..) .. CL:MACROEXPAND ..) #+SB-XC-HOST
+;;; (DEFMACRO FOO (..) .. SB!XC:MACROEXPAND ..) idiom. This is
+;;; disgusting and unmaintainable, and there are obviously better
+;;; solutions and maybe even good solutions, but I'm disinclined to
 ;;; hunt for good solutions until the system works and I can test them
 ;;; in isolation.
 (sb!int:def!macro assemble ((&optional segment vop &key labels) &body body
          (t
           `(,inst **current-segment** **current-vop** ,@args)))))
 
-;;; Note: The need to capture SYMBOL-MACROLET bindings of **CURRENT-SEGMENT*
-;;; and **CURRENT-VOP** prevents this from being an ordinary function.
+;;; Note: The need to capture SYMBOL-MACROLET bindings of
+;;; **CURRENT-SEGMENT* and **CURRENT-VOP** prevents this from being an
+;;; ordinary function.
 (defmacro emit-label (label)
   #!+sb-doc
   "Emit LABEL at this location in the current segment."
   `(%emit-label **current-segment** **current-vop** ,label))
 
-;;; Note: The need to capture SYMBOL-MACROLET bindings of **CURRENT-SEGMENT*
-;;; prevents this from being an ordinary function.
+;;; Note: The need to capture SYMBOL-MACROLET bindings of
+;;; **CURRENT-SEGMENT* prevents this from being an ordinary function.
 (defmacro emit-postit (function)
   `(%emit-postit **current-segment** ,function))
 
-;;; Note: The need to capture SYMBOL-MACROLET bindings of **CURRENT-SEGMENT*
-;;; and **CURRENT-VOP** prevents this from being an ordinary function.
+;;; Note: The need to capture SYMBOL-MACROLET bindings of
+;;; **CURRENT-SEGMENT* and **CURRENT-VOP** prevents this from being an
+;;; ordinary function.
 (defmacro align (bits &optional (fill-byte 0))
   #!+sb-doc
   "Emit an alignment restriction to the current segment."
   (process-back-patches segment)
   (segment-final-posn segment))
 
-;;; Call FUNCTION on all the stuff accumulated in SEGMENT. FUNCTION should
-;;; accept a single vector argument. It will be called zero or more times
-;;; on vectors of the appropriate byte type. The concatenation of the
-;;; vector arguments from all the calls is the contents of SEGMENT.
+;;; Call FUNCTION on all the stuff accumulated in SEGMENT. FUNCTION
+;;; should accept a single vector argument. It will be called zero or
+;;; more times on vectors of the appropriate byte type. The
+;;; concatenation of the vector arguments from all the calls is the
+;;; contents of SEGMENT.
 ;;;
-;;; KLUDGE: This implementation is sort of slow and gross, calling FUNCTION
-;;; repeatedly and consing a fresh vector for its argument each time. It might
-;;; be possible to make a more efficient version by making FINALIZE-SEGMENT do
-;;; all the compacting currently done by this function: then this function
-;;; could become trivial and fast, calling FUNCTION once on the entire
-;;; compacted segment buffer. -- WHN 19990322
+;;; KLUDGE: This implementation is sort of slow and gross, calling
+;;; FUNCTION repeatedly and consing a fresh vector for its argument
+;;; each time. It might be possible to make a more efficient version
+;;; by making FINALIZE-SEGMENT do all the compacting currently done by
+;;; this function: then this function could become trivial and fast,
+;;; calling FUNCTION once on the entire compacted segment buffer. --
+;;; WHN 19990322
 (defun on-segment-contents-vectorly (segment function)
   (let ((buffer (segment-buffer segment))
        (i0 0))
       (frob i0 (segment-final-index segment))))
   (values))
 
-;;; Write the code accumulated in SEGMENT to STREAM, and return the number of
-;;; bytes written.
+;;; Write the code accumulated in SEGMENT to STREAM, and return the
+;;; number of bytes written.
 (defun write-segment-contents (segment stream)
   (let ((result 0))
     (declare (type index result))
 \f
 ;;;; interface to the instruction set definition
 
-;;; Define a function named NAME that merges its arguments into a single
-;;; integer and then emits the bytes of that integer in the correct order
-;;; based on the endianness of the target-backend.
+;;; Define a function named NAME that merges its arguments into a
+;;; single integer and then emits the bytes of that integer in the
+;;; correct order based on the endianness of the target-backend.
 (defmacro define-bitfield-emitter (name total-bits &rest byte-specs)
   (sb!int:collect ((arg-names) (arg-types))
     (let* ((total-bits (eval total-bits))
                                 (cdr option-spec)))))
                 pdefs))
          (:printer-list
-          ;; same as :PRINTER, but is EVALed first, and is a list of printers
+          ;; same as :PRINTER, but is EVALed first, and is a list of
+          ;; printers
           (push
            (eval
             `(eval
           (let ((,postits (segment-postits ,segment-name)))
             (setf (segment-postits ,segment-name) nil)
             (symbol-macrolet
-                (;; Apparently this binding is intended to keep anyone from
-                 ;; accidentally using **CURRENT-SEGMENT** within the body
-                 ;; of the emitter. The error message sorta suggests that
-                 ;; this can happen accidentally by including one emitter
-                 ;; inside another. But I dunno.. -- WHN 19990323
+                (;; Apparently this binding is intended to keep
+                 ;; anyone from accidentally using
+                 ;; **CURRENT-SEGMENT** within the body of the
+                 ;; emitter. The error message sorta suggests that
+                 ;; this can happen accidentally by including one
+                 ;; emitter inside another. But I dunno.. -- WHN
+                 ;; 19990323
                  (**current-segment**
                   ;; FIXME: I can't see why we have to use
                   ;;   (MACROLET ((LOSE () (ERROR ..))) (LOSE))
index bef3289..b3b9457 100644 (file)
 ;;; We can always use Multiple-Value-Bind, since the macro is clever about
 ;;; binding a single variable.
 (defun make-type-check-form (types)
-  (collect ((temps))
-    (dotimes (i (length types))
-      (temps (gensym)))
-
-    `(multiple-value-bind ,(temps)
-                         'dummy
+  (let ((temps (make-gensym-list (length types))))
+    `(multiple-value-bind ,temps 'dummy
        ,@(mapcar #'(lambda (temp type)
                     (let* ((spec
                             (let ((*unparse-function-type-simplify* t))
                          (%type-check-error
                           ,temp
                           ',(type-specifier (third type))))))
-                (temps) types)
-       (values ,@(temps)))))
+                temps
+                types)
+       (values ,@temps))))
 
 ;;; Splice in explicit type check code immediately before the node which is
 ;;; Cont's Dest. This code receives the value(s) that were being passed to
index 0e02d0f..fe56d65 100644 (file)
@@ -12,7 +12,7 @@
 (file-comment
  "$Header$")
 
-(defmacro sb!xc:deftype (name arglist &body body)
+(def!macro sb!xc:deftype (name arglist &body body)
   #!+sb-doc
   "Define a new type, with syntax like DEFMACRO."
   (unless (symbolp name)
index a7ec03b..8cfaea5 100644 (file)
           (eq (car form) 'function))
       ;; a function def
       (let ((wrapper-name (symbolicate prefix "-" arg-name "-WRAPPER"))
-           (wrapper-args nil))
-       (dotimes (i (length funargs))
-         (push (gensym) wrapper-args))
+           (wrapper-args (make-gensym-list (length funargs))))
        (values `#',wrapper-name
                `(defun ,wrapper-name ,wrapper-args
                   (funcall ,form ,@wrapper-args))))
                                    arg ,args-var ',name)))
                             ,args-var))))))))))
 
-;;; FIXME: old CMU CL version, doesn't work with SBCL bootstrapping
-;;; scheme, kept around for reference until I get the new sbcl-0.6.4
-;;; version to work, then can be deleted
-#|
-(defun gen-format-def-form (header descrips &optional (evalp t))
-  #!+sb-doc
-  "Generate a form to define an instruction format. See
-  DEFINE-INSTRUCTION-FORMAT for more info."
-  (when (atom header)
-    (setf header (list header)))
-  (destructuring-bind (name length &key default-printer include) header
-    (let ((args-var (gensym))
-         (length-var (gensym))
-         (all-wrapper-defs nil)
-         (arg-count 0))
-      (collect ((arg-def-forms))
-       (dolist (descrip descrips)
-         (let ((name (pop descrip)))
-           (multiple-value-bind (descrip wrapper-defs)
-               (munge-fun-refs
-                descrip evalp t (format nil "~:@(~A~)-~D" name arg-count))
-             (arg-def-forms
-              (update-args-form args-var `',name descrip evalp length-var))
-             (setf all-wrapper-defs
-                   (nconc wrapper-defs all-wrapper-defs)))
-           (incf arg-count)))
-       `(progn
-          ,@all-wrapper-defs
-          (eval-when (:compile-toplevel :execute)
-            (let ((,length-var ,length)
-                  (,args-var
-                   ,(and include
-                         `(copy-list
-                           (format-args
-                            (format-or-lose ,include))))))
-              ,@(arg-def-forms)
-              (setf (gethash ',name *disassem-inst-formats*)
-                    (make-instruction-format
-                     :name ',name
-                     :length (bits-to-bytes ,length-var)
-                     :default-printer ,(maybe-quote evalp default-printer)
-                     :args ,args-var))
-              (eval
-               `(progn
-                  ,@(mapcar #'(lambda (arg)
-                                (when (arg-fields arg)
-                                  (gen-arg-access-macro-def-form
-                                   arg ,args-var ',name)))
-                            ,args-var))))))))))
-|#
-
 ;;; FIXME: probably needed only at build-the-system time, not in
 ;;; final target system
 (defun modify-or-add-arg (arg-name
               ;; just use the same as the forms
               (setq vars nil))
              (t
-              (setq vars nil)
-              (dotimes (i (length forms))
-                (push (gensym) vars))))
+              (setq vars (make-gensym-list (length forms)))))
        (set-arg-temps vars forms arg kind funstate)))
     (or vars forms)))
 
index 08c5b95..62f3561 100644 (file)
 (sb!int:file-comment
   "$Header$")
 
-;;; FIXME: It might make sense to use SB!VM:BYTE-FOO values here instead of the
-;;; various ASSEMBLY-UNIT-FOO things. One problem: BYTE is exported from the CL
-;;; package, so ANSI says that we're not supposed to be attaching any new
-;;; meanings to it. Perhaps rename SB!VM:BYTE-FOO to SB!VM:VMBYTE-FOO or
-;;; SB!VM:VM-BYTE-FOO, and then define the SB!VM:VMBYTE or SB!VM:VM-BYTE types?
+;;; FIXME: It might make sense to use SB!VM:BYTE-FOO values here
+;;; instead of the various ASSEMBLY-UNIT-FOO things, and then define a
+;;; BYTE type. One problem: BYTE is exported from the CL package, so
+;;; ANSI says that we're not supposed to be attaching any new meanings
+;;; to it. Perhaps rename SB!VM:BYTE-FOO to SB!VM:VMBYTE-FOO or
+;;; SB!VM:VM-BYTE-FOO, and then define the SB!VM:VMBYTE or
+;;; SB!VM:VM-BYTE types?
 ;;;
 ;;; If this was done, some of this file could go away, and the rest
-;;; could probably be merged back into assem.lisp. (This file was created
-;;; simply in order to move the ASSEMBLY-UNIT-related definitions before
-;;; compiler/generic/core.lisp in the build sequence.
-
-;;; ASSEMBLY-UNIT-BITS -- the number of bits in the minimum assembly unit,
-;;; (also refered to as a ``byte''). Hopefully, different instruction
-;;; sets won't require changing this.
+;;; could probably be merged back into assem.lisp. (This file was
+;;; created simply in order to move the ASSEMBLY-UNIT-related
+;;; definitions before compiler/generic/core.lisp in the build
+;;; sequence.)
+
+;;; ASSEMBLY-UNIT-BITS -- the number of bits in the minimum assembly
+;;; unit, (also refered to as a ``byte''). Hopefully, different
+;;; instruction sets won't require changing this.
 (defconstant assembly-unit-bits 8)
 (defconstant assembly-unit-mask (1- (ash 1 assembly-unit-bits)))
 
 
 ;;; Some functions which accept assembly units can meaningfully accept
 ;;; signed values with the same number of bits and silently munge them
-;;; into appropriate unsigned values. (This is handy behavior e.g. when
-;;; assembling branch instructions on the X86.)
+;;; into appropriate unsigned values. (This is handy behavior e.g.
+;;; when assembling branch instructions on the X86.)
 (deftype possibly-signed-assembly-unit ()
   `(or assembly-unit
        (signed-byte ,assembly-unit-bits)))
 
-;;; the maximum alignment we can guarantee given the object
-;;; format. If the loader only loads objects 8-byte aligned, we can't do
-;;; any better then that ourselves.
+;;; the maximum alignment we can guarantee given the object format. If
+;;; the loader only loads objects 8-byte aligned, we can't do any
+;;; better then that ourselves.
 (defconstant max-alignment 3)
 
 (deftype alignment ()
   `(integer 0 ,max-alignment))
-
-;;; the maximum an index will ever become. Well, actually,
-;;; just a bound on it so we can define a type. There is no real hard
-;;; limit on indexes, but we will run out of memory sometime.
-(defconstant max-index (1- most-positive-fixnum))
-
-(deftype index ()
-  `(integer 0 ,max-index))
-
-;;; like MAX-INDEX, except for positions
-(defconstant max-posn (1- most-positive-fixnum))
-
-(deftype posn ()
-  `(integer 0 ,max-posn))
-
index c82296e..6e46173 100644 (file)
@@ -38,8 +38,6 @@
 ;;;; somewhere else, not "early-c", since they're after all not part
 ;;;; of the compiler.
 
-(def!type sb!kernel:index () `(integer 0 (,sb!xc:array-dimension-limit)))
-
 ;;; the type of LAYOUT-DEPTHOID slot values
 (def!type sb!kernel::layout-depthoid () '(or index (integer -1 -1)))
 
index d4c389b..9cb9f3b 100644 (file)
   (flushable)
   :derive-type (result-type-specifier-nth-arg 1))
 
-(defknown map (type-specifier callable sequence &rest sequence) consed-sequence
+(defknown (map %map) (type-specifier callable sequence &rest sequence) consed-sequence
   (flushable call)
 ; :DERIVE-TYPE 'TYPE-SPEC-ARG1 ? Nope... (MAP NIL ...) returns NULL, not NIL.
   )
 (defknown %map-to-nil-on-vector (callable vector) null (flushable call))
 (defknown %map-to-nil-on-sequence (callable sequence) null (flushable call))
 
-;;; returns predicate result...
+;;; returns the result from the predicate...
 (defknown some (callable sequence &rest sequence) t
   (foldable flushable call))
 
   (values (simple-array * (*)) index index index)
   (foldable flushable))
 (defknown %set-symbol-package (symbol t) t (unsafe))
-(defknown %coerce-name-to-function (t) function (flushable))
+(defknown %coerce-name-to-function ((or symbol cons)) function (flushable))
+(defknown %coerce-callable-to-function (callable) function (flushable))
 
 ;;; Structure slot accessors or setters are magically "known" to be
 ;;; these functions, although the var remains the Slot-Accessor
index 2f2755f..d588f17 100644 (file)
                           (and dest (not (if-p dest))))))
                (let ((name (leaf-name leaf)))
                  (when (symbolp name)
-                   (let ((dums (loop repeat (length (combination-args call))
-                                     collect (gensym))))
+                   (let ((dums (make-gensym-list (length
+                                                  (combination-args call)))))
                      (transform-call call
                                      `(lambda ,dums
                                         (,name ,@dums))))))))))))
         (table (component-failed-optimizations *component-being-compiled*))
         (flame (if (transform-important transform)
                    (policy node (>= speed brevity))
-                 (policy node (> speed brevity))))
+                   (policy node (> speed brevity))))
         (*compiler-error-context* node))
     (cond ((not (member (transform-when transform)
                        (if *byte-compiling*
        (careful-call fun args call "constant folding")
       (if (not win)
        (setf (combination-kind call) :error)
-       (let ((dummies (loop repeat (length args)
-                            collect (gensym))))
+       (let ((dummies (make-gensym-list (length args))))
          (transform-call
           call
           `(lambda ,dummies
                           (t nil))))
          (when count
            (with-ir1-environment node
-             (let* ((dums (loop repeat count collect (gensym)))
+             (let* ((dums (make-gensym-list count))
                     (ignore (gensym))
                     (fun (ir1-convert-lambda
                           `(lambda (&optional ,@dums &rest ,ignore)
     (give-up-ir1-transform))
   (setf (node-derived-type node) *wild-type*)
   (if vals
-      (let ((dummies (loop repeat (1- (length vals))
-                      collect (gensym))))
+      (let ((dummies (make-gensym-list (length (cdr vals)))))
        `(lambda (val ,@dummies)
           (declare (ignore ,@dummies))
           val))
index 9e7cd2e..89c17f6 100644 (file)
 
   (values))
 
-;;; Called by IR1-Convert-Hairy-Args when we run into a rest or keyword arg.
-;;; The arguments are similar to that function, but we split off any rest arg
-;;; and pass it in separately. Rest is the rest arg var, or NIL if there is no
-;;; rest arg. Keys is a list of the keyword argument vars.
+;;; Called by IR1-Convert-Hairy-Args when we run into a rest or
+;;; keyword arg. The arguments are similar to that function, but we
+;;; split off any rest arg and pass it in separately. Rest is the rest
+;;; arg var, or NIL if there is no rest arg. Keys is a list of the
+;;; keyword argument vars.
 ;;;
 ;;; When there are keyword arguments, we introduce temporary gensym
-;;; variables to hold the values while keyword defaulting is in progress to get
-;;; the required sequential binding semantics.
+;;; variables to hold the values while keyword defaulting is in
+;;; progress to get the required sequential binding semantics.
 ;;;
 ;;; This gets interesting mainly when there are keyword arguments with
-;;; supplied-p vars or non-constant defaults. In either case, pass in a
-;;; supplied-p var. If the default is non-constant, we introduce an IF in the
-;;; main entry that tests the supplied-p var and decides whether to evaluate
-;;; the default or not. In this case, the real incoming value is NIL, so we
-;;; must union NULL with the declared type when computing the type for the main
-;;; entry's argument.
+;;; supplied-p vars or non-constant defaults. In either case, pass in
+;;; a supplied-p var. If the default is non-constant, we introduce an
+;;; IF in the main entry that tests the supplied-p var and decides
+;;; whether to evaluate the default or not. In this case, the real
+;;; incoming value is NIL, so we must union NULL with the declared
+;;; type when computing the type for the main entry's argument.
 (defun ir1-convert-more (res default-vars default-vals entry-vars entry-vals
                             rest more-context more-count keys supplied-p-p
                             body aux-vars aux-vals cont)
             (default (arg-info-default info))
             (hairy-default (not (sb!xc:constantp default)))
             (supplied-p (arg-info-supplied-p info))
-            (n-val (make-symbol (format nil ; FIXME: GENSYM?
+            (n-val (make-symbol (format nil
                                         "~A-DEFAULTING-TEMP"
                                         (leaf-name key))))
             (key-type (leaf-type key))
 ;;; (not symbols). %FUNCALL is used directly in some places where the
 ;;; call should always be open-coded even if FUNCALL is :NOTINLINE.
 (deftransform funcall ((function &rest args) * * :when :both)
-  (collect ((arg-names))
-    (dolist (arg args)
-      (declare (ignore arg))
-      (arg-names (gensym "FUNCALL-ARG-NAMES-")))
-    `(lambda (function ,@(arg-names))
+  (let ((arg-names (make-gensym-list (length args))))
+    `(lambda (function ,@arg-names)
        (%funcall ,(if (csubtypep (continuation-type function)
                                 (specifier-type 'function))
                      'function
-                     '(if (functionp function)
-                          function
-                          (%coerce-name-to-function function)))
-                ,@(arg-names)))))
+                     '(%coerce-callable-to-function function))
+                ,@arg-names))))
 
 (def-ir1-translator %funcall ((function &rest args) start cont)
   (let ((fun-cont (make-continuation)))
       `(%funcall ,function ,@args)
       (values nil t)))
 
-(deftransform %coerce-name-to-function ((thing) * * :when :both)
-  (give-up-ir1-transform
-   "might be a symbol, so must call FDEFINITION at runtime"))
+(deftransform %coerce-callable-to-function ((thing) (function) *
+                                           :when :both
+                                           :important t)
+  "optimize away possible call to FDEFINITION at runtime"
+  'thing)
 \f
 ;;;; symbol macros
 
     (ir1-convert start fun-cont
                 (if (and (consp fun) (eq (car fun) 'function))
                     fun
-                    (once-only ((fun fun))
-                      `(if (functionp ,fun)
-                           ,fun
-                           (%coerce-name-to-function ,fun)))))
+                    `(%coerce-callable-to-function ,fun)))
     (setf (continuation-dest fun-cont) node)
     (assert-continuation-type fun-cont
                              (specifier-type '(or function symbol)))
index eb93a01..f08add4 100644 (file)
   (etypecase fun
     (clambda
      (let ((nargs (length (lambda-vars fun)))
-          (n-supplied (gensym)))
-       (collect ((temps))
-        (dotimes (i nargs)
-          (temps (gensym)))
-        `(lambda (,n-supplied ,@(temps))
-           (declare (type index ,n-supplied))
-           ,(if (policy nil (zerop safety))
-                `(declare (ignore ,n-supplied))
-                `(%verify-argument-count ,n-supplied ,nargs))
-           (%funcall ,fun ,@(temps))))))
+          (n-supplied (gensym))
+          (temps (make-gensym-list (length (lambda-vars fun)))))
+       `(lambda (,n-supplied ,@temps)
+         (declare (type index ,n-supplied))
+         ,(if (policy nil (zerop safety))
+              `(declare (ignore ,n-supplied))
+              `(%verify-argument-count ,n-supplied ,nargs))
+         (%funcall ,fun ,@temps))))
     (optional-dispatch
      (let* ((min (optional-dispatch-min-args fun))
            (max (optional-dispatch-max-args fun))
            (more (optional-dispatch-more-entry fun))
-           (n-supplied (gensym)))
-       (collect ((temps)
-                (entries))
-        (dotimes (i max)
-          (temps (gensym)))
-
+           (n-supplied (gensym))
+           (temps (make-gensym-list max)))
+       (collect ((entries))
         (do ((eps (optional-dispatch-entry-points fun) (rest eps))
              (n min (1+ n)))
             ((null eps))
           (entries `((= ,n-supplied ,n)
-                     (%funcall ,(first eps) ,@(subseq (temps) 0 n)))))
-
-        `(lambda (,n-supplied ,@(temps))
+                     (%funcall ,(first eps) ,@(subseq temps 0 n)))))
+        `(lambda (,n-supplied ,@temps)
            ;; FIXME: Make sure that INDEX type distinguishes between target
            ;; and host. (Probably just make the SB!XC:DEFTYPE different from
            ;; CL:DEFTYPE.)
                           (n-count (gensym)))
                       `(multiple-value-bind (,n-context ,n-count)
                            (%more-arg-context ,n-supplied ,max)
-                         (%funcall ,more ,@(temps) ,n-context ,n-count))))))
+                         (%funcall ,more ,@temps ,n-context ,n-count))))))
             (t
              (%argument-count-error ,n-supplied)))))))))
 
         (args (combination-args call))
         (more (nthcdr max args))
         (flame (policy call (or (> speed brevity) (> space brevity))))
-        (loser nil))
-    (collect ((temps)
-             (more-temps)
-             (ignores)
+        (loser nil)
+        (temps (make-gensym-list max))
+        (more-temps (make-gensym-list (length more))))
+    (collect ((ignores)
              (supplied)
              (key-vars))
 
               (setf (basic-combination-kind call) :error)
               (return-from convert-more-call))))))
 
-      (dotimes (i max)
-       (temps (gensym "FIXED-ARG-TEMP-")))
-
-      (dotimes (i (length more))
-       (more-temps (gensym "MORE-ARG-TEMP-")))
-
       (when (optional-dispatch-keyp fun)
        (when (oddp (length more))
          (compiler-warning "function called with odd number of ~
          (return-from convert-more-call))
 
        (do ((key more (cddr key))
-            (temp (more-temps) (cddr temp)))
+            (temp more-temps (cddr temp)))
            ((null key))
          (let ((cont (first key)))
            (unless (constant-continuation-p cont)
 
       (collect ((call-args))
        (do ((var arglist (cdr var))
-            (temp (temps) (cdr temp)))
+            (temp temps (cdr temp)))
            (())
          (let ((info (lambda-var-arg-info (car var))))
            (if info
                   (when (arg-info-supplied-p info)
                     (call-args t)))
                  (:rest
-                  (call-args `(list ,@(more-temps)))
+                  (call-args `(list ,@more-temps))
                   (return))
                  (:keyword
                   (return)))
              (call-args (not (null temp))))))
 
        (convert-hairy-fun-entry ref call (optional-dispatch-main-entry fun)
-                                (append (temps) (more-temps))
+                                (append temps more-temps)
                                 (ignores) (call-args)))))
 
   (values))
index ac826c1..061658d 100644 (file)
             `((setf (symbol-function ',name)
                     (lambda (&rest rest)
                       (declare (ignore rest))
-                      (error "Can't FUNCALL the SYMBOL-FUNCTION of ~
-                              special forms.")))))))))
+                      (error "can't FUNCALL the SYMBOL-FUNCTION of ~
+                              special forms")))))))))
 
 ;;; Similar to DEF-IR1-TRANSLATOR, except that we pass if the syntax is
 ;;; invalid.
     (dolist (name names)
       (let ((mask (cdr (assoc name alist))))
        (unless mask
-         (error "Unknown attribute name: ~S." name))
+         (error "unknown attribute name: ~S" name))
        (res mask)))
     (res)))
 
   for various optimizers that the function might have."
   (when (and (intersection attributes '(any call unwind))
             (intersection attributes '(movable)))
-    (error "Function cannot have both good and bad attributes: ~S" attributes))
+    (error "function cannot have both good and bad attributes: ~S" attributes))
 
   `(%defknown ',(if (and (consp name)
                         (not (eq (car name) 'setf)))
 
   If supplied, Result-Form is the value to return."
   (unless (member ends '(nil :head :tail :both))
-    (error "Losing Ends value: ~S." ends))
+    (error "losing ENDS value: ~S" ends))
   (let ((n-component (gensym))
        (n-tail (gensym)))
     `(let* ((,n-component ,component)
   "Do-Blocks-Backwards (Block-Var Component [Ends] [Result-Form]) {Declaration}* {Form}*
   Like Do-Blocks, only iterate over the blocks in reverse order."
   (unless (member ends '(nil :head :tail :both))
-    (error "Losing Ends value: ~S." ends))
+    (error "losing ENDS value: ~S" ends))
   (let ((n-component (gensym))
        (n-head (gensym)))
     `(let* ((,n-component ,component)
   Next. Key, Test and Test-Not are the same as for generic sequence
   functions."
   (when (and test-p not-p)
-    (error "It's silly to supply both :Test and :Test-Not."))
+    (error "It's silly to supply both :TEST and :TEST-NOT arguments."))
   (if not-p
       (do ((current list (funcall next current)))
          ((null current) nil)
   linked by the accessor function Next. Key, Test and Test-Not are the same as
   for generic sequence functions."
   (when (and test-p not-p)
-    (error "Silly to supply both :Test and :Test-Not."))
+    (error "It's silly to supply both :TEST and :TEST-NOT arguments."))
   (if not-p
       (do ((current list (funcall next current))
           (i 0 (1+ i)))
index 47fca9c..f00d8c3 100644 (file)
 \f
 ;;;; mapping onto sequences: the MAP function
 
-;;; Try to compile MAP efficiently when we can determine sequence
+;;; MAP is %MAP plus a check to make sure that any length specified in
+;;; the result type matches the actual result. We also wrap it in a
+;;; TRULY-THE for the most specific type we can determine.
+(deftransform map ((result-type-arg fun &rest seqs) * * :node node)
+  (let* ((seq-names (make-gensym-list (length seqs)))
+        (bare `(%map result-type-arg fun ,@seq-names))
+        (constant-result-type-arg-p (constant-continuation-p result-type-arg))
+        ;; what we know about the type of the result. (Note that the
+        ;; "result type" argument is not necessarily the type of the
+        ;; result, since NIL means the result has NULL type.)
+        (result-type (if (not constant-result-type-arg-p)
+                         'consed-sequence
+                         (let ((result-type-arg-value
+                                (continuation-value result-type-arg)))
+                           (if (null result-type-arg-value)
+                               'null
+                               result-type-arg-value)))))
+    `(lambda (result-type-arg fun ,@seq-names)
+       (truly-the ,result-type
+        ,(cond ((policy node (> speed safety))
+                bare)
+               ((not constant-result-type-arg-p)
+                `(sequence-of-checked-length-given-type ,bare
+                                                        result-type-arg))
+               (t
+                (let ((result-ctype (specifier-type result-type)))
+                  (if (array-type-p result-ctype)
+                      (let* ((dims (array-type-dimensions result-ctype))
+                             (dim (first dims)))
+                        (if (eq dim '*)
+                            bare
+                            `(vector-of-checked-length-given-length ,bare
+                                                                    ,dim)))
+                      bare))))))))
+
+;;; Try to compile %MAP efficiently when we can determine sequence
 ;;; argument types at compile time.
 ;;;
 ;;; Note: This transform was written to allow open coding of
 ;;; handle that case more efficiently, but it's left as an exercise to
 ;;; the reader, because the code is complicated enough already and I
 ;;; don't happen to need that functionality right now. -- WHN 20000410
-;;;
-;;; FIXME: Now that we have this transform, we should be able
-;;; to get rid of the macros MAP-TO-LIST, MAP-TO-SIMPLE,
-;;; and MAP-FOR-EFFECT.
-(deftransform map ((result-type fun &rest seqs) * *)
+(deftransform %map ((result-type fun &rest seqs) * * :policy (>= speed space))
   "open code"
   (unless seqs (abort-ir1-transform "no sequence args"))
   (unless (constant-continuation-p result-type)
                   (t (give-up-ir1-transform
                       "internal error: unexpected sequence type"))))
            (t
-            (let* ((seq-args (mapcar (lambda (seq)
-                                       (declare (ignore seq))
-                                       (gensym "SEQ"))
-                                     seqs))
+            (let* ((seq-args (make-gensym-list (length seqs)))
                    (index-bindingoids
                     (mapcar (lambda (seq-arg seq-supertype)
                               (let ((i (gensym "I"))) 
                 ;; of the &REST vars.)
                 `(lambda (result-type fun ,@seq-args)
                    (declare (ignore result-type))
-                   (do ((really-fun (if (functionp fun)
-                                        fun
-                                        (%coerce-name-to-function fun)))
+                   (do ((really-fun (%coerce-callable-to-function fun))
                         ,@index-bindingoids
                         (acc nil))
                    ((or ,@tests)
index 0492451..1b3eee6 100644 (file)
@@ -35,8 +35,7 @@
 
 ;;; Bind the values and make a closure that returns them.
 (def-source-transform constantly (value &rest values)
-  (let ((temps (loop repeat (1+ (length values))
-                    collect (gensym)))
+  (let ((temps (make-gensym-list (1+ (length values))))
        (dum (gensym)))
     `(let ,(loop for temp in temps and
                 value in (list* value values)
@@ -55,7 +54,7 @@
       (function-type-nargs (continuation-type fun))
     (cond
      ((and min (eql min max))
-      (let ((dums (loop repeat min collect (gensym))))
+      (let ((dums (make-gensym-list min)))
        `#'(lambda ,dums (not (funcall fun ,@dums)))))
      ((let* ((cont (node-cont node))
             (dest (continuation-dest cont)))
          ((not (policy nil (>= speed space) (>= speed cspeed)))
           (values nil t))
          (t
-          (collect ((vars))
-            (dotimes (i nargs) (vars (gensym)))
-            (do ((var (vars) next)
-                 (next (cdr (vars)) (cdr next))
+          (let ((vars (make-gensym-list nargs)))
+            (do ((var vars next)
+                 (next (cdr vars) (cdr next))
                  (result 't))
                 ((null next)
-                 `((lambda ,(vars) ,result) . ,args))
+                 `((lambda ,vars ,result) . ,args))
               (let ((v1 (first var)))
                 (dolist (v2 next)
                   (setq result `(if (,predicate ,v1 ,v2) nil ,result))))))))))
 ;;;; If the control string is a compile-time constant, then replace it
 ;;;; with a use of the FORMATTER macro so that the control string is
 ;;;; ``compiled.'' Furthermore, if the destination is either a stream
-;;;; or T and the control string is a function (i.e. formatter), then
-;;;; convert the call to format to just a funcall of that function.
+;;;; or T and the control string is a function (i.e. FORMATTER), then
+;;;; convert the call to FORMAT to just a FUNCALL of that function.
 
 (deftransform format ((dest control &rest args) (t simple-string &rest t) *
                      :policy (> speed space))
   (unless (constant-continuation-p control)
     (give-up-ir1-transform "The control string is not a constant."))
-  (let ((arg-names (mapcar #'(lambda (x) (declare (ignore x)) (gensym)) args)))
+  (let ((arg-names (make-gensym-list (length args))))
     `(lambda (dest control ,@arg-names)
        (declare (ignore control))
        (format dest (formatter ,(continuation-value control)) ,@arg-names))))
 
 (deftransform format ((stream control &rest args) (stream function &rest t) *
                      :policy (> speed space))
-  (let ((arg-names (mapcar #'(lambda (x) (declare (ignore x)) (gensym)) args)))
+  (let ((arg-names (make-gensym-list (length args))))
     `(lambda (stream control ,@arg-names)
        (funcall control stream ,@arg-names)
        nil)))
 
 (deftransform format ((tee control &rest args) ((member t) function &rest t) *
                      :policy (> speed space))
-  (let ((arg-names (mapcar #'(lambda (x) (declare (ignore x)) (gensym)) args)))
+  (let ((arg-names (make-gensym-list (length args))))
     `(lambda (tee control ,@arg-names)
        (declare (ignore tee))
        (funcall control *standard-output* ,@arg-names)