OSDN Git Service

* mach.scm (<derived-arch-data>): New member large-insn-word?.
[pf3gnuchains/pf3gnuchains4x.git] / cgen / decode.scm
1 ; Application independent decoder support.
2 ; Copyright (C) 2000, 2004, 2009 Red Hat, Inc.
3 ; This file is part of CGEN.
4 ;
5 ; This file provides utilities for building instruction set decoders.
6 ; At present its rather limited, and is geared towards the simulator
7 ; where the goal is hyper-efficiency [not that there isn't room for much
8 ; improvement, but rather that that's what the current focus is].
9 ;
10 ; The CPU description file provides the first pass's bit mask with the
11 ; `decode-assist' spec.  This gives the decoder a head start on how to
12 ; efficiently decode the instruction set.  The rest of the decoder is
13 ; determined algorithmically.
14 ; ??? Need to say more here.
15 ;
16 ; The main entry point is decode-build-table.
17 ;
18 ; Main procedure call tree:
19 ; decode-build-table
20 ;     /build-slots
21 ;     /build-decode-table-guts
22 ;         /build-decode-table-entry
23 ;             /build-slots
24 ;             /build-decode-table-guts
25 ;
26 ; /build-slots//build-decode-table-guts are recursively called to construct a
27 ; tree of "table-guts" elements, and then the application recurses on the
28 ; result.  For example see sim-decode.scm.
29 ;
30 ; FIXME: Don't create more than 3 shifts (i.e. no more than 3 groups).
31 ; FIXME: Exits when insns are unambiguously determined, even if there are more
32 ; opcode bits to examine.
33 \f
34 ; Decoder data structures and accessors.
35 ; The set of instruction is internally recorded as a tree of two data
36 ; structures: "table-guts" and "table-entry".
37 ; [The choice of "table-guts" is historical, a better name will come to mind
38 ; eventually.]
39
40 ; Decoded tables data structure, termed "dtable-guts".
41 ; A simple data structure of 4 elements:
42 ; bitnums:  list of bits that have been used thus far to decode the insn
43 ; startbit: bit offset in instruction of value in C local variable `insn'
44 ;           (note that this is independent of LSB0?)
45 ; bitsize:  size of value in C local variable `insn'
46 ; entries:  list of insns that match the decoding thus far,
47 ;           each entry in the list is a `dtable-entry' record
48
49 (define (dtable-guts-make bitnums startbit bitsize entries)
50   (vector bitnums startbit bitsize entries)
51 )
52
53 ; Accessors.
54 (define (dtable-guts-bitnums tg) (vector-ref tg 0))
55 (define (dtable-guts-startbit tg) (vector-ref tg 1))
56 (define (dtable-guts-bitsize tg) (vector-ref tg 2))
57 (define (dtable-guts-entries tg) (vector-ref tg 3))
58
59 ; A decoded subtable.
60 ; A simple data structure of 3 elements:
61 ; key: name to distinguish this subtable from others, used for lookup
62 ; table: a table-guts element
63 ; name: name of C variable containing the table
64 ;
65 ; The implementation uses a list so the lookup can use assv.
66
67 (define (subdtable-make key table name)
68   (list key table name)
69 )
70
71 ; Accessors.
72 (define (subdtable-key st) (car st))
73 (define (subdtable-table st) (cadr st))
74 (define (subdtable-name st) (caddr st))
75
76 ; List of decode subtables.
77 (define /decode-subtables nil)
78
79 (define (subdtable-lookup key) (assv key /decode-subtables))
80
81 ; Add SUBTABLE-GUTS to the subtables list if not already present.
82 ; Result is the subtable entry already present, or new entry.
83 ; The key is computed so as to make comparisons possible with assv.
84
85 (define (subdtable-add subtable-guts name)
86   (let* ((key (string->symbol
87                (string-append
88                 (numbers->string (dtable-guts-bitnums subtable-guts) " ")
89                 " " (number->string (dtable-guts-bitsize subtable-guts))
90                 (string-map
91                  (lambda (elm)
92                    (case (dtable-entry-type elm)
93                      ((insn)
94                       (stringsym-append " " (obj:name (dtable-entry-value elm))))
95                      ((table)
96                       (stringsym-append " " (subdtable-name (dtable-entry-value elm))))
97                      ((expr)
98                       (stringsym-append " " (exprtable-name (dtable-entry-value elm))))
99                      (else (error "bad dtable entry type:"
100                                   (dtable-entry-type elm)))))
101                  (dtable-guts-entries subtable-guts)))))
102          (entry (subdtable-lookup key)))
103     (if (not entry)
104         (begin
105           (set! /decode-subtables (cons (subdtable-make key subtable-guts name)
106                                         /decode-subtables))
107           (car /decode-subtables))
108         entry))
109 )
110
111 ; An instruction and predicate for final matching.
112
113 (define (exprtable-entry-make insn expr)
114   (vector insn expr (rtl-find-ifields expr))
115 )
116
117 ; Accessors.
118
119 (define (exprtable-entry-insn entry) (vector-ref entry 0))
120 (define (exprtable-entry-expr entry) (vector-ref entry 1))
121 (define (exprtable-entry-iflds entry) (vector-ref entry 2))
122
123 ; Return a pseudo-cost of processing exprentry X.
124
125 (define (exprentry-cost x)
126   (let ((expr (exprtable-entry-expr x)))
127     (case (rtx-name expr)
128       ((member) (length (rtx-member-set expr)))
129       (else 4)))
130 )
131
132 ; Sort an exprtable, optimum choices first.
133 ; Basically an optimum choice is a cheaper choice.
134
135 (define (exprtable-sort expr-list)
136   (sort expr-list
137         (lambda (a b)
138           (let ((costa (exprentry-cost a))
139                 (costb (exprentry-cost b)))
140             (< costa costb))))
141 )
142
143 ; Return the name of the expr table for INSN-EXPRS,
144 ; which is a list of exprtable-entry elements.
145
146 (define (/gen-exprtable-name insn-exprs)
147   (string-map (lambda (x)
148                 (string-append (obj:str-name (exprtable-entry-insn x))
149                                "-"
150                                (rtx-strdump (exprtable-entry-expr x))))
151               insn-exprs)
152 )
153
154 ; A set of instructions that need expressions to distinguish.
155 ; Typically the expressions are ifield-assertion specs.
156 ; INSN-EXPRS is a sorted list of exprtable-entry elements.
157 ; The list is considered sorted in the sense that the first insn to satisfy
158 ; its predicate is chosen.
159
160 (define (exprtable-make name insn-exprs)
161   (vector name insn-exprs)
162 )
163
164 ; Accessors.
165
166 (define (exprtable-name etable) (vector-ref etable 0))
167 (define (exprtable-insns etable) (vector-ref etable 1))
168
169 ; Decoded table entry data structure.
170 ; A simple data structure of 3 elements:
171 ; index: index in the parent table
172 ; entry type indicator: 'insn or 'table or 'expr
173 ; value: the insn or subtable or exprtable
174
175 (define (dtable-entry-make index type value)
176   (assert value)
177   (vector index type value)
178 )
179
180 ; Accessors.
181 (define (dtable-entry-index te) (vector-ref te 0))
182 (define (dtable-entry-type te) (vector-ref te 1))
183 (define (dtable-entry-value te) (vector-ref te 2))
184 \f
185 ; Return #t if BITNUM is a good bit to use for decoding.
186 ; MASKS is a list of opcode masks.
187 ; MASK-LENS is a list of lengths of each value in MASKS.
188 ; BITNUM is the number of the bit to test.  It's value depends on LSB0?.
189 ; It can be no larger than the smallest element in MASKS.
190 ; E.g. If MASK-LENS consists of 16 and 32 and LSB0? is #f, BITNUM must
191 ; be from 0 to 15.
192 ; FIXME: This isn't quite right.  What if LSB0? = #t?  Need decode-bitsize.
193 ; LSB0? is non-#f if bit number 0 is the least significant bit.
194 ;
195 ; FIXME: This is just a first cut, but the governing intent is to not require
196 ; targets to specify decode tables, hints, or algorithms.
197 ; Certainly as it becomes useful they can supply such information.
198 ; The point is to avoid having to as much as possible.
199 ;
200 ; FIXME: Bit numbers shouldn't be considered in isolation.
201 ; It would be better to compute use counts of all of them and then see
202 ; if there's a cluster of high use counts.
203
204 (define (/usable-decode-bit? masks mask-lens bitnum lsb0?)
205   (let* ((has-bit (map (lambda (msk len)
206                          (bit-set? msk (if lsb0? bitnum (- len bitnum 1))))
207                        masks mask-lens)))
208     (or (all-true? has-bit)
209         ; If half or more insns use the bit, it's a good one.
210         ; FIXME: An empirical guess at best.
211         (>= (count-true has-bit) (quotient (length has-bit) 2))
212         ))
213 )
214
215 ; Compute population counts for each bit.  Return it as a vector indexed by bit
216 ; number.  Rather than computing raw popularity, attempt to compute
217 ; "disinguishing value" or inverse-entropy for each bit.  The idea is that the
218 ; larger the number for any particular bit slot, the more instructions it can
219 ; be used to distinguish.  Raw mask popularity is not enough -- popular masks
220 ; may include useless "reserved" fields whose values don't change, and thus are
221 ; useless in distinguishing.
222 ;
223 ; NOTE: mask-lens are not necessarily all the same value.
224 ; E.g. for the m32r it can consist of both 16 and 32.
225 ; But all masks must exist in the window specified by STARTBIT,DECODE-BITSIZE,
226 ; and all bits in the result must live in that window.
227 ; If no distinguishing bit fits in the window, return an empty vector.
228
229 (define (/distinguishing-bit-population masks mask-lens values lsb0?)
230   (let* ((max-length (apply max mask-lens))
231          (0-population (make-vector max-length 0))
232          (1-population (make-vector max-length 0))
233          (num-insns (length masks)))
234     ; Compute the 1- and 0-population vectors
235     (for-each (lambda (mask len value)
236                 (logit 5 " population count mask=" (number->hex mask) " len=" len "\n")
237                 (for-each (lambda (bitno)
238                             (let ((lsb-bitno (if lsb0? bitno (- len bitno 1))))
239                               ; ignore this bit if it's not set in the mask
240                               (if (bit-set? mask lsb-bitno)
241                                 (let ((chosen-pop-vector (if (bit-set? value lsb-bitno)
242                                                              1-population 0-population)))
243                                   (vector-set! chosen-pop-vector bitno
244                                                (+ 1 (vector-ref chosen-pop-vector bitno)))))))
245                           (/range len)))
246               masks mask-lens values)
247     ; Compute an aggregate "distinguishing value" for each bit.
248     (list->vector
249      (map (lambda (p0 p1)
250             (logit 4 p0 "/" p1 " ")
251             ; The most useful bits for decoding are those with counts in both
252             ; p0 and p1. These are the bits which distinguish one insn from
253             ; another. Assign these bits a high value (greater than num-insns).
254             ;
255             ; The next most useful bits are those with counts in either p0
256             ; or p1.  These bits represent specializations of other insns.
257             ; Assign these bits a value between 0 and (num-insns - 1). Note that
258             ; p0 + p1 is guaranteed to be <= num-insns. The value 0 is assigned
259             ; to bits for which p0 or p1 is equal to num_insns. These are bits
260             ; which are always 1 or always 0 in the ISA and are useless for
261             ; decoding purposes.
262             ;
263             ; Bits with no count in either p0 or p1 are useless for decoding
264             ; and should never be considered. Assigning these bits a value of
265             ; 0 ensures this.
266             (cond
267              ((= (+ p0 p1) 0) 0)
268              ((= (* p0 p1) 0) (- num-insns (+ p0 p1)))
269              (else (+ num-insns (sqrt (* p0 p1))))))
270           (vector->list 0-population) (vector->list 1-population))))
271 )
272
273 ; Return a list (0 ... LIMIT-1).
274
275 (define (/range limit)
276   (let loop ((i 0)
277              (indices (list)))
278     (if (= i limit)
279         (reverse! indices)
280         (loop (+ i 1) (cons i indices))))
281 )
282
283 ; Return a list (BASE ... BASE+SIZE-1).
284
285 (define (/range2 base size)
286   (let loop ((i base)
287              (indices (list)))
288     (if (= i (+ base size))
289         (reverse! indices)
290         (loop (+ i 1) (cons i indices))))
291 )
292
293 ; Return a copy of VECTOR, with all entries with given INDICES set
294 ; to VALUE.
295
296 (define (/vector-copy-set-all vector indices value)
297   (let ((new-vector (make-vector (vector-length vector))))
298     (for-each (lambda (index)
299                 (vector-set! new-vector index (if (memq index indices)
300                                                   value
301                                                   (vector-ref vector index))))
302               (/range (vector-length vector)))
303     new-vector)
304 )
305
306 ; Return a list of indices whose counts in the given vector exceed the given
307 ; threshold.
308 ; Sort them in decreasing order of popularity.
309
310 (define (/population-above-threshold population threshold)
311   (let* ((unsorted
312           (find (lambda (index) (if (vector-ref population index)
313                                     (>= (vector-ref population index) threshold)
314                                     #f))
315                 (/range (vector-length population))))
316          (sorted
317           (sort unsorted (lambda (i1 i2) (> (vector-ref population i1)
318                                             (vector-ref population i2))))))
319     sorted)
320 )
321
322 ; Return the top few most popular indices in the population vector,
323 ; ignoring any that are already used (marked by #f).  Don't exceed
324 ; `size' unless the clustering is just too good to pass up.
325
326 (define (/population-top-few population size)
327   (let loop ((old-picks (list))
328              (remaining-population population)
329              (count-threshold (apply max (map (lambda (value) (or value 0))
330                                               (vector->list population)))))
331       (let* ((new-picks (/population-above-threshold remaining-population count-threshold)))
332         (logit 4 "/population-top-few"
333                " desired=" size
334                " picks=(" old-picks ") pop=(" remaining-population ")"
335                " threshold=" count-threshold " new-picks=(" new-picks ")\n")
336         (cond
337          ; No point picking bits with population count of zero.  This leads to
338          ; the generation of layers of subtables which resolve nothing.  Generating
339          ; these tables can slow the build by several orders of magnitude.
340          ((= 0 count-threshold)
341           (logit 2 "/population-top-few: count-threshold is zero!\n")
342           old-picks)
343          ; No new matches?
344          ((null? new-picks)
345           (if (null? old-picks)
346               (logit 2 "/population-top-few: No bits left to pick from!\n"))
347           old-picks)
348          ; Way too many matches?
349          ((> (+ (length new-picks) (length old-picks)) (+ size 3))
350           (list-take (+ 3 size) (append old-picks new-picks))) ; prefer old-picks
351          ; About right number of matches?
352          ((> (+ (length new-picks) (length old-picks)) (- size 1))
353           (append old-picks new-picks))
354          ; Not enough?  Lower the threshold a bit and try to add some more.
355          (else
356           (loop (append old-picks new-picks)
357                 (/vector-copy-set-all remaining-population new-picks #f)
358                 ; Notice magic clustering decay parameter
359                 ;  vvvv
360                 (* 0.75 count-threshold))))))
361 )
362
363 ; Given list of insns, return list of bit numbers of constant bits in opcode
364 ; that they all share (or mostly share), up to MAX elements.
365 ; ALREADY-USED is a list of bitnums we can't use.
366 ; STARTBIT is the bit offset of the instruction value that C variable `insn'
367 ; holds (note that this is independent of LSB0?).
368 ; DECODE-BITSIZE is the number of bits of the insn that `insn' holds.
369 ; LSB0? is non-#f if bit number 0 is the least significant bit.
370 ;
371 ; Nil is returned if there are none, meaning that there is an ambiguity in
372 ; the specification up to the current word as defined by startbit,
373 ; decode-bitsize, and more bytes need to be fetched.
374 ;
375 ; We assume INSN-LIST matches all opcode bits before STARTBIT (if any).
376 ; FIXME: Revisit, as a more optimal decoder is sometimes achieved by doing
377 ; a cluster of opcode bits that appear later in the insn, and then coming
378 ; back to earlier ones.
379 ;
380 ; All insns are assumed to start at the same address so we handle insns of
381 ; varying lengths - we only analyze the common bits in all of them.
382 ;
383 ; Note that if we get called again to compute further opcode bits, we
384 ; start looking at STARTBIT again (rather than keeping track of how far in
385 ; the insn word we've progressed).  We could do this as an optimization, but
386 ; we also have to handle the case where the initial set of decode bits misses
387 ; some and thus we have to go back and look at them.  It may also turn out
388 ; that an opcode bit is skipped over because it doesn't contribute much
389 ; information to the decoding process (see /usable-decode-bit?).  As the
390 ; possible insn list gets wittled down, the bit will become significant.  Thus
391 ; the optimization is left for later.
392 ; Also, see preceding FIXME: We can't proceed past startbit + decode-bitsize
393 ; until we've processed all bits up to startbit + decode-bitsize.
394
395 (define (decode-get-best-bits insn-list already-used startbit max decode-bitsize lsb0?)
396   (let* ((raw-population (/distinguishing-bit-population (map insn-base-mask insn-list)
397                                                          (map insn-base-mask-length insn-list)
398                                                          (map insn-value insn-list)
399                                                          lsb0?))
400          ;; (undecoded (if lsb0?
401          ;;             (/range2 startbit (+ startbit decode-bitsize))
402          ;;             (/range2 (- startbit decode-bitsize) startbit)))
403          (used+undecoded already-used) ; (append already-used undecoded))
404          (filtered-population (/vector-copy-set-all raw-population used+undecoded #f))
405          (favorite-indices (/population-top-few filtered-population max))
406          (sorted-indices (sort favorite-indices (lambda (a b) 
407                                                   (if lsb0? (> a b) (< a b))))))
408     (logit 3
409            "Best decode bits (prev=" already-used " start=" startbit " decode=" decode-bitsize ")"
410            "=>"
411            "(" sorted-indices ")\n")
412     sorted-indices)
413 )
414
415 (define (OLDdecode-get-best-bits insn-list already-used startbit max decode-bitsize lsb0?)
416   (let ((masks (map insn-base-mask insn-list))
417         ; ??? We assume mask lengths are repeatedly used for insns longer
418         ; than the base insn size.
419         (mask-lens (map insn-base-mask-length insn-list))
420         (endbit (if lsb0?
421                     -1 ; FIXME: for now (gets sparc port going)
422                     (+ startbit decode-bitsize)))
423         (incr (if lsb0? -1 1)))
424     (let loop ((result nil)
425                (bitnum (if lsb0?
426                            (+ startbit (- decode-bitsize 1))
427                            startbit)))
428       (if (or (= (length result) max) (= bitnum endbit))
429           (reverse! result)
430           (if (and (not (memq bitnum already-used))
431                    (/usable-decode-bit? masks mask-lens bitnum lsb0?))
432               (loop (cons bitnum result) (+ bitnum incr))
433               (loop result (+ bitnum incr))))
434       ))
435 )
436
437 ;; Subroutine of /opcode-slots to simplify it.
438 ;; Compute either the opcode value or mask for the bits in BITNUMS.
439 ;; DEFAULT is 0 when computing the opcode value, 1 for the mask value.
440 ;; DECODE-LEN is (length BITNUMS).
441
442 (define (/get-subopcode-value value insn-len decode-len bitnums default lsb0?)
443   ;;(display (list val insn-len decode-len bl)) (newline)
444   ;; Oh My God.  This isn't tail recursive.
445   (letrec ((compute
446             ;; BNS is the remaining elements of BITNUMS to examine.
447             ;; THIS-BN ranges from (length bitnums), ..., 3, 2, 1.
448             (lambda (bns this-bn)
449               (if (null? bns)
450                   0
451                   (let ((bn (car bns)))
452                     (+ (if (or (and (>= bn insn-len) (= default 1))
453                                (and (< bn insn-len)
454                                     (bit-set? value
455                                               (if lsb0?
456                                                   bn
457                                                   (- insn-len bn 1)))))
458                            (integer-expt 2 (- this-bn 1))
459                            0)
460                        (compute (cdr bns) (- this-bn 1))))))))
461     (compute bitnums decode-len))
462 )
463
464 ; Return list of decode table entry numbers for INSN's opcode bits BITNUMS.
465 ; This is the indices into the decode table that match the instruction.
466 ; LSB0? is non-#f if bit number 0 is the least significant bit.
467 ;
468 ; Example: If BITNUMS is (0 1 2 3 4 5), and the constant (i.e. opcode) part of
469 ; the those bits of INSN is #b1100xx (where 'x' indicates a non-constant
470 ; part), then the result is (#b110000 #b110001 #b110010 #b110011).
471
472 (define (/opcode-slots insn bitnums lsb0?)
473   (let ((opcode (insn-value insn)) ;; FIXME: unused, overridden below
474         (insn-len (insn-base-mask-length insn))
475         (decode-len (length bitnums)))
476     (let* ((opcode (/get-subopcode-value (insn-value insn) insn-len decode-len bitnums 0 lsb0?))
477            (opcode-mask (/get-subopcode-value (insn-base-mask insn) insn-len decode-len bitnums 1 lsb0?))
478            (indices (missing-bit-indices opcode-mask (- (integer-expt 2 decode-len) 1))))
479       (logit 3 "insn =" (obj:name insn)
480              " insn-value=" (number->hex (insn-value insn))
481              " insn-base-mask=" (number->hex (insn-base-mask insn))
482              " insn-len=" insn-len
483              " decode-len=" decode-len
484              " opcode=" (number->hex opcode)
485              " opcode-mask=" (number->hex opcode-mask)
486              " indices=" indices "\n")
487       (map (lambda (index) (+ opcode index)) indices)))
488 )
489
490 ; Subroutine of /build-slots.
491 ; Fill slot in INSN-VEC that INSN goes into.
492 ; BITNUMS is the list of opcode bits.
493 ; LSB0? is non-#f if bit number 0 is the least significant bit.
494 ;
495 ; Example: If BITNUMS is (0 1 2 3 4 5) and the constant (i.e. opcode) part of
496 ; the first six bits of INSN is #b1100xx (where 'x' indicates a non-constant
497 ; part), then elements 48 49 50 51 of INSN-VEC are cons'd with INSN.
498 ; Each "slot" is a list of matching instructions.
499
500 (define (/fill-slot! insn-vec insn bitnums lsb0?)
501   (logit 3 "Filling slots for " (obj:str-name insn)
502          ", bitnums " bitnums "\n")
503   (let ((slot-nums (/opcode-slots insn bitnums lsb0?)))
504     ;(display (list "Filling slot(s)" slot-nums "...")) (newline)
505     (for-each (lambda (slot-num)
506                 (vector-set! insn-vec slot-num
507                              (cons insn (vector-ref insn-vec slot-num))))
508               slot-nums)
509     *UNSPECIFIED*
510     )
511 )
512
513 ; Given a list of constant bitnums (ones that are predominantly, though perhaps
514 ; not always, in the opcode), record each insn in INSN-LIST in the proper slot.
515 ; LSB0? is non-#f if bit number 0 is the least significant bit.
516 ; The result is a vector of insn lists.  Each slot is a list of insns
517 ; that go in that slot.
518
519 (define (/build-slots insn-list bitnums lsb0?)
520   (let ((result (make-vector (integer-expt 2 (length bitnums)) nil)))
521     ; Loop over each element, filling RESULT.
522     (for-each (lambda (insn)
523                 (/fill-slot! result insn bitnums lsb0?))
524               insn-list)
525     result)
526 )
527 \f
528 ; Compute the name of a decode table, prefixed with PREFIX.
529 ; INDEX-LIST is a list of pairs: list of bitnums, table entry number,
530 ; in reverse order of traversal (since they're built with cons).
531 ; INDEX-LIST may be empty.
532
533 (define (/gen-decode-table-name prefix index-list)
534   (set! index-list (reverse index-list))
535   (string-append
536    prefix
537    "table"
538    (string-map (lambda (elm) (string-append "_" (number->string elm)))
539                 ; CDR of each element is the table index.
540                (map cdr index-list)))
541 )
542
543 ; Generate one decode table entry for INSN-VEC at INDEX.
544 ; INSN-VEC is a vector of slots where each slot is a list of instructions that
545 ; map to that slot (opcode value).  If a slot is nil, no insn has that opcode
546 ; value so the decoder marks it as being invalid.
547 ; STARTBIT is the bit offset of the instruction value that C variable `insn'
548 ; holds (note that this is independent of LSB0?).
549 ; DECODE-BITSIZE is the number of bits of the insn that `insn' holds.
550 ; INDEX-LIST is a list of pairs: list of bitnums, table entry number.
551 ; LSB0? is non-#f if bit number 0 is the least significant bit.
552 ; INVALID-INSN is an <insn> object to use for invalid insns.
553 ; The result is a dtable-entry element (or "slot").
554
555 ; ??? For debugging.
556 (define /build-decode-table-entry-args #f)
557
558 (define (/build-decode-table-entry insn-vec startbit decode-bitsize index index-list lsb0? invalid-insn)
559   (let ((slot (vector-ref insn-vec index)))
560     (logit 2 "Processing decode entry "
561            (number->string index)
562            " in "
563            (/gen-decode-table-name "decode_" index-list)
564            ", "
565            (cond ((null? slot) "invalid")
566                  ((= 1 (length slot)) (insn-syntax (car slot)))
567                  (else "subtable"))
568            " ...\n")
569
570     (cond
571      ; If no insns map to this value, mark it as invalid.
572      ((null? slot) (dtable-entry-make index 'insn invalid-insn))
573
574      ; If only one insn maps to this value, that's it for this insn.
575      ((= 1 (length slot))
576       ; FIXME: Incomplete: need to check further opcode bits.
577       (dtable-entry-make index 'insn (car slot)))
578
579      ; Otherwise more than one insn maps to this value and we need to look at
580      ; further opcode bits.
581      (else
582       (logit 3 "Building subtable at index " (number->string index)
583              ", decode-bitsize = " (number->string decode-bitsize)
584              ", indices used thus far:"
585              (string-map (lambda (i) (string-append " " (number->string i)))
586                          (apply append (map car index-list)))
587              "\n")
588
589       (let ((bitnums (decode-get-best-bits slot
590                                            (apply append (map car index-list))
591                                            startbit 4
592                                            decode-bitsize lsb0?)))
593
594         ; If bitnums is nil, either there is an ambiguity or we need to read
595         ; more of the instruction in order to distinguish insns in SLOT.
596         (if (and (null? bitnums)
597                  (< startbit (apply min (map insn-length slot))))
598             (begin
599               ; We might be able to resolve the ambiguity by reading more bits.
600               ; We know from the < test that there are, indeed, more bits to
601               ; be read.
602               ; FIXME: It's technically possible that the next
603               ; startbit+decode-bitsize chunk has no usable bits and we have to
604               ; iterate, but rather unlikely.
605               ; The calculation of the new startbit, decode-bitsize will
606               ; undoubtedly need refinement.
607               (set! startbit (+ startbit decode-bitsize))
608               (set! decode-bitsize
609                     (min decode-bitsize
610                          (- (apply min (map insn-length slot))
611                             startbit)))
612               (set! bitnums (decode-get-best-bits slot
613                                                   ;nil ; FIXME: what to put here?
614                                                   (apply append (map car index-list))
615                                                   startbit 4
616                                                   decode-bitsize lsb0?))))
617
618         ; If bitnums is still nil there is an ambiguity.
619         (if (null? bitnums)
620             (begin
621               ; Try filtering out insns which are more general cases of
622               ; other insns in the slot.  The filtered insns will appear
623               ; in other slots as appropriate.
624               (set! slot (filter-non-specialized-ambiguous-insns slot))
625
626               (if (= 1 (length slot))
627                   ; Only 1 insn left in the slot, so take it.
628                   (dtable-entry-make index 'insn (car slot))
629                   ; There is still more than one insn in 'slot',
630                   ; so there is still an ambiguity.
631                   (begin
632                     ; If all insns are marked as DECODE-SPLIT, don't warn.
633                     (if (not (all-true? (map (lambda (insn)
634                                                (obj-has-attr? insn 'DECODE-SPLIT))
635                                              slot)))
636                         (message "WARNING: Decoder ambiguity detected: "
637                                  (string-drop1 ; drop leading comma
638                                   (string-map (lambda (insn)
639                                                 (string-append ", " (obj:str-name insn)))
640                                               slot))
641                                  "\n"))
642                         ; Things aren't entirely hopeless.  We've warned about
643                         ; the ambiguity.  Now, if there are any identical insns,
644                         ; filter them out.  If only one remains, then use it.
645                     (set! slot (filter-identical-ambiguous-insns slot))
646                     (if (= 1 (length slot))
647                         ; Only 1 insn left in the slot, so take it.
648                         (dtable-entry-make index 'insn (car slot))
649                         ; Otherwise, see if any ifield-assertion
650                         ; specs are present.
651                         ; FIXME: For now we assume that if they all have an
652                         ; ifield-assertion spec, then there is no ambiguity (it's left
653                         ; to the programmer to get it right).  This can be made more
654                         ; clever later.
655                         ; FIXME: May need to back up startbit if we've tried to read
656                         ; more of the instruction.  We currently require that
657                         ; all bits get used before advancing startbit, so this
658                         ; shouldn't be necessary.  Verify.
659                         (let ((assertions (map insn-ifield-assertion slot)))
660                           (if (not (all-true? assertions))
661                               (begin
662                                 ; Save arguments for debugging purposes.
663                                 (set! /build-decode-table-entry-args
664                                       (list insn-vec startbit decode-bitsize index index-list lsb0? invalid-insn))
665                                 (error "Unable to resolve ambiguity (maybe need some ifield-assertion specs?)")))
666                                 ; FIXME: Punt on even simple cleverness for now.
667                           (let ((exprtable-entries
668                                  (exprtable-sort (map exprtable-entry-make
669                                                       slot
670                                                       assertions))))
671                             (dtable-entry-make index 'expr
672                                                (exprtable-make
673                                                 (/gen-exprtable-name exprtable-entries)
674                                                 exprtable-entries))))))))
675
676             ; There is no ambiguity so generate the subtable.
677             ; Need to build `subtable' separately because we
678             ; may be appending to /decode-subtables recursively.
679             (let* ((insn-vec (/build-slots slot bitnums lsb0?))
680                    (subtable
681                     (/build-decode-table-guts insn-vec bitnums startbit
682                                               decode-bitsize index-list lsb0?
683                                               invalid-insn)))
684               (dtable-entry-make index 'table
685                                  (subdtable-add subtable
686                                                 (/gen-decode-table-name "" index-list)))))))
687      )
688     )
689 )
690
691 ; Given a vector of insn slots INSN-VEC, generate the guts of the decode table,
692 ; recorded as a "dtable-guts" data structure.
693 ;
694 ; BITNUMS is the list of bit numbers used to build the slot table.
695 ; I.e., (= (vector-length insn-vec) (ash 1 (length bitnums))).
696 ; STARTBIT is the bit offset of the instruction value that C variable `insn'
697 ; holds (note that this is independent of LSB0?).
698 ; For example, it is initially zero.  If DECODE-BITSIZE is 16 and after
699 ; scanning the first fetched piece of the instruction, more decoding is
700 ; needed, another piece will be fetched and STARTBIT will then be 16.
701 ; DECODE-BITSIZE is the number of bits of the insn that `insn' holds.
702 ; INDEX-LIST is a list of pairs: list of bitnums, table entry number.
703 ; Decode tables consist of entries of two types: actual insns and
704 ; pointers to other tables.
705 ; LSB0? is non-#f if bit number 0 is the least significant bit.
706 ; INVALID-INSN is an <insn> object representing invalid insns.
707 ;
708 ; BITNUMS is recorded with the guts so that tables whose contents are
709 ; identical but are accessed by different bitnums are treated as separate in
710 ; /decode-subtables.  Not sure this will ever happen, but play it safe.
711
712 (define (/build-decode-table-guts insn-vec bitnums startbit decode-bitsize index-list lsb0? invalid-insn)
713   (logit 2 "Processing decoder for bits"
714          (numbers->string bitnums " ")
715          ", startbit " startbit
716          ", decode-bitsize " decode-bitsize
717          ", index-list " index-list
718          " ...\n")
719   (assert (= (vector-length insn-vec) (ash 1 (length bitnums))))
720
721   (dtable-guts-make
722    bitnums startbit decode-bitsize
723    (map (lambda (index)
724           (/build-decode-table-entry insn-vec startbit decode-bitsize index
725                                      (cons (cons bitnums index)
726                                            index-list)
727                                      lsb0? invalid-insn))
728         (iota (vector-length insn-vec))))
729 )
730
731 ; Entry point.
732 ; Return a table that efficiently decodes INSN-LIST.
733 ; The table is a "dtable-guts" data structure, see dtable-guts-make.
734 ;
735 ; BITNUMS is the set of bits to initially key off of.
736 ; DECODE-BITSIZE is the number of bits of the instruction that `insn' holds.
737 ; LSB0? is non-#f if bit number 0 is the least significant bit.
738 ; INVALID-INSN is an <insn> object representing the `invalid' insn (for
739 ; instructions values that don't decode to any entry in INSN-LIST).
740
741 (define (decode-build-table insn-list bitnums decode-bitsize lsb0? invalid-insn)
742   ; Initialize the list of subtables computed.
743   (set! /decode-subtables nil)
744
745   ; ??? Another way to handle simple forms of ifield-assertions (like those
746   ; created by insn specialization) is to record a copy of the insn for each
747   ; possible value of the ifield and modify its ifield list with the ifield's
748   ; value.  This would then let the decoder table builder handle it normally.
749   ; I wouldn't create N insns, but would rather create an intermediary record
750   ; that recorded the necessary bits (insn, ifield-list, remaining
751   ; ifield-assertions).
752
753   (let ((insn-vec (/build-slots insn-list bitnums lsb0?)))
754     (let ((table-guts (/build-decode-table-guts insn-vec bitnums
755                                                 0 decode-bitsize
756                                                 nil lsb0?
757                                                 invalid-insn)))
758       table-guts))
759 )