OSDN Git Service

[cgen]
[pf3gnuchains/pf3gnuchains3x.git] / cgen / decode.scm
1 ; Application independent decoder support.
2 ; Copyright (C) 2000, 2004 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 "table 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 ; bitsize:  size of value in C local variable `insn', the number
45 ;           of bits of the instruction read thus far
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 (define (-distinguishing-bit-population masks mask-lens values lsb0?)
224   (let* ((max-length (apply max mask-lens))
225          (0-population (make-vector max-length 0))
226          (1-population (make-vector max-length 0))
227          (num-insns (length masks)))
228     ; Compute the 1- and 0-population vectors
229     (for-each (lambda (mask len value)
230                 (logit 5 " population count mask=" (number->hex mask) " len=" len "\n")
231                 (for-each (lambda (bitno)
232                             (let ((lsb-bitno (if lsb0? bitno (- len bitno 1))))
233                               ; ignore this bit if it's not set in the mask
234                               (if (bit-set? mask lsb-bitno)
235                                 (let ((chosen-pop-vector (if (bit-set? value lsb-bitno)
236                                                              1-population 0-population)))
237                                   (vector-set! chosen-pop-vector bitno 
238                                              (+ 1 (vector-ref chosen-pop-vector bitno)))))))
239                           (-range len)))
240               masks mask-lens values)
241     ; Compute an aggregate "distinguishing value" for each bit.
242     (list->vector
243      (map (lambda (p0 p1)
244             (logit 4 p0 "/" p1 " ")
245             ; The most useful bits for decoding are those with counts in both
246             ; p0 and p1. These are the bits which distinguish one insn from
247             ; another. Assign these bits a high value (greater than num-insns).
248             ;
249             ; The next most useful bits are those with counts in either p0
250             ; or p1.  These bits represent specializations of other insns.
251             ; Assign these bits a value between 0 and (num-insns - 1). Note that
252             ; p0 + p1 is guaranteed to be <= num-insns. The value 0 is assigned
253             ; to bits for which p0 or p1 is equal to num_insns. These are bits
254             ; which are always 1 or always 0 in the ISA and are useless for
255             ; decoding purposes.
256             ;
257             ; Bits with no count in either p0 or p1 are useless for decoding
258             ; and should never be considered. Assigning these bits a value of
259             ; 0 ensures this.
260             (cond
261              ((= (+ p0 p1) 0) 0)
262              ((= (* p0 p1) 0) (- num-insns (+ p0 p1)))
263              (else (+ num-insns (sqrt (* p0 p1))))))
264           (vector->list 0-population) (vector->list 1-population))))
265 )
266
267 ; Return a list (0 ... limit-1)
268
269 (define (-range limit)
270   (let loop ((i 0)
271              (indices (list)))
272     (if (= i limit) (reverse indices) (loop (+ i 1) (cons i indices))))
273 )
274
275 ; Return a list (base ... base+size-1)
276
277 (define (-range2 base size)
278   (let loop ((i base)
279              (indices (list)))
280     (if (= i (+ base size)) (reverse indices) (loop (+ i 1) (cons i indices))))
281 )
282
283 ; Return a copy of given vector, with all entries with given indices set
284 ; to `value'
285
286 (define (-vector-copy-set-all vector indices value)
287   (let ((new-vector (make-vector (vector-length vector))))
288     (for-each (lambda (index)
289                 (vector-set! new-vector index (if (memq index indices)
290                                                   value
291                                                   (vector-ref vector index))))
292               (-range (vector-length vector)))
293     new-vector)
294 )
295
296 ; Return a list of indices whose counts in the given vector exceed the given
297 ; threshold.
298 ; Sort them in decreasing order of populatority.
299
300 (define (-population-above-threshold population threshold)
301   (let* ((unsorted
302           (find (lambda (index) (if (vector-ref population index) 
303                                     (>= (vector-ref population index) threshold)
304                                     #f))
305                 (-range (vector-length population))))
306          (sorted
307           (sort unsorted (lambda (i1 i2) (> (vector-ref population i1)
308                                             (vector-ref population i2))))))
309     sorted)
310 )
311
312 ; Return the top few most popular indices in the population vector,
313 ; ignoring any that are already used (marked by #f).  Don't exceed
314 ; `size' unless the clustering is just too good to pass up.
315
316 (define (-population-top-few population size)
317   (let loop ((old-picks (list))
318              (remaining-population population)
319              (count-threshold (apply max (map (lambda (value) (if value value 0))
320                                               (vector->list population)))))
321       (let* ((new-picks (-population-above-threshold remaining-population count-threshold)))
322         (logit 4 "-population-top-few"
323                " desired=" size
324                " picks=(" old-picks ") pop=(" remaining-population ")"
325                " threshold=" count-threshold " new-picks=(" new-picks ")\n")
326         (cond 
327          ; No point picking bits with population count of zero.  This leads to
328          ; the generation of layers of subtables which resolve nothing.  Generating
329          ; these tables can slow the build by several orders of magnitude.
330          ((= 0 count-threshold)
331           (logit 2 "-population-top-few: count-threshold is zero!\n")
332           old-picks)
333          ; No new matches?
334          ((null? new-picks)
335           (if (null? old-picks)
336               (logit 2 "-population-top-few: No bits left to pick from!\n"))
337           old-picks)
338          ; Way too many matches?
339          ((> (+ (length new-picks) (length old-picks)) (+ size 3))
340           (list-take (+ 3 size) (append old-picks new-picks))) ; prefer old-picks
341          ; About right number of matches?
342          ((> (+ (length new-picks) (length old-picks)) (- size 1))
343           (append old-picks new-picks))
344          ; Not enough?  Lower the threshold a bit and try to add some more.
345          (else
346           (loop (append old-picks new-picks)
347                 (-vector-copy-set-all remaining-population new-picks #f)
348                 ; Notice magic clustering decay parameter
349                 ;  vvvv
350                 (* 0.75 count-threshold))))))
351 )
352
353 ; Given list of insns, return list of bit numbers of constant bits in opcode
354 ; that they all share (or mostly share), up to MAX elements.
355 ; ALREADY-USED is a list of bitnums we can't use.
356 ; STARTBIT is the bit offset of the instruction value that C variable `insn'
357 ; holds (note that this is independent of LSB0?).
358 ; DECODE-BITSIZE is the number of bits of the insn that `insn' holds.
359 ; LSB0? is non-#f if bit number 0 is the least significant bit.
360 ;
361 ; Nil is returned if there are none, meaning that there is an ambiguity in
362 ; the specification up to the current word.
363 ;
364 ; We assume INSN-LIST matches all opcode bits before STARTBIT.
365 ; FIXME: Revisit, as a more optimal decoder is sometimes achieved by doing
366 ; a cluster of opcode bits that appear later in the insn, and then coming
367 ; back to earlier ones.
368 ;
369 ; All insns are assumed to start at the same address so we handle insns of
370 ; varying lengths - we only analyze the common bits in all of them.
371 ;
372 ; Note that if we get called again to compute further opcode bits, we
373 ; start looking at STARTBIT again (rather than keeping track of how far in
374 ; the insn word we've progressed).  We could do this as an optimization, but
375 ; we also have to handle the case where the initial set of decode bits misses
376 ; some and thus we have to go back and look at them.  It may also turn out
377 ; that an opcode bit is skipped over because it doesn't contribute much
378 ; information to the decoding process (see -usable-decode-bit?).  As the
379 ; possible insn list gets wittled down, the bit will become significant.  Thus
380 ; the optimization is left for later.  Also, see preceding FIXME.
381
382 (define (decode-get-best-bits insn-list already-used startbit max decode-bitsize lsb0?)
383   (let* ((raw-population (-distinguishing-bit-population (map insn-base-mask insn-list)
384                                                          (map insn-base-mask-length insn-list)
385                                                          (map insn-value insn-list)
386                                                          lsb0?))
387          ; (undecoded (if lsb0?
388         ;               (-range2 startbit (+ startbit decode-bitsize))
389                 ;       (-range2 (- startbit decode-bitsize) startbit)))
390          (used+undecoded already-used) ; (append already-used undecoded))
391          (filtered-population (-vector-copy-set-all raw-population used+undecoded #f))
392          (favorite-indices (-population-top-few filtered-population max))
393          (sorted-indices (sort favorite-indices (lambda (a b) 
394                                                   (if lsb0? (> a b) (< a b))))))
395     (logit 3 
396            "Best decode bits (prev=" already-used " start=" startbit " decode=" decode-bitsize ")"
397            "=>"
398            "(" sorted-indices ")\n")
399     sorted-indices)
400 )
401
402 (define (OLDdecode-get-best-bits insn-list already-used startbit max decode-bitsize lsb0?)
403   (let ((masks (map insn-base-mask insn-list))
404         ; ??? We assume mask lengths are repeatedly used for insns longer
405         ; than the base insn size.
406         (mask-lens (map insn-base-mask-length insn-list))
407         (endbit (if lsb0?
408                     -1 ; FIXME: for now (gets sparc port going)
409                     (+ startbit decode-bitsize)))
410         (incr (if lsb0? -1 1)))
411     (let loop ((result nil)
412                (bitnum (if lsb0?
413                            (+ startbit (- decode-bitsize 1))
414                            startbit)))
415       (if (or (= (length result) max) (= bitnum endbit))
416           (reverse! result)
417           (if (and (not (memq bitnum already-used))
418                    (-usable-decode-bit? masks mask-lens bitnum lsb0?))
419               (loop (cons bitnum result) (+ bitnum incr))
420               (loop result (+ bitnum incr))))
421       ))
422 )
423
424 ; Return list of decode table entry numbers for INSN's opcode bits BITNUMS.
425 ; This is the indices into the decode table that match the instruction.
426 ; LSB0? is non-#f if bit number 0 is the least significant bit.
427 ;
428 ; Example: If BITNUMS is (0 1 2 3 4 5), and the constant (i.e. opcode) part of
429 ; the those bits of INSN is #b1100xx (where 'x' indicates a non-constant
430 ; part), then the result is (#b110000 #b110001 #b110010 #b110011).
431
432 (define (-opcode-slots insn bitnums lsb0?)
433   (letrec ((opcode (insn-value insn))
434            (insn-len (insn-base-mask-length insn))
435            (decode-len (length bitnums))
436            (compute (lambda (val insn-len decode-len bl default)
437                       ;(display (list val insn-len decode-len bl)) (newline)
438                       ; Oh My God.  This isn't tail recursive.
439                       (if (null? bl)
440                           0
441                           (+ (if (or (and (>= (car bl) insn-len) (= default 1))
442                                      (and (< (car bl) insn-len)
443                                           (bit-set? val
444                                                     (if lsb0?
445                                                         (car bl)
446                                                         (- insn-len (car bl) 1)))))
447                                  (integer-expt 2 (- (length bl) 1))
448                                  0)
449                              (compute val insn-len decode-len (cdr bl) default))))))
450     (let* ((opcode (compute (insn-value insn) insn-len decode-len bitnums 0))
451            (opcode-mask (compute (insn-base-mask insn) insn-len decode-len bitnums 1))
452            (indices (missing-bit-indices opcode-mask (- (integer-expt 2 decode-len) 1))))
453       (logit 3 "insn =" (obj:name insn)
454              " insn-value=" (number->hex (insn-value insn))
455              " insn-base-mask=" (number->hex (insn-base-mask insn))
456              " insn-len=" insn-len
457              " decode-len=" decode-len
458              " opcode=" (number->hex opcode)
459              " opcode-mask=" (number->hex opcode-mask)
460              " indices=" indices "\n")
461       (map (lambda (index) (+ opcode index)) indices)))
462 )
463
464 ; Subroutine of -build-slots.
465 ; Fill slot in INSN-VEC that INSN goes into.
466 ; BITNUMS is the list of opcode bits.
467 ; LSB0? is non-#f if bit number 0 is the least significant bit.
468 ;
469 ; Example: If BITNUMS is (0 1 2 3 4 5) and the constant (i.e. opcode) part of
470 ; the first six bits of INSN is #b1100xx (where 'x' indicates a non-constant
471 ; part), then elements 48 49 50 51 of INSN-VEC are cons'd with INSN.
472 ; Each "slot" is a list of matching instructions.
473
474 (define (-fill-slot! insn-vec insn bitnums lsb0?)
475   ;(display (string-append "fill-slot!: " (obj:str-name insn) " ")) (display bitnums) (newline)
476   (let ((slot-nums (-opcode-slots insn bitnums lsb0?)))
477     ;(display (list "Filling slot(s)" slot-nums "...")) (newline)
478     (for-each (lambda (slot-num)
479                 (vector-set! insn-vec slot-num
480                              (cons insn (vector-ref insn-vec slot-num))))
481               slot-nums)
482     *UNSPECIFIED*
483     )
484 )
485
486 ; Given a list of constant bitnums (ones that are predominantly, though perhaps
487 ; not always, in the opcode), record each insn in INSN-LIST in the proper slot.
488 ; LSB0? is non-#f if bit number 0 is the least significant bit.
489 ; The result is a vector of insn lists.  Each slot is a list of insns
490 ; that go in that slot.
491
492 (define (-build-slots insn-list bitnums lsb0?)
493   (let ((result (make-vector (integer-expt 2 (length bitnums)) nil)))
494     ; Loop over each element, filling RESULT.
495     (for-each (lambda (insn)
496                 (-fill-slot! result insn bitnums lsb0?))
497               insn-list)
498     result)
499 )
500 \f
501 ; Compute the name of a decode table, prefixed with PREFIX.
502 ; INDEX-LIST is a list of pairs: list of bitnums, table entry number,
503 ; in reverse order of traversal (since they're built with cons).
504 ; INDEX-LIST may be empty.
505
506 (define (-gen-decode-table-name prefix index-list)
507   (set! index-list (reverse index-list))
508   (string-append
509    prefix
510    "table"
511    (string-map (lambda (elm) (string-append "_" (number->string elm)))
512                 ; CDR of each element is the table index.
513                (map cdr index-list)))
514 )
515
516 ; Generate one decode table entry for INSN-VEC at INDEX.
517 ; INSN-VEC is a vector of slots where each slot is a list of instructions that
518 ; map to that slot (opcode value).  If a slot is nil, no insn has that opcode
519 ; value so the decoder marks it as being invalid.
520 ; STARTBIT is the bit offset of the instruction value that C variable `insn'
521 ; holds (note that this is independent of LSB0?).
522 ; DECODE-BITSIZE is the number of bits of the insn that `insn' holds.
523 ; INDEX-LIST is a list of pairs: list of bitnums, table entry number.
524 ; LSB0? is non-#f if bit number 0 is the least significant bit.
525 ; INVALID-INSN is an <insn> object to use for invalid insns.
526 ; The result is a dtable-entry element (or "slot").
527
528 ; ??? For debugging.
529 (define -build-decode-table-entry-args #f)
530
531 (define (-build-decode-table-entry insn-vec startbit decode-bitsize index index-list lsb0? invalid-insn)
532   (let ((slot (vector-ref insn-vec index)))
533     (logit 2 "Processing decode entry "
534            (number->string index)
535            " in "
536            (-gen-decode-table-name "decode_" index-list)
537            ", "
538            (cond ((null? slot) "invalid")
539                  ((= 1 (length slot)) (insn-syntax (car slot)))
540                  (else "subtable"))
541            " ...\n")
542
543     (cond
544      ; If no insns map to this value, mark it as invalid.
545      ((null? slot) (dtable-entry-make index 'insn invalid-insn))
546
547      ; If only one insn maps to this value, that's it for this insn.
548      ((= 1 (length slot))
549       ; FIXME: Incomplete: need to check further opcode bits.
550       (dtable-entry-make index 'insn (car slot)))
551
552      ; Otherwise more than one insn maps to this value and we need to look at
553      ; further opcode bits.
554      (else
555       (logit 3 "Building subtable at index " (number->string index)
556              ", decode-bitsize = " (number->string decode-bitsize)
557              ", indices used thus far:"
558              (string-map (lambda (i) (string-append " " (number->string i)))
559                          (apply append (map car index-list)))
560              "\n")
561
562       (let ((bitnums (decode-get-best-bits slot
563                                            (apply append (map car index-list))
564                                            startbit 4
565                                            decode-bitsize lsb0?)))
566
567         ; If bitnums is nil, either there is an ambiguity or we need to read
568         ; more of the instruction in order to distinguish insns in SLOT.
569         (if (and (null? bitnums)
570                  (< startbit (apply min (map insn-length slot))))
571             (begin
572               ; We might be able to resolve the ambiguity by reading more bits.
573               ; We know from the < test that there are, indeed, more bits to
574               ; be read.
575               (set! startbit (+ startbit decode-bitsize))
576               ; FIXME: The calculation of the new decode-bitsize will
577               ; undoubtedly need refinement.
578               (set! decode-bitsize
579                     (min decode-bitsize
580                          (- (apply min (map insn-length slot))
581                             startbit)))
582               (set! bitnums (decode-get-best-bits slot
583                                                   ;nil ; FIXME: what to put here?
584                                                   (apply append (map car index-list))
585                                                   startbit 4
586                                                   decode-bitsize lsb0?))))
587
588         ; If bitnums is still nil there is an ambiguity.
589         (if (null? bitnums)
590             (begin
591               ; Try filtering out insns which are more general cases of
592               ; other insns in the slot.  The filtered insns will appear
593               ; in other slots as appropriate.
594               (set! slot (filter-non-specialized-ambiguous-insns slot))
595
596               (if (= 1 (length slot))
597                   ; Only 1 insn left in the slot, so take it.
598                   (dtable-entry-make index 'insn (car slot))
599                   ; There is still more than one insn in 'slot',
600                   ; so there is still an ambiguity.
601                   (begin
602                     ; If all insns are marked as DECODE-SPLIT, don't warn.
603                     (if (not (all-true? (map (lambda (insn)
604                                                (obj-has-attr? insn 'DECODE-SPLIT))
605                                              slot)))
606                         (message "WARNING: Decoder ambiguity detected: "
607                                  (string-drop1 ; drop leading comma
608                                   (string-map (lambda (insn)
609                                                 (string-append ", " (obj:str-name insn)))
610                                               slot))
611                                  "\n"))
612                         ; Things aren't entirely hopeless.  We've warned about
613                         ; the ambiguity.  Now, if there are any identical insns,
614                         ; filter them out.  If only one remains, then use it.
615                     (set! slot (filter-identical-ambiguous-insns slot))
616                     (if (= 1 (length slot))
617                         ; Only 1 insn left in the slot, so take it.
618                         (dtable-entry-make index 'insn (car slot))
619                         ; Otherwise, see if any ifield-assertion
620                         ; specs are present.
621                         ; FIXME: For now we assume that if they all have an
622                         ; ifield-assertion spec, then there is no ambiguity (it's left
623                         ; to the programmer to get it right).  This can be made more
624                         ; clever later.
625                         ; FIXME: May need to back up startbit if we've tried to read
626                         ; more of the instruction.
627                         (let ((assertions (map insn-ifield-assertion slot)))
628                           (if (not (all-true? assertions))
629                               (begin
630                                 ; Save arguments for debugging purposes.
631                                 (set! -build-decode-table-entry-args
632                                       (list insn-vec startbit decode-bitsize index index-list lsb0? invalid-insn))
633                                 (error "Unable to resolve ambiguity (maybe need some ifield-assertion specs?)")))
634                                 ; FIXME: Punt on even simple cleverness for now.
635                           (let ((exprtable-entries
636                                  (exprtable-sort (map exprtable-entry-make
637                                                       slot
638                                                       assertions))))
639                             (dtable-entry-make index 'expr
640                                                (exprtable-make
641                                                 (-gen-exprtable-name exprtable-entries)
642                                                 exprtable-entries))))))))
643
644             ; There is no ambiguity so generate the subtable.
645             ; Need to build `subtable' separately because we
646             ; may be appending to -decode-subtables recursively.
647             (let* ((insn-vec (-build-slots slot bitnums lsb0?))
648                    (subtable
649                     (-build-decode-table-guts insn-vec bitnums startbit
650                                               decode-bitsize index-list lsb0?
651                                               invalid-insn)))
652               (dtable-entry-make index 'table
653                                  (subdtable-add subtable
654                                                 (-gen-decode-table-name "" index-list)))))))
655      )
656     )
657 )
658
659 ; Given vector of insn slots, generate the guts of the decode table, recorded
660 ; as a list of 3 elements: bitnums, decode-bitsize, and list of entries.
661 ; Bitnums is recorded with the guts so that tables whose contents are
662 ; identical but are accessed by different bitnums are treated as separate in
663 ; -decode-subtables.  Not sure this will ever happen, but play it safe.
664 ;
665 ; BITNUMS is the list of bit numbers used to build the slot table.
666 ; STARTBIT is the bit offset of the instruction value that C variable `insn'
667 ; holds (note that this is independent of LSB0?).
668 ; For example, it is initially zero.  If DECODE-BITSIZE is 16 and after
669 ; scanning the first fetched piece of the instruction, more decoding is
670 ; needed, another piece will be fetched and STARTBIT will then be 16.
671 ; DECODE-BITSIZE is the number of bits of the insn that `insn' holds.
672 ; INDEX-LIST is a list of pairs: list of bitnums, table entry number.
673 ; Decode tables consist of entries of two types: actual insns and
674 ; pointers to other tables.
675 ; LSB0? is non-#f if bit number 0 is the least significant bit.
676 ; INVALID-INSN is an <insn> object representing invalid insns.
677
678 (define (-build-decode-table-guts insn-vec bitnums startbit decode-bitsize index-list lsb0? invalid-insn)
679   (logit 2 "Processing decoder for bits"
680          (numbers->string bitnums " ")
681          " ...\n")
682
683   (dtable-guts-make
684    bitnums startbit decode-bitsize
685    (map (lambda (index)
686           (-build-decode-table-entry insn-vec startbit decode-bitsize index
687                                      (cons (cons bitnums index)
688                                            index-list)
689                                      lsb0? invalid-insn))
690         (iota (vector-length insn-vec))))
691 )
692
693 ; Entry point.
694 ; Return a table that efficiently decodes INSN-LIST.
695 ; BITNUMS is the set of bits to initially key off of.
696 ; DECODE-BITSIZE is the number of bits of the instruction that `insn' holds.
697 ; LSB0? is non-#f if bit number 0 is the least significant bit.
698 ; INVALID-INSN is an <insn> object representing the `invalid' insn (for
699 ; instructions values that don't decode to any entry in INSN-LIST).
700
701 (define (decode-build-table insn-list bitnums decode-bitsize lsb0? invalid-insn)
702   ; Initialize the list of subtables computed.
703   (set! -decode-subtables nil)
704
705   ; ??? Another way to handle simple forms of ifield-assertions (like those
706   ; created by insn specialization) is to record a copy of the insn for each
707   ; possible value of the ifield and modify its ifield list with the ifield's
708   ; value.  This would then let the decoder table builder handle it normally.
709   ; I wouldn't create N insns, but would rather create an intermediary record
710   ; that recorded the necessary bits (insn, ifield-list, remaining
711   ; ifield-assertions).
712
713   (let ((insn-vec (-build-slots insn-list bitnums lsb0?)))
714     (let ((table-guts (-build-decode-table-guts insn-vec bitnums
715                                                 0 decode-bitsize
716                                                 nil lsb0?
717                                                 invalid-insn)))
718       table-guts))
719 )