1 /* GAS interface for targets using CGEN: Cpu tools GENerator.
2 Copyright (C) 1996-2018 Free Software Foundation, Inc.
4 This file is part of GAS, the GNU Assembler.
6 GAS is free software; you can redistribute it and/or modify
7 it under the terms of the GNU General Public License as published by
8 the Free Software Foundation; either version 3, or (at your option)
11 GAS is distributed in the hope that it will be useful, but WITHOUT
12 ANY WARRANTY; without even the implied warranty of MERCHANTABILITY
13 or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public
14 License for more details.
16 You should have received a copy of the GNU General Public License
17 along with GAS; see the file COPYING. If not, write to the Free Software
18 Foundation, 51 Franklin Street - Fifth Floor, Boston, MA 02110-1301, USA. */
23 #include "cgen-desc.h"
26 #include "dwarf2dbg.h"
29 #include "struc-symbol.h"
31 #ifdef OBJ_COMPLEX_RELC
32 static expressionS * make_right_shifted_expr
33 (expressionS *, const int, const int);
35 static unsigned long gas_cgen_encode_addend
36 (const unsigned long, const unsigned long, const unsigned long, \
37 const unsigned long, const unsigned long, const unsigned long, \
40 static const char * weak_operand_overflow_check
41 (const expressionS *, const CGEN_OPERAND *);
43 static void queue_fixup_recursively
44 (const int, const int, expressionS *, \
45 const CGEN_MAYBE_MULTI_IFLD *, const int, const int);
47 static int rightshift = 0;
49 static void queue_fixup (int, int, expressionS *);
51 /* Opcode table descriptor, must be set by md_begin. */
53 CGEN_CPU_DESC gas_cgen_cpu_desc;
55 /* Callback to insert a register into the symbol table.
56 A target may choose to let GAS parse the registers.
57 ??? Not currently used. */
60 cgen_asm_record_register (char *name, int number)
62 /* Use symbol_create here instead of symbol_new so we don't try to
63 output registers into the object file's symbol table. */
64 symbol_table_insert (symbol_create (name, reg_section,
65 number, &zero_address_frag));
68 /* We need to keep a list of fixups. We can't simply generate them as
69 we go, because that would require us to first create the frag, and
70 that would screw up references to ``.''.
72 This is used by cpu's with simple operands. It keeps knowledge of what
73 an `expressionS' is and what a `fixup' is out of CGEN which for the time
76 OPINDEX is the index in the operand table.
77 OPINFO is something the caller chooses to help in reloc determination. */
84 struct cgen_maybe_multi_ifield * field;
88 static struct fixup fixups[GAS_CGEN_MAX_FIXUPS];
89 static int num_fixups;
91 /* Prepare to parse an instruction.
92 ??? May wish to make this static and delete calls in md_assemble. */
95 gas_cgen_init_parse (void)
103 queue_fixup (int opindex, int opinfo, expressionS *expP)
105 /* We need to generate a fixup for this expression. */
106 if (num_fixups >= GAS_CGEN_MAX_FIXUPS)
107 as_fatal (_("too many fixups"));
108 fixups[num_fixups].exp = *expP;
109 fixups[num_fixups].opindex = opindex;
110 fixups[num_fixups].opinfo = opinfo;
114 /* The following functions allow fixup chains to be stored, retrieved,
115 and swapped. They are a generalization of a pre-existing scheme
116 for storing, restoring and swapping fixup chains that was used by
117 the m32r port. The functionality is essentially the same, only
118 instead of only being able to store a single fixup chain, an entire
119 array of fixup chains can be stored. It is the user's responsibility
120 to keep track of how many fixup chains have been stored and which
121 elements of the array they are in.
123 The algorithms used are the same as in the old scheme. Other than the
124 "array-ness" of the whole thing, the functionality is identical to the
127 gas_cgen_initialize_saved_fixups_array():
128 Sets num_fixups_in_chain to 0 for each element. Call this from
129 md_begin() if you plan to use these functions and you want the
130 fixup count in each element to be set to 0 initially. This is
131 not necessary, but it's included just in case. It performs
132 the same function for each element in the array of fixup chains
133 that gas_init_parse() performs for the current fixups.
135 gas_cgen_save_fixups (element):
136 element - element number of the array you wish to store the fixups
137 to. No mechanism is built in for tracking what element
140 gas_cgen_restore_fixups (element):
141 element - element number of the array you wish to restore the fixups
144 gas_cgen_swap_fixups(int element):
145 element - swap the current fixups with those in this element number.
150 struct fixup fixup_chain[GAS_CGEN_MAX_FIXUPS];
151 int num_fixups_in_chain;
154 static struct saved_fixups stored_fixups[MAX_SAVED_FIXUP_CHAINS];
157 gas_cgen_initialize_saved_fixups_array (void)
161 while (i < MAX_SAVED_FIXUP_CHAINS)
162 stored_fixups[i++].num_fixups_in_chain = 0;
166 gas_cgen_save_fixups (int i)
168 if (i < 0 || i >= MAX_SAVED_FIXUP_CHAINS)
170 as_fatal ("index into stored_fixups[] out of bounds");
174 stored_fixups[i].num_fixups_in_chain = num_fixups;
175 memcpy (stored_fixups[i].fixup_chain, fixups,
176 sizeof (fixups[0]) * num_fixups);
181 gas_cgen_restore_fixups (int i)
183 if (i < 0 || i >= MAX_SAVED_FIXUP_CHAINS)
185 as_fatal ("index into stored_fixups[] out of bounds");
189 num_fixups = stored_fixups[i].num_fixups_in_chain;
190 memcpy (fixups, stored_fixups[i].fixup_chain,
191 (sizeof (stored_fixups[i].fixup_chain[0])) * num_fixups);
192 stored_fixups[i].num_fixups_in_chain = 0;
196 gas_cgen_swap_fixups (int i)
198 if (i < 0 || i >= MAX_SAVED_FIXUP_CHAINS)
200 as_fatal ("index into stored_fixups[] out of bounds");
205 gas_cgen_restore_fixups (i);
207 else if (stored_fixups[i].num_fixups_in_chain == 0)
208 gas_cgen_save_fixups (i);
213 struct fixup tmp_fixup;
215 tmp = stored_fixups[i].num_fixups_in_chain;
216 stored_fixups[i].num_fixups_in_chain = num_fixups;
219 for (tmp = GAS_CGEN_MAX_FIXUPS; tmp--;)
221 tmp_fixup = stored_fixups[i].fixup_chain [tmp];
222 stored_fixups[i].fixup_chain[tmp] = fixups [tmp];
223 fixups [tmp] = tmp_fixup;
228 /* Default routine to record a fixup.
229 This is a cover function to fix_new.
230 It exists because we record INSN with the fixup.
232 FRAG and WHERE are their respective arguments to fix_new_exp.
234 OPINFO is something the caller chooses to help in reloc determination.
236 At this point we do not use a bfd_reloc_code_real_type for
237 operands residing in the insn, but instead just use the
238 operand index. This lets us easily handle fixups for any
239 operand type. We pick a BFD reloc type in md_apply_fix. */
242 gas_cgen_record_fixup (fragS *frag, int where, const CGEN_INSN *insn,
243 int length, const CGEN_OPERAND *operand, int opinfo,
244 symbolS *symbol, offsetT offset)
248 /* It may seem strange to use operand->attrs and not insn->attrs here,
249 but it is the operand that has a pc relative relocation. */
250 fixP = fix_new (frag, where, length / 8, symbol, offset,
251 CGEN_OPERAND_ATTR_VALUE (operand, CGEN_OPERAND_PCREL_ADDR),
252 (bfd_reloc_code_real_type)
253 ((int) BFD_RELOC_UNUSED
254 + (int) operand->type));
255 fixP->fx_cgen.insn = insn;
256 fixP->fx_cgen.opinfo = opinfo;
257 fixP->fx_cgen.field = NULL;
258 fixP->fx_cgen.msb_field_p = 0;
263 /* Default routine to record a fixup given an expression.
264 This is a cover function to fix_new_exp.
265 It exists because we record INSN with the fixup.
267 FRAG and WHERE are their respective arguments to fix_new_exp.
269 OPINFO is something the caller chooses to help in reloc determination.
271 At this point we do not use a bfd_reloc_code_real_type for
272 operands residing in the insn, but instead just use the
273 operand index. This lets us easily handle fixups for any
274 operand type. We pick a BFD reloc type in md_apply_fix. */
277 gas_cgen_record_fixup_exp (fragS *frag, int where, const CGEN_INSN *insn,
278 int length, const CGEN_OPERAND *operand, int opinfo,
283 /* It may seem strange to use operand->attrs and not insn->attrs here,
284 but it is the operand that has a pc relative relocation. */
285 fixP = fix_new_exp (frag, where, length / 8, exp,
286 CGEN_OPERAND_ATTR_VALUE (operand, CGEN_OPERAND_PCREL_ADDR),
287 (bfd_reloc_code_real_type)
288 ((int) BFD_RELOC_UNUSED
289 + (int) operand->type));
290 fixP->fx_cgen.insn = insn;
291 fixP->fx_cgen.opinfo = opinfo;
292 fixP->fx_cgen.field = NULL;
293 fixP->fx_cgen.msb_field_p = 0;
298 #ifdef OBJ_COMPLEX_RELC
300 expr_build_binary (operatorT op, symbolS * s1, symbolS * s2)
308 return make_expr_symbol (& e);
312 /* Used for communication between the next two procedures. */
313 static jmp_buf expr_jmp_buf;
314 static int expr_jmp_buf_p;
316 /* Callback for cgen interface. Parse the expression at *STRP.
317 The result is an error message or NULL for success (in which case
318 *STRP is advanced past the parsed text).
319 WANT is an indication of what the caller is looking for.
320 If WANT == CGEN_ASM_PARSE_INIT the caller is beginning to try to match
321 a table entry with the insn, reset the queued fixups counter.
322 An enum cgen_parse_operand_result is stored in RESULTP.
323 OPINDEX is the operand's table entry index.
324 OPINFO is something the caller chooses to help in reloc determination.
325 The resulting value is stored in VALUEP. */
328 gas_cgen_parse_operand (CGEN_CPU_DESC cd ATTRIBUTE_UNUSED,
329 enum cgen_parse_operand_type want, const char **strP,
330 int opindex, int opinfo,
331 enum cgen_parse_operand_result *resultP,
335 /* These are volatile to survive the setjmp. */
336 char * volatile hold;
337 enum cgen_parse_operand_result * volatile resultP_1;
338 volatile int opinfo_1;
341 static enum cgen_parse_operand_result *resultP_1;
347 #ifdef OBJ_COMPLEX_RELC
348 volatile int signed_p = 0;
349 symbolS * stmp = NULL;
350 bfd_reloc_code_real_type reloc_type;
351 const CGEN_OPERAND * operand;
354 if (want == CGEN_PARSE_OPERAND_INIT)
356 gas_cgen_init_parse ();
361 hold = input_line_pointer;
362 input_line_pointer = (char *) *strP;
365 /* We rely on md_operand to longjmp back to us.
366 This is done via gas_cgen_md_operand. */
367 if (setjmp (expr_jmp_buf) != 0)
370 input_line_pointer = (char *) hold;
371 *resultP_1 = CGEN_PARSE_OPERAND_RESULT_ERROR;
372 return _("illegal operand");
380 *strP = input_line_pointer;
381 input_line_pointer = hold;
383 #ifdef TC_CGEN_PARSE_FIX_EXP
384 opinfo_1 = TC_CGEN_PARSE_FIX_EXP (opinfo_1, & exp);
387 /* FIXME: Need to check `want'. */
392 errmsg = _("illegal operand");
393 *resultP = CGEN_PARSE_OPERAND_RESULT_ERROR;
396 errmsg = _("missing operand");
397 *resultP = CGEN_PARSE_OPERAND_RESULT_ERROR;
400 if (want == CGEN_PARSE_OPERAND_SYMBOLIC)
402 *valueP = exp.X_add_number;
403 *resultP = CGEN_PARSE_OPERAND_RESULT_NUMBER;
406 *valueP = exp.X_add_number;
407 *resultP = CGEN_PARSE_OPERAND_RESULT_REGISTER;
411 #ifdef OBJ_COMPLEX_RELC
412 /* Look up operand, check to see if there's an obvious
413 overflow (this helps disambiguate some insn parses). */
414 operand = cgen_operand_lookup_by_num (cd, opindex);
415 errmsg = weak_operand_overflow_check (& exp, operand);
419 /* Fragment the expression as necessary, and queue a reloc. */
420 memset (& dummy_fixup, 0, sizeof (fixS));
422 reloc_type = md_cgen_lookup_reloc (0, operand, & dummy_fixup);
424 if (exp.X_op == O_symbol
425 && reloc_type == BFD_RELOC_RELC
426 && exp.X_add_symbol->sy_value.X_op == O_constant
427 && (!exp.X_add_symbol->bsym
428 || (exp.X_add_symbol->bsym->section != expr_section
429 && exp.X_add_symbol->bsym->section != absolute_section
430 && exp.X_add_symbol->bsym->section != undefined_section)))
432 /* Local labels will have been (eagerly) turned into constants
433 by now, due to the inappropriately deep insight of the
434 expression parser. Unfortunately make_expr_symbol
435 prematurely dives into the symbol evaluator, and in this
436 case it gets a bad answer, so we manually create the
437 expression symbol we want here. */
438 stmp = symbol_create (FAKE_LABEL_NAME, expr_section, 0,
439 & zero_address_frag);
440 symbol_set_value_expression (stmp, & exp);
443 stmp = make_expr_symbol (& exp);
445 /* If this is a pc-relative RELC operand, we
446 need to subtract "." from the expression. */
447 if (reloc_type == BFD_RELOC_RELC
448 && CGEN_OPERAND_ATTR_VALUE (operand, CGEN_OPERAND_PCREL_ADDR))
449 stmp = expr_build_binary (O_subtract, stmp, expr_build_dot ());
451 /* FIXME: this is not a perfect heuristic for figuring out
452 whether an operand is signed: it only works when the operand
453 is an immediate. it's not terribly likely that any other
454 values will be signed relocs, but it's possible. */
455 if (operand && (operand->hw_type == HW_H_SINT))
458 if (stmp->bsym && (stmp->bsym->section == expr_section)
459 && ! S_IS_LOCAL (stmp))
462 stmp->bsym->flags |= BSF_SRELC;
464 stmp->bsym->flags |= BSF_RELC;
467 /* Now package it all up for the fixup emitter. */
470 exp.X_add_symbol = stmp;
471 exp.X_add_number = 0;
473 /* Re-init rightshift quantity, just in case. */
474 rightshift = operand->length;
475 queue_fixup_recursively (opindex, opinfo_1, & exp,
476 (reloc_type == BFD_RELOC_RELC) ?
477 & (operand->index_fields) : 0,
481 ? CGEN_PARSE_OPERAND_RESULT_ERROR
482 : CGEN_PARSE_OPERAND_RESULT_QUEUED;
485 queue_fixup (opindex, opinfo_1, &exp);
487 *resultP = CGEN_PARSE_OPERAND_RESULT_QUEUED;
495 /* md_operand handler to catch unrecognized expressions and halt the
496 parsing process so the next entry can be tried.
498 ??? This could be done differently by adding code to `expression'. */
501 gas_cgen_md_operand (expressionS *expressionP ATTRIBUTE_UNUSED)
503 /* Don't longjmp if we're not called from within cgen_parse_operand(). */
505 longjmp (expr_jmp_buf, 1);
508 /* Finish assembling instruction INSN.
509 BUF contains what we've built up so far.
510 LENGTH is the size of the insn in bits.
511 RELAX_P is non-zero if relaxable insns should be emitted as such.
512 Otherwise they're emitted in non-relaxable forms.
513 The "result" is stored in RESULT if non-NULL. */
516 gas_cgen_finish_insn (const CGEN_INSN *insn, CGEN_INSN_BYTES_PTR buf,
517 unsigned int length, int relax_p, finished_insnS *result)
522 unsigned int byte_len = length / 8;
524 /* ??? Target foo issues various warnings here, so one might want to provide
525 a hook here. However, our caller is defined in tc-foo.c so there
526 shouldn't be a need for a hook. */
528 /* Write out the instruction.
529 It is important to fetch enough space in one call to `frag_more'.
530 We use (f - frag_now->fr_literal) to compute where we are and we
531 don't want frag_now to change between calls.
533 Relaxable instructions: We need to ensure we allocate enough
534 space for the largest insn. */
536 if (CGEN_INSN_ATTR_VALUE (insn, CGEN_INSN_RELAXED))
537 /* These currently shouldn't get here. */
540 /* Is there a relaxable insn with the relaxable operand needing a fixup? */
543 if (relax_p && CGEN_INSN_ATTR_VALUE (insn, CGEN_INSN_RELAXABLE))
545 /* Scan the fixups for the operand affected by relaxing
546 (i.e. the branch address). */
548 for (i = 0; i < num_fixups; ++i)
550 if (CGEN_OPERAND_ATTR_VALUE (cgen_operand_lookup_by_num (gas_cgen_cpu_desc, fixups[i].opindex),
559 if (relax_operand != -1)
567 #ifdef TC_CGEN_MAX_RELAX
568 max_len = TC_CGEN_MAX_RELAX (insn, byte_len);
570 max_len = CGEN_MAX_INSN_SIZE;
572 /* Ensure variable part and fixed part are in same fragment. */
573 /* FIXME: Having to do this seems like a hack. */
576 /* Allocate space for the fixed part. */
577 f = frag_more (byte_len);
579 /* Create a relaxable fragment for this instruction. */
582 exp = &fixups[relax_operand].exp;
583 sym = exp->X_add_symbol;
584 off = exp->X_add_number;
585 if (exp->X_op != O_constant && exp->X_op != O_symbol)
587 /* Handle complex expressions. */
588 sym = make_expr_symbol (exp);
592 frag_var (rs_machine_dependent,
593 max_len - byte_len /* max chars */,
594 0 /* variable part already allocated */,
595 /* FIXME: When we machine generate the relax table,
596 machine generate a macro to compute subtype. */
602 /* Record the operand number with the fragment so md_convert_frag
603 can use gas_cgen_md_record_fixup to record the appropriate reloc. */
604 old_frag->fr_cgen.insn = insn;
605 old_frag->fr_cgen.opindex = fixups[relax_operand].opindex;
606 old_frag->fr_cgen.opinfo = fixups[relax_operand].opinfo;
608 result->frag = old_frag;
612 f = frag_more (byte_len);
614 result->frag = frag_now;
617 /* If we're recording insns as numbers (rather than a string of bytes),
618 target byte order handling is deferred until now. */
620 cgen_put_insn_value (gas_cgen_cpu_desc, (unsigned char *) f, length, *buf);
622 memcpy (f, buf, byte_len);
625 /* Emit DWARF2 debugging information. */
626 dwarf2_emit_insn (byte_len);
628 /* Create any fixups. */
629 for (i = 0; i < num_fixups; ++i)
632 const CGEN_OPERAND *operand =
633 cgen_operand_lookup_by_num (gas_cgen_cpu_desc, fixups[i].opindex);
635 /* Don't create fixups for these. That's done during relaxation.
636 We don't need to test for CGEN_INSN_RELAXED as they can't get here
639 && CGEN_INSN_ATTR_VALUE (insn, CGEN_INSN_RELAXABLE)
640 && CGEN_OPERAND_ATTR_VALUE (operand, CGEN_OPERAND_RELAX))
643 #ifndef md_cgen_record_fixup_exp
644 #define md_cgen_record_fixup_exp gas_cgen_record_fixup_exp
647 fixP = md_cgen_record_fixup_exp (frag_now, f - frag_now->fr_literal,
648 insn, length, operand,
651 fixP->fx_cgen.field = fixups[i].field;
652 fixP->fx_cgen.msb_field_p = fixups[i].msb_field_p;
654 result->fixups[i] = fixP;
659 result->num_fixups = num_fixups;
664 #ifdef OBJ_COMPLEX_RELC
665 /* Queue many fixups, recursively. If the field is a multi-ifield,
666 repeatedly queue its sub-parts, right shifted to fit into the field (we
667 assume here multi-fields represent a left-to-right, MSB0-LSB0
671 queue_fixup_recursively (const int opindex,
674 const CGEN_MAYBE_MULTI_IFLD * field,
676 const int part_of_multi)
678 if (field && field->count)
682 for (i = 0; i < field->count; ++ i)
683 queue_fixup_recursively (opindex, opinfo, expP,
684 & (field->val.multi[i]), signed_p, i);
688 expressionS * new_exp = expP;
691 printf ("queueing fixup for field %s\n",
692 (field ? field->val.leaf->name : "??"));
693 print_symbol_value (expP->X_add_symbol);
695 if (field && part_of_multi != -1)
697 rightshift -= field->val.leaf->length;
699 /* Shift reloc value by number of bits remaining after this
702 new_exp = make_right_shifted_expr (expP, rightshift, signed_p);
705 /* Truncate reloc values to length, *after* leftmost one. */
706 fixups[num_fixups].msb_field_p = (part_of_multi <= 0);
707 fixups[num_fixups].field = (CGEN_MAYBE_MULTI_IFLD *) field;
709 queue_fixup (opindex, opinfo, new_exp);
713 /* Encode the self-describing RELC reloc format's addend. */
716 gas_cgen_encode_addend (const unsigned long start, /* in bits */
717 const unsigned long len, /* in bits */
718 const unsigned long oplen, /* in bits */
719 const unsigned long wordsz, /* in bytes */
720 const unsigned long chunksz, /* in bytes */
721 const unsigned long signed_p,
722 const unsigned long trunc_p)
724 unsigned long res = 0L;
727 res |= (oplen & 0x3F) << 6;
728 res |= (len & 0x3F) << 12;
729 res |= (wordsz & 0xF) << 18;
730 res |= (chunksz & 0xF) << 22;
731 res |= (CGEN_INSN_LSB0_P ? 1 : 0) << 27;
732 res |= signed_p << 28;
733 res |= trunc_p << 29;
738 /* Purpose: make a weak check that the expression doesn't overflow the
739 operand it's to be inserted into.
741 Rationale: some insns used to use %operators to disambiguate during a
742 parse. when these %operators are translated to expressions by the macro
743 expander, the ambiguity returns. we attempt to disambiguate by field
746 Method: check to see if the expression's top node is an O_and operator,
747 and the mask is larger than the operand length. This would be an
748 overflow, so signal it by returning an error string. Any other case is
749 ambiguous, so we assume it's OK and return NULL. */
752 weak_operand_overflow_check (const expressionS * exp,
753 const CGEN_OPERAND * operand)
755 const unsigned long len = operand->length;
757 unsigned long opmask = (((1L << (len - 1)) - 1) << 1) | 1;
762 if (exp->X_op != O_bit_and)
764 /* Check for implicit overflow flag. */
765 if (CGEN_OPERAND_ATTR_VALUE
766 (operand, CGEN_OPERAND_RELOC_IMPLIES_OVERFLOW))
767 return _("a reloc on this operand implies an overflow");
771 mask = exp->X_add_number;
773 if (exp->X_add_symbol
774 && exp->X_add_symbol->sy_value.X_op == O_constant)
775 mask |= exp->X_add_symbol->sy_value.X_add_number;
778 && exp->X_op_symbol->sy_value.X_op == O_constant)
779 mask |= exp->X_op_symbol->sy_value.X_add_number;
781 /* Want to know if mask covers more bits than opmask.
782 this is the same as asking if mask has any bits not in opmask,
783 or whether (mask & ~opmask) is nonzero. */
784 if (mask && (mask & ~opmask))
787 printf ("overflow: (mask = %8.8x, ~opmask = %8.8x, AND = %8.8x)\n",
788 mask, ~opmask, (mask & ~opmask));
790 return _("operand mask overflow");
797 make_right_shifted_expr (expressionS * exp,
802 expressionS * new_exp;
804 stmp = expr_build_binary (O_right_shift,
805 make_expr_symbol (exp),
806 expr_build_uconstant (amount));
809 stmp->bsym->flags |= BSF_SRELC;
811 stmp->bsym->flags |= BSF_RELC;
813 /* Then wrap that in a "symbol expr" for good measure. */
814 new_exp = XNEW (expressionS);
815 memset (new_exp, 0, sizeof (expressionS));
816 new_exp->X_op = O_symbol;
817 new_exp->X_op_symbol = 0;
818 new_exp->X_add_symbol = stmp;
819 new_exp->X_add_number = 0;
826 /* Apply a fixup to the object code. This is called for all the
827 fixups we generated by the call to fix_new_exp, above. In the call
828 above we used a reloc code which was the largest legal reloc code
829 plus the operand index. Here we undo that to recover the operand
830 index. At this point all symbol values should be fully resolved,
831 and we attempt to completely resolve the reloc. If we can not do
832 that, we determine the correct reloc code and put it back in the fixup. */
834 /* FIXME: This function handles some of the fixups and bfd_install_relocation
835 handles the rest. bfd_install_relocation (or some other bfd function)
836 should handle them all. */
839 gas_cgen_md_apply_fix (fixS *fixP, valueT *valP, segT seg ATTRIBUTE_UNUSED)
841 char *where = fixP->fx_frag->fr_literal + fixP->fx_where;
842 valueT value = * valP;
843 /* Canonical name, since used a lot. */
844 CGEN_CPU_DESC cd = gas_cgen_cpu_desc;
846 if (fixP->fx_addsy == (symbolS *) NULL)
849 /* We don't actually support subtracting a symbol. */
850 if (fixP->fx_subsy != (symbolS *) NULL)
851 as_bad_where (fixP->fx_file, fixP->fx_line, _("expression too complex"));
853 if ((int) fixP->fx_r_type >= (int) BFD_RELOC_UNUSED)
855 int opindex = (int) fixP->fx_r_type - (int) BFD_RELOC_UNUSED;
856 const CGEN_OPERAND *operand = cgen_operand_lookup_by_num (cd, opindex);
858 bfd_reloc_code_real_type reloc_type;
859 const CGEN_INSN *insn = fixP->fx_cgen.insn;
860 #ifdef OBJ_COMPLEX_RELC
865 if (fixP->fx_cgen.field)
867 /* Use the twisty little pointer path
868 back to the ifield if it exists. */
869 start = fixP->fx_cgen.field->val.leaf->start;
870 length = fixP->fx_cgen.field->val.leaf->length;
874 /* Or the far less useful operand-size guesstimate. */
875 start = operand->start;
876 length = operand->length;
879 /* FIXME: this is not a perfect heuristic for figuring out
880 whether an operand is signed: it only works when the operand
881 is an immediate. it's not terribly likely that any other
882 values will be signed relocs, but it's possible. */
883 if (operand && (operand->hw_type == HW_H_SINT))
887 /* If the reloc has been fully resolved finish the operand here. */
888 /* FIXME: This duplicates the capabilities of code in BFD. */
890 /* FIXME: If partial_inplace isn't set bfd_install_relocation won't
891 finish the job. Testing for pcrel is a temporary hack. */
894 CGEN_FIELDS *fields = xmalloc (CGEN_CPU_SIZEOF_FIELDS (cd));
896 CGEN_CPU_SET_FIELDS_BITSIZE (cd) (fields, CGEN_INSN_BITSIZE (insn));
897 CGEN_CPU_SET_VMA_OPERAND (cd) (cd, opindex, fields, (bfd_vma) value);
901 CGEN_INSN_INT insn_value =
902 cgen_get_insn_value (cd, (unsigned char *) where,
903 CGEN_INSN_BITSIZE (insn));
905 /* ??? 0 is passed for `pc'. */
906 errmsg = CGEN_CPU_INSERT_OPERAND (cd) (cd, opindex, fields,
907 &insn_value, (bfd_vma) 0);
908 cgen_put_insn_value (cd, (unsigned char *) where,
909 CGEN_INSN_BITSIZE (insn), insn_value);
912 /* ??? 0 is passed for `pc'. */
913 errmsg = CGEN_CPU_INSERT_OPERAND (cd) (cd, opindex, fields,
914 (unsigned char *) where,
918 as_bad_where (fixP->fx_file, fixP->fx_line, "%s", errmsg);
926 /* The operand isn't fully resolved. Determine a BFD reloc value
927 based on the operand information and leave it to
928 bfd_install_relocation. Note that this doesn't work when
929 partial_inplace == false. */
931 reloc_type = md_cgen_lookup_reloc (insn, operand, fixP);
932 #ifdef OBJ_COMPLEX_RELC
933 if (reloc_type == BFD_RELOC_RELC)
935 /* Change addend to "self-describing" form,
936 for BFD to handle in the linker. */
937 value = gas_cgen_encode_addend (start, operand->length,
938 length, fixP->fx_size,
939 cd->insn_chunk_bitsize / 8,
941 ! (fixP->fx_cgen.msb_field_p));
945 if (reloc_type != BFD_RELOC_NONE)
946 fixP->fx_r_type = reloc_type;
949 as_bad_where (fixP->fx_file, fixP->fx_line,
950 _("unresolved expression that must be resolved"));
955 else if (fixP->fx_done)
957 /* We're finished with this fixup. Install it because
958 bfd_install_relocation won't be called to do it. */
959 switch (fixP->fx_r_type)
962 md_number_to_chars (where, value, 1);
965 md_number_to_chars (where, value, 2);
968 md_number_to_chars (where, value, 4);
971 md_number_to_chars (where, value, 8);
974 as_bad_where (fixP->fx_file, fixP->fx_line,
975 _("internal error: can't install fix for reloc type %d (`%s')"),
976 fixP->fx_r_type, bfd_get_reloc_code_name (fixP->fx_r_type));
981 bfd_install_relocation will be called to finish things up. */
983 /* Tuck `value' away for use by tc_gen_reloc.
984 See the comment describing fx_addnumber in write.h.
985 This field is misnamed (or misused :-). */
986 fixP->fx_addnumber = value;
989 bfd_reloc_code_real_type
990 gas_cgen_pcrel_r_type (bfd_reloc_code_real_type r)
994 case BFD_RELOC_8: r = BFD_RELOC_8_PCREL; break;
995 case BFD_RELOC_16: r = BFD_RELOC_16_PCREL; break;
996 case BFD_RELOC_24: r = BFD_RELOC_24_PCREL; break;
997 case BFD_RELOC_32: r = BFD_RELOC_32_PCREL; break;
998 case BFD_RELOC_64: r = BFD_RELOC_64_PCREL; break;
1005 /* Translate internal representation of relocation info to BFD target format.
1007 FIXME: To what extent can we get all relevant targets to use this? */
1010 gas_cgen_tc_gen_reloc (asection *section ATTRIBUTE_UNUSED, fixS *fixP)
1012 bfd_reloc_code_real_type r_type = fixP->fx_r_type;
1015 reloc = XNEW (arelent);
1017 #ifdef GAS_CGEN_PCREL_R_TYPE
1019 r_type = GAS_CGEN_PCREL_R_TYPE (r_type);
1021 reloc->howto = bfd_reloc_type_lookup (stdoutput, r_type);
1023 if (reloc->howto == (reloc_howto_type *) NULL)
1025 as_bad_where (fixP->fx_file, fixP->fx_line,
1026 _("relocation is not supported"));
1030 gas_assert (!fixP->fx_pcrel == !reloc->howto->pc_relative);
1032 reloc->sym_ptr_ptr = XNEW (asymbol *);
1033 *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixP->fx_addsy);
1035 /* Use fx_offset for these cases. */
1036 if (fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY
1037 || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT)
1038 reloc->addend = fixP->fx_offset;
1040 reloc->addend = fixP->fx_addnumber;
1042 reloc->address = fixP->fx_frag->fr_address + fixP->fx_where;
1046 /* Perform any cgen specific initialisation.
1047 Called after gas_cgen_cpu_desc has been created. */
1050 gas_cgen_begin (void)
1052 if (flag_signed_overflow_ok)
1053 cgen_set_signed_overflow_ok (gas_cgen_cpu_desc);
1055 cgen_clear_signed_overflow_ok (gas_cgen_cpu_desc);