88a40d2603c4bdb9b8a453bd8e67552a4a5d75f5
[sbcl.git] / src / compiler / assem.lisp
1 ;;;; scheduling assembler
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
11
12 (in-package "SB!ASSEM")
13 \f
14 ;;;; assembly control parameters
15
16 (defvar *assem-scheduler-p* nil)
17 (declaim (type boolean *assem-scheduler-p*))
18
19 (defvar *assem-instructions* (make-hash-table :test 'equal))
20 (declaim (type hash-table *assem-instructions*))
21
22 (defvar *assem-max-locations* 0)
23 (declaim (type index *assem-max-locations*))
24 \f
25 ;;;; the SEGMENT structure
26
27 ;;; This structure holds the state of the assembler.
28 (defstruct (segment (:copier nil))
29   ;; the type of this segment (for debugging output and stuff)
30   (type :regular :type (member :regular :elsewhere))
31   ;; Ordinarily this is a vector where instructions are written. If
32   ;; the segment is made invalid (e.g. by APPEND-SEGMENT) then the
33   ;; vector can be replaced by NIL. This used to be an adjustable
34   ;; array, but we now do the array size management manually for
35   ;; performance reasons (as of 2006-05-13 hairy array operations
36   ;; are rather slow compared to simple ones).
37   (buffer (make-array 0 :element-type 'assembly-unit)
38           :type (or null (simple-array assembly-unit)))
39   ;; whether or not to run the scheduler. Note: if the instruction
40   ;; definitions were not compiled with the scheduler turned on, this
41   ;; has no effect.
42   (run-scheduler nil)
43   ;; If a function, then this is funcalled for each inst emitted with
44   ;; the segment, the VOP, the name of the inst (as a string), and the
45   ;; inst arguments.
46   (inst-hook nil :type (or function null))
47   ;; what position does this correspond to? Initially, positions and
48   ;; indexes are the same, but after we start collapsing choosers,
49   ;; positions can change while indexes stay the same.
50   (current-posn 0 :type index)
51   (%current-index 0 :type index)
52   ;; a list of all the annotations that have been output to this segment
53   (annotations nil :type list)
54   ;; a pointer to the last cons cell in the annotations list. This is
55   ;; so we can quickly add things to the end of the annotations list.
56   (last-annotation nil :type list)
57   ;; the number of bits of alignment at the last time we synchronized
58   (alignment max-alignment :type alignment)
59   ;; the position the last time we synchronized
60   (sync-posn 0 :type index)
61   ;; The posn and index everything ends at. This is not maintained
62   ;; while the data is being generated, but is filled in after.
63   ;; Basically, we copy CURRENT-POSN and CURRENT-INDEX so that we can
64   ;; trash them while processing choosers and back-patches.
65   (final-posn 0 :type index)
66   (final-index 0 :type index)
67   ;; *** State used by the scheduler during instruction queueing.
68   ;;
69   ;; a list of postits. These are accumulated between instructions.
70   (postits nil :type list)
71   ;; ``Number'' for last instruction queued. Used only to supply insts
72   ;; with unique sset-element-number's.
73   (inst-number 0 :type index)
74   ;; SIMPLE-VECTORs mapping locations to the instruction that reads them and
75   ;; instructions that write them
76   (readers (make-array *assem-max-locations* :initial-element nil)
77            :type simple-vector)
78   (writers (make-array *assem-max-locations* :initial-element nil)
79            :type simple-vector)
80   ;; The number of additional cycles before the next control transfer,
81   ;; or NIL if a control transfer hasn't been queued. When a delayed
82   ;; branch is queued, this slot is set to the delay count.
83   (branch-countdown nil :type (or null (and fixnum unsigned-byte)))
84   ;; *** These two slots are used both by the queuing noise and the
85   ;; scheduling noise.
86   ;;
87   ;; All the instructions that are pending and don't have any
88   ;; unresolved dependents. We don't list branches here even if they
89   ;; would otherwise qualify. They are listed above.
90   (emittable-insts-sset (make-sset) :type sset)
91   ;; list of queued branches. We handle these specially, because they
92   ;; have to be emitted at a specific place (e.g. one slot before the
93   ;; end of the block).
94   (queued-branches nil :type list)
95   ;; *** state used by the scheduler during instruction scheduling
96   ;;
97   ;; the instructions who would have had a read dependent removed if
98   ;; it were not for a delay slot. This is a list of lists. Each
99   ;; element in the top level list corresponds to yet another cycle of
100   ;; delay. Each element in the second level lists is a dotted pair,
101   ;; holding the dependency instruction and the dependent to remove.
102   (delayed nil :type list)
103   ;; The emittable insts again, except this time as a list sorted by depth.
104   (emittable-insts-queue nil :type list)
105   ;; Whether or not to collect dynamic statistics. This is just the same as
106   ;; *COLLECT-DYNAMIC-STATISTICS* but is faster to reference.
107   #!+sb-dyncount
108   (collect-dynamic-statistics nil))
109 (sb!c::defprinter (segment)
110   type)
111
112 (declaim (inline segment-current-index))
113 (defun segment-current-index (segment)
114   (segment-%current-index segment))
115
116 (defun (setf segment-current-index) (new-value segment)
117   (declare (type index new-value)
118            (type segment segment))
119   ;; FIXME: It would be lovely to enforce this, but first FILL-IN will
120   ;; need to be convinced to stop rolling SEGMENT-CURRENT-INDEX
121   ;; backwards.
122   ;;
123   ;; Enforce an observed regularity which makes it easier to think
124   ;; about what's going on in the (legacy) code: The segment never
125   ;; shrinks. -- WHN the reverse engineer
126   #+nil (aver (>= new-value (segment-current-index segment)))
127   (let* ((buffer (segment-buffer segment))
128          (new-buffer-size (length buffer)))
129     (declare (type (simple-array (unsigned-byte 8)) buffer)
130              (type index new-buffer-size))
131     ;; Make sure the array is big enough.
132     (when (<= new-buffer-size new-value)
133       (do ()
134           ((> new-buffer-size new-value))
135         ;; When we have to increase the size of the array, we want to
136         ;; roughly double the vector length: that way growing the array
137         ;; to size N conses only O(N) bytes in total. But just doubling
138         ;; the length would leave a zero-length vector unchanged. Hence,
139         ;; take the MAX with 1..
140         (setf new-buffer-size (max 1 (* 2 new-buffer-size))))
141       (let ((new-buffer (make-array new-buffer-size
142                                     :element-type '(unsigned-byte 8))))
143         (replace new-buffer buffer)
144         (setf (segment-buffer segment) new-buffer)))
145     ;; Now that the array has the intended next free byte, we can point to it.
146     (setf (segment-%current-index segment) new-value)))
147
148 ;;; Various functions (like BACK-PATCH-FUN or CHOOSER-WORST-CASE-FUN)
149 ;;; aren't cleanly parameterized, but instead use
150 ;;; SEGMENT-CURRENT-INDEX and/or SEGMENT-CURRENT-POSN as global
151 ;;; variables. So code which calls such functions needs to modify
152 ;;; SEGMENT-CURRENT-INDEX and SEGMENT-CURRENT-POSN. This is left over
153 ;;; from the old new-assem.lisp C-style code, and so all the
154 ;;; destruction happens to be done after other uses of these slots are
155 ;;; done and things basically work. However, (1) it's fundamentally
156 ;;; nasty, and (2) at least one thing doesn't work right: OpenMCL
157 ;;; properly points out that SUBSEQ's indices aren't supposed to
158 ;;; exceed its logical LENGTH, i.e. its FILL-POINTER, i.e.
159 ;;; SEGMENT-CURRENT-INDEX.
160 ;;;
161 ;;; As a quick fix involving minimal modification of legacy code,
162 ;;; we do such sets of SEGMENT-CURRENT-INDEX and SEGMENT-CURRENT-POSN
163 ;;; using this macro, which restores 'em afterwards.
164 ;;;
165 ;;; FIXME: It'd probably be better to cleanly parameterize things like
166 ;;; BACK-PATCH-FUN so we can avoid this nastiness altogether.
167 (defmacro with-modified-segment-index-and-posn ((segment index posn)
168                                                 &body body)
169   (with-unique-names (n-segment old-index old-posn)
170     `(let* ((,n-segment ,segment)
171             (,old-index (segment-current-index ,n-segment))
172             (,old-posn (segment-current-posn ,n-segment)))
173        (unwind-protect
174            (progn
175              (setf (segment-current-index ,n-segment) ,index
176                    (segment-current-posn ,n-segment) ,posn)
177              ,@body)
178          (setf (segment-current-index ,n-segment) ,old-index
179                (segment-current-posn ,n-segment) ,old-posn)))))
180 \f
181 ;;;; structures/types used by the scheduler
182
183 (!def-boolean-attribute instruction
184   ;; This attribute is set if the scheduler can freely flush this
185   ;; instruction if it thinks it is not needed. Examples are NOP and
186   ;; instructions that have no side effect not described by the
187   ;; writes.
188   flushable
189   ;; This attribute is set when an instruction can cause a control
190   ;; transfer. For test instructions, the delay is used to determine
191   ;; how many instructions follow the branch.
192   branch
193   ;; This attribute indicates that this ``instruction'' can be
194   ;; variable length, and therefore had better never be used in a
195   ;; branch delay slot.
196   variable-length)
197
198 (def!struct (instruction
199             (:include sset-element)
200             (:conc-name inst-)
201             (:constructor make-instruction (number emitter attributes delay))
202             (:copier nil))
203   ;; The function to envoke to actually emit this instruction. Gets called
204   ;; with the segment as its one argument.
205   (emitter (missing-arg) :type (or null function))
206   ;; The attributes of this instruction.
207   (attributes (instruction-attributes) :type sb!c:attributes)
208   ;; Number of instructions or cycles of delay before additional
209   ;; instructions can read our writes.
210   (delay 0 :type (and fixnum unsigned-byte))
211   ;; the maximum number of instructions in the longest dependency
212   ;; chain from this instruction to one of the independent
213   ;; instructions. This is used as a heuristic at to which
214   ;; instructions should be scheduled first.
215   (depth nil :type (or null (and fixnum unsigned-byte)))
216   ;; Note: When trying remember which of the next four is which, note
217   ;; that the ``read'' or ``write'' always refers to the dependent
218   ;; (second) instruction.
219   ;;
220   ;; instructions whose writes this instruction tries to read
221   (read-dependencies (make-sset) :type sset)
222   ;; instructions whose writes or reads are overwritten by this instruction
223   (write-dependencies (make-sset) :type sset)
224   ;; instructions which write what we read or write
225   (write-dependents (make-sset) :type sset)
226   ;; instructions which read what we write
227   (read-dependents (make-sset) :type sset))
228 #!+sb-show-assem (defvar *inst-ids* (make-hash-table :test 'eq))
229 #!+sb-show-assem (defvar *next-inst-id* 0)
230 (sb!int:def!method print-object ((inst instruction) stream)
231   (print-unreadable-object (inst stream :type t :identity t)
232     #!+sb-show-assem
233     (princ (or (gethash inst *inst-ids*)
234                (setf (gethash inst *inst-ids*)
235                      (incf *next-inst-id*)))
236            stream)
237     (format stream
238             #!+sb-show-assem " emitter=~S" #!-sb-show-assem "emitter=~S"
239             (let ((emitter (inst-emitter inst)))
240               (if emitter
241                   (multiple-value-bind (lambda lexenv-p name)
242                       (function-lambda-expression emitter)
243                     (declare (ignore lambda lexenv-p))
244                     name)
245                   '<flushed>)))
246     (when (inst-depth inst)
247       (format stream ", depth=~W" (inst-depth inst)))))
248
249 #!+sb-show-assem
250 (defun reset-inst-ids ()
251   (clrhash *inst-ids*)
252   (setf *next-inst-id* 0))
253 \f
254 ;;;; the scheduler itself
255
256 (defmacro without-scheduling ((&optional (segment '(%%current-segment%%)))
257                               &body body)
258   #!+sb-doc
259   "Execute BODY (as a PROGN) without scheduling any of the instructions
260    generated inside it. This is not protected by UNWIND-PROTECT, so
261    DO NOT use THROW or RETURN-FROM to escape from it."
262   ;; FIXME: Why not just use UNWIND-PROTECT? Or is there some other
263   ;; reason why we shouldn't use THROW or RETURN-FROM?
264   (let ((var (gensym))
265         (seg (gensym)))
266     `(let* ((,seg ,segment)
267             (,var (segment-run-scheduler ,seg)))
268        (when ,var
269          (schedule-pending-instructions ,seg)
270          (setf (segment-run-scheduler ,seg) nil))
271        ,@body
272        (setf (segment-run-scheduler ,seg) ,var))))
273
274 (defmacro note-dependencies ((segment inst) &body body)
275   (sb!int:once-only ((segment segment) (inst inst))
276     `(macrolet ((reads (loc) `(note-read-dependency ,',segment ,',inst ,loc))
277                 (writes (loc &rest keys)
278                   `(note-write-dependency ,',segment ,',inst ,loc ,@keys)))
279        ,@body)))
280
281 (defun note-read-dependency (segment inst read)
282   (multiple-value-bind (loc-num size)
283       (sb!c:location-number read)
284     #!+sb-show-assem (format *trace-output*
285                              "~&~S reads ~S[~W for ~W]~%"
286                              inst read loc-num size)
287     (when loc-num
288       ;; Iterate over all the locations for this TN.
289       (do ((index loc-num (1+ index))
290            (end-loc (+ loc-num (or size 1))))
291           ((>= index end-loc))
292         (declare (type (mod 2048) index end-loc))
293         (let ((writers (svref (segment-writers segment) index)))
294           (when writers
295             ;; The inst that wrote the value we want to read must have
296             ;; completed.
297             (let ((writer (car writers)))
298               (sset-adjoin writer (inst-read-dependencies inst))
299               (sset-adjoin inst (inst-read-dependents writer))
300               (sset-delete writer (segment-emittable-insts-sset segment))
301               ;; And it must have been completed *after* all other
302               ;; writes to that location. Actually, that isn't quite
303               ;; true. Each of the earlier writes could be done
304               ;; either before this last write, or after the read, but
305               ;; we have no way of representing that.
306               (dolist (other-writer (cdr writers))
307                 (sset-adjoin other-writer (inst-write-dependencies writer))
308                 (sset-adjoin writer (inst-write-dependents other-writer))
309                 (sset-delete other-writer
310                              (segment-emittable-insts-sset segment))))
311             ;; And we don't need to remember about earlier writes any
312             ;; more. Shortening the writers list means that we won't
313             ;; bother generating as many explicit arcs in the graph.
314             (setf (cdr writers) nil)))
315         (push inst (svref (segment-readers segment) index)))))
316   (values))
317
318 (defun note-write-dependency (segment inst write &key partially)
319   (multiple-value-bind (loc-num size)
320       (sb!c:location-number write)
321     #!+sb-show-assem (format *trace-output*
322                              "~&~S writes ~S[~W for ~W]~%"
323                              inst write loc-num size)
324     (when loc-num
325       ;; Iterate over all the locations for this TN.
326       (do ((index loc-num (1+ index))
327            (end-loc (+ loc-num (or size 1))))
328           ((>= index end-loc))
329         (declare (type (mod 2048) index end-loc))
330         ;; All previous reads of this location must have completed.
331         (dolist (prev-inst (svref (segment-readers segment) index))
332           (unless (eq prev-inst inst)
333             (sset-adjoin prev-inst (inst-write-dependencies inst))
334             (sset-adjoin inst (inst-write-dependents prev-inst))
335             (sset-delete prev-inst (segment-emittable-insts-sset segment))))
336         (when partially
337           ;; All previous writes to the location must have completed.
338           (dolist (prev-inst (svref (segment-writers segment) index))
339             (sset-adjoin prev-inst (inst-write-dependencies inst))
340             (sset-adjoin inst (inst-write-dependents prev-inst))
341             (sset-delete prev-inst (segment-emittable-insts-sset segment)))
342           ;; And we can forget about remembering them, because
343           ;; depending on us is as good as depending on them.
344           (setf (svref (segment-writers segment) index) nil))
345         (push inst (svref (segment-writers segment) index)))))
346   (values))
347
348 ;;; This routine is called by due to uses of the INST macro when the
349 ;;; scheduler is turned on. The change to the dependency graph has
350 ;;; already been computed, so we just have to check to see whether the
351 ;;; basic block is terminated.
352 (defun queue-inst (segment inst)
353   #!+sb-show-assem (format *trace-output* "~&queuing ~S~%" inst)
354   #!+sb-show-assem (format *trace-output*
355                            "  reads ~S~%  writes ~S~%"
356                            (sb!int:collect ((reads))
357                              (do-sset-elements (read
358                                                 (inst-read-dependencies inst))
359                                 (reads read))
360                              (reads))
361                            (sb!int:collect ((writes))
362                              (do-sset-elements (write
363                                                 (inst-write-dependencies inst))
364                                 (writes write))
365                              (writes)))
366   (aver (segment-run-scheduler segment))
367   (let ((countdown (segment-branch-countdown segment)))
368     (when countdown
369       (decf countdown)
370       (aver (not (instruction-attributep (inst-attributes inst)
371                                          variable-length))))
372     (cond ((instruction-attributep (inst-attributes inst) branch)
373            (unless countdown
374              (setf countdown (inst-delay inst)))
375            (push (cons countdown inst)
376                  (segment-queued-branches segment)))
377           (t
378            (sset-adjoin inst (segment-emittable-insts-sset segment))))
379     (when countdown
380       (setf (segment-branch-countdown segment) countdown)
381       (when (zerop countdown)
382         (schedule-pending-instructions segment))))
383   (values))
384
385 ;;; Emit all the pending instructions, and reset any state. This is
386 ;;; called whenever we hit a label (i.e. an entry point of some kind)
387 ;;; and when the user turns the scheduler off (otherwise, the queued
388 ;;; instructions would sit there until the scheduler was turned back
389 ;;; on, and emitted in the wrong place).
390 (defun schedule-pending-instructions (segment)
391   (aver (segment-run-scheduler segment))
392
393   ;; Quick blow-out if nothing to do.
394   (when (and (sset-empty (segment-emittable-insts-sset segment))
395              (null (segment-queued-branches segment)))
396     (return-from schedule-pending-instructions
397                  (values)))
398
399   #!+sb-show-assem (format *trace-output*
400                            "~&scheduling pending instructions..~%")
401
402   ;; Note that any values live at the end of the block have to be
403   ;; computed last.
404   (let ((emittable-insts (segment-emittable-insts-sset segment))
405         (writers (segment-writers segment)))
406     (dotimes (index (length writers))
407       (let* ((writer (svref writers index))
408              (inst (car writer))
409              (overwritten (cdr writer)))
410         (when writer
411           (when overwritten
412             (let ((write-dependencies (inst-write-dependencies inst)))
413               (dolist (other-inst overwritten)
414                 (sset-adjoin inst (inst-write-dependents other-inst))
415                 (sset-adjoin other-inst write-dependencies)
416                 (sset-delete other-inst emittable-insts))))
417           ;; If the value is live at the end of the block, we can't flush it.
418           (setf (instruction-attributep (inst-attributes inst) flushable)
419                 nil)))))
420
421   ;; Grovel through the entire graph in the forward direction finding
422   ;; all the leaf instructions.
423   (labels ((grovel-inst (inst)
424              (let ((max 0))
425                (do-sset-elements (dep (inst-write-dependencies inst))
426                  (let ((dep-depth (or (inst-depth dep) (grovel-inst dep))))
427                    (when (> dep-depth max)
428                      (setf max dep-depth))))
429                (do-sset-elements (dep (inst-read-dependencies inst))
430                  (let ((dep-depth
431                         (+ (or (inst-depth dep) (grovel-inst dep))
432                            (inst-delay dep))))
433                    (when (> dep-depth max)
434                      (setf max dep-depth))))
435                (cond ((and (sset-empty (inst-read-dependents inst))
436                            (instruction-attributep (inst-attributes inst)
437                                                    flushable))
438                       #!+sb-show-assem (format *trace-output*
439                                                "flushing ~S~%"
440                                                inst)
441                       (setf (inst-emitter inst) nil)
442                       (setf (inst-depth inst) max))
443                      (t
444                       (setf (inst-depth inst) max))))))
445     (let ((emittable-insts nil)
446           (delayed nil))
447       (do-sset-elements (inst (segment-emittable-insts-sset segment))
448         (grovel-inst inst)
449         (if (zerop (inst-delay inst))
450             (push inst emittable-insts)
451             (setf delayed
452                   (add-to-nth-list delayed inst (1- (inst-delay inst))))))
453       (setf (segment-emittable-insts-queue segment)
454             (sort emittable-insts #'> :key #'inst-depth))
455       (setf (segment-delayed segment) delayed))
456     (dolist (branch (segment-queued-branches segment))
457       (grovel-inst (cdr branch))))
458   #!+sb-show-assem (format *trace-output*
459                            "queued branches: ~S~%"
460                            (segment-queued-branches segment))
461   #!+sb-show-assem (format *trace-output*
462                            "initially emittable: ~S~%"
463                            (segment-emittable-insts-queue segment))
464   #!+sb-show-assem (format *trace-output*
465                            "initially delayed: ~S~%"
466                            (segment-delayed segment))
467
468   ;; Accumulate the results in reverse order. Well, actually, this
469   ;; list will be in forward order, because we are generating the
470   ;; reverse order in reverse.
471   (let ((results nil))
472
473     ;; Schedule all the branches in their exact locations.
474     (let ((insts-from-end (segment-branch-countdown segment)))
475       (dolist (branch (segment-queued-branches segment))
476         (let ((inst (cdr branch)))
477           (dotimes (i (- (car branch) insts-from-end))
478             ;; Each time through this loop we need to emit another
479             ;; instruction. First, we check to see whether there is
480             ;; any instruction that must be emitted before (i.e. must
481             ;; come after) the branch inst. If so, emit it. Otherwise,
482             ;; just pick one of the emittable insts. If there is
483             ;; nothing to do, then emit a nop. ### Note: despite the
484             ;; fact that this is a loop, it really won't work for
485             ;; repetitions other then zero and one. For example, if
486             ;; the branch has two dependents and one of them dpends on
487             ;; the other, then the stuff that grabs a dependent could
488             ;; easily grab the wrong one. But I don't feel like fixing
489             ;; this because it doesn't matter for any of the
490             ;; architectures we are using or plan on using.
491             (flet ((maybe-schedule-dependent (dependents)
492                      (do-sset-elements (inst dependents)
493                        ;; If do-sset-elements enters the body, then there is a
494                        ;; dependent. Emit it.
495                        (note-resolved-dependencies segment inst)
496                        ;; Remove it from the emittable insts.
497                        (setf (segment-emittable-insts-queue segment)
498                              (delete inst
499                                      (segment-emittable-insts-queue segment)
500                                      :test #'eq))
501                        ;; And if it was delayed, removed it from the delayed
502                        ;; list. This can happen if there is a load in a
503                        ;; branch delay slot.
504                        (block scan-delayed
505                          (do ((delayed (segment-delayed segment)
506                                        (cdr delayed)))
507                              ((null delayed))
508                            (do ((prev nil cons)
509                                 (cons (car delayed) (cdr cons)))
510                                ((null cons))
511                              (when (eq (car cons) inst)
512                                (if prev
513                                    (setf (cdr prev) (cdr cons))
514                                    (setf (car delayed) (cdr cons)))
515                                (return-from scan-delayed nil)))))
516                        ;; And return it.
517                        (return inst))))
518               (let ((fill (or (maybe-schedule-dependent
519                                (inst-read-dependents inst))
520                               (maybe-schedule-dependent
521                                (inst-write-dependents inst))
522                               (schedule-one-inst segment t)
523                               :nop)))
524                 #!+sb-show-assem (format *trace-output*
525                                          "filling branch delay slot with ~S~%"
526                                          fill)
527                 (push fill results)))
528             (advance-one-inst segment)
529             (incf insts-from-end))
530           (note-resolved-dependencies segment inst)
531           (push inst results)
532           #!+sb-show-assem (format *trace-output* "emitting ~S~%" inst)
533           (advance-one-inst segment))))
534
535     ;; Keep scheduling stuff until we run out.
536     (loop
537       (let ((inst (schedule-one-inst segment nil)))
538         (unless inst
539           (return))
540         (push inst results)
541         (advance-one-inst segment)))
542
543     ;; Now call the emitters, but turn the scheduler off for the duration.
544     (setf (segment-run-scheduler segment) nil)
545     (dolist (inst results)
546       (if (eq inst :nop)
547           (sb!c:emit-nop segment)
548           (funcall (inst-emitter inst) segment)))
549     (setf (segment-run-scheduler segment) t))
550
551   ;; Clear out any residue left over.
552   (setf (segment-inst-number segment) 0)
553   (setf (segment-queued-branches segment) nil)
554   (setf (segment-branch-countdown segment) nil)
555   (setf (segment-emittable-insts-sset segment) (make-sset))
556   (fill (segment-readers segment) nil)
557   (fill (segment-writers segment) nil)
558
559   ;; That's all, folks.
560   (values))
561
562 ;;; a utility for maintaining the segment-delayed list. We cdr down
563 ;;; list n times (extending it if necessary) and then push thing on
564 ;;; into the car of that cons cell.
565 (defun add-to-nth-list (list thing n)
566   (do ((cell (or list (setf list (list nil)))
567              (or (cdr cell) (setf (cdr cell) (list nil))))
568        (i n (1- i)))
569       ((zerop i)
570        (push thing (car cell))
571        list)))
572
573 ;;; Find the next instruction to schedule and return it after updating
574 ;;; any dependency information. If we can't do anything useful right
575 ;;; now, but there is more work to be done, return :NOP to indicate
576 ;;; that a nop must be emitted. If we are all done, return NIL.
577 (defun schedule-one-inst (segment delay-slot-p)
578   (do ((prev nil remaining)
579        (remaining (segment-emittable-insts-queue segment) (cdr remaining)))
580       ((null remaining))
581     (let ((inst (car remaining)))
582       (unless (and delay-slot-p
583                    (instruction-attributep (inst-attributes inst)
584                                            variable-length))
585         ;; We've got us a live one here. Go for it.
586         #!+sb-show-assem (format *trace-output* "emitting ~S~%" inst)
587         ;; Delete it from the list of insts.
588         (if prev
589             (setf (cdr prev) (cdr remaining))
590             (setf (segment-emittable-insts-queue segment)
591                   (cdr remaining)))
592         ;; Note that this inst has been emitted.
593         (note-resolved-dependencies segment inst)
594         ;; And return.
595         (return-from schedule-one-inst
596                      ;; Are we wanting to flush this instruction?
597                      (if (inst-emitter inst)
598                          ;; Nope, it's still a go. So return it.
599                          inst
600                          ;; Yes, so pick a new one. We have to start
601                          ;; over, because note-resolved-dependencies
602                          ;; might have changed the emittable-insts-queue.
603                          (schedule-one-inst segment delay-slot-p))))))
604   ;; Nothing to do, so make something up.
605   (cond ((segment-delayed segment)
606          ;; No emittable instructions, but we have more work to do. Emit
607          ;; a NOP to fill in a delay slot.
608          #!+sb-show-assem (format *trace-output* "emitting a NOP~%")
609          :nop)
610         (t
611          ;; All done.
612          nil)))
613
614 ;;; This function is called whenever an instruction has been
615 ;;; scheduled, and we want to know what possibilities that opens up.
616 ;;; So look at all the instructions that this one depends on, and
617 ;;; remove this instruction from their dependents list. If we were the
618 ;;; last dependent, then that dependency can be emitted now.
619 (defun note-resolved-dependencies (segment inst)
620   (aver (sset-empty (inst-read-dependents inst)))
621   (aver (sset-empty (inst-write-dependents inst)))
622   (do-sset-elements (dep (inst-write-dependencies inst))
623     ;; These are the instructions who have to be completed before our
624     ;; write fires. Doesn't matter how far before, just before.
625     (let ((dependents (inst-write-dependents dep)))
626       (sset-delete inst dependents)
627       (when (and (sset-empty dependents)
628                  (sset-empty (inst-read-dependents dep)))
629         (insert-emittable-inst segment dep))))
630   (do-sset-elements (dep (inst-read-dependencies inst))
631     ;; These are the instructions who write values we read. If there
632     ;; is no delay, then just remove us from the dependent list.
633     ;; Otherwise, record the fact that in n cycles, we should be
634     ;; removed.
635     (if (zerop (inst-delay dep))
636         (let ((dependents (inst-read-dependents dep)))
637           (sset-delete inst dependents)
638           (when (and (sset-empty dependents)
639                      (sset-empty (inst-write-dependents dep)))
640             (insert-emittable-inst segment dep)))
641         (setf (segment-delayed segment)
642               (add-to-nth-list (segment-delayed segment)
643                                (cons dep inst)
644                                (inst-delay dep)))))
645   (values))
646
647 ;;; Process the next entry in segment-delayed. This is called whenever
648 ;;; anyone emits an instruction.
649 (defun advance-one-inst (segment)
650   (let ((delayed-stuff (pop (segment-delayed segment))))
651     (dolist (stuff delayed-stuff)
652       (if (consp stuff)
653           (let* ((dependency (car stuff))
654                  (dependent (cdr stuff))
655                  (dependents (inst-read-dependents dependency)))
656             (sset-delete dependent dependents)
657             (when (and (sset-empty dependents)
658                        (sset-empty (inst-write-dependents dependency)))
659               (insert-emittable-inst segment dependency)))
660           (insert-emittable-inst segment stuff)))))
661
662 ;;; Note that inst is emittable by sticking it in the
663 ;;; SEGMENT-EMITTABLE-INSTS-QUEUE list. We keep the emittable-insts
664 ;;; sorted with the largest ``depths'' first. Except that if INST is a
665 ;;; branch, don't bother. It will be handled correctly by the branch
666 ;;; emitting code in SCHEDULE-PENDING-INSTRUCTIONS.
667 (defun insert-emittable-inst (segment inst)
668   (unless (instruction-attributep (inst-attributes inst) branch)
669     #!+sb-show-assem (format *trace-output* "now emittable: ~S~%" inst)
670     (do ((my-depth (inst-depth inst))
671          (remaining (segment-emittable-insts-queue segment) (cdr remaining))
672          (prev nil remaining))
673         ((or (null remaining) (> my-depth (inst-depth (car remaining))))
674          (if prev
675              (setf (cdr prev) (cons inst remaining))
676              (setf (segment-emittable-insts-queue segment)
677                    (cons inst remaining))))))
678   (values))
679 \f
680 ;;;; structure used during output emission
681
682 ;;; common supertype for all the different kinds of annotations
683 (def!struct (annotation (:constructor nil)
684                         (:copier nil))
685   ;; Where in the raw output stream was this annotation emitted?
686   (index 0 :type index)
687   ;; What position does that correspond to?
688   (posn nil :type (or index null)))
689
690 (def!struct (label (:include annotation)
691                    (:constructor gen-label ())
692                    (:copier nil))
693   ;; (doesn't need any additional information beyond what is in the
694   ;; annotation structure)
695   )
696 (sb!int:def!method print-object ((label label) stream)
697   (if (or *print-escape* *print-readably*)
698       (print-unreadable-object (label stream :type t)
699         (prin1 (sb!c:label-id label) stream))
700       (format stream "L~D" (sb!c:label-id label))))
701
702 ;;; a constraint on how the output stream must be aligned
703 (def!struct (alignment-note (:include annotation)
704                             (:conc-name alignment-)
705                             (:predicate alignment-p)
706                             (:constructor make-alignment (bits size fill-byte))
707                             (:copier nil))
708   ;; the minimum number of low-order bits that must be zero
709   (bits 0 :type alignment)
710   ;; the amount of filler we are assuming this alignment op will take
711   (size 0 :type (integer 0 #.(1- (ash 1 max-alignment))))
712   ;; the byte used as filling
713   (fill-byte 0 :type (or assembly-unit (signed-byte #.assembly-unit-bits))))
714
715 ;;; a reference to someplace that needs to be back-patched when
716 ;;; we actually know what label positions, etc. are
717 (def!struct (back-patch (:include annotation)
718                         (:constructor make-back-patch (size fun))
719                         (:copier nil))
720   ;; the area affected by this back-patch
721   (size 0 :type index :read-only t)
722   ;; the function to use to generate the real data
723   (fun nil :type function :read-only t))
724
725 ;;; This is similar to a BACK-PATCH, but also an indication that the
726 ;;; amount of stuff output depends on label positions, etc.
727 ;;; BACK-PATCHes can't change their mind about how much stuff to emit,
728 ;;; but CHOOSERs can.
729 (def!struct (chooser (:include annotation)
730                      (:constructor make-chooser
731                                    (size alignment maybe-shrink worst-case-fun))
732                      (:copier nil))
733   ;; the worst case size for this chooser. There is this much space
734   ;; allocated in the output buffer.
735   (size 0 :type index :read-only t)
736   ;; the worst case alignment this chooser is guaranteed to preserve
737   (alignment 0 :type alignment :read-only t)
738   ;; the function to call to determine if we can use a shorter
739   ;; sequence. It returns NIL if nothing shorter can be used, or emits
740   ;; that sequence and returns T.
741   (maybe-shrink nil :type function :read-only t)
742   ;; the function to call to generate the worst case sequence. This is
743   ;; used when nothing else can be condensed.
744   (worst-case-fun nil :type function :read-only t))
745
746 ;;; This is used internally when we figure out a chooser or alignment
747 ;;; doesn't really need as much space as we initially gave it.
748 (def!struct (filler (:include annotation)
749                     (:constructor make-filler (bytes))
750                     (:copier nil))
751   ;; the number of bytes of filler here
752   (bytes 0 :type index))
753 \f
754 ;;;; output functions
755
756 ;;; interface: Emit the supplied BYTE to SEGMENT, growing SEGMENT if
757 ;;; necessary.
758 (defun emit-byte (segment byte)
759   (declare (type segment segment))
760   (declare (type possibly-signed-assembly-unit byte))
761   (let ((old-index (segment-current-index segment)))
762     (incf (segment-current-index segment))
763     (setf (aref (segment-buffer segment) old-index)
764           (logand byte assembly-unit-mask)))
765   (incf (segment-current-posn segment))
766   (values))
767
768 ;;; interface: Output AMOUNT copies of FILL-BYTE to SEGMENT.
769 (defun emit-skip (segment amount &optional (fill-byte 0))
770   (declare (type segment segment)
771            (type index amount))
772   (dotimes (i amount)
773     (emit-byte segment fill-byte))
774   (values))
775
776 ;;; This is used to handle the common parts of annotation emission. We
777 ;;; just assign the POSN and INDEX of NOTE and tack it on to the end
778 ;;; of SEGMENT's annotations list.
779 (defun emit-annotation (segment note)
780   (declare (type segment segment)
781            (type annotation note))
782   (when (annotation-posn note)
783     (error "attempt to emit ~S a second time" note))
784   (setf (annotation-posn note) (segment-current-posn segment))
785   (setf (annotation-index note) (segment-current-index segment))
786   (let ((last (segment-last-annotation segment))
787         (new (list note)))
788     (setf (segment-last-annotation segment)
789           (if last
790               (setf (cdr last) new)
791               (setf (segment-annotations segment) new))))
792   (values))
793
794 ;;; Note that the instruction stream has to be back-patched when label
795 ;;; positions are finally known. SIZE bytes are reserved in SEGMENT,
796 ;;; and function will be called with two arguments: the segment and
797 ;;; the position. The function should look at the position and the
798 ;;; position of any labels it wants to and emit the correct sequence.
799 ;;; (And it better be the same size as SIZE). SIZE can be zero, which
800 ;;; is useful if you just want to find out where things ended up.
801 (defun emit-back-patch (segment size function)
802   (emit-annotation segment (make-back-patch size function))
803   (emit-skip segment size))
804
805 ;;; Note that the instruction stream here depends on the actual
806 ;;; positions of various labels, so can't be output until label
807 ;;; positions are known. Space is made in SEGMENT for at least SIZE
808 ;;; bytes. When all output has been generated, the MAYBE-SHRINK
809 ;;; functions for all choosers are called with three arguments: the
810 ;;; segment, the position, and a magic value. The MAYBE-SHRINK
811 ;;; decides if it can use a shorter sequence, and if so, emits that
812 ;;; sequence to the segment and returns T. If it can't do better than
813 ;;; the worst case, it should return NIL (without emitting anything).
814 ;;; When calling LABEL-POSITION, it should pass it the position and
815 ;;; the magic-value it was passed so that LABEL-POSITION can return
816 ;;; the correct result. If the chooser never decides to use a shorter
817 ;;; sequence, the WORST-CASE-FUN will be called, just like a
818 ;;; BACK-PATCH. (See EMIT-BACK-PATCH.)
819 (defun emit-chooser (segment size alignment maybe-shrink worst-case-fun)
820   (declare (type segment segment) (type index size) (type alignment alignment)
821            (type function maybe-shrink worst-case-fun))
822   (let ((chooser (make-chooser size alignment maybe-shrink worst-case-fun)))
823     (emit-annotation segment chooser)
824     (emit-skip segment size)
825     (adjust-alignment-after-chooser segment chooser)))
826
827 ;;; This is called in EMIT-CHOOSER and COMPRESS-SEGMENT in order to
828 ;;; recompute the current alignment information in light of this
829 ;;; chooser. If the alignment guaranteed by the chooser is less than
830 ;;; the segment's current alignment, we have to adjust the segment's
831 ;;; notion of the current alignment.
832 ;;;
833 ;;; The hard part is recomputing the sync posn, because it's not just
834 ;;; the chooser's posn. Consider a chooser that emits either one or
835 ;;; three words. It preserves 8-byte (3 bit) alignments, because the
836 ;;; difference between the two choices is 8 bytes.
837 (defun adjust-alignment-after-chooser (segment chooser)
838   (declare (type segment segment) (type chooser chooser))
839   (let ((alignment (chooser-alignment chooser))
840         (seg-alignment (segment-alignment segment)))
841     (when (< alignment seg-alignment)
842       ;; The chooser might change the alignment of the output. So we
843       ;; have to figure out what the worst case alignment could be.
844       (setf (segment-alignment segment) alignment)
845       (let* ((posn (chooser-posn chooser))
846              (sync-posn (segment-sync-posn segment))
847              (offset (- posn sync-posn))
848              (delta (logand offset (1- (ash 1 alignment)))))
849         (setf (segment-sync-posn segment) (- posn delta)))))
850   (values))
851
852 ;;; This is used internally whenever a chooser or alignment decides it
853 ;;; doesn't need as much space as it originally thought.
854 (defun emit-filler (segment n-bytes)
855   (declare (type index n-bytes))
856   (let ((last (segment-last-annotation segment)))
857     (cond ((and last (filler-p (car last)))
858            (incf (filler-bytes (car last)) n-bytes))
859           (t
860            (emit-annotation segment (make-filler n-bytes)))))
861   (incf (segment-current-index segment) n-bytes)
862   (values))
863
864 ;;; EMIT-LABEL (the interface) basically just expands into this,
865 ;;; supplying the SEGMENT and VOP.
866 (defun %emit-label (segment vop label)
867   (when (segment-run-scheduler segment)
868     (schedule-pending-instructions segment))
869   (let ((postits (segment-postits segment)))
870     (setf (segment-postits segment) nil)
871     (dolist (postit postits)
872       (emit-back-patch segment 0 postit)))
873   (let ((hook (segment-inst-hook segment)))
874     (when hook
875       (funcall hook segment vop :label label)))
876   (emit-annotation segment label))
877
878 ;;; Called by the EMIT-ALIGNMENT macro to emit an alignment note. We check to
879 ;;; see if we can guarantee the alignment restriction by just outputting a
880 ;;; fixed number of bytes. If so, we do so. Otherwise, we create and emit an
881 ;;; alignment note.
882 (defun %emit-alignment (segment vop bits &optional (fill-byte 0))
883   (when (segment-run-scheduler segment)
884     (schedule-pending-instructions segment))
885   (let ((hook (segment-inst-hook segment)))
886     (when hook
887       (funcall hook segment vop :align bits)))
888   (let ((alignment (segment-alignment segment))
889         (offset (- (segment-current-posn segment)
890                    (segment-sync-posn segment))))
891     (cond ((> bits alignment)
892            ;; We need more bits of alignment. First emit enough noise
893            ;; to get back in sync with alignment, and then emit an
894            ;; alignment note to cover the rest.
895            (let ((slop (logand offset (1- (ash 1 alignment)))))
896              (unless (zerop slop)
897                (emit-skip segment (- (ash 1 alignment) slop) fill-byte)))
898            (let ((size (logand (1- (ash 1 bits))
899                                (lognot (1- (ash 1 alignment))))))
900              (aver (> size 0))
901              (emit-annotation segment (make-alignment bits size fill-byte))
902              (emit-skip segment size fill-byte))
903            (setf (segment-alignment segment) bits)
904            (setf (segment-sync-posn segment) (segment-current-posn segment)))
905           (t
906            ;; The last alignment was more restrictive than this one.
907            ;; So we can just figure out how much noise to emit
908            ;; assuming the last alignment was met.
909            (let* ((mask (1- (ash 1 bits)))
910                   (new-offset (logand (+ offset mask) (lognot mask))))
911              (emit-skip segment (- new-offset offset) fill-byte))
912            ;; But we emit an alignment with size=0 so we can verify
913            ;; that everything works.
914            (emit-annotation segment (make-alignment bits 0 fill-byte)))))
915   (values))
916
917 ;;; This is used to find how ``aligned'' different offsets are.
918 ;;; Returns the number of low-order 0 bits, up to MAX-ALIGNMENT.
919 (defun find-alignment (offset)
920   (dotimes (i max-alignment max-alignment)
921     (when (logbitp i offset)
922       (return i))))
923
924 ;;; Emit a postit. The function will be called as a back-patch with
925 ;;; the position the following instruction is finally emitted. Postits
926 ;;; do not interfere at all with scheduling.
927 (defun %emit-postit (segment function)
928   (push function (segment-postits segment))
929   (values))
930 \f
931 ;;;; output compression/position assignment stuff
932
933 ;;; Grovel though all the annotations looking for choosers. When we
934 ;;; find a chooser, invoke the maybe-shrink function. If it returns T,
935 ;;; it output some other byte sequence.
936 (defun compress-output (segment)
937   (dotimes (i 5) ; it better not take more than one or two passes.
938     (let ((delta 0))
939       (setf (segment-alignment segment) max-alignment)
940       (setf (segment-sync-posn segment) 0)
941       (do* ((prev nil)
942             (remaining (segment-annotations segment) next)
943             (next (cdr remaining) (cdr remaining)))
944            ((null remaining))
945         (let* ((note (car remaining))
946                (posn (annotation-posn note)))
947           (unless (zerop delta)
948             (decf posn delta)
949             (setf (annotation-posn note) posn))
950           (cond
951            ((chooser-p note)
952             (with-modified-segment-index-and-posn (segment (chooser-index note)
953                                                            posn)
954               (setf (segment-last-annotation segment) prev)
955               (cond
956                ((funcall (chooser-maybe-shrink note) segment posn delta)
957                 ;; It emitted some replacement.
958                 (let ((new-size (- (segment-current-index segment)
959                                    (chooser-index note)))
960                       (old-size (chooser-size note)))
961                   (when (> new-size old-size)
962                     (error "~S emitted ~W bytes, but claimed its max was ~W."
963                            note new-size old-size))
964                   (let ((additional-delta (- old-size new-size)))
965                     (when (< (find-alignment additional-delta)
966                              (chooser-alignment note))
967                       (error "~S shrunk by ~W bytes, but claimed that it ~
968                               preserves ~W bits of alignment."
969                              note additional-delta (chooser-alignment note)))
970                     (incf delta additional-delta)
971                     (emit-filler segment additional-delta))
972                   (setf prev (segment-last-annotation segment))
973                   (if prev
974                       (setf (cdr prev) (cdr remaining))
975                       (setf (segment-annotations segment)
976                             (cdr remaining)))))
977                (t
978                 ;; The chooser passed on shrinking. Make sure it didn't
979                 ;; emit anything.
980                 (unless (= (segment-current-index segment)
981                            (chooser-index note))
982                   (error "Chooser ~S passed, but not before emitting ~W bytes."
983                          note
984                          (- (segment-current-index segment)
985                             (chooser-index note))))
986                 ;; Act like we just emitted this chooser.
987                 (let ((size (chooser-size note)))
988                   (incf (segment-current-index segment) size)
989                   (incf (segment-current-posn segment) size))
990                 ;; Adjust the alignment accordingly.
991                 (adjust-alignment-after-chooser segment note)
992                 ;; And keep this chooser for next time around.
993                 (setf prev remaining)))))
994            ((alignment-p note)
995             (unless (zerop (alignment-size note))
996               ;; Re-emit the alignment, letting it collapse if we know
997               ;; anything more about the alignment guarantees of the
998               ;; segment.
999               (let ((index (alignment-index note)))
1000                 (with-modified-segment-index-and-posn (segment index posn)
1001                   (setf (segment-last-annotation segment) prev)
1002                   (%emit-alignment segment nil (alignment-bits note)
1003                                    (alignment-fill-byte note))
1004                   (let* ((new-index (segment-current-index segment))
1005                          (size (- new-index index))
1006                          (old-size (alignment-size note))
1007                          (additional-delta (- old-size size)))
1008                     (when (minusp additional-delta)
1009                       (error "Alignment ~S needs more space now?  It was ~W, ~
1010                               and is ~W now."
1011                              note old-size size))
1012                     (when (plusp additional-delta)
1013                       (emit-filler segment additional-delta)
1014                       (incf delta additional-delta)))
1015                   (setf prev (segment-last-annotation segment))
1016                   (if prev
1017                       (setf (cdr prev) (cdr remaining))
1018                       (setf (segment-annotations segment)
1019                             (cdr remaining)))))))
1020            (t
1021             (setf prev remaining)))))
1022       (when (zerop delta)
1023         (return))
1024       (decf (segment-final-posn segment) delta)))
1025   (values))
1026
1027 ;;; We have run all the choosers we can, so now we have to figure out
1028 ;;; exactly how much space each alignment note needs.
1029 (defun finalize-positions (segment)
1030   (let ((delta 0))
1031     (do* ((prev nil)
1032           (remaining (segment-annotations segment) next)
1033           (next (cdr remaining) (cdr remaining)))
1034          ((null remaining))
1035       (let* ((note (car remaining))
1036              (posn (- (annotation-posn note) delta)))
1037         (cond
1038          ((alignment-p note)
1039           (let* ((bits (alignment-bits note))
1040                  (mask (1- (ash 1 bits)))
1041                  (new-posn (logand (+ posn mask) (lognot mask)))
1042                  (size (- new-posn posn))
1043                  (old-size (alignment-size note))
1044                  (additional-delta (- old-size size)))
1045             (aver (<= 0 size old-size))
1046             (unless (zerop additional-delta)
1047               (setf (segment-last-annotation segment) prev)
1048               (incf delta additional-delta)
1049               (with-modified-segment-index-and-posn (segment
1050                                                      (alignment-index note)
1051                                                      posn)
1052                 (emit-filler segment additional-delta)
1053                 (setf prev (segment-last-annotation segment))
1054                 (if prev
1055                     (setf (cdr prev) next)
1056                     (setf (segment-annotations segment) next))))))
1057          (t
1058           (setf (annotation-posn note) posn)
1059           (setf prev remaining)
1060           (setf next (cdr remaining))))))
1061     (unless (zerop delta)
1062       (decf (segment-final-posn segment) delta)))
1063   (values))
1064
1065 ;;; Grovel over segment, filling in any backpatches. If any choosers
1066 ;;; are left over, we need to emit their worst case variant.
1067 (defun process-back-patches (segment)
1068   (do* ((prev nil)
1069         (remaining (segment-annotations segment) next)
1070         (next (cdr remaining) (cdr remaining)))
1071       ((null remaining))
1072     (let ((note (car remaining)))
1073       (flet ((fill-in (function old-size)
1074                (let ((index (annotation-index note))
1075                      (posn (annotation-posn note)))
1076                  (with-modified-segment-index-and-posn (segment index posn)
1077                    (setf (segment-last-annotation segment) prev)
1078                    (funcall function segment posn)
1079                    (let ((new-size (- (segment-current-index segment) index)))
1080                      (unless (= new-size old-size)
1081                        (error "~S emitted ~W bytes, but claimed it was ~W."
1082                               note new-size old-size)))
1083                    (let ((tail (segment-last-annotation segment)))
1084                      (if tail
1085                          (setf (cdr tail) next)
1086                          (setf (segment-annotations segment) next)))
1087                    (setf next (cdr prev))))))
1088         (cond ((back-patch-p note)
1089                (fill-in (back-patch-fun note)
1090                         (back-patch-size note)))
1091               ((chooser-p note)
1092                (fill-in (chooser-worst-case-fun note)
1093                         (chooser-size note)))
1094               (t
1095                (setf prev remaining)))))))
1096 \f
1097 ;;;; interface to the rest of the compiler
1098
1099 ;;; This holds the current segment while assembling. Use ASSEMBLE to
1100 ;;; change it.
1101 ;;;
1102 ;;; The double asterisks in the name are intended to suggest that this
1103 ;;; isn't just any old special variable, it's an extra-special
1104 ;;; variable, because sometimes MACROLET is used to bind it. So be
1105 ;;; careful out there..
1106 ;;;
1107 ;;; (This used to be called **CURRENT-SEGMENT** in SBCL until 0.7.3,
1108 ;;; and just *CURRENT-SEGMENT* in CMU CL. In both cases, the rebinding
1109 ;;; now done with MACROLET was done with SYMBOL-MACROLET instead. The
1110 ;;; rename-with-double-asterisks was because the SYMBOL-MACROLET made
1111 ;;; it an extra-special variable. The change over to
1112 ;;; %%CURRENT-SEGMENT%% was because ANSI forbids the use of
1113 ;;; SYMBOL-MACROLET on special variable names, and CLISP correctly
1114 ;;; complains about this when being used as a bootstrap host.)
1115 (defmacro %%current-segment%% () '**current-segment**)
1116 (defvar **current-segment**)
1117
1118 ;;; Just like %%CURRENT-SEGMENT%%, except this holds the current vop.
1119 ;;; This is used only to keep track of which vops emit which insts.
1120 ;;;
1121 ;;; The double asterisks in the name are intended to suggest that this
1122 ;;; isn't just any old special variable, it's an extra-special
1123 ;;; variable, because sometimes MACROLET is used to bind it. So be
1124 ;;; careful out there..
1125 (defmacro %%current-vop%% () '**current-vop**)
1126 (defvar **current-vop** nil)
1127
1128 ;;; We also MACROLET %%CURRENT-SEGMENT%% to a local holding the
1129 ;;; segment so uses of %%CURRENT-SEGMENT%% inside the body don't have
1130 ;;; to keep dereferencing the symbol. Given that ASSEMBLE is the only
1131 ;;; interface to **CURRENT-SEGMENT**, we don't have to worry about the
1132 ;;; special value becomming out of sync with the lexical value. Unless
1133 ;;; some bozo closes over it, but nobody does anything like that...
1134 ;;;
1135 ;;; FIXME: The way this macro uses MACROEXPAND internally breaks my
1136 ;;; old assumptions about macros which are needed both in the host and
1137 ;;; the target. (This is more or less the same way that PUSH-IN,
1138 ;;; DELETEF-IN, and !DEF-BOOLEAN-ATTRIBUTE break my old assumptions,
1139 ;;; except that they used GET-SETF-EXPANSION instead of MACROEXPAND to
1140 ;;; do the dirty deed.) The quick and dirty "solution" here is the
1141 ;;; same as there: use cut and paste to duplicate the defmacro in a
1142 ;;; (SB!INT:DEF!MACRO FOO (..) .. CL:MACROEXPAND ..) #+SB-XC-HOST
1143 ;;; (DEFMACRO FOO (..) .. SB!XC:MACROEXPAND ..) idiom. This is
1144 ;;; disgusting and unmaintainable, and there are obviously better
1145 ;;; solutions and maybe even good solutions, but I'm disinclined to
1146 ;;; hunt for good solutions until the system works and I can test them
1147 ;;; in isolation.
1148 ;;;
1149 ;;; The above comment remains true, except that instead of a cut-and-paste
1150 ;;; copy we now have a macrolet. This is charitably called progress.
1151 ;;; -- NS 2008-09-19
1152 (macrolet
1153     ((def (defmacro macroexpand)
1154        `(,defmacro assemble ((&optional segment vop &key labels) &body body
1155                              &environment env)
1156           #!+sb-doc
1157           "Execute BODY (as a progn) with SEGMENT as the current segment."
1158           (flet ((label-name-p (thing)
1159                    (and thing (symbolp thing))))
1160             (let* ((seg-var (gensym "SEGMENT-"))
1161                    (vop-var (gensym "VOP-"))
1162                    (visible-labels (remove-if-not #'label-name-p body))
1163                    (inherited-labels
1164                     (multiple-value-bind (expansion expanded)
1165                         (,macroexpand '..inherited-labels.. env)
1166                       (if expanded expansion nil)))
1167                    (new-labels (append labels
1168                                        (set-difference visible-labels
1169                                                        inherited-labels)))
1170                    (nested-labels (set-difference (append inherited-labels new-labels)
1171                                                   visible-labels)))
1172               (when (intersection labels inherited-labels)
1173                 (error "duplicate nested labels: ~S"
1174                        (intersection labels inherited-labels)))
1175               `(let* ((,seg-var ,(or segment '(%%current-segment%%)))
1176                       (,vop-var ,(or vop '(%%current-vop%%)))
1177                       ,@(when segment
1178                               `((**current-segment** ,seg-var)))
1179                       ,@(when vop
1180                               `((**current-vop** ,vop-var)))
1181                       ,@(mapcar (lambda (name)
1182                                   `(,name (gen-label)))
1183                                 new-labels))
1184                  (declare (ignorable ,vop-var ,seg-var)
1185                           ;; Must be done so that contribs and user code doing
1186                           ;; low-level stuff don't need to worry about this.
1187                           (disable-package-locks %%current-segment%% %%current-vop%%))
1188                  (macrolet ((%%current-segment%% () ',seg-var)
1189                             (%%current-vop%% () ',vop-var))
1190                    ;; KLUDGE: Some host lisps (CMUCL 18e Sparc at least)
1191                    ;; can't deal with this declaration, so disable it on host.
1192                    ;; Ditto for later ENABLE-PACKAGE-LOCKS %%C-S%% declaration.
1193                    #-sb-xc-host
1194                    (declare (enable-package-locks %%current-segment%% %%current-vop%%))
1195                    (symbol-macrolet (,@(when (or inherited-labels nested-labels)
1196                                              `((..inherited-labels.. ,nested-labels))))
1197                      ,@(mapcar (lambda (form)
1198                                  (if (label-name-p form)
1199                                      `(emit-label ,form)
1200                                      form))
1201                                body)))))))))
1202   (def sb!int:def!macro macroexpand)
1203   #+sb-xc-host
1204   (def sb!xc:defmacro %macroexpand))
1205
1206 (defmacro inst (&whole whole instruction &rest args &environment env)
1207   #!+sb-doc
1208   "Emit the specified instruction to the current segment."
1209   (let ((inst (gethash (symbol-name instruction) *assem-instructions*)))
1210     (cond ((null inst)
1211            (error "unknown instruction: ~S" instruction))
1212           ((functionp inst)
1213            (funcall inst (cdr whole) env))
1214           (t
1215            `(,inst (%%current-segment%%) (%%current-vop%%) ,@args)))))
1216
1217 ;;; Note: The need to capture MACROLET bindings of %%CURRENT-SEGMENT%%
1218 ;;; and %%CURRENT-VOP%% prevents this from being an ordinary function.
1219 (defmacro emit-label (label)
1220   #!+sb-doc
1221   "Emit LABEL at this location in the current segment."
1222   `(%emit-label (%%current-segment%%) (%%current-vop%%) ,label))
1223
1224 ;;; Note: The need to capture MACROLET bindings of
1225 ;;; %%CURRENT-SEGMENT%% prevents this from being an ordinary function.
1226 (defmacro emit-postit (function)
1227   `(%emit-postit (%%current-segment%%) ,function))
1228
1229 ;;; Note: The need to capture SYMBOL-MACROLET bindings of
1230 ;;; **CURRENT-SEGMENT* and (%%CURRENT-VOP%%) prevents this from being an
1231 ;;; ordinary function.
1232 (defmacro emit-alignment (bits &optional (fill-byte 0))
1233   #!+sb-doc
1234   "Emit an alignment restriction to the current segment."
1235   `(%emit-alignment (%%current-segment%%) (%%current-vop%%) ,bits ,fill-byte))
1236
1237 (defun label-position (label &optional if-after delta)
1238   #!+sb-doc
1239   "Return the current position for LABEL. Chooser maybe-shrink functions
1240    should supply IF-AFTER and DELTA in order to ensure correct results."
1241   (let ((posn (label-posn label)))
1242     (if (and if-after (> posn if-after))
1243         (- posn delta)
1244         posn)))
1245
1246 (defun append-segment (segment other-segment)
1247   #!+sb-doc
1248   "Append OTHER-SEGMENT to the end of SEGMENT. Don't use OTHER-SEGMENT
1249    for anything after this."
1250   (when (segment-run-scheduler segment)
1251     (schedule-pending-instructions segment))
1252   (let ((postits (segment-postits segment)))
1253     (setf (segment-postits segment) (segment-postits other-segment))
1254     (dolist (postit postits)
1255       (emit-back-patch segment 0 postit)))
1256   #!-(or x86 x86-64)
1257   (%emit-alignment segment nil max-alignment)
1258   #!+(or x86 x86-64)
1259   (unless (eq :elsewhere (segment-type other-segment))
1260     (%emit-alignment segment nil max-alignment))
1261   (let ((segment-current-index-0 (segment-current-index segment))
1262         (segment-current-posn-0  (segment-current-posn  segment)))
1263     (incf (segment-current-index segment)
1264           (segment-current-index other-segment))
1265     (replace (segment-buffer segment)
1266              (segment-buffer other-segment)
1267              :start1 segment-current-index-0)
1268     (setf (segment-buffer other-segment) nil) ; to prevent accidental reuse
1269     (incf (segment-current-posn segment)
1270           (segment-current-posn other-segment))
1271     (let ((other-annotations (segment-annotations other-segment)))
1272       (when other-annotations
1273         (dolist (note other-annotations)
1274           (incf (annotation-index note) segment-current-index-0)
1275           (incf (annotation-posn note) segment-current-posn-0))
1276         ;; This SEGMENT-LAST-ANNOTATION code is confusing. Is it really
1277         ;; worth enough in efficiency to justify it? -- WHN 19990322
1278         (let ((last (segment-last-annotation segment)))
1279           (if last
1280               (setf (cdr last) other-annotations)
1281               (setf (segment-annotations segment) other-annotations)))
1282         (setf (segment-last-annotation segment)
1283               (segment-last-annotation other-segment)))))
1284   (values))
1285
1286 (defun finalize-segment (segment)
1287   #!+sb-doc
1288   "Do any final processing of SEGMENT and return the total number of bytes
1289    covered by this segment."
1290   (when (segment-run-scheduler segment)
1291     (schedule-pending-instructions segment))
1292   (setf (segment-run-scheduler segment) nil)
1293   (let ((postits (segment-postits segment)))
1294     (setf (segment-postits segment) nil)
1295     (dolist (postit postits)
1296       (emit-back-patch segment 0 postit)))
1297   (setf (segment-final-index segment) (segment-current-index segment))
1298   (setf (segment-final-posn segment) (segment-current-posn segment))
1299   (setf (segment-inst-hook segment) nil)
1300   (compress-output segment)
1301   (finalize-positions segment)
1302   (process-back-patches segment)
1303   (segment-final-posn segment))
1304
1305 ;;; Call FUNCTION on all the stuff accumulated in SEGMENT. FUNCTION
1306 ;;; should accept a single vector argument. It will be called zero or
1307 ;;; more times on vectors of the appropriate byte type. The
1308 ;;; concatenation of the vector arguments from all the calls is the
1309 ;;; contents of SEGMENT.
1310 ;;;
1311 ;;; KLUDGE: This implementation is sort of slow and gross, calling
1312 ;;; FUNCTION repeatedly and consing a fresh vector for its argument
1313 ;;; each time. It might be possible to make a more efficient version
1314 ;;; by making FINALIZE-SEGMENT do all the compacting currently done by
1315 ;;; this function: then this function could become trivial and fast,
1316 ;;; calling FUNCTION once on the entire compacted segment buffer. --
1317 ;;; WHN 19990322
1318 (defun on-segment-contents-vectorly (segment function)
1319   (declare (type function function))
1320   (let ((buffer (segment-buffer segment))
1321         (i0 0))
1322     (declare (type (simple-array (unsigned-byte 8)) buffer))
1323     (flet ((frob (i0 i1)
1324              (when (< i0 i1)
1325                (funcall function (subseq buffer i0 i1)))))
1326       (dolist (note (segment-annotations segment))
1327         (when (filler-p note)
1328           (let ((i1 (filler-index note)))
1329             (frob i0 i1)
1330             (setf i0 (+ i1 (filler-bytes note))))))
1331       (frob i0 (segment-final-index segment))))
1332   (values))
1333
1334 ;;; Write the code accumulated in SEGMENT to STREAM, and return the
1335 ;;; number of bytes written.
1336 (defun write-segment-contents (segment stream)
1337   (let ((result 0))
1338     (declare (type index result))
1339     (on-segment-contents-vectorly segment
1340                                   (lambda (v)
1341                                     (declare (type (vector assembly-unit) v))
1342                                     (incf result (length v))
1343                                     (write-sequence v stream)))
1344     result))
1345 \f
1346 ;;;; interface to the instruction set definition
1347
1348 ;;; Define a function named NAME that merges its arguments into a
1349 ;;; single integer and then emits the bytes of that integer in the
1350 ;;; correct order based on the endianness of the target-backend.
1351 (defmacro define-bitfield-emitter (name total-bits &rest byte-specs)
1352   (sb!int:collect ((arg-names) (arg-types))
1353     (let* ((total-bits (eval total-bits))
1354            (overall-mask (ash -1 total-bits))
1355            (num-bytes (multiple-value-bind (quo rem)
1356                           (truncate total-bits assembly-unit-bits)
1357                         (unless (zerop rem)
1358                           (error "~W isn't an even multiple of ~W."
1359                                  total-bits assembly-unit-bits))
1360                         quo))
1361            (bytes (make-array num-bytes :initial-element nil))
1362            (segment-arg (sb!xc:gensym "SEGMENT-")))
1363       (dolist (byte-spec-expr byte-specs)
1364         (let* ((byte-spec (eval byte-spec-expr))
1365                (byte-size (byte-size byte-spec))
1366                (byte-posn (byte-position byte-spec))
1367                (arg (sb!xc:gensym (format nil "~:@(ARG-FOR-~S-~)" byte-spec-expr))))
1368           (when (ldb-test (byte byte-size byte-posn) overall-mask)
1369             (error "The byte spec ~S either overlaps another byte spec, or ~
1370                     extends past the end."
1371                    byte-spec-expr))
1372           (setf (ldb byte-spec overall-mask) -1)
1373           (arg-names arg)
1374           (arg-types `(type (integer ,(ash -1 (1- byte-size))
1375                                      ,(1- (ash 1 byte-size)))
1376                             ,arg))
1377           (multiple-value-bind (start-byte offset)
1378               (floor byte-posn assembly-unit-bits)
1379             (let ((end-byte (floor (1- (+ byte-posn byte-size))
1380                                    assembly-unit-bits)))
1381               (flet ((maybe-ash (expr offset)
1382                        (if (zerop offset)
1383                            expr
1384                            `(ash ,expr ,offset))))
1385                 (declare (inline maybe-ash))
1386                 (cond ((zerop byte-size))
1387                       ((= start-byte end-byte)
1388                        (push (maybe-ash `(ldb (byte ,byte-size 0) ,arg)
1389                                         offset)
1390                              (svref bytes start-byte)))
1391                       (t
1392                        (push (maybe-ash
1393                               `(ldb (byte ,(- assembly-unit-bits offset) 0)
1394                                     ,arg)
1395                               offset)
1396                              (svref bytes start-byte))
1397                        (do ((index (1+ start-byte) (1+ index)))
1398                            ((>= index end-byte))
1399                          (push
1400                           `(ldb (byte ,assembly-unit-bits
1401                                       ,(- (* assembly-unit-bits
1402                                              (- index start-byte))
1403                                           offset))
1404                                 ,arg)
1405                           (svref bytes index)))
1406                        (let ((len (rem (+ byte-size offset)
1407                                        assembly-unit-bits)))
1408                          (push
1409                           `(ldb (byte ,(if (zerop len)
1410                                            assembly-unit-bits
1411                                            len)
1412                                       ,(- (* assembly-unit-bits
1413                                              (- end-byte start-byte))
1414                                           offset))
1415                                 ,arg)
1416                           (svref bytes end-byte))))))))))
1417       (unless (= overall-mask -1)
1418         (error "There are holes."))
1419       (let ((forms nil))
1420         (dotimes (i num-bytes)
1421           (let ((pieces (svref bytes i)))
1422             (aver pieces)
1423             (push `(emit-byte ,segment-arg
1424                               ,(if (cdr pieces)
1425                                    `(logior ,@pieces)
1426                                    (car pieces)))
1427                   forms)))
1428         `(defun ,name (,segment-arg ,@(arg-names))
1429            (declare (type segment ,segment-arg) ,@(arg-types))
1430            ,@(ecase sb!c:*backend-byte-order*
1431                (:little-endian (nreverse forms))
1432                (:big-endian forms))
1433            ',name)))))
1434
1435 (defun grovel-lambda-list (lambda-list vop-var)
1436   (let ((segment-name (car lambda-list))
1437         (vop-var (or vop-var (sb!xc:gensym "VOP"))))
1438     (sb!int:collect ((new-lambda-list))
1439       (new-lambda-list segment-name)
1440       (new-lambda-list vop-var)
1441       (labels
1442           ((grovel (state lambda-list)
1443              (when lambda-list
1444                (let ((param (car lambda-list)))
1445                  (cond
1446                   ((member param sb!xc:lambda-list-keywords)
1447                    (new-lambda-list param)
1448                    (grovel param (cdr lambda-list)))
1449                   (t
1450                    (ecase state
1451                      ((nil)
1452                       (new-lambda-list param)
1453                       `(cons ,param ,(grovel state (cdr lambda-list))))
1454                      (&optional
1455                       (multiple-value-bind (name default supplied-p)
1456                           (if (consp param)
1457                               (values (first param)
1458                                       (second param)
1459                                       (or (third param)
1460                                           (sb!xc:gensym "SUPPLIED-P-")))
1461                               (values param nil (sb!xc:gensym "SUPPLIED-P-")))
1462                         (new-lambda-list (list name default supplied-p))
1463                         `(and ,supplied-p
1464                               (cons ,(if (consp name)
1465                                          (second name)
1466                                          name)
1467                                     ,(grovel state (cdr lambda-list))))))
1468                      (&key
1469                       (multiple-value-bind (name default supplied-p)
1470                           (if (consp param)
1471                               (values (first param)
1472                                       (second param)
1473                                       (or (third param)
1474                                           (sb!xc:gensym "SUPPLIED-P-")))
1475                               (values param nil (sb!xc:gensym "SUPPLIED-P-")))
1476                         (new-lambda-list (list name default supplied-p))
1477                         (multiple-value-bind (key var)
1478                             (if (consp name)
1479                                 (values (first name) (second name))
1480                                 (values (keywordicate name) name))
1481                           `(append (and ,supplied-p (list ',key ,var))
1482                                    ,(grovel state (cdr lambda-list))))))
1483                      (&rest
1484                       (new-lambda-list param)
1485                       (grovel state (cdr lambda-list))
1486                       param))))))))
1487         (let ((reconstructor (grovel nil (cdr lambda-list))))
1488           (values (new-lambda-list)
1489                   segment-name
1490                   vop-var
1491                   reconstructor))))))
1492
1493 (defun extract-nths (index glue list-of-lists-of-lists)
1494   (mapcar (lambda (list-of-lists)
1495             (cons glue
1496                   (mapcar (lambda (list)
1497                             (nth index list))
1498                           list-of-lists)))
1499           list-of-lists-of-lists))
1500
1501 (defmacro define-instruction (name lambda-list &rest options)
1502   (let* ((sym-name (symbol-name name))
1503          (defun-name (sb!int:symbolicate sym-name "-INST-EMITTER"))
1504          (vop-var nil)
1505          (postits (gensym "POSTITS-"))
1506          (emitter nil)
1507          (decls nil)
1508          (attributes nil)
1509          (cost nil)
1510          (dependencies nil)
1511          (delay nil)
1512          (pinned nil)
1513          (pdefs nil))
1514     (sb!int:/noshow "entering DEFINE-INSTRUCTION" name lambda-list options)
1515     (dolist (option-spec options)
1516       (sb!int:/noshow option-spec)
1517       (multiple-value-bind (option args)
1518           (if (consp option-spec)
1519               (values (car option-spec) (cdr option-spec))
1520               (values option-spec nil))
1521         (sb!int:/noshow option args)
1522         (case option
1523           (:emitter
1524            (when emitter
1525              (error "You can only specify :EMITTER once per instruction."))
1526            (setf emitter args))
1527           (:declare
1528            (setf decls (append decls args)))
1529           (:attributes
1530            (setf attributes (append attributes args)))
1531           (:cost
1532            (setf cost (first args)))
1533           (:dependencies
1534            (setf dependencies (append dependencies args)))
1535           (:delay
1536            (when delay
1537              (error "You can only specify :DELAY once per instruction."))
1538            (setf delay args))
1539           (:pinned
1540            (setf pinned t))
1541           (:vop-var
1542            (if vop-var
1543                (error "You can only specify :VOP-VAR once per instruction.")
1544                (setf vop-var (car args))))
1545           (:printer
1546            (sb!int:/noshow "uniquifying :PRINTER with" args)
1547            (push (eval `(list (multiple-value-list
1548                                ,(sb!disassem:gen-printer-def-forms-def-form
1549                                  name
1550                                  (let ((*print-right-margin* 1000))
1551                                    (format nil "~@:(~A[~A]~)" name args))
1552                                  (cdr option-spec)))))
1553                  pdefs))
1554           (:printer-list
1555            ;; same as :PRINTER, but is EVALed first, and is a list of
1556            ;; printers
1557            (push
1558             (eval
1559              `(eval
1560                `(list ,@(mapcar (lambda (printer)
1561                                   `(multiple-value-list
1562                                     ,(sb!disassem:gen-printer-def-forms-def-form
1563                                       ',name
1564                                       (let ((*print-right-margin* 1000))
1565                                         (format nil "~@:(~A[~A]~)" ',name printer))
1566                                       printer
1567                                       nil)))
1568                                 ,(cadr option-spec)))))
1569             pdefs))
1570           (t
1571            (error "unknown option: ~S" option)))))
1572     (sb!int:/noshow "done processing options")
1573     (setf pdefs (nreverse pdefs))
1574     (multiple-value-bind
1575         (new-lambda-list segment-name vop-name arg-reconstructor)
1576         (grovel-lambda-list lambda-list vop-var)
1577       (sb!int:/noshow new-lambda-list segment-name vop-name arg-reconstructor)
1578       (push `(let ((hook (segment-inst-hook ,segment-name)))
1579                (when hook
1580                  (funcall hook ,segment-name ,vop-name ,sym-name
1581                           ,arg-reconstructor)))
1582             emitter)
1583       (push `(dolist (postit ,postits)
1584                (emit-back-patch ,segment-name 0 postit))
1585             emitter)
1586       (unless cost (setf cost 1))
1587       #!+sb-dyncount
1588       (push `(when (segment-collect-dynamic-statistics ,segment-name)
1589                (let* ((info (sb!c:ir2-component-dyncount-info
1590                              (sb!c:component-info
1591                               sb!c:*component-being-compiled*)))
1592                       (costs (sb!c:dyncount-info-costs info))
1593                       (block-number (sb!c:block-number
1594                                      (sb!c:ir2-block-block
1595                                       (sb!c:vop-block ,vop-name)))))
1596                  (incf (aref costs block-number) ,cost)))
1597             emitter)
1598       (when *assem-scheduler-p*
1599         (if pinned
1600             (setf emitter
1601                   `((when (segment-run-scheduler ,segment-name)
1602                       (schedule-pending-instructions ,segment-name))
1603                     ,@emitter))
1604             (let ((flet-name
1605                    (gensym (concatenate 'string "EMIT-" sym-name "-INST-")))
1606                   (inst-name (gensym "INST-")))
1607               (setf emitter `((flet ((,flet-name (,segment-name)
1608                                        ,@emitter))
1609                                 (if (segment-run-scheduler ,segment-name)
1610                                     (let ((,inst-name
1611                                            (make-instruction
1612                                             (incf (segment-inst-number
1613                                                    ,segment-name))
1614                                             #',flet-name
1615                                             (instruction-attributes
1616                                              ,@attributes)
1617                                             (progn ,@delay))))
1618                                       ,@(when dependencies
1619                                           `((note-dependencies
1620                                                 (,segment-name ,inst-name)
1621                                               ,@dependencies)))
1622                                       (queue-inst ,segment-name ,inst-name))
1623                                     (,flet-name ,segment-name))))))))
1624       `(progn
1625          (defun ,defun-name ,new-lambda-list
1626            ,@(when decls
1627                `((declare ,@decls)))
1628            (let ((,postits (segment-postits ,segment-name)))
1629              ;; Must be done so that contribs and user code doing
1630              ;; low-level stuff don't need to worry about this.
1631              (declare (disable-package-locks %%current-segment%%))
1632              (setf (segment-postits ,segment-name) nil)
1633              (macrolet ((%%current-segment%% ()
1634                           (error "You can't use INST without an ~
1635                                   ASSEMBLE inside emitters.")))
1636                ;; KLUDGE: Some host lisps (CMUCL 18e Sparc at least)
1637                ;; can't deal with this declaration, so disable it on host
1638                ;; Ditto for earlier ENABLE-PACKAGE-LOCKS %%C-S%% %%C-V%%
1639                ;; declaration.
1640                #-sb-xc-host
1641                (declare (enable-package-locks %%current-segment%%))
1642                ,@emitter))
1643            (values))
1644          (eval-when (:compile-toplevel :load-toplevel :execute)
1645            (%define-instruction ,sym-name ',defun-name))
1646          ,@(extract-nths 1 'progn pdefs)
1647          ,@(when pdefs
1648              `((sb!disassem:install-inst-flavors
1649                 ',name
1650                 (append ,@(extract-nths 0 'list pdefs)))))))))
1651
1652 (defmacro define-instruction-macro (name lambda-list &body body)
1653   (with-unique-names (whole env)
1654     (multiple-value-bind (body local-defs)
1655         (sb!kernel:parse-defmacro lambda-list whole body name
1656                                   'instruction-macro
1657                                   :environment env)
1658       `(eval-when (:compile-toplevel :load-toplevel :execute)
1659          (%define-instruction ,(symbol-name name)
1660                               (lambda (,whole ,env)
1661                                 ,@local-defs
1662                                 (block ,name
1663                                   ,body)))))))
1664
1665 (defun %define-instruction (name defun)
1666   (setf (gethash name *assem-instructions*) defun)
1667   name)