OSDN Git Service

* hardware.scm (hw-pc?): New function.
[pf3gnuchains/pf3gnuchains4x.git] / cgen / utils-gen.scm
1 ; Application independent utilities for C/C++ code generation.
2 ; Copyright (C) 2000, 2001, 2005, 2009 Red Hat, Inc.
3 ; This file is part of CGEN.
4 ; See file COPYING.CGEN for details.
5
6 ; Attributes.
7
8 (define (attr-bool-gen-decl attr) "")
9
10 (define (attr-bool-gen-defn attr) "")
11
12 (define (attr-int-gen-decl attr) "")
13
14 (define (attr-int-gen-defn attr) 
15   (string-append
16    "static const CGEN_ATTR_ENTRY " (gen-sym attr)
17    "_attr [] ATTRIBUTE_UNUSED = \n{\n  {\"integer\", " (number->string (attr-default attr)) "},\n  { 0, 0 }\n};\n\n" ))
18
19 (define (attr-gen-decl attr)
20   (gen-enum-decl (symbol-append (obj:name attr) '-attr)
21                  (obj:comment attr)
22                  (string-append (obj:str-name attr) "_")
23                  (attr-values attr))
24 )
25
26 (define (attr-gen-defn attr)
27   (string-append
28    "static const CGEN_ATTR_ENTRY "
29    (gen-sym attr) "_attr"
30    "[] ATTRIBUTE_UNUSED =\n{\n"
31    (string-map (lambda (elm)
32                  (let* ((san (and (pair? elm) (pair? (cdr elm))
33                                   (attr-value (cddr elm) 'sanitize #f))))
34                    (gen-sanitize
35                     (if (and san (not (eq? san 'none)))
36                         san
37                         #f)
38                     (string-append "  { "
39                                    "\""
40                                    (gen-c-symbol (car elm))
41                                    "\", "
42                                    (string-upcase (gen-sym attr))
43                                    "_"
44                                    (string-upcase (gen-c-symbol (car elm)))
45                                    " },\n"))))
46                (attr-values attr))
47    "  { 0, 0 }\n"
48    "};\n\n")
49 )
50
51 (method-make! <boolean-attribute> 'gen-decl attr-bool-gen-decl)
52 (method-make! <bitset-attribute> 'gen-decl attr-gen-decl)
53 (method-make! <integer-attribute> 'gen-decl attr-int-gen-decl)
54 (method-make! <enum-attribute> 'gen-decl attr-gen-decl)
55
56 (method-make! <boolean-attribute> 'gen-defn attr-bool-gen-defn)
57 (method-make! <bitset-attribute> 'gen-defn attr-gen-defn)
58 (method-make! <integer-attribute> 'gen-defn attr-int-gen-defn)
59 (method-make! <enum-attribute> 'gen-defn attr-gen-defn)
60 \f
61 ; Ifield extraction utilities.
62
63 ; Return the C data type to use to hold an extracted and decoded
64 ; <ifield> from an insn.  Usually this is just an int, but for register
65 ; numbers or large unsigned immediates, an unsigned int may be preferable.
66 ; Then there's floats (??? which aren't handled yet).
67
68 (define (gen-ifld-type f)
69   (mode:c-type (ifld-decode-mode f))
70 )
71
72 ; Return C declaration of variable(s) to hold <ifield> F.
73 ; MACRO? is #t if the result is part of a macro.
74
75 (define (gen-ifld-extract-decl f indent macro?)
76   (string-append indent (gen-ifld-type f) " " (gen-sym f) ";"
77                  (if macro? " \\\n" "\n"))
78 )
79
80 ; Return C code to extract a field from the base part of an insn.
81 ;
82 ; TOTAL-LENGTH is the total length of the value in VAL.
83 ; BASE-VALUE is a C expression (string) containing the base part of the insn.
84
85 (define (/gen-ifld-extract-base f total-length base-value)
86   (let ((extraction
87          (string-append "EXTRACT_"
88                         (if (current-arch-insn-lsb0?) "LSB0_" "MSB0_")
89                         (if (> total-length 32) "LG" "")
90                         (case (mode:class (ifld-mode f))
91                           ((INT) "SINT")
92                           ((UINT) "UINT")
93                           (else (error "unsupported mode class"
94                                        (mode:class (ifld-mode f)))))
95                         " ("
96                         base-value ", "
97                         (number->string total-length) ", "
98                         (number->string (+ (ifld-start f)
99                                            (ifld-word-offset f))) ", "
100                         (number->string (ifld-length f))
101                         ")"))
102         (decode (ifld-decode f)))
103     ; If the field doesn't have a special decode expression,
104     ; just return the raw extracted value.  Otherwise, emit
105     ; the expression.
106     (if (not decode)
107         extraction
108         ; cadr: fetches expression to be evaluated
109         ; caar: fetches symbol in arglist
110         ; cadar: fetches `pc' symbol in arglist
111         (rtl-c DFLT
112                (obj-isa-list f)
113                (list (list (caar decode) 'UINT extraction)
114                      (list (cadar decode) 'IAI "pc"))
115                (cadr decode)
116                #:rtl-cover-fns? #f #:ifield-var? #t)))
117 )
118
119 ; Subroutine of /gen-ifld-extract-beyond to extract the relevant value
120 ; from WORD-NAME and move it into place.
121
122 (define (/gen-extract-word word-name word-start word-length
123                            field-start field-length
124                            unsigned? lsb0?)
125   (let* ((word-end (+ word-start word-length))
126          (start (if lsb0? (+ 1 (- field-start field-length)) field-start))
127          (end (+ start field-length))
128          (base (if (< start word-start) word-start start)))
129     (string-append "("
130                    "EXTRACT_"
131                    (if lsb0? "LSB0_" "MSB0_")
132                    (if (> word-length 32) "LG" "")
133                    (if (and (not unsigned?)
134                             ; Only want sign extension for word with sign bit.
135                             (bitrange-overlap? field-start 1
136                                                word-start word-length
137                                                lsb0?))
138                        "SINT"
139                        "UINT")
140                    " ("
141                    ; What to extract from.
142                    word-name
143                    ", "
144                    ; Size of this chunk.
145                    (number->string word-length)
146                    ", "
147                    ; MSB of this chunk.
148                    (number->string
149                     (if lsb0?
150                         (if (> end word-end)
151                             (- word-end 1)
152                             (- end word-start 1))
153                         (if (< start word-start)
154                             0
155                             (- start word-start))))
156                    ", "
157                    ; Length of field within this chunk.
158                    (number->string (if (< end word-end)
159                                        (- end base)
160                                        (- word-end base)))
161                    ") << "
162                    ; Adjustment for this chunk within a full field.
163                    (number->string (if (> end word-end)
164                                        (- end word-end)
165                                        0))
166                    ")"))
167 )
168
169 ; Return C code to extract a field that extends beyond the base insn.
170 ;
171 ; Things get tricky in the non-integral-insn case (no kidding).
172 ; This case includes every architecture with at least one insn larger
173 ; than 32 bits, and all architectures where insns smaller than 32 bits
174 ; can't be interpreted as an int.
175 ; ??? And maybe other architectures not considered yet.
176 ; We want to handle these reasonably fast as this includes architectures like
177 ; the ARC and I960 where 99% of the insns are 32 bits, with a few insns that
178 ; take a 32 bit immediate.  It would be a real shame to unnecessarily slow down
179 ; handling of 99% of the instruction set just for a few insns.  Fortunately
180 ; for these chips base-insn includes these insns, so things fall out naturally.
181 ;
182 ; BASE-LENGTH is base-insn-bitsize.
183 ; TOTAL-LENGTH is the total length of the insn.
184 ; VAR-LIST is a list of variables containing the insn.
185 ; Each element in VAR-LIST is (name start length).
186 ; The contents of the insn are in several variables: insn, word_[123...],
187 ; where `insn' contains the "base insn" and `word_N' is a set of variables
188 ; recording the rest of the insn, 32 bits at a time (with the last one
189 ; containing whatever is left over).
190
191 (define (/gen-ifld-extract-beyond f base-length total-length var-list)
192    ; First compute the list of variables that contains pieces of the
193    ; desired value.
194    (let ((start (+ (ifld-start f) (ifld-word-offset f)))
195          (length (ifld-length f))
196          ;(word-start (ifld-word-offset f))
197          ;(word-length (ifld-word-length f))
198          ; extraction code
199          (extraction #f)
200          ; extra processing to perform on extracted value
201          (decode (ifld-decode f))
202          (lsb0? (current-arch-insn-lsb0?)))
203      ; Find which vars are needed and move the value into place.
204      (let loop ((var-list var-list) (result (list ")")))
205        (if (null? var-list)
206            (set! extraction (apply string-append (cons "(0" result)))
207            (let ((var-name (caar var-list))
208                  (var-start (cadar var-list))
209                  (var-length (caddar var-list)))
210              (if (bitrange-overlap? start length
211                                     var-start var-length
212                                     lsb0?)
213                  (loop (cdr var-list)
214                        (cons "|"
215                              (cons (/gen-extract-word var-name
216                                                       var-start
217                                                       var-length
218                                                       start length
219                                                       (eq? (mode:class (ifld-mode f))
220                                                            'UINT)
221                                                       lsb0?)
222                                    result)))
223                  (loop (cdr var-list) result)))))
224      ; If the field doesn't have a special decode expression, just return the
225      ; raw extracted value.  Otherwise, emit the expression.
226      (if (not decode)
227          extraction
228          ; cadr: fetches expression to be evaluated
229          ; caar: fetches symbol in arglist
230          ; cadar: fetches `pc' symbol in arglist
231          (rtl-c DFLT
232                 (obj-isa-list f)
233                 (list (list (caar decode) 'UINT extraction)
234                       (list (cadar decode) 'IAI "pc"))
235                 (cadr decode)
236                 #:rtl-cover-fns? #f #:ifield-var? #t)))
237 )
238
239 ; Return C code to extract <ifield> F.
240
241 (define (gen-ifld-extract f indent base-length total-length base-value var-list macro?)
242   (string-append
243    indent
244    (gen-sym f)
245    " = "
246    (if (adata-integral-insn? CURRENT-ARCH)
247        (/gen-ifld-extract-base f total-length base-value)
248        (if (ifld-beyond-base? f)
249            (/gen-ifld-extract-beyond f base-length total-length var-list)
250            (/gen-ifld-extract-base f base-length base-value)))
251    ";"
252    (if macro? " \\\n" "\n")
253    )
254 )
255
256 ; Return C code to extract a <multi-ifield> from an insn.
257 ; This must have the same signature as gen-ifld-extract as both can be
258 ; made methods in application code.
259
260 (define (gen-multi-ifld-extract f indent base-length total-length base-value var-list macro?)
261   ; The subfields must have already been extracted.
262   (let* ((decode-proc (ifld-decode f))
263          (varname (gen-sym f))
264          (decode (string-list
265                   ;; First, the block that extract the multi-ifield into the ifld variable.
266                   (rtl-c VOID (obj-isa-list f) nil
267                          (multi-ifld-extract f)
268                          #:rtl-cover-fns? #f #:ifield-var? #t)
269                   ;; Next, the decode routine that modifies it.
270                   (if decode-proc
271                       (string-append
272                        "  " varname " = "
273                        (rtl-c DFLT
274                               (obj-isa-list f)
275                               (list (list (caar decode-proc) 'UINT varname)
276                                     (list (cadar decode-proc) 'IAI "pc"))
277                               (cadr decode-proc)
278                               #:rtl-cover-fns? #f #:ifield-var? #t)
279                        ";\n")
280                       "")
281                  )))
282     (if macro?
283         (backslash "\n" decode)
284         decode))
285 )
286
287 ; Return C symbol of variable containing the extracted field value
288 ; in the extraction code.  E.g. f_rd = EXTRACT_UINT (insn, ...).
289
290 (define (gen-extracted-ifld-value f)
291   (gen-sym f)
292 )
293
294 ; Subroutine of gen-extract-ifields to compute arguments for /extract-chunk
295 ; to extract values beyond the base insn.
296 ; This is also used by gen-define-ifields to know how many vars are needed.
297 ;
298 ; The result is a list of (offset . length) pairs.
299 ;
300 ; ??? Here's a case where explicitly defined instruction formats can
301 ; help - without them we can only use heuristics (which must evolve).
302 ; At least all the details are tucked away here.
303
304 (define (/extract-chunk-specs base-length total-length alignment)
305   (let ((chunk-length
306          (case alignment
307            ; For the aligned and forced case split the insn up into base-insn
308            ; sized chunks.  For the unaligned case, use a chunk-length of 32.
309            ; 32 was chosen because the values are extracted into portable ints.
310            ((aligned forced) (min base-length 32))
311            ((unaligned) 32)
312            (else (error "unknown alignment" alignment)))))
313     (let loop ((start base-length)
314                (remaining (- total-length base-length))
315                (result nil))
316       (if (<= remaining 0)
317           (reverse! result)
318           (loop (+ start chunk-length)
319                 (- remaining chunk-length)
320                 ; Always fetch full CHUNK-LENGTH-sized chunks here,
321                 ; even if we don't actually need that many bytes.
322                 ; gen-ifetch only handles "normal" fetch sizes,
323                 ; and /gen-extract-word already knows how to find what
324                 ; it needs if we give it too much.
325                 (cons (cons start chunk-length)
326                       result)))))
327 )
328
329 ; Subroutine of gen-define-ifmt-ifields and gen-extract-ifmt-ifields to
330 ; insert the subfields of any multi-ifields present into IFLDS.
331 ; Subfields are inserted before their corresponding multi-ifield as they
332 ; are initialized in order.
333
334 (define (/extract-insert-subfields iflds)
335   (let loop ((result nil) (iflds iflds))
336     (cond ((null? iflds)
337            (reverse! result))
338           ((multi-ifield? (car iflds))
339            (loop (cons (car iflds)
340                        ; There's no real need to reverse the subfields here
341                        ; other than to keep them in order.
342                        (append (reverse (multi-ifld-subfields (car iflds)))
343                                result))
344                  (cdr iflds)))
345           (else
346            (loop (cons (car iflds) result) (cdr iflds)))))
347 )
348
349 ; Return C code to define local vars to contain IFIELDS.
350 ; All insns using the result have the same TOTAL-LENGTH (in bits).
351 ; INDENT is a string prepended to each line.
352 ; MACRO? is #t if the code is part of a macro (and thus '\\' must be appended
353 ; to each line).
354
355 (define (gen-define-ifields ifields total-length indent macro?)
356   (let* ((base-length (if (adata-integral-insn? CURRENT-ARCH)
357                           32
358                           (state-base-insn-bitsize)))
359          (chunk-specs (/extract-chunk-specs base-length total-length
360                                             (current-arch-default-alignment))))
361     (string-list
362      (string-list-map (lambda (f)
363                         (gen-ifld-extract-decl f indent macro?))
364                       ifields)
365      ; Define enough ints to hold the trailing part of the insn,
366      ; N bits at a time.
367      ; ??? This could be more intelligent of course.  Later.
368      ; ??? Making these global to us would allow filling them during
369      ; decoding.
370      (if (> total-length base-length)
371          (string-list
372           indent
373           "/* Contents of trailing part of insn.  */"
374           (if macro? " \\\n" "\n")
375           (string-list-map (lambda (chunk-num)
376                              (string-list indent
377                                           "UINT word_"
378                                           (number->string chunk-num)
379                                           (if macro? "; \\\n" ";\n")))
380                            (iota (length chunk-specs) 1)))
381          "")))
382 )
383
384 ; Return C code to define local vars to contain IFIELDS of <iformat> IFMT.
385 ; INDENT is a string prepended to each line.
386 ; MACRO? is #t if the code is part of a macro (and thus '\\' must be appended
387 ; to each line).
388 ; USE-MACRO? is #t if instead of generating the fields, we return the macro
389 ; that does that.
390
391 (define (gen-define-ifmt-ifields ifmt indent macro? use-macro?)
392   (let ((macro-name (string-append
393                      "EXTRACT_" (string-upcase (gen-sym ifmt))
394                      "_VARS"))
395         (ifields (/extract-insert-subfields (ifmt-ifields ifmt))))
396     (if use-macro?
397         (string-list indent macro-name
398                      " /*"
399                      (string-list-map (lambda (fld)
400                                         (string-append " " (obj:str-name fld)))
401                                       ifields)
402                      " */\n")
403         (let ((indent (if macro? (string-append indent "  ") indent)))
404           (string-list
405            (if macro?
406                (string-list "#define " macro-name " \\\n")
407                (string-list indent "/* Instruction fields.  */\n"))
408            (gen-define-ifields ifields (ifmt-length ifmt) indent macro?)
409            indent "unsigned int length;"
410            ; The last line doesn't have a trailing '\\'.
411            "\n"
412            ))))
413 )
414
415 ; Subroutine of gen-extract-ifields to fetch one value into VAR-NAME.
416
417 (define (/extract-chunk offset bits var-name macro?)
418   (string-append
419    "  "
420    var-name
421    " = "
422    (gen-ifetch "pc" offset bits)
423    ";"
424    (if macro? " \\\n" "\n"))
425 )
426
427 ; Subroutine of gen-extract-ifields to compute the var-list arg to
428 ; gen-ifld-extract-beyond.
429 ; The result is a list of `(name start length)' elements describing the
430 ; variables holding the parts of the insn.
431 ; CHUNK-SPECS is a list of (offset . length) pairs.
432
433 (define (/gen-extract-beyond-var-list base-length var-prefix chunk-specs lsb0?)
434   ; ??? lsb0? support ok?
435   (cons (list "insn" 0 base-length)
436         (map (lambda (chunk-num chunk-spec)
437                (list (string-append var-prefix (number->string chunk-num))
438                      (car chunk-spec)
439                      (cdr chunk-spec)))
440              (iota (length chunk-specs) 1)
441              chunk-specs))
442 )
443
444 ; Return C code to extract IFIELDS.
445 ; All insns using the result have the same TOTAL-LENGTH (in bits).
446 ; MACRO? is #t if the code is part of a macro (and thus '\\' must be appended
447 ; to each line).
448 ;
449 ; Here is where we handle integral-insn vs non-integeral-insn architectures.
450 ;
451 ; Examples of architectures that can be handled as integral-insns are:
452 ; sparc, m32r, mips, etc.
453 ;
454 ; Examples of architectures that can't be handled as integral insns are:
455 ; arc, i960, fr30, i386, m68k.
456 ; [i386,m68k are only mentioned for completeness.  cgen ports of these
457 ; would be great, but more thought is needed first]
458 ;
459 ; C variable `insn' is assumed to contain the base part of the insn
460 ; (max base-insn-bitsize insn-bitsize).  In the m32r case insn-bitsize
461 ; can be less than base-insn-bitsize.
462 ;
463 ; ??? Need to see how well gcc optimizes this.
464 ;
465 ; ??? Another way to do this is to put this code in an inline function that
466 ; gets passed pointers to each ifield variable.  GCC is smart enough to
467 ; produce optimal code for this, but other compilers may not have inlining
468 ; or the indirection removal.  I think the slowdown for a non-scache simulator
469 ; would be phenomenal and while one can say "too bad, use gcc", I'm defering
470 ; doing this for now.
471
472 (define (gen-extract-ifields ifields total-length indent macro?)
473   (let* ((base-length (if (adata-integral-insn? CURRENT-ARCH)
474                           32
475                           (state-base-insn-bitsize)))
476          (chunk-specs (/extract-chunk-specs base-length total-length
477                                             (current-arch-default-alignment))))
478     (string-list
479      ; If the insn has a trailing part, fetch it.
480      ; ??? Could have more intelligence here.  Later.
481      (if (> total-length base-length)
482          (let ()
483            (string-list-map (lambda (chunk-spec chunk-num)
484                               (/extract-chunk (car chunk-spec)
485                                               (cdr chunk-spec)
486                                               (string-append
487                                                "word_"
488                                                (number->string chunk-num))
489                                               macro?))
490                             chunk-specs
491                             (iota (length chunk-specs) 1)))
492          "")
493      (string-list-map
494       (lambda (f)
495         ; Dispatching on a method works better, as would a generic fn.
496         ; ??? Written this way to pass through Hobbit, doesn't handle
497         ; ((if foo a b) (arg1 arg2)).
498         (if (multi-ifield? f)
499             (gen-multi-ifld-extract
500              f indent base-length total-length "insn"
501              (/gen-extract-beyond-var-list base-length "word_"
502                                            chunk-specs
503                                            (current-arch-insn-lsb0?))
504              macro?)
505             (gen-ifld-extract
506              f indent base-length total-length "insn"
507              (/gen-extract-beyond-var-list base-length "word_"
508                                            chunk-specs
509                                            (current-arch-insn-lsb0?))
510              macro?)))
511       ifields)
512      ))
513 )
514
515 ; Return C code to extract the fields of <iformat> IFMT.
516 ; MACRO? is #t if the code is part of a macro (and thus '\\' must be appended
517 ; to each line).
518 ; USE-MACRO? is #t if instead of generating the fields, we return the macro
519 ; that does that.
520
521 (define (gen-extract-ifmt-ifields ifmt indent macro? use-macro?)
522   (let ((macro-name (string-append
523                      "EXTRACT_" (string-upcase (gen-sym ifmt))
524                      "_CODE"))
525         (ifields (/extract-insert-subfields (ifmt-ifields ifmt))))
526     (if use-macro?
527         (string-list indent macro-name "\n")
528         (let ((indent (if macro? (string-append indent "  ") indent)))
529           (string-list
530            (if macro?
531                (string-list "#define " macro-name " \\\n")
532                "")
533            indent "length = "
534            (number->string (bits->bytes (ifmt-length ifmt)))
535            ";"
536            (if macro? " \\\n" "\n")
537            (gen-extract-ifields ifields (ifmt-length ifmt) indent macro?)
538            ; The last line doesn't have a trailing '\\'.
539            "\n"
540            ))))
541 )
542 \f
543 ; Instruction format utilities.
544
545 (define (gen-sfmt-enum-decl sfmt-list)
546   (gen-enum-decl "@prefix@_sfmt_type"
547                  "semantic formats in cpu family @cpu@"
548                  "@PREFIX@_"
549                  (map (lambda (sfmt) (cons (obj:name sfmt) nil))
550                       sfmt-list))
551 )