ab4403e5a5ac387bca5e78509352913542fd6394
[sbcl.git] / src / compiler / represent.lisp
1 ;;;; This file contains the implementation-independent code for the
2 ;;;; representation selection phase in the compiler. Representation
3 ;;;; selection decides whether to use non-descriptor representations
4 ;;;; for objects and emits the appropriate representation-specific move
5 ;;;; and coerce vops.
6
7 ;;;; This software is part of the SBCL system. See the README file for
8 ;;;; more information.
9 ;;;;
10 ;;;; This software is derived from the CMU CL system, which was
11 ;;;; written at Carnegie Mellon University and released into the
12 ;;;; public domain. The software is in the public domain and is
13 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
14 ;;;; files for more information.
15
16 (in-package "SB!C")
17 \f
18 ;;;; error routines
19 ;;;;
20 ;;;; Problems in the VM definition often show up here, so we try to be
21 ;;;; as implementor-friendly as possible.
22
23 ;;; Given a TN ref for a VOP argument or result, return these values:
24 ;;; 1. True if the operand is an argument, false otherwise.
25 ;;; 2. The ordinal position of the operand.
26 ;;; 3. True if the operand is a more operand, false otherwise.
27 ;;; 4. The costs for this operand.
28 ;;; 5. The load-scs vector for this operand (NIL if more-p.)
29 ;;; 6. True if the costs or SCs in the VOP-INFO are inconsistent with the
30 ;;;    currently record ones.
31 (defun get-operand-info (ref)
32   (declare (type tn-ref ref))
33   (let* ((arg-p (not (tn-ref-write-p ref)))
34          (vop (tn-ref-vop ref))
35          (info (vop-info vop)))
36     (flet ((frob (refs costs load more-cost)
37              (do ((refs refs (tn-ref-across refs))
38                   (costs costs (cdr costs))
39                   (load load (cdr load))
40                   (n 0 (1+ n)))
41                  ((null costs)
42                   (aver more-cost)
43                   (values arg-p
44                           (+ n
45                              (or (position-in #'tn-ref-across ref refs)
46                                  (error "couldn't find REF?"))
47                              1)
48                           t
49                           more-cost
50                           nil
51                           nil))
52                (when (eq refs ref)
53                  (let ((parse (vop-parse-or-lose (vop-info-name info))))
54                    (multiple-value-bind (ccosts cscs)
55                        (compute-loading-costs
56                         (elt (if arg-p
57                                  (vop-parse-args parse)
58                                  (vop-parse-results parse))
59                              n)
60                         arg-p)
61
62                      (return
63                       (values arg-p
64                               (1+ n)
65                               nil
66                               (car costs)
67                               (car load)
68                               (not (and (equalp ccosts (car costs))
69                                         (equalp cscs (car load))))))))))))
70       (if arg-p
71           (frob (vop-args vop) (vop-info-arg-costs info)
72                 (vop-info-arg-load-scs info)
73                 (vop-info-more-arg-costs info))
74           (frob (vop-results vop) (vop-info-result-costs info)
75                 (vop-info-result-load-scs info)
76                 (vop-info-more-result-costs info))))))
77
78 ;;; Convert a load-costs vector to the list of SCs allowed by the operand
79 ;;; restriction.
80 (defun listify-restrictions (restr)
81   (declare (type sc-vector restr))
82   (collect ((res))
83     (dotimes (i sc-number-limit)
84       (when (eq (svref restr i) t)
85         (res (svref *backend-sc-numbers* i))))
86     (res)))
87
88 ;;; Try to give a helpful error message when Ref has no cost specified for
89 ;;; some SC allowed by the TN's primitive-type.
90 (defun bad-costs-error (ref)
91   (declare (type tn-ref ref))
92   (let* ((tn (tn-ref-tn ref))
93          (ptype (tn-primitive-type tn)))
94     (multiple-value-bind (arg-p pos more-p costs load-scs incon)
95         (get-operand-info ref)
96       (collect ((losers))
97         (dolist (scn (primitive-type-scs ptype))
98           (unless (svref costs scn)
99             (losers (svref *backend-sc-numbers* scn))))
100
101         (unless (losers)
102           (error "Representation selection flamed out for no obvious reason.~@
103                   Try again after recompiling the VM definition."))
104         
105         (error "~S is not valid as the ~:R ~:[result~;argument~] to the~@
106                 ~S VOP, since the TN's primitive type ~S allows SCs:~%  ~S~@
107                 ~:[which cannot be coerced or loaded into the allowed SCs:~
108                 ~%  ~S~;~*~]~:[~;~@
109                 Current cost info inconsistent with that in effect at compile ~
110                 time. Recompile.~%Compilation order may be incorrect.~]"
111                tn pos arg-p
112                (template-name (vop-info (tn-ref-vop ref)))
113                (primitive-type-name ptype)
114                (mapcar #'sc-name (losers))
115                more-p
116                (unless more-p
117                  (mapcar #'sc-name (listify-restrictions load-scs)))
118                incon)))))
119
120 ;;; Try to give a helpful error message when we fail to do a coercion
121 ;;; for some reason.
122 (defun bad-coerce-error (op)
123   (declare (type tn-ref op))
124   (let* ((op-tn (tn-ref-tn op))
125          (op-sc (tn-sc op-tn))
126          (op-scn (sc-number op-sc))
127          (ptype (tn-primitive-type op-tn))
128          (write-p (tn-ref-write-p op)))
129     (multiple-value-bind (arg-p pos more-p costs load-scs incon)
130         (get-operand-info op)
131       (declare (ignore costs more-p))
132       (collect ((load-lose)
133                 (no-move-scs)
134                 (move-lose))
135         (dotimes (i sc-number-limit)
136           (let ((i-sc (svref *backend-sc-numbers* i)))
137             (when (eq (svref load-scs i) t)
138               (cond ((not (sc-allowed-by-primitive-type i-sc ptype))
139                      (load-lose i-sc))
140                     ((not (find-move-vop op-tn write-p i-sc ptype
141                                          #'sc-move-vops))
142                      (let ((vops (if write-p
143                                      (svref (sc-move-vops op-sc) i)
144                                      (svref (sc-move-vops i-sc) op-scn))))
145                        (if vops
146                            (dolist (vop vops) (move-lose (template-name vop)))
147                            (no-move-scs i-sc))))
148                     (t
149                      (error "Representation selection flamed out for no ~
150                              obvious reason."))))))
151         
152         (unless (or (load-lose) (no-move-scs) (move-lose))
153           (error "Representation selection flamed out for no obvious reason.~@
154                   Try again after recompiling the VM definition."))
155
156         (error "~S is not valid as the ~:R ~:[result~;argument~] to VOP:~
157                 ~%  ~S~%Primitive type: ~S~@
158                 SC restrictions:~%  ~S~@
159                 ~@[The primitive type disallows these loadable SCs:~%  ~S~%~]~
160                 ~@[No move VOPs are defined to coerce to these allowed SCs:~
161                 ~%  ~S~%~]~
162                 ~@[These move VOPs couldn't be used due to operand type ~
163                 restrictions:~%  ~S~%~]~
164                 ~:[~;~@
165                 Current cost info inconsistent with that in effect at compile ~
166                 time. Recompile.~%Compilation order may be incorrect.~]"
167                op-tn pos arg-p
168                (template-name (vop-info (tn-ref-vop op)))
169                (primitive-type-name ptype)
170                (mapcar #'sc-name (listify-restrictions load-scs))
171                (mapcar #'sc-name (load-lose))
172                (mapcar #'sc-name (no-move-scs))
173                (move-lose)
174                incon)))))
175
176 (defun bad-move-arg-error (val pass)
177   (declare (type tn val pass))
178   (error "no :MOVE-ARGUMENT VOP defined to move ~S (SC ~S) to ~
179           ~S (SC ~S)"
180          val (sc-name (tn-sc val))
181          pass (sc-name (tn-sc pass))))
182 \f
183 ;;;; VM consistency checking
184 ;;;;
185 ;;;; We do some checking of the consistency of the VM definition at load
186 ;;;; time.
187
188 ;;; FIXME: should probably be conditional on #!+SB-SHOW
189 (defun check-move-function-consistency ()
190   (dotimes (i sc-number-limit)
191     (let ((sc (svref *backend-sc-numbers* i)))
192       (when sc
193         (let ((moves (sc-move-functions sc)))
194           (dolist (const (sc-constant-scs sc))
195             (unless (svref moves (sc-number const))
196               (warn "no move function defined to load SC ~S from constant ~
197                      SC ~S"
198                     (sc-name sc) (sc-name const))))
199
200           (dolist (alt (sc-alternate-scs sc))
201             (unless (svref moves (sc-number alt))
202               (warn "no move function defined to load SC ~S from alternate ~
203                      SC ~S"
204                     (sc-name sc) (sc-name alt)))
205             (unless (svref (sc-move-functions alt) i)
206               (warn "no move function defined to save SC ~S to alternate ~
207                      SC ~S"
208                     (sc-name sc) (sc-name alt)))))))))
209 \f
210 ;;;; representation selection
211
212 ;;; VOPs that we ignore in initial cost computation. We ignore SET in
213 ;;; the hopes that nobody is setting specials inside of loops. We
214 ;;; ignore TYPE-CHECK-ERROR because we don't want the possibility of
215 ;;; error to bias the result. Notes are suppressed for T-C-E as well,
216 ;;; since we don't need to worry about the efficiency of that case.
217 (defparameter *ignore-cost-vops* '(set type-check-error))
218 (defparameter *suppress-note-vops* '(type-check-error))
219
220 ;;; We special-case the move VOP, since using this costs for the
221 ;;; normal MOVE would spuriously encourage descriptor representations.
222 ;;; We won't actually need to coerce to descriptor and back, since we
223 ;;; will replace the MOVE with a specialized move VOP. What we do is
224 ;;; look at the other operand. If its representation has already been
225 ;;; chosen (e.g. if it is wired), then we use the appropriate move
226 ;;; costs, otherwise we just ignore the references.
227 (defun add-representation-costs (refs scs costs
228                                       ops-slot costs-slot more-costs-slot
229                                       write-p)
230   (do ((ref refs (tn-ref-next ref)))
231       ((null ref))
232     (flet ((add-costs (cost)
233              (dolist (scn scs)
234                (let ((res (svref cost scn)))
235                  (unless res
236                    (bad-costs-error ref))
237                  (incf (svref costs scn) res)))))
238       (let* ((vop (tn-ref-vop ref))
239              (info (vop-info vop)))
240         (unless (find (vop-info-name info) *ignore-cost-vops*)
241           (case (vop-info-name info)
242             (move
243              (let ((rep (tn-sc
244                          (tn-ref-tn
245                           (if write-p
246                               (vop-args vop)
247                               (vop-results vop))))))
248                (when rep
249                  (if write-p
250                      (dolist (scn scs)
251                        (let ((res (svref (sc-move-costs
252                                           (svref *backend-sc-numbers* scn))
253                                          (sc-number rep))))
254                          (when res
255                            (incf (svref costs scn) res))))
256                      (dolist (scn scs)
257                        (let ((res (svref (sc-move-costs rep) scn)))
258                          (when res
259                            (incf (svref costs scn) res))))))))
260             (t
261              (do ((cost (funcall costs-slot info) (cdr cost))
262                   (op (funcall ops-slot vop) (tn-ref-across op)))
263                  ((null cost)
264                   (add-costs (funcall more-costs-slot info)))
265                (when (eq op ref)
266                  (add-costs (car cost))
267                  (return)))))))))
268   (values))
269
270 ;;; Return the best representation for a normal TN. SCs is a list
271 ;;; of the SC numbers of the SCs to select from. Costs is a scratch
272 ;;; vector.
273 ;;;
274 ;;; What we do is sum the costs for each reference to TN in each of
275 ;;; the SCs, and then return the SC having the lowest cost. A second
276 ;;; value is returned which is true when the selection is unique which
277 ;;; is often not the case for the MOVE VOP.
278 (defun select-tn-representation (tn scs costs)
279   (declare (type tn tn) (type sc-vector costs)
280            (inline add-representation-costs))
281   (dolist (scn scs)
282     (setf (svref costs scn) 0))
283
284   (add-representation-costs (tn-reads tn) scs costs
285                             #'vop-args #'vop-info-arg-costs
286                             #'vop-info-more-arg-costs
287                             nil)
288   (add-representation-costs (tn-writes tn) scs costs
289                             #'vop-results #'vop-info-result-costs
290                             #'vop-info-more-result-costs
291                             t)
292
293   (let ((min most-positive-fixnum)
294         (min-scn nil)
295         (unique nil))
296     (dolist (scn scs)
297       (let ((cost (svref costs scn)))
298         (cond ((= cost min)
299                (setf unique nil))
300               ((< cost min)
301                (setq min cost)
302                (setq min-scn scn)
303                (setq unique t)))))
304     (values (svref *backend-sc-numbers* min-scn) unique)))
305
306 ;;; Prepare for the possibility of a TN being allocated on the number stack by
307 ;;; setting NUMBER-STACK-P in all functions that TN is referenced in and in all
308 ;;; the functions in their tail sets. Refs is a TN-Refs list of references to
309 ;;; the TN.
310 (defun note-number-stack-tn (refs)
311   (declare (type (or tn-ref null) refs))
312
313   (do ((ref refs (tn-ref-next ref)))
314       ((null ref))
315     (let* ((lambda (block-home-lambda
316                     (ir2-block-block
317                      (vop-block (tn-ref-vop ref)))))
318            (tails (lambda-tail-set lambda)))
319       (flet ((frob (fun)
320                (setf (ir2-environment-number-stack-p
321                       (environment-info
322                        (lambda-environment fun)))
323                      t)))
324         (frob lambda)
325         (when tails
326           (dolist (fun (tail-set-functions tails))
327             (frob fun))))))
328
329   (values))
330
331 ;;; If TN is a variable, return the name. If TN is used by a VOP emitted
332 ;;; for a return, then return a string indicating this. Otherwise, return NIL.
333 (defun get-operand-name (tn arg-p)
334   (declare (type tn tn))
335   (let* ((actual (if (eq (tn-kind tn) :alias) (tn-save-tn tn) tn))
336          (reads (tn-reads tn))
337          (leaf (tn-leaf actual)))
338     (cond ((lambda-var-p leaf) (leaf-name leaf))
339           ((and (not arg-p) reads
340                 (return-p (vop-node (tn-ref-vop reads))))
341            "<return value>")
342           (t
343            nil))))
344
345 ;;; If policy indicates, give an efficiency note for doing the coercion
346 ;;; Vop, where Op is the operand we are coercing for and Dest-TN is the
347 ;;; distinct destination in a move.
348 (defun do-coerce-efficiency-note (vop op dest-tn)
349   (declare (type vop-info vop) (type tn-ref op) (type (or tn null) dest-tn))
350   (let* ((note (or (template-note vop) (template-name vop)))
351          (cost (template-cost vop))
352          (op-vop (tn-ref-vop op))
353          (op-node (vop-node op-vop))
354          (op-tn (tn-ref-tn op))
355          (*compiler-error-context* op-node))
356     (cond ((eq (tn-kind op-tn) :constant))
357           ((policy op-node (and (<= speed inhibit-warnings)
358                                 (<= space inhibit-warnings))))
359           ((member (template-name (vop-info op-vop)) *suppress-note-vops*))
360           ((null dest-tn)
361            (let* ((op-info (vop-info op-vop))
362                   (op-note (or (template-note op-info)
363                                (template-name op-info)))
364                   (arg-p (not (tn-ref-write-p op)))
365                   (name (get-operand-name op-tn arg-p))
366                   (pos (1+ (or (position-in #'tn-ref-across op
367                                             (if arg-p
368                                                 (vop-args op-vop)
369                                                 (vop-results op-vop)))
370                                (error "couldn't find op? bug!")))))
371              (compiler-note
372               "doing ~A (cost ~D)~:[~2*~; ~:[to~;from~] ~S~], for:~%~6T~
373                the ~:R ~:[result~;argument~] of ~A"
374               note cost name arg-p name
375               pos arg-p op-note)))
376           (t
377            (compiler-note "doing ~A (cost ~D)~@[ from ~S~]~@[ to ~S~]"
378                           note cost (get-operand-name op-tn t)
379                           (get-operand-name dest-tn nil)))))
380   (values))
381
382 ;;; Find a move VOP to move from the operand OP-TN to some other
383 ;;; representation corresponding to OTHER-SC and OTHER-PTYPE. Slot is the SC
384 ;;; slot that we grab from (move or move-argument). Write-P indicates that OP
385 ;;; is a VOP result, so OP is the move result and other is the arg, otherwise
386 ;;; OP is the arg and other is the result.
387 ;;;
388 ;;; If an operand is of primitive type T, then we use the type of the other
389 ;;; operand instead, effectively intersecting the argument and result type
390 ;;; assertions. This way, a move VOP can restrict whichever operand makes more
391 ;;; sense, without worrying about which operand has the type info.
392 (defun find-move-vop (op-tn write-p other-sc other-ptype slot)
393   (declare (type tn op-tn) (type sc other-sc)
394            (type primitive-type other-ptype)
395            (type function slot))
396   (let* ((op-sc (tn-sc op-tn))
397          (op-scn (sc-number op-sc))
398          (other-scn (sc-number other-sc))
399          (any-ptype *backend-t-primitive-type*)
400          (op-ptype (tn-primitive-type op-tn)))
401     (let ((other-ptype (if (eq other-ptype any-ptype) op-ptype other-ptype))
402           (op-ptype (if (eq op-ptype any-ptype) other-ptype op-ptype)))
403       (dolist (info (if write-p
404                         (svref (funcall slot op-sc) other-scn)
405                         (svref (funcall slot other-sc) op-scn))
406                     nil)
407         (when (and (operand-restriction-ok
408                     (first (template-arg-types info))
409                     (if write-p other-ptype op-ptype)
410                     :tn op-tn :t-ok nil)
411                    (operand-restriction-ok
412                     (first (template-result-types info))
413                     (if write-p op-ptype other-ptype)
414                     :t-ok nil))
415           (return info))))))
416         
417 ;;; Emit a coercion VOP for Op Before the specifed VOP or die trying. SCS
418 ;;; is the operand's LOAD-SCS vector, which we use to determine what SCs the
419 ;;; VOP will accept. We pick any acceptable coerce VOP, since it practice it
420 ;;; seems uninteresting to have more than one applicable.
421 ;;;
422 ;;; On the X86 port, stack SCs may be placed in the list of operand
423 ;;; preferred SCs, and to prevent these stack SCs being selected when
424 ;;; a register SC is available the non-stack SCs are searched first.
425 ;;;
426 ;;; What we do is look at each SC allowed by both the operand restriction
427 ;;; and the operand primitive-type, and see whether there is a move VOP
428 ;;; which moves between the operand's SC and load SC. If we find such a
429 ;;; VOP, then we make a TN having the load SC as the representation.
430 ;;;
431 ;;; Dest-TN is the TN that we are moving to, for a move or move-arg. This
432 ;;; is only for efficiency notes.
433 ;;;
434 ;;; If the TN is an unused result TN, then we don't actually emit the move;
435 ;;; we just change to the right kind of TN.
436 (defun emit-coerce-vop (op dest-tn scs before)
437   (declare (type tn-ref op) (type sc-vector scs) (type (or vop null) before)
438            (type (or tn null) dest-tn))
439   (let* ((op-tn (tn-ref-tn op))
440          (ptype (tn-primitive-type op-tn))
441          (write-p (tn-ref-write-p op))
442          (vop (tn-ref-vop op))
443          (node (vop-node vop))
444          (block (vop-block vop)))
445     (flet ((check-sc (scn sc)
446              (when (sc-allowed-by-primitive-type sc ptype)
447                (let ((res (find-move-vop op-tn write-p sc ptype
448                                          #'sc-move-vops)))
449                  (when res
450                    (when (>= (vop-info-cost res)
451                              *efficiency-note-cost-threshold*)
452                      (do-coerce-efficiency-note res op dest-tn))
453                    (let ((temp (make-representation-tn ptype scn)))
454                      (change-tn-ref-tn op temp)
455                      (cond
456                        ((not write-p)
457                         (emit-move-template node block res op-tn temp before))
458                        ((and (null (tn-reads op-tn))
459                              (eq (tn-kind op-tn) :normal)))
460                        (t
461                         (emit-move-template node block res temp op-tn
462                                             before))))
463                    t)))))
464       ;; Search the non-stack load SCs first.
465       (dotimes (scn sc-number-limit)
466         (let ((sc (svref *backend-sc-numbers* scn)))
467           (when (and (eq (svref scs scn) t)
468                      (not (eq (sb-kind (sc-sb sc)) :unbounded))
469                      (check-sc scn sc))
470             (return-from emit-coerce-vop))))
471       ;; Search the stack SCs if the above failed.
472       (dotimes (scn sc-number-limit (bad-coerce-error op))
473         (let ((sc (svref *backend-sc-numbers* scn)))
474           (when (and (eq (svref scs scn) t)
475                      (eq (sb-kind (sc-sb sc)) :unbounded)
476                      (check-sc scn sc))
477             (return)))))))
478
479 ;;; Scan some operands and call EMIT-COERCE-VOP on any for which we can't
480 ;;; load the operand. The coerce VOP is inserted Before the specified VOP.
481 ;;; Dest-TN is the destination TN if we are doing a move or move-arg, and is
482 ;;; NIL otherwise. This is only used for efficiency notes.
483 #!-sb-fluid (declaim (inline coerce-some-operands))
484 (defun coerce-some-operands (ops dest-tn load-scs before)
485   (declare (type (or tn-ref null) ops) (list load-scs)
486            (type (or tn null) dest-tn) (type (or vop null) before))
487   (do ((op ops (tn-ref-across op))
488        (scs load-scs (cdr scs)))
489       ((null scs))
490     (unless (svref (car scs)
491                    (sc-number (tn-sc (tn-ref-tn op))))
492       (emit-coerce-vop op dest-tn (car scs) before)))
493   (values))
494
495 ;;; Emit coerce VOPs for the args and results, as needed.
496 (defun coerce-vop-operands (vop)
497   (declare (type vop vop))
498   (let ((info (vop-info vop)))
499     (coerce-some-operands (vop-args vop) nil (vop-info-arg-load-scs info) vop)
500     (coerce-some-operands (vop-results vop) nil (vop-info-result-load-scs info)
501                           (vop-next vop)))
502   (values))
503
504 ;;; Iterate over the more operands to a call VOP, emitting move-arg VOPs and
505 ;;; any necessary coercions. We determine which FP to use by looking at the
506 ;;; MOVE-ARGS annotation. If the vop is a :LOCAL-CALL, we insert any needed
507 ;;; coercions before the ALLOCATE-FRAME so that lifetime analysis doesn't get
508 ;;; confused (since otherwise, only passing locations are written between A-F
509 ;;; and call.)
510 (defun emit-arg-moves (vop)
511   (let* ((info (vop-info vop))
512          (node (vop-node vop))
513          (block (vop-block vop))
514          (how (vop-info-move-args info))
515          (args (vop-args vop))
516          (fp-tn (tn-ref-tn args))
517          (nfp-tn (if (eq how :local-call)
518                      (tn-ref-tn (tn-ref-across args))
519                      nil))
520          (pass-locs (first (vop-codegen-info vop)))
521          (prev (vop-prev vop)))
522     (do ((val (do ((arg args (tn-ref-across arg))
523                    (req (template-arg-types info) (cdr req)))
524                   ((null req) arg))
525               (tn-ref-across val))
526          (pass pass-locs (cdr pass)))
527         ((null val)
528          (aver (null pass)))
529       (let* ((val-tn (tn-ref-tn val))
530              (pass-tn (first pass))
531              (pass-sc (tn-sc pass-tn))
532              (res (find-move-vop val-tn nil pass-sc
533                                  (tn-primitive-type pass-tn)
534                                  #'sc-move-arg-vops)))
535         (unless res
536           (bad-move-arg-error val-tn pass-tn))
537         
538         (change-tn-ref-tn val pass-tn)
539         (let* ((this-fp
540                 (cond ((not (sc-number-stack-p pass-sc)) fp-tn)
541                       (nfp-tn)
542                       (t
543                        (aver (eq how :known-return))
544                        (setq nfp-tn (make-number-stack-pointer-tn))
545                        (setf (tn-sc nfp-tn)
546                              (svref *backend-sc-numbers*
547                                     (first (primitive-type-scs
548                                             (tn-primitive-type nfp-tn)))))
549                        (emit-context-template
550                         node block
551                         (template-or-lose 'compute-old-nfp)
552                         nfp-tn vop)
553                        (aver (not (sc-number-stack-p (tn-sc nfp-tn))))
554                        nfp-tn)))
555                (new (emit-move-arg-template node block res val-tn this-fp
556                                             pass-tn vop))
557                (after
558                 (cond ((eq how :local-call)
559                        (aver (eq (vop-info-name (vop-info prev))
560                                  'allocate-frame))
561                        prev)
562                       (prev (vop-next prev))
563                       (t
564                        (ir2-block-start-vop block)))))
565           (coerce-some-operands (vop-args new) pass-tn
566                                 (vop-info-arg-load-scs res)
567                                 after)))))
568   (values))
569
570 ;;; Scan the IR2 looking for move operations that need to be replaced with
571 ;;; special-case VOPs and emitting coercion VOPs for operands of normal VOPs.
572 ;;; We delete moves to TNs that are never read at this point, rather than
573 ;;; possibly converting them to some expensive move operation.
574 (defun emit-moves-and-coercions (block)
575   (declare (type ir2-block block))
576   (do ((vop (ir2-block-start-vop block)
577             (vop-next vop)))
578       ((null vop))
579     (let ((info (vop-info vop))
580           (node (vop-node vop))
581           (block (vop-block vop)))
582       (cond
583        ((eq (vop-info-name info) 'move)
584         (let* ((args (vop-args vop))
585                (x (tn-ref-tn args))
586                (y (tn-ref-tn (vop-results vop)))
587                (res (find-move-vop x nil (tn-sc y) (tn-primitive-type y)
588                                    #'sc-move-vops)))
589           (cond ((and (null (tn-reads y))
590                       (eq (tn-kind y) :normal))
591                  (delete-vop vop))
592                 ((eq res info))
593                 (res
594                  (when (>= (vop-info-cost res)
595                            *efficiency-note-cost-threshold*)
596                    (do-coerce-efficiency-note res args y))
597                  (emit-move-template node block res x y vop)
598                  (delete-vop vop))
599                 (t
600                  (coerce-vop-operands vop)))))
601        ((vop-info-move-args info)
602         (emit-arg-moves vop))
603        (t
604         (coerce-vop-operands vop))))))
605
606 ;;; If TN is in a number stack SC, make all the right annotations. Note
607 ;;; that this should be called after TN has been referenced, since it must
608 ;;; iterate over the referencing environments.
609 #!-sb-fluid (declaim (inline note-if-number-stack))
610 (defun note-if-number-stack (tn 2comp restricted)
611   (declare (type tn tn) (type ir2-component 2comp))
612   (when (if restricted
613             (eq (sb-name (sc-sb (tn-sc tn))) 'non-descriptor-stack)
614             (sc-number-stack-p (tn-sc tn)))
615     (unless (ir2-component-nfp 2comp)
616       (setf (ir2-component-nfp 2comp) (make-nfp-tn)))
617     (note-number-stack-tn (tn-reads tn))
618     (note-number-stack-tn (tn-writes tn)))
619   (values))
620
621 ;;; Entry to representation selection. First we select the representation for
622 ;;; all normal TNs, setting the TN-SC. After selecting the TN representations,
623 ;;; we set the SC for all :ALIAS TNs to be the representation chosen for the
624 ;;; original TN. We then scan all the IR2, emitting any necessary coerce and
625 ;;; move-arg VOPs. Finally, we scan all TNs looking for ones that might be
626 ;;; placed on the number stack, noting this so that the number-FP can be
627 ;;; allocated. This must be done last, since references in new environments may
628 ;;; be introduced by MOVE-ARG insertion.
629 (defun select-representations (component)
630   (let ((costs (make-array sc-number-limit))
631         (2comp (component-info component)))
632
633     ;; First pass; only allocate SCs where there is a distinct choice.
634     (do ((tn (ir2-component-normal-tns 2comp)
635              (tn-next tn)))
636         ((null tn))
637       (aver (tn-primitive-type tn))
638       (unless (tn-sc tn)
639         (let* ((scs (primitive-type-scs (tn-primitive-type tn))))
640           (cond ((rest scs)
641                  (multiple-value-bind (sc unique)
642                      (select-tn-representation tn scs costs)
643                    (when unique
644                       (setf (tn-sc tn) sc))))
645                 (t
646                  (setf (tn-sc tn)
647                        (svref *backend-sc-numbers* (first scs))))))))
648
649     (do ((tn (ir2-component-normal-tns 2comp)
650              (tn-next tn)))
651         ((null tn))
652       (aver (tn-primitive-type tn))
653       (unless (tn-sc tn)
654         (let* ((scs (primitive-type-scs (tn-primitive-type tn)))
655                (sc (if (rest scs)
656                        (select-tn-representation tn scs costs)
657                        (svref *backend-sc-numbers* (first scs)))))
658           (aver sc)
659           (setf (tn-sc tn) sc))))
660
661     (do ((alias (ir2-component-alias-tns 2comp)
662                 (tn-next alias)))
663         ((null alias))
664       (setf (tn-sc alias) (tn-sc (tn-save-tn alias))))
665
666     (do-ir2-blocks (block component)
667       (emit-moves-and-coercions block))
668
669     (macrolet ((frob (slot restricted)
670                  `(do ((tn (,slot 2comp) (tn-next tn)))
671                       ((null tn))
672                     (note-if-number-stack tn 2comp ,restricted))))
673       (frob ir2-component-normal-tns nil)
674       (frob ir2-component-wired-tns t)
675       (frob ir2-component-restricted-tns t)))
676
677   (values))