OSDN Git Service

* config/stormy16/stormy16.h (GO_IF_MODE_DEPENDENT_ADDRESS): Remove.
[pf3gnuchains/gcc-fork.git] / gcc / config / stormy16 / stormy16.c
1 /* Xstormy16 target functions.
2    Copyright (C) 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, 2005,
3    2006, 2007, 2008, 2009, 2010, 2011  Free Software Foundation, Inc.
4    Contributed by Red Hat, Inc.
5
6    This file is part of GCC.
7
8    GCC is free software; you can redistribute it and/or modify
9    it under the terms of the GNU General Public License as published by
10    the Free Software Foundation; either version 3, or (at your option)
11    any later version.
12
13    GCC is distributed in the hope that it will be useful,
14    but WITHOUT ANY WARRANTY; without even the implied warranty of
15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16    GNU General Public License for more details.
17
18    You should have received a copy of the GNU General Public License
19    along with GCC; see the file COPYING3.  If not see
20    <http://www.gnu.org/licenses/>.  */
21
22 #include "config.h"
23 #include "system.h"
24 #include "coretypes.h"
25 #include "tm.h"
26 #include "rtl.h"
27 #include "regs.h"
28 #include "hard-reg-set.h"
29 #include "insn-config.h"
30 #include "conditions.h"
31 #include "insn-flags.h"
32 #include "output.h"
33 #include "insn-attr.h"
34 #include "flags.h"
35 #include "recog.h"
36 #include "diagnostic-core.h"
37 #include "obstack.h"
38 #include "tree.h"
39 #include "expr.h"
40 #include "optabs.h"
41 #include "except.h"
42 #include "function.h"
43 #include "target.h"
44 #include "target-def.h"
45 #include "tm_p.h"
46 #include "langhooks.h"
47 #include "gimple.h"
48 #include "df.h"
49 #include "ggc.h"
50
51 static rtx emit_addhi3_postreload (rtx, rtx, rtx);
52 static void xstormy16_asm_out_constructor (rtx, int);
53 static void xstormy16_asm_out_destructor (rtx, int);
54 static void xstormy16_asm_output_mi_thunk (FILE *, tree, HOST_WIDE_INT,
55                                            HOST_WIDE_INT, tree);
56
57 static void xstormy16_init_builtins (void);
58 static rtx xstormy16_expand_builtin (tree, rtx, rtx, enum machine_mode, int);
59 static bool xstormy16_rtx_costs (rtx, int, int, int *, bool);
60 static int xstormy16_address_cost (rtx, bool);
61 static bool xstormy16_return_in_memory (const_tree, const_tree);
62
63 static GTY(()) section *bss100_section;
64
65 /* Compute a (partial) cost for rtx X.  Return true if the complete
66    cost has been computed, and false if subexpressions should be
67    scanned.  In either case, *TOTAL contains the cost result.  */
68
69 static bool
70 xstormy16_rtx_costs (rtx x, int code, int outer_code ATTRIBUTE_UNUSED,
71                      int *total, bool speed ATTRIBUTE_UNUSED)
72 {
73   switch (code)
74     {
75     case CONST_INT:
76       if (INTVAL (x) < 16 && INTVAL (x) >= 0)
77         *total = COSTS_N_INSNS (1) / 2;
78       else if (INTVAL (x) < 256 && INTVAL (x) >= 0)
79         *total = COSTS_N_INSNS (1);
80       else
81         *total = COSTS_N_INSNS (2);
82       return true;
83
84     case CONST_DOUBLE:
85     case CONST:
86     case SYMBOL_REF:
87     case LABEL_REF:
88       *total = COSTS_N_INSNS (2);
89       return true;
90
91     case MULT:
92       *total = COSTS_N_INSNS (35 + 6);
93       return true;
94     case DIV:
95       *total = COSTS_N_INSNS (51 - 6);
96       return true;
97
98     default:
99       return false;
100     }
101 }
102
103 static int
104 xstormy16_address_cost (rtx x, bool speed ATTRIBUTE_UNUSED)
105 {
106   return (CONST_INT_P (x) ? 2
107           : GET_CODE (x) == PLUS ? 7
108           : 5);
109 }
110
111 /* Branches are handled as follows:
112
113    1. HImode compare-and-branches.  The machine supports these
114       natively, so the appropriate pattern is emitted directly.
115
116    2. SImode EQ and NE.  These are emitted as pairs of HImode
117       compare-and-branches.
118
119    3. SImode LT, GE, LTU and GEU.  These are emitted as a sequence
120       of a SImode subtract followed by a branch (not a compare-and-branch),
121       like this:
122       sub
123       sbc
124       blt
125
126    4. SImode GT, LE, GTU, LEU.  These are emitted as a sequence like:
127       sub
128       sbc
129       blt
130       or
131       bne.  */
132
133 /* Emit a branch of kind CODE to location LOC.  */
134
135 void
136 xstormy16_emit_cbranch (enum rtx_code code, rtx op0, rtx op1, rtx loc)
137 {
138   rtx condition_rtx, loc_ref, branch, cy_clobber;
139   rtvec vec;
140   enum machine_mode mode;
141
142   mode = GET_MODE (op0);
143   gcc_assert (mode == HImode || mode == SImode);
144
145   if (mode == SImode
146       && (code == GT || code == LE || code == GTU || code == LEU))
147     {
148       int unsigned_p = (code == GTU || code == LEU);
149       int gt_p = (code == GT || code == GTU);
150       rtx lab = NULL_RTX;
151
152       if (gt_p)
153         lab = gen_label_rtx ();
154       xstormy16_emit_cbranch (unsigned_p ? LTU : LT, op0, op1, gt_p ? lab : loc);
155       /* This should be generated as a comparison against the temporary
156          created by the previous insn, but reload can't handle that.  */
157       xstormy16_emit_cbranch (gt_p ? NE : EQ, op0, op1, loc);
158       if (gt_p)
159         emit_label (lab);
160       return;
161     }
162   else if (mode == SImode
163            && (code == NE || code == EQ)
164            && op1 != const0_rtx)
165     {
166       rtx op0_word, op1_word;
167       rtx lab = NULL_RTX;
168       int num_words = GET_MODE_BITSIZE (mode) / BITS_PER_WORD;
169       int i;
170
171       if (code == EQ)
172         lab = gen_label_rtx ();
173
174       for (i = 0; i < num_words - 1; i++)
175         {
176           op0_word = simplify_gen_subreg (word_mode, op0, mode,
177                                           i * UNITS_PER_WORD);
178           op1_word = simplify_gen_subreg (word_mode, op1, mode,
179                                           i * UNITS_PER_WORD);
180           xstormy16_emit_cbranch (NE, op0_word, op1_word, code == EQ ? lab : loc);
181         }
182       op0_word = simplify_gen_subreg (word_mode, op0, mode,
183                                       i * UNITS_PER_WORD);
184       op1_word = simplify_gen_subreg (word_mode, op1, mode,
185                                       i * UNITS_PER_WORD);
186       xstormy16_emit_cbranch (code, op0_word, op1_word, loc);
187
188       if (code == EQ)
189         emit_label (lab);
190       return;
191     }
192
193   /* We can't allow reload to try to generate any reload after a branch,
194      so when some register must match we must make the temporary ourselves.  */
195   if (mode != HImode)
196     {
197       rtx tmp;
198       tmp = gen_reg_rtx (mode);
199       emit_move_insn (tmp, op0);
200       op0 = tmp;
201     }
202
203   condition_rtx = gen_rtx_fmt_ee (code, mode, op0, op1);
204   loc_ref = gen_rtx_LABEL_REF (VOIDmode, loc);
205   branch = gen_rtx_SET (VOIDmode, pc_rtx,
206                         gen_rtx_IF_THEN_ELSE (VOIDmode, condition_rtx,
207                                               loc_ref, pc_rtx));
208
209   cy_clobber = gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (BImode, CARRY_REGNUM));
210
211   if (mode == HImode)
212     vec = gen_rtvec (2, branch, cy_clobber);
213   else if (code == NE || code == EQ)
214     vec = gen_rtvec (2, branch, gen_rtx_CLOBBER (VOIDmode, op0));
215   else
216     {
217       rtx sub;
218 #if 0
219       sub = gen_rtx_SET (VOIDmode, op0, gen_rtx_MINUS (SImode, op0, op1));
220 #else
221       sub = gen_rtx_CLOBBER (SImode, op0);
222 #endif
223       vec = gen_rtvec (3, branch, sub, cy_clobber);
224     }
225
226   emit_jump_insn (gen_rtx_PARALLEL (VOIDmode, vec));
227 }
228
229 /* Take a SImode conditional branch, one of GT/LE/GTU/LEU, and split
230    the arithmetic operation.  Most of the work is done by
231    xstormy16_expand_arith.  */
232
233 void
234 xstormy16_split_cbranch (enum machine_mode mode, rtx label, rtx comparison,
235                          rtx dest)
236 {
237   rtx op0 = XEXP (comparison, 0);
238   rtx op1 = XEXP (comparison, 1);
239   rtx seq, last_insn;
240   rtx compare;
241
242   start_sequence ();
243   xstormy16_expand_arith (mode, COMPARE, dest, op0, op1);
244   seq = get_insns ();
245   end_sequence ();
246
247   gcc_assert (INSN_P (seq));
248
249   last_insn = seq;
250   while (NEXT_INSN (last_insn) != NULL_RTX)
251     last_insn = NEXT_INSN (last_insn);
252
253   compare = SET_SRC (XVECEXP (PATTERN (last_insn), 0, 0));
254   PUT_CODE (XEXP (compare, 0), GET_CODE (comparison));
255   XEXP (compare, 1) = gen_rtx_LABEL_REF (VOIDmode, label);
256   emit_insn (seq);
257 }
258
259
260 /* Return the string to output a conditional branch to LABEL, which is
261    the operand number of the label.
262
263    OP is the conditional expression, or NULL for branch-always.
264
265    REVERSED is nonzero if we should reverse the sense of the comparison.
266
267    INSN is the insn.  */
268
269 char *
270 xstormy16_output_cbranch_hi (rtx op, const char *label, int reversed, rtx insn)
271 {
272   static char string[64];
273   int need_longbranch = (op != NULL_RTX
274                          ? get_attr_length (insn) == 8
275                          : get_attr_length (insn) == 4);
276   int really_reversed = reversed ^ need_longbranch;
277   const char *ccode;
278   const char *templ;
279   const char *operands;
280   enum rtx_code code;
281
282   if (! op)
283     {
284       if (need_longbranch)
285         ccode = "jmpf";
286       else
287         ccode = "br";
288       sprintf (string, "%s %s", ccode, label);
289       return string;
290     }
291
292   code = GET_CODE (op);
293
294   if (! REG_P (XEXP (op, 0)))
295     {
296       code = swap_condition (code);
297       operands = "%3,%2";
298     }
299   else
300       operands = "%2,%3";
301
302   /* Work out which way this really branches.  */
303   if (really_reversed)
304     code = reverse_condition (code);
305
306   switch (code)
307     {
308     case EQ:   ccode = "z";   break;
309     case NE:   ccode = "nz";  break;
310     case GE:   ccode = "ge";  break;
311     case LT:   ccode = "lt";  break;
312     case GT:   ccode = "gt";  break;
313     case LE:   ccode = "le";  break;
314     case GEU:  ccode = "nc";  break;
315     case LTU:  ccode = "c";   break;
316     case GTU:  ccode = "hi";  break;
317     case LEU:  ccode = "ls";  break;
318
319     default:
320       gcc_unreachable ();
321     }
322
323   if (need_longbranch)
324     templ = "b%s %s,.+8 | jmpf %s";
325   else
326     templ = "b%s %s,%s";
327   sprintf (string, templ, ccode, operands, label);
328
329   return string;
330 }
331
332 /* Return the string to output a conditional branch to LABEL, which is
333    the operand number of the label, but suitable for the tail of a
334    SImode branch.
335
336    OP is the conditional expression (OP is never NULL_RTX).
337
338    REVERSED is nonzero if we should reverse the sense of the comparison.
339
340    INSN is the insn.  */
341
342 char *
343 xstormy16_output_cbranch_si (rtx op, const char *label, int reversed, rtx insn)
344 {
345   static char string[64];
346   int need_longbranch = get_attr_length (insn) >= 8;
347   int really_reversed = reversed ^ need_longbranch;
348   const char *ccode;
349   const char *templ;
350   char prevop[16];
351   enum rtx_code code;
352
353   code = GET_CODE (op);
354
355   /* Work out which way this really branches.  */
356   if (really_reversed)
357     code = reverse_condition (code);
358
359   switch (code)
360     {
361     case EQ:   ccode = "z";   break;
362     case NE:   ccode = "nz";  break;
363     case GE:   ccode = "ge";  break;
364     case LT:   ccode = "lt";  break;
365     case GEU:  ccode = "nc";  break;
366     case LTU:  ccode = "c";   break;
367
368       /* The missing codes above should never be generated.  */
369     default:
370       gcc_unreachable ();
371     }
372
373   switch (code)
374     {
375     case EQ: case NE:
376       {
377         int regnum;
378
379         gcc_assert (REG_P (XEXP (op, 0)));
380
381         regnum = REGNO (XEXP (op, 0));
382         sprintf (prevop, "or %s,%s", reg_names[regnum], reg_names[regnum+1]);
383       }
384       break;
385
386     case GE: case LT: case GEU: case LTU:
387       strcpy (prevop, "sbc %2,%3");
388       break;
389
390     default:
391       gcc_unreachable ();
392     }
393
394   if (need_longbranch)
395     templ = "%s | b%s .+6 | jmpf %s";
396   else
397     templ = "%s | b%s %s";
398   sprintf (string, templ, prevop, ccode, label);
399
400   return string;
401 }
402 \f
403 /* Many machines have some registers that cannot be copied directly to or from
404    memory or even from other types of registers.  An example is the `MQ'
405    register, which on most machines, can only be copied to or from general
406    registers, but not memory.  Some machines allow copying all registers to and
407    from memory, but require a scratch register for stores to some memory
408    locations (e.g., those with symbolic address on the RT, and those with
409    certain symbolic address on the SPARC when compiling PIC).  In some cases,
410    both an intermediate and a scratch register are required.
411
412    You should define these macros to indicate to the reload phase that it may
413    need to allocate at least one register for a reload in addition to the
414    register to contain the data.  Specifically, if copying X to a register
415    RCLASS in MODE requires an intermediate register, you should define
416    `SECONDARY_INPUT_RELOAD_CLASS' to return the largest register class all of
417    whose registers can be used as intermediate registers or scratch registers.
418
419    If copying a register RCLASS in MODE to X requires an intermediate or scratch
420    register, `SECONDARY_OUTPUT_RELOAD_CLASS' should be defined to return the
421    largest register class required.  If the requirements for input and output
422    reloads are the same, the macro `SECONDARY_RELOAD_CLASS' should be used
423    instead of defining both macros identically.
424
425    The values returned by these macros are often `GENERAL_REGS'.  Return
426    `NO_REGS' if no spare register is needed; i.e., if X can be directly copied
427    to or from a register of RCLASS in MODE without requiring a scratch register.
428    Do not define this macro if it would always return `NO_REGS'.
429
430    If a scratch register is required (either with or without an intermediate
431    register), you should define patterns for `reload_inM' or `reload_outM', as
432    required..  These patterns, which will normally be implemented with a
433    `define_expand', should be similar to the `movM' patterns, except that
434    operand 2 is the scratch register.
435
436    Define constraints for the reload register and scratch register that contain
437    a single register class.  If the original reload register (whose class is
438    RCLASS) can meet the constraint given in the pattern, the value returned by
439    these macros is used for the class of the scratch register.  Otherwise, two
440    additional reload registers are required.  Their classes are obtained from
441    the constraints in the insn pattern.
442
443    X might be a pseudo-register or a `subreg' of a pseudo-register, which could
444    either be in a hard register or in memory.  Use `true_regnum' to find out;
445    it will return -1 if the pseudo is in memory and the hard register number if
446    it is in a register.
447
448    These macros should not be used in the case where a particular class of
449    registers can only be copied to memory and not to another class of
450    registers.  In that case, secondary reload registers are not needed and
451    would not be helpful.  Instead, a stack location must be used to perform the
452    copy and the `movM' pattern should use memory as an intermediate storage.
453    This case often occurs between floating-point and general registers.  */
454
455 enum reg_class
456 xstormy16_secondary_reload_class (enum reg_class rclass,
457                                   enum machine_mode mode ATTRIBUTE_UNUSED,
458                                   rtx x)
459 {
460   /* This chip has the interesting property that only the first eight
461      registers can be moved to/from memory.  */
462   if ((MEM_P (x)
463        || ((GET_CODE (x) == SUBREG || REG_P (x))
464            && (true_regnum (x) == -1
465                || true_regnum (x) >= FIRST_PSEUDO_REGISTER)))
466       && ! reg_class_subset_p (rclass, EIGHT_REGS))
467     return EIGHT_REGS;
468
469   return NO_REGS;
470 }
471
472 enum reg_class
473 xstormy16_preferred_reload_class (rtx x, enum reg_class rclass)
474 {
475   if (rclass == GENERAL_REGS && MEM_P (x))
476     return EIGHT_REGS;
477
478   return rclass;
479 }
480
481 /* Predicate for symbols and addresses that reflect special 8-bit
482    addressing.  */
483
484 int
485 xstormy16_below100_symbol (rtx x,
486                            enum machine_mode mode ATTRIBUTE_UNUSED)
487 {
488   if (GET_CODE (x) == CONST)
489     x = XEXP (x, 0);
490   if (GET_CODE (x) == PLUS && CONST_INT_P (XEXP (x, 1)))
491     x = XEXP (x, 0);
492
493   if (GET_CODE (x) == SYMBOL_REF)
494     return (SYMBOL_REF_FLAGS (x) & SYMBOL_FLAG_XSTORMY16_BELOW100) != 0;
495
496   if (CONST_INT_P (x))
497     {
498       HOST_WIDE_INT i = INTVAL (x);
499
500       if ((i >= 0x0000 && i <= 0x00ff)
501           || (i >= 0x7f00 && i <= 0x7fff))
502         return 1;
503     }
504   return 0;
505 }
506
507 /* Likewise, but only for non-volatile MEMs, for patterns where the
508    MEM will get split into smaller sized accesses.  */
509
510 int
511 xstormy16_splittable_below100_operand (rtx x, enum machine_mode mode)
512 {
513   if (MEM_P (x) && MEM_VOLATILE_P (x))
514     return 0;
515   return xstormy16_below100_operand (x, mode);
516 }
517
518 /* Expand an 8-bit IOR.  This either detects the one case we can
519    actually do, or uses a 16-bit IOR.  */
520
521 void
522 xstormy16_expand_iorqi3 (rtx *operands)
523 {
524   rtx in, out, outsub, val;
525
526   out = operands[0];
527   in = operands[1];
528   val = operands[2];
529
530   if (xstormy16_onebit_set_operand (val, QImode))
531     {
532       if (!xstormy16_below100_or_register (in, QImode))
533         in = copy_to_mode_reg (QImode, in);
534       if (!xstormy16_below100_or_register (out, QImode))
535         out = gen_reg_rtx (QImode);
536       emit_insn (gen_iorqi3_internal (out, in, val));
537       if (out != operands[0])
538         emit_move_insn (operands[0], out);
539       return;
540     }
541
542   if (! REG_P (in))
543     in = copy_to_mode_reg (QImode, in);
544
545   if (! REG_P (val) && ! CONST_INT_P (val))
546     val = copy_to_mode_reg (QImode, val);
547
548   if (! REG_P (out))
549     out = gen_reg_rtx (QImode);
550
551   in = simplify_gen_subreg (HImode, in, QImode, 0);
552   outsub = simplify_gen_subreg (HImode, out, QImode, 0);
553
554   if (! CONST_INT_P (val))
555     val = simplify_gen_subreg (HImode, val, QImode, 0);
556
557   emit_insn (gen_iorhi3 (outsub, in, val));
558
559   if (out != operands[0])
560     emit_move_insn (operands[0], out);
561 }
562
563 /* Expand an 8-bit AND.  This either detects the one case we can
564    actually do, or uses a 16-bit AND.  */
565
566 void
567 xstormy16_expand_andqi3 (rtx *operands)
568 {
569   rtx in, out, outsub, val;
570
571   out = operands[0];
572   in = operands[1];
573   val = operands[2];
574
575   if (xstormy16_onebit_clr_operand (val, QImode))
576     {
577       if (!xstormy16_below100_or_register (in, QImode))
578         in = copy_to_mode_reg (QImode, in);
579       if (!xstormy16_below100_or_register (out, QImode))
580         out = gen_reg_rtx (QImode);
581       emit_insn (gen_andqi3_internal (out, in, val));
582       if (out != operands[0])
583         emit_move_insn (operands[0], out);
584       return;
585     }
586
587   if (! REG_P (in))
588     in = copy_to_mode_reg (QImode, in);
589
590   if (! REG_P (val) && ! CONST_INT_P (val))
591     val = copy_to_mode_reg (QImode, val);
592
593   if (! REG_P (out))
594     out = gen_reg_rtx (QImode);
595
596   in = simplify_gen_subreg (HImode, in, QImode, 0);
597   outsub = simplify_gen_subreg (HImode, out, QImode, 0);
598
599   if (! CONST_INT_P (val))
600     val = simplify_gen_subreg (HImode, val, QImode, 0);
601
602   emit_insn (gen_andhi3 (outsub, in, val));
603
604   if (out != operands[0])
605     emit_move_insn (operands[0], out);
606 }
607
608 #define LEGITIMATE_ADDRESS_INTEGER_P(X, OFFSET)                         \
609   (CONST_INT_P (X)                                                      \
610   && (unsigned HOST_WIDE_INT) (INTVAL (X) + (OFFSET) + 2048) < 4096)
611
612 #define LEGITIMATE_ADDRESS_CONST_INT_P(X, OFFSET)                        \
613  (CONST_INT_P (X)                                                        \
614   && INTVAL (X) + (OFFSET) >= 0                                          \
615   && INTVAL (X) + (OFFSET) < 0x8000                                      \
616   && (INTVAL (X) + (OFFSET) < 0x100 || INTVAL (X) + (OFFSET) >= 0x7F00))
617
618 bool
619 xstormy16_legitimate_address_p (enum machine_mode mode ATTRIBUTE_UNUSED,
620                                 rtx x, bool strict)
621 {
622   if (LEGITIMATE_ADDRESS_CONST_INT_P (x, 0))
623     return true;
624
625   if (GET_CODE (x) == PLUS
626       && LEGITIMATE_ADDRESS_INTEGER_P (XEXP (x, 1), 0))
627     {
628       x = XEXP (x, 0);
629       /* PR 31232: Do not allow INT+INT as an address.  */
630       if (CONST_INT_P (x))
631         return false;
632     }
633
634   if ((GET_CODE (x) == PRE_MODIFY && CONST_INT_P (XEXP (XEXP (x, 1), 1)))
635       || GET_CODE (x) == POST_INC
636       || GET_CODE (x) == PRE_DEC)
637     x = XEXP (x, 0);
638
639   if (REG_P (x)
640       && REGNO_OK_FOR_BASE_P (REGNO (x))
641       && (! strict || REGNO (x) < FIRST_PSEUDO_REGISTER))
642     return true;
643
644   if (xstormy16_below100_symbol (x, mode))
645     return true;
646
647   return false;
648 }
649
650 /* Worker function for TARGET_MODE_DEPENDENT_ADDRESS_P.
651
652    On this chip, this is true if the address is valid with an offset
653    of 0 but not of 6, because in that case it cannot be used as an
654    address for DImode or DFmode, or if the address is a post-increment
655    or pre-decrement address.  */
656
657 static bool
658 xstormy16_mode_dependent_address_p (const_rtx x)
659 {
660   if (LEGITIMATE_ADDRESS_CONST_INT_P (x, 0)
661       && ! LEGITIMATE_ADDRESS_CONST_INT_P (x, 6))
662     return true;
663
664   if (GET_CODE (x) == PLUS
665       && LEGITIMATE_ADDRESS_INTEGER_P (XEXP (x, 1), 0)
666       && ! LEGITIMATE_ADDRESS_INTEGER_P (XEXP (x, 1), 6))
667     return true;
668
669   /* Auto-increment addresses are now treated generically in recog.c.  */
670   return false;
671 }
672
673 int
674 short_memory_operand (rtx x, enum machine_mode mode)
675 {
676   if (! memory_operand (x, mode))
677     return 0;
678   return (GET_CODE (XEXP (x, 0)) != PLUS);
679 }
680
681 /* Splitter for the 'move' patterns, for modes not directly implemented
682    by hardware.  Emit insns to copy a value of mode MODE from SRC to
683    DEST.
684
685    This function is only called when reload_completed.  */
686
687 void
688 xstormy16_split_move (enum machine_mode mode, rtx dest, rtx src)
689 {
690   int num_words = GET_MODE_BITSIZE (mode) / BITS_PER_WORD;
691   int direction, end, i;
692   int src_modifies = 0;
693   int dest_modifies = 0;
694   int src_volatile = 0;
695   int dest_volatile = 0;
696   rtx mem_operand;
697   rtx auto_inc_reg_rtx = NULL_RTX;
698
699   /* Check initial conditions.  */
700   gcc_assert (reload_completed
701               && mode != QImode && mode != HImode
702               && nonimmediate_operand (dest, mode)
703               && general_operand (src, mode));
704
705   /* This case is not supported below, and shouldn't be generated.  */
706   gcc_assert (! MEM_P (dest) || ! MEM_P (src));
707
708   /* This case is very very bad after reload, so trap it now.  */
709   gcc_assert (GET_CODE (dest) != SUBREG && GET_CODE (src) != SUBREG);
710
711   /* The general idea is to copy by words, offsetting the source and
712      destination.  Normally the least-significant word will be copied
713      first, but for pre-dec operations it's better to copy the
714      most-significant word first.  Only one operand can be a pre-dec
715      or post-inc operand.
716
717      It's also possible that the copy overlaps so that the direction
718      must be reversed.  */
719   direction = 1;
720
721   if (MEM_P (dest))
722     {
723       mem_operand = XEXP (dest, 0);
724       dest_modifies = side_effects_p (mem_operand);
725       if (auto_inc_p (mem_operand))
726         auto_inc_reg_rtx = XEXP (mem_operand, 0);
727       dest_volatile = MEM_VOLATILE_P (dest);
728       if (dest_volatile)
729         {
730           dest = copy_rtx (dest);
731           MEM_VOLATILE_P (dest) = 0;
732         }
733     }
734   else if (MEM_P (src))
735     {
736       mem_operand = XEXP (src, 0);
737       src_modifies = side_effects_p (mem_operand);
738       if (auto_inc_p (mem_operand))
739         auto_inc_reg_rtx = XEXP (mem_operand, 0);
740       src_volatile = MEM_VOLATILE_P (src);
741       if (src_volatile)
742         {
743           src = copy_rtx (src);
744           MEM_VOLATILE_P (src) = 0;
745         }
746     }
747   else
748     mem_operand = NULL_RTX;
749
750   if (mem_operand == NULL_RTX)
751     {
752       if (REG_P (src)
753           && REG_P (dest)
754           && reg_overlap_mentioned_p (dest, src)
755           && REGNO (dest) > REGNO (src))
756         direction = -1;
757     }
758   else if (GET_CODE (mem_operand) == PRE_DEC
759       || (GET_CODE (mem_operand) == PLUS
760           && GET_CODE (XEXP (mem_operand, 0)) == PRE_DEC))
761     direction = -1;
762   else if (MEM_P (src) && reg_overlap_mentioned_p (dest, src))
763     {
764       int regno;
765
766       gcc_assert (REG_P (dest));
767       regno = REGNO (dest);
768
769       gcc_assert (refers_to_regno_p (regno, regno + num_words,
770                                      mem_operand, 0));
771
772       if (refers_to_regno_p (regno, regno + 1, mem_operand, 0))
773         direction = -1;
774       else if (refers_to_regno_p (regno + num_words - 1, regno + num_words,
775                                   mem_operand, 0))
776         direction = 1;
777       else
778         /* This means something like
779            (set (reg:DI r0) (mem:DI (reg:HI r1)))
780            which we'd need to support by doing the set of the second word
781            last.  */
782         gcc_unreachable ();
783     }
784
785   end = direction < 0 ? -1 : num_words;
786   for (i = direction < 0 ? num_words - 1 : 0; i != end; i += direction)
787     {
788       rtx w_src, w_dest, insn;
789
790       if (src_modifies)
791         w_src = gen_rtx_MEM (word_mode, mem_operand);
792       else
793         w_src = simplify_gen_subreg (word_mode, src, mode, i * UNITS_PER_WORD);
794       if (src_volatile)
795         MEM_VOLATILE_P (w_src) = 1;
796       if (dest_modifies)
797         w_dest = gen_rtx_MEM (word_mode, mem_operand);
798       else
799         w_dest = simplify_gen_subreg (word_mode, dest, mode,
800                                       i * UNITS_PER_WORD);
801       if (dest_volatile)
802         MEM_VOLATILE_P (w_dest) = 1;
803
804       /* The simplify_subreg calls must always be able to simplify.  */
805       gcc_assert (GET_CODE (w_src) != SUBREG
806                   && GET_CODE (w_dest) != SUBREG);
807
808       insn = emit_insn (gen_rtx_SET (VOIDmode, w_dest, w_src));
809       if (auto_inc_reg_rtx)
810         REG_NOTES (insn) = alloc_EXPR_LIST (REG_INC,
811                                             auto_inc_reg_rtx,
812                                             REG_NOTES (insn));
813     }
814 }
815
816 /* Expander for the 'move' patterns.  Emit insns to copy a value of
817    mode MODE from SRC to DEST.  */
818
819 void
820 xstormy16_expand_move (enum machine_mode mode, rtx dest, rtx src)
821 {
822   if (MEM_P (dest) && (GET_CODE (XEXP (dest, 0)) == PRE_MODIFY))
823     {
824       rtx pmv      = XEXP (dest, 0);
825       rtx dest_reg = XEXP (pmv, 0);
826       rtx dest_mod = XEXP (pmv, 1);
827       rtx set      = gen_rtx_SET (Pmode, dest_reg, dest_mod);
828       rtx clobber  = gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (BImode, CARRY_REGNUM));
829
830       dest = gen_rtx_MEM (mode, dest_reg);
831       emit_insn (gen_rtx_PARALLEL (VOIDmode, gen_rtvec (2, set, clobber)));
832     }
833   else if (MEM_P (src) && (GET_CODE (XEXP (src, 0)) == PRE_MODIFY))
834     {
835       rtx pmv     = XEXP (src, 0);
836       rtx src_reg = XEXP (pmv, 0);
837       rtx src_mod = XEXP (pmv, 1);
838       rtx set     = gen_rtx_SET (Pmode, src_reg, src_mod);
839       rtx clobber = gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (BImode, CARRY_REGNUM));
840
841       src = gen_rtx_MEM (mode, src_reg);
842       emit_insn (gen_rtx_PARALLEL (VOIDmode, gen_rtvec (2, set, clobber)));
843     }
844
845   /* There are only limited immediate-to-memory move instructions.  */
846   if (! reload_in_progress
847       && ! reload_completed
848       && MEM_P (dest)
849       && (! CONST_INT_P (XEXP (dest, 0))
850           || ! xstormy16_legitimate_address_p (mode, XEXP (dest, 0), 0))
851       && ! xstormy16_below100_operand (dest, mode)
852       && ! REG_P (src)
853       && GET_CODE (src) != SUBREG)
854     src = copy_to_mode_reg (mode, src);
855
856   /* Don't emit something we would immediately split.  */
857   if (reload_completed
858       && mode != HImode && mode != QImode)
859     {
860       xstormy16_split_move (mode, dest, src);
861       return;
862     }
863
864   emit_insn (gen_rtx_SET (VOIDmode, dest, src));
865 }
866 \f
867 /* Stack Layout:
868
869    The stack is laid out as follows:
870
871 SP->
872 FP->    Local variables
873         Register save area (up to 4 words)
874         Argument register save area for stdarg (NUM_ARGUMENT_REGISTERS words)
875
876 AP->    Return address (two words)
877         9th procedure parameter word
878         10th procedure parameter word
879         ...
880         last procedure parameter word
881
882   The frame pointer location is tuned to make it most likely that all
883   parameters and local variables can be accessed using a load-indexed
884   instruction.  */
885
886 /* A structure to describe the layout.  */
887 struct xstormy16_stack_layout
888 {
889   /* Size of the topmost three items on the stack.  */
890   int locals_size;
891   int register_save_size;
892   int stdarg_save_size;
893   /* Sum of the above items.  */
894   int frame_size;
895   /* Various offsets.  */
896   int first_local_minus_ap;
897   int sp_minus_fp;
898   int fp_minus_ap;
899 };
900
901 /* Does REGNO need to be saved?  */
902 #define REG_NEEDS_SAVE(REGNUM, IFUN)                                    \
903   ((df_regs_ever_live_p (REGNUM) && ! call_used_regs[REGNUM])           \
904    || (IFUN && ! fixed_regs[REGNUM] && call_used_regs[REGNUM]           \
905        && (REGNUM != CARRY_REGNUM)                                      \
906        && (df_regs_ever_live_p (REGNUM) || ! current_function_is_leaf)))
907
908 /* Compute the stack layout.  */
909
910 struct xstormy16_stack_layout
911 xstormy16_compute_stack_layout (void)
912 {
913   struct xstormy16_stack_layout layout;
914   int regno;
915   const int ifun = xstormy16_interrupt_function_p ();
916
917   layout.locals_size = get_frame_size ();
918
919   layout.register_save_size = 0;
920   for (regno = 0; regno < FIRST_PSEUDO_REGISTER; regno++)
921     if (REG_NEEDS_SAVE (regno, ifun))
922       layout.register_save_size += UNITS_PER_WORD;
923
924   if (cfun->stdarg)
925     layout.stdarg_save_size = NUM_ARGUMENT_REGISTERS * UNITS_PER_WORD;
926   else
927     layout.stdarg_save_size = 0;
928
929   layout.frame_size = (layout.locals_size
930                        + layout.register_save_size
931                        + layout.stdarg_save_size);
932
933   if (crtl->args.size <= 2048 && crtl->args.size != -1)
934     {
935       if (layout.frame_size - INCOMING_FRAME_SP_OFFSET
936           + crtl->args.size <= 2048)
937         layout.fp_minus_ap = layout.frame_size - INCOMING_FRAME_SP_OFFSET;
938       else
939         layout.fp_minus_ap = 2048 - crtl->args.size;
940     }
941   else
942     layout.fp_minus_ap = (layout.stdarg_save_size
943                           + layout.register_save_size
944                           - INCOMING_FRAME_SP_OFFSET);
945   layout.sp_minus_fp = (layout.frame_size - INCOMING_FRAME_SP_OFFSET
946                         - layout.fp_minus_ap);
947   layout.first_local_minus_ap = layout.sp_minus_fp - layout.locals_size;
948   return layout;
949 }
950
951 /* Worker function for TARGET_CAN_ELIMINATE.  */
952
953 static bool
954 xstormy16_can_eliminate (const int from, const int to)
955 {
956   return (from == ARG_POINTER_REGNUM && to == STACK_POINTER_REGNUM
957           ? ! frame_pointer_needed
958           : true);
959 }
960
961 /* Determine how all the special registers get eliminated.  */
962
963 int
964 xstormy16_initial_elimination_offset (int from, int to)
965 {
966   struct xstormy16_stack_layout layout;
967   int result;
968
969   layout = xstormy16_compute_stack_layout ();
970
971   if (from == FRAME_POINTER_REGNUM && to == HARD_FRAME_POINTER_REGNUM)
972     result = layout.sp_minus_fp - layout.locals_size;
973   else if (from == FRAME_POINTER_REGNUM && to == STACK_POINTER_REGNUM)
974     result = - layout.locals_size;
975   else if (from == ARG_POINTER_REGNUM && to == HARD_FRAME_POINTER_REGNUM)
976     result = - layout.fp_minus_ap;
977   else if (from == ARG_POINTER_REGNUM && to == STACK_POINTER_REGNUM)
978     result = - (layout.sp_minus_fp + layout.fp_minus_ap);
979   else
980     gcc_unreachable ();
981
982   return result;
983 }
984
985 static rtx
986 emit_addhi3_postreload (rtx dest, rtx src0, rtx src1)
987 {
988   rtx set, clobber, insn;
989
990   set = gen_rtx_SET (VOIDmode, dest, gen_rtx_PLUS (HImode, src0, src1));
991   clobber = gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (BImode, CARRY_REGNUM));
992   insn = emit_insn (gen_rtx_PARALLEL (VOIDmode, gen_rtvec (2, set, clobber)));
993   return insn;
994 }
995
996 /* Called after register allocation to add any instructions needed for
997    the prologue.  Using a prologue insn is favored compared to putting
998    all of the instructions in the TARGET_ASM_FUNCTION_PROLOGUE macro,
999    since it allows the scheduler to intermix instructions with the
1000    saves of the caller saved registers.  In some cases, it might be
1001    necessary to emit a barrier instruction as the last insn to prevent
1002    such scheduling.
1003
1004    Also any insns generated here should have RTX_FRAME_RELATED_P(insn) = 1
1005    so that the debug info generation code can handle them properly.  */
1006
1007 void
1008 xstormy16_expand_prologue (void)
1009 {
1010   struct xstormy16_stack_layout layout;
1011   int regno;
1012   rtx insn;
1013   rtx mem_push_rtx;
1014   const int ifun = xstormy16_interrupt_function_p ();
1015
1016   mem_push_rtx = gen_rtx_POST_INC (Pmode, stack_pointer_rtx);
1017   mem_push_rtx = gen_rtx_MEM (HImode, mem_push_rtx);
1018
1019   layout = xstormy16_compute_stack_layout ();
1020
1021   if (layout.locals_size >= 32768)
1022     error ("local variable memory requirements exceed capacity");
1023
1024   /* Save the argument registers if necessary.  */
1025   if (layout.stdarg_save_size)
1026     for (regno = FIRST_ARGUMENT_REGISTER;
1027          regno < FIRST_ARGUMENT_REGISTER + NUM_ARGUMENT_REGISTERS;
1028          regno++)
1029       {
1030         rtx dwarf;
1031         rtx reg = gen_rtx_REG (HImode, regno);
1032
1033         insn = emit_move_insn (mem_push_rtx, reg);
1034         RTX_FRAME_RELATED_P (insn) = 1;
1035
1036         dwarf = gen_rtx_SEQUENCE (VOIDmode, rtvec_alloc (2));
1037
1038         XVECEXP (dwarf, 0, 0) = gen_rtx_SET (VOIDmode,
1039                                              gen_rtx_MEM (Pmode, stack_pointer_rtx),
1040                                              reg);
1041         XVECEXP (dwarf, 0, 1) = gen_rtx_SET (Pmode, stack_pointer_rtx,
1042                                              plus_constant (stack_pointer_rtx,
1043                                                             GET_MODE_SIZE (Pmode)));
1044         add_reg_note (insn, REG_FRAME_RELATED_EXPR, dwarf);
1045         RTX_FRAME_RELATED_P (XVECEXP (dwarf, 0, 0)) = 1;
1046         RTX_FRAME_RELATED_P (XVECEXP (dwarf, 0, 1)) = 1;
1047       }
1048
1049   /* Push each of the registers to save.  */
1050   for (regno = 0; regno < FIRST_PSEUDO_REGISTER; regno++)
1051     if (REG_NEEDS_SAVE (regno, ifun))
1052       {
1053         rtx dwarf;
1054         rtx reg = gen_rtx_REG (HImode, regno);
1055
1056         insn = emit_move_insn (mem_push_rtx, reg);
1057         RTX_FRAME_RELATED_P (insn) = 1;
1058
1059         dwarf = gen_rtx_SEQUENCE (VOIDmode, rtvec_alloc (2));
1060
1061         XVECEXP (dwarf, 0, 0) = gen_rtx_SET (VOIDmode,
1062                                              gen_rtx_MEM (Pmode, stack_pointer_rtx),
1063                                              reg);
1064         XVECEXP (dwarf, 0, 1) = gen_rtx_SET (Pmode, stack_pointer_rtx,
1065                                              plus_constant (stack_pointer_rtx,
1066                                                             GET_MODE_SIZE (Pmode)));
1067         add_reg_note (insn, REG_FRAME_RELATED_EXPR, dwarf);
1068         RTX_FRAME_RELATED_P (XVECEXP (dwarf, 0, 0)) = 1;
1069         RTX_FRAME_RELATED_P (XVECEXP (dwarf, 0, 1)) = 1;
1070       }
1071
1072   /* It's just possible that the SP here might be what we need for
1073      the new FP...  */
1074   if (frame_pointer_needed && layout.sp_minus_fp == layout.locals_size)
1075     {
1076       insn = emit_move_insn (hard_frame_pointer_rtx, stack_pointer_rtx);
1077       RTX_FRAME_RELATED_P (insn) = 1;
1078     }
1079
1080   /* Allocate space for local variables.  */
1081   if (layout.locals_size)
1082     {
1083       insn = emit_addhi3_postreload (stack_pointer_rtx, stack_pointer_rtx,
1084                                      GEN_INT (layout.locals_size));
1085       RTX_FRAME_RELATED_P (insn) = 1;
1086     }
1087
1088   /* Set up the frame pointer, if required.  */
1089   if (frame_pointer_needed && layout.sp_minus_fp != layout.locals_size)
1090     {
1091       insn = emit_move_insn (hard_frame_pointer_rtx, stack_pointer_rtx);
1092       RTX_FRAME_RELATED_P (insn) = 1;
1093
1094       if (layout.sp_minus_fp)
1095         {
1096           insn = emit_addhi3_postreload (hard_frame_pointer_rtx,
1097                                          hard_frame_pointer_rtx,
1098                                          GEN_INT (- layout.sp_minus_fp));
1099           RTX_FRAME_RELATED_P (insn) = 1;
1100         }
1101     }
1102 }
1103
1104 /* Do we need an epilogue at all?  */
1105
1106 int
1107 direct_return (void)
1108 {
1109   return (reload_completed
1110           && xstormy16_compute_stack_layout ().frame_size == 0
1111           && ! xstormy16_interrupt_function_p ());
1112 }
1113
1114 /* Called after register allocation to add any instructions needed for
1115    the epilogue.  Using an epilogue insn is favored compared to putting
1116    all of the instructions in the TARGET_ASM_FUNCTION_PROLOGUE macro,
1117    since it allows the scheduler to intermix instructions with the
1118    saves of the caller saved registers.  In some cases, it might be
1119    necessary to emit a barrier instruction as the last insn to prevent
1120    such scheduling.  */
1121
1122 void
1123 xstormy16_expand_epilogue (void)
1124 {
1125   struct xstormy16_stack_layout layout;
1126   rtx mem_pop_rtx;
1127   int regno;
1128   const int ifun = xstormy16_interrupt_function_p ();
1129
1130   mem_pop_rtx = gen_rtx_PRE_DEC (Pmode, stack_pointer_rtx);
1131   mem_pop_rtx = gen_rtx_MEM (HImode, mem_pop_rtx);
1132
1133   layout = xstormy16_compute_stack_layout ();
1134
1135   /* Pop the stack for the locals.  */
1136   if (layout.locals_size)
1137     {
1138       if (frame_pointer_needed && layout.sp_minus_fp == layout.locals_size)
1139         emit_move_insn (stack_pointer_rtx, hard_frame_pointer_rtx);
1140       else
1141         emit_addhi3_postreload (stack_pointer_rtx, stack_pointer_rtx,
1142                                 GEN_INT (- layout.locals_size));
1143     }
1144
1145   /* Restore any call-saved registers.  */
1146   for (regno = FIRST_PSEUDO_REGISTER - 1; regno >= 0; regno--)
1147     if (REG_NEEDS_SAVE (regno, ifun))
1148       emit_move_insn (gen_rtx_REG (HImode, regno), mem_pop_rtx);
1149
1150   /* Pop the stack for the stdarg save area.  */
1151   if (layout.stdarg_save_size)
1152     emit_addhi3_postreload (stack_pointer_rtx, stack_pointer_rtx,
1153                             GEN_INT (- layout.stdarg_save_size));
1154
1155   /* Return.  */
1156   if (ifun)
1157     emit_jump_insn (gen_return_internal_interrupt ());
1158   else
1159     emit_jump_insn (gen_return_internal ());
1160 }
1161
1162 int
1163 xstormy16_epilogue_uses (int regno)
1164 {
1165   if (reload_completed && call_used_regs[regno])
1166     {
1167       const int ifun = xstormy16_interrupt_function_p ();
1168       return REG_NEEDS_SAVE (regno, ifun);
1169     }
1170   return 0;
1171 }
1172
1173 void
1174 xstormy16_function_profiler (void)
1175 {
1176   sorry ("function_profiler support");
1177 }
1178 \f
1179 /* Update CUM to advance past an argument in the argument list.  The
1180    values MODE, TYPE and NAMED describe that argument.  Once this is
1181    done, the variable CUM is suitable for analyzing the *following*
1182    argument with `TARGET_FUNCTION_ARG', etc.
1183
1184    This function need not do anything if the argument in question was
1185    passed on the stack.  The compiler knows how to track the amount of
1186    stack space used for arguments without any special help.  However,
1187    it makes life easier for xstormy16_build_va_list if it does update
1188    the word count.  */
1189
1190 static void
1191 xstormy16_function_arg_advance (CUMULATIVE_ARGS *cum, enum machine_mode mode,
1192                                 const_tree type, bool named ATTRIBUTE_UNUSED)
1193 {
1194   /* If an argument would otherwise be passed partially in registers,
1195      and partially on the stack, the whole of it is passed on the
1196      stack.  */
1197   if (*cum < NUM_ARGUMENT_REGISTERS
1198       && *cum + XSTORMY16_WORD_SIZE (type, mode) > NUM_ARGUMENT_REGISTERS)
1199     *cum = NUM_ARGUMENT_REGISTERS;
1200
1201   *cum += XSTORMY16_WORD_SIZE (type, mode);
1202 }
1203
1204 static rtx
1205 xstormy16_function_arg (CUMULATIVE_ARGS *cum, enum machine_mode mode,
1206                         const_tree type, bool named ATTRIBUTE_UNUSED)
1207 {
1208   if (mode == VOIDmode)
1209     return const0_rtx;
1210   if (targetm.calls.must_pass_in_stack (mode, type)
1211       || *cum + XSTORMY16_WORD_SIZE (type, mode) > NUM_ARGUMENT_REGISTERS)
1212     return NULL_RTX;
1213   return gen_rtx_REG (mode, *cum + FIRST_ARGUMENT_REGISTER);
1214 }
1215
1216 /* Build the va_list type.
1217
1218    For this chip, va_list is a record containing a counter and a pointer.
1219    The counter is of type 'int' and indicates how many bytes
1220    have been used to date.  The pointer indicates the stack position
1221    for arguments that have not been passed in registers.
1222    To keep the layout nice, the pointer is first in the structure.  */
1223
1224 static tree
1225 xstormy16_build_builtin_va_list (void)
1226 {
1227   tree f_1, f_2, record, type_decl;
1228
1229   record = (*lang_hooks.types.make_type) (RECORD_TYPE);
1230   type_decl = build_decl (BUILTINS_LOCATION,
1231                           TYPE_DECL, get_identifier ("__va_list_tag"), record);
1232
1233   f_1 = build_decl (BUILTINS_LOCATION,
1234                     FIELD_DECL, get_identifier ("base"),
1235                       ptr_type_node);
1236   f_2 = build_decl (BUILTINS_LOCATION,
1237                     FIELD_DECL, get_identifier ("count"),
1238                       unsigned_type_node);
1239
1240   DECL_FIELD_CONTEXT (f_1) = record;
1241   DECL_FIELD_CONTEXT (f_2) = record;
1242
1243   TYPE_STUB_DECL (record) = type_decl;
1244   TYPE_NAME (record) = type_decl;
1245   TYPE_FIELDS (record) = f_1;
1246   DECL_CHAIN (f_1) = f_2;
1247
1248   layout_type (record);
1249
1250   return record;
1251 }
1252
1253 /* Implement the stdarg/varargs va_start macro.  STDARG_P is nonzero if this
1254    is stdarg.h instead of varargs.h.  VALIST is the tree of the va_list
1255    variable to initialize.  NEXTARG is the machine independent notion of the
1256    'next' argument after the variable arguments.  */
1257
1258 static void
1259 xstormy16_expand_builtin_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
1260 {
1261   tree f_base, f_count;
1262   tree base, count;
1263   tree t,u;
1264
1265   if (xstormy16_interrupt_function_p ())
1266     error ("cannot use va_start in interrupt function");
1267
1268   f_base = TYPE_FIELDS (va_list_type_node);
1269   f_count = DECL_CHAIN (f_base);
1270
1271   base = build3 (COMPONENT_REF, TREE_TYPE (f_base), valist, f_base, NULL_TREE);
1272   count = build3 (COMPONENT_REF, TREE_TYPE (f_count), valist, f_count,
1273                   NULL_TREE);
1274
1275   t = make_tree (TREE_TYPE (base), virtual_incoming_args_rtx);
1276   u = build_int_cst (NULL_TREE, - INCOMING_FRAME_SP_OFFSET);
1277   u = fold_convert (TREE_TYPE (count), u);
1278   t = build2 (POINTER_PLUS_EXPR, TREE_TYPE (base), t, u);
1279   t = build2 (MODIFY_EXPR, TREE_TYPE (base), base, t);
1280   TREE_SIDE_EFFECTS (t) = 1;
1281   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
1282
1283   t = build2 (MODIFY_EXPR, TREE_TYPE (count), count,
1284               build_int_cst (NULL_TREE,
1285                              crtl->args.info * UNITS_PER_WORD));
1286   TREE_SIDE_EFFECTS (t) = 1;
1287   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
1288 }
1289
1290 /* Implement the stdarg/varargs va_arg macro.  VALIST is the variable
1291    of type va_list as a tree, TYPE is the type passed to va_arg.
1292    Note:  This algorithm is documented in stormy-abi.  */
1293
1294 static tree
1295 xstormy16_gimplify_va_arg_expr (tree valist, tree type, gimple_seq *pre_p,
1296                                 gimple_seq *post_p ATTRIBUTE_UNUSED)
1297 {
1298   tree f_base, f_count;
1299   tree base, count;
1300   tree count_tmp, addr, t;
1301   tree lab_gotaddr, lab_fromstack;
1302   int size, size_of_reg_args, must_stack;
1303   tree size_tree;
1304
1305   f_base = TYPE_FIELDS (va_list_type_node);
1306   f_count = DECL_CHAIN (f_base);
1307
1308   base = build3 (COMPONENT_REF, TREE_TYPE (f_base), valist, f_base, NULL_TREE);
1309   count = build3 (COMPONENT_REF, TREE_TYPE (f_count), valist, f_count,
1310                   NULL_TREE);
1311
1312   must_stack = targetm.calls.must_pass_in_stack (TYPE_MODE (type), type);
1313   size_tree = round_up (size_in_bytes (type), UNITS_PER_WORD);
1314   gimplify_expr (&size_tree, pre_p, NULL, is_gimple_val, fb_rvalue);
1315
1316   size_of_reg_args = NUM_ARGUMENT_REGISTERS * UNITS_PER_WORD;
1317
1318   count_tmp = get_initialized_tmp_var (count, pre_p, NULL);
1319   lab_gotaddr = create_artificial_label (UNKNOWN_LOCATION);
1320   lab_fromstack = create_artificial_label (UNKNOWN_LOCATION);
1321   addr = create_tmp_var (ptr_type_node, NULL);
1322
1323   if (!must_stack)
1324     {
1325       tree r;
1326
1327       t = fold_convert (TREE_TYPE (count), size_tree);
1328       t = build2 (PLUS_EXPR, TREE_TYPE (count), count_tmp, t);
1329       r = fold_convert (TREE_TYPE (count), size_int (size_of_reg_args));
1330       t = build2 (GT_EXPR, boolean_type_node, t, r);
1331       t = build3 (COND_EXPR, void_type_node, t,
1332                   build1 (GOTO_EXPR, void_type_node, lab_fromstack),
1333                   NULL_TREE);
1334       gimplify_and_add (t, pre_p);
1335
1336       t = build2 (POINTER_PLUS_EXPR, ptr_type_node, base, count_tmp);
1337       gimplify_assign (addr, t, pre_p);
1338
1339       t = build1 (GOTO_EXPR, void_type_node, lab_gotaddr);
1340       gimplify_and_add (t, pre_p);
1341
1342       t = build1 (LABEL_EXPR, void_type_node, lab_fromstack);
1343       gimplify_and_add (t, pre_p);
1344     }
1345
1346   /* Arguments larger than a word might need to skip over some
1347      registers, since arguments are either passed entirely in
1348      registers or entirely on the stack.  */
1349   size = PUSH_ROUNDING (int_size_in_bytes (type));
1350   if (size > 2 || size < 0 || must_stack)
1351     {
1352       tree r, u;
1353
1354       r = size_int (NUM_ARGUMENT_REGISTERS * UNITS_PER_WORD);
1355       u = build2 (MODIFY_EXPR, TREE_TYPE (count_tmp), count_tmp, r);
1356
1357       t = fold_convert (TREE_TYPE (count), r);
1358       t = build2 (GE_EXPR, boolean_type_node, count_tmp, t);
1359       t = build3 (COND_EXPR, void_type_node, t, NULL_TREE, u);
1360       gimplify_and_add (t, pre_p);
1361     }
1362
1363   t = size_int (NUM_ARGUMENT_REGISTERS * UNITS_PER_WORD
1364                 + INCOMING_FRAME_SP_OFFSET);
1365   t = fold_convert (TREE_TYPE (count), t);
1366   t = build2 (MINUS_EXPR, TREE_TYPE (count), count_tmp, t);
1367   t = build2 (PLUS_EXPR, TREE_TYPE (count), t,
1368               fold_convert (TREE_TYPE (count), size_tree));
1369   t = fold_convert (TREE_TYPE (t), fold (t));
1370   t = fold_build1 (NEGATE_EXPR, TREE_TYPE (t), t);
1371   t = build2 (POINTER_PLUS_EXPR, TREE_TYPE (base), base, t);
1372   gimplify_assign (addr, t, pre_p);
1373
1374   t = build1 (LABEL_EXPR, void_type_node, lab_gotaddr);
1375   gimplify_and_add (t, pre_p);
1376
1377   t = fold_convert (TREE_TYPE (count), size_tree);
1378   t = build2 (PLUS_EXPR, TREE_TYPE (count), count_tmp, t);
1379   gimplify_assign (count, t, pre_p);
1380
1381   addr = fold_convert (build_pointer_type (type), addr);
1382   return build_va_arg_indirect_ref (addr);
1383 }
1384
1385 /* Worker function for TARGET_TRAMPOLINE_INIT.  */
1386
1387 static void
1388 xstormy16_trampoline_init (rtx m_tramp, tree fndecl, rtx static_chain)
1389 {
1390   rtx temp = gen_reg_rtx (HImode);
1391   rtx reg_fnaddr = gen_reg_rtx (HImode);
1392   rtx reg_addr, reg_addr_mem;
1393
1394   reg_addr = copy_to_reg (XEXP (m_tramp, 0));
1395   reg_addr_mem = adjust_automodify_address (m_tramp, HImode, reg_addr, 0);
1396
1397   emit_move_insn (temp, GEN_INT (0x3130 | STATIC_CHAIN_REGNUM));
1398   emit_move_insn (reg_addr_mem, temp);
1399   emit_insn (gen_addhi3 (reg_addr, reg_addr, const2_rtx));
1400   reg_addr_mem = adjust_automodify_address (reg_addr_mem, VOIDmode, NULL, 2);
1401
1402   emit_move_insn (temp, static_chain);
1403   emit_move_insn (reg_addr_mem, temp);
1404   emit_insn (gen_addhi3 (reg_addr, reg_addr, const2_rtx));
1405   reg_addr_mem = adjust_automodify_address (reg_addr_mem, VOIDmode, NULL, 2);
1406
1407   emit_move_insn (reg_fnaddr, XEXP (DECL_RTL (fndecl), 0));
1408   emit_move_insn (temp, reg_fnaddr);
1409   emit_insn (gen_andhi3 (temp, temp, GEN_INT (0xFF)));
1410   emit_insn (gen_iorhi3 (temp, temp, GEN_INT (0x0200)));
1411   emit_move_insn (reg_addr_mem, temp);
1412   emit_insn (gen_addhi3 (reg_addr, reg_addr, const2_rtx));
1413   reg_addr_mem = adjust_automodify_address (reg_addr_mem, VOIDmode, NULL, 2);
1414
1415   emit_insn (gen_lshrhi3 (reg_fnaddr, reg_fnaddr, GEN_INT (8)));
1416   emit_move_insn (reg_addr_mem, reg_fnaddr);
1417 }
1418
1419 /* Worker function for FUNCTION_VALUE.  */
1420
1421 rtx
1422 xstormy16_function_value (const_tree valtype, const_tree func ATTRIBUTE_UNUSED)
1423 {
1424   enum machine_mode mode;
1425   mode = TYPE_MODE (valtype);
1426   PROMOTE_MODE (mode, 0, valtype);
1427   return gen_rtx_REG (mode, RETURN_VALUE_REGNUM);
1428 }
1429
1430 /* A C compound statement that outputs the assembler code for a thunk function,
1431    used to implement C++ virtual function calls with multiple inheritance.  The
1432    thunk acts as a wrapper around a virtual function, adjusting the implicit
1433    object parameter before handing control off to the real function.
1434
1435    First, emit code to add the integer DELTA to the location that contains the
1436    incoming first argument.  Assume that this argument contains a pointer, and
1437    is the one used to pass the `this' pointer in C++.  This is the incoming
1438    argument *before* the function prologue, e.g. `%o0' on a sparc.  The
1439    addition must preserve the values of all other incoming arguments.
1440
1441    After the addition, emit code to jump to FUNCTION, which is a
1442    `FUNCTION_DECL'.  This is a direct pure jump, not a call, and does not touch
1443    the return address.  Hence returning from FUNCTION will return to whoever
1444    called the current `thunk'.
1445
1446    The effect must be as if @var{function} had been called directly
1447    with the adjusted first argument.  This macro is responsible for
1448    emitting all of the code for a thunk function;
1449    TARGET_ASM_FUNCTION_PROLOGUE and TARGET_ASM_FUNCTION_EPILOGUE are
1450    not invoked.
1451
1452    The THUNK_FNDECL is redundant.  (DELTA and FUNCTION have already been
1453    extracted from it.)  It might possibly be useful on some targets, but
1454    probably not.  */
1455
1456 static void
1457 xstormy16_asm_output_mi_thunk (FILE *file,
1458                                tree thunk_fndecl ATTRIBUTE_UNUSED,
1459                                HOST_WIDE_INT delta,
1460                                HOST_WIDE_INT vcall_offset ATTRIBUTE_UNUSED,
1461                                tree function)
1462 {
1463   int regnum = FIRST_ARGUMENT_REGISTER;
1464
1465   /* There might be a hidden first argument for a returned structure.  */
1466   if (aggregate_value_p (TREE_TYPE (TREE_TYPE (function)), function))
1467     regnum += 1;
1468
1469   fprintf (file, "\tadd %s,#0x%x\n", reg_names[regnum], (int) delta & 0xFFFF);
1470   fputs ("\tjmpf ", file);
1471   assemble_name (file, XSTR (XEXP (DECL_RTL (function), 0), 0));
1472   putc ('\n', file);
1473 }
1474
1475 /* The purpose of this function is to override the default behavior of
1476    BSS objects.  Normally, they go into .bss or .sbss via ".common"
1477    directives, but we need to override that and put them in
1478    .bss_below100.  We can't just use a section override (like we do
1479    for .data_below100), because that makes them initialized rather
1480    than uninitialized.  */
1481
1482 void
1483 xstormy16_asm_output_aligned_common (FILE *stream,
1484                                      tree decl,
1485                                      const char *name,
1486                                      int size,
1487                                      int align,
1488                                      int global)
1489 {
1490   rtx mem = decl == NULL_TREE ? NULL_RTX : DECL_RTL (decl);
1491   rtx symbol;
1492
1493   if (mem != NULL_RTX
1494       && MEM_P (mem)
1495       && GET_CODE (symbol = XEXP (mem, 0)) == SYMBOL_REF
1496       && SYMBOL_REF_FLAGS (symbol) & SYMBOL_FLAG_XSTORMY16_BELOW100)
1497     {
1498       const char *name2;
1499       int p2align = 0;
1500
1501       switch_to_section (bss100_section);
1502
1503       while (align > 8)
1504         {
1505           align /= 2;
1506           p2align ++;
1507         }
1508
1509       name2 = default_strip_name_encoding (name);
1510       if (global)
1511         fprintf (stream, "\t.globl\t%s\n", name2);
1512       if (p2align)
1513         fprintf (stream, "\t.p2align %d\n", p2align);
1514       fprintf (stream, "\t.type\t%s, @object\n", name2);
1515       fprintf (stream, "\t.size\t%s, %d\n", name2, size);
1516       fprintf (stream, "%s:\n\t.space\t%d\n", name2, size);
1517       return;
1518     }
1519
1520   if (!global)
1521     {
1522       fprintf (stream, "\t.local\t");
1523       assemble_name (stream, name);
1524       fprintf (stream, "\n");
1525     }
1526   fprintf (stream, "\t.comm\t");
1527   assemble_name (stream, name);
1528   fprintf (stream, ",%u,%u\n", size, align / BITS_PER_UNIT);
1529 }
1530
1531 /* Implement TARGET_ASM_INIT_SECTIONS.  */
1532
1533 static void
1534 xstormy16_asm_init_sections (void)
1535 {
1536   bss100_section
1537     = get_unnamed_section (SECTION_WRITE | SECTION_BSS,
1538                            output_section_asm_op,
1539                            "\t.section \".bss_below100\",\"aw\",@nobits");
1540 }
1541
1542 /* Mark symbols with the "below100" attribute so that we can use the
1543    special addressing modes for them.  */
1544
1545 static void
1546 xstormy16_encode_section_info (tree decl, rtx r, int first)
1547 {
1548   default_encode_section_info (decl, r, first);
1549
1550    if (TREE_CODE (decl) == VAR_DECL
1551       && (lookup_attribute ("below100", DECL_ATTRIBUTES (decl))
1552           || lookup_attribute ("BELOW100", DECL_ATTRIBUTES (decl))))
1553     {
1554       rtx symbol = XEXP (r, 0);
1555
1556       gcc_assert (GET_CODE (symbol) == SYMBOL_REF);
1557       SYMBOL_REF_FLAGS (symbol) |= SYMBOL_FLAG_XSTORMY16_BELOW100;
1558     }
1559 }
1560
1561 #undef  TARGET_ASM_CONSTRUCTOR
1562 #define TARGET_ASM_CONSTRUCTOR  xstormy16_asm_out_constructor
1563 #undef  TARGET_ASM_DESTRUCTOR
1564 #define TARGET_ASM_DESTRUCTOR   xstormy16_asm_out_destructor
1565
1566 /* Output constructors and destructors.  Just like
1567    default_named_section_asm_out_* but don't set the sections writable.  */
1568
1569 static void
1570 xstormy16_asm_out_destructor (rtx symbol, int priority)
1571 {
1572   const char *section = ".dtors";
1573   char buf[16];
1574
1575   /* ??? This only works reliably with the GNU linker.  */
1576   if (priority != DEFAULT_INIT_PRIORITY)
1577     {
1578       sprintf (buf, ".dtors.%.5u",
1579                /* Invert the numbering so the linker puts us in the proper
1580                   order; constructors are run from right to left, and the
1581                   linker sorts in increasing order.  */
1582                MAX_INIT_PRIORITY - priority);
1583       section = buf;
1584     }
1585
1586   switch_to_section (get_section (section, 0, NULL));
1587   assemble_align (POINTER_SIZE);
1588   assemble_integer (symbol, POINTER_SIZE / BITS_PER_UNIT, POINTER_SIZE, 1);
1589 }
1590
1591 static void
1592 xstormy16_asm_out_constructor (rtx symbol, int priority)
1593 {
1594   const char *section = ".ctors";
1595   char buf[16];
1596
1597   /* ??? This only works reliably with the GNU linker.  */
1598   if (priority != DEFAULT_INIT_PRIORITY)
1599     {
1600       sprintf (buf, ".ctors.%.5u",
1601                /* Invert the numbering so the linker puts us in the proper
1602                   order; constructors are run from right to left, and the
1603                   linker sorts in increasing order.  */
1604                MAX_INIT_PRIORITY - priority);
1605       section = buf;
1606     }
1607
1608   switch_to_section (get_section (section, 0, NULL));
1609   assemble_align (POINTER_SIZE);
1610   assemble_integer (symbol, POINTER_SIZE / BITS_PER_UNIT, POINTER_SIZE, 1);
1611 }
1612 \f
1613 /* Print a memory address as an operand to reference that memory location.  */
1614
1615 void
1616 xstormy16_print_operand_address (FILE *file, rtx address)
1617 {
1618   HOST_WIDE_INT offset;
1619   int pre_dec, post_inc;
1620
1621   /* There are a few easy cases.  */
1622   if (CONST_INT_P (address))
1623     {
1624       fprintf (file, HOST_WIDE_INT_PRINT_DEC, INTVAL (address) & 0xFFFF);
1625       return;
1626     }
1627
1628   if (CONSTANT_P (address) || LABEL_P (address))
1629     {
1630       output_addr_const (file, address);
1631       return;
1632     }
1633
1634   /* Otherwise, it's hopefully something of the form
1635      (plus:HI (pre_dec:HI (reg:HI ...)) (const_int ...)).  */
1636   if (GET_CODE (address) == PLUS)
1637     {
1638       gcc_assert (CONST_INT_P (XEXP (address, 1)));
1639       offset = INTVAL (XEXP (address, 1));
1640       address = XEXP (address, 0);
1641     }
1642   else
1643     offset = 0;
1644
1645   pre_dec = (GET_CODE (address) == PRE_DEC);
1646   post_inc = (GET_CODE (address) == POST_INC);
1647   if (pre_dec || post_inc)
1648     address = XEXP (address, 0);
1649
1650   gcc_assert (REG_P (address));
1651
1652   fputc ('(', file);
1653   if (pre_dec)
1654     fputs ("--", file);
1655   fputs (reg_names [REGNO (address)], file);
1656   if (post_inc)
1657     fputs ("++", file);
1658   if (offset != 0)
1659     fprintf (file, "," HOST_WIDE_INT_PRINT_DEC, offset);
1660   fputc (')', file);
1661 }
1662
1663 /* Print an operand to an assembler instruction.  */
1664
1665 void
1666 xstormy16_print_operand (FILE *file, rtx x, int code)
1667 {
1668   switch (code)
1669     {
1670     case 'B':
1671         /* There is either one bit set, or one bit clear, in X.
1672            Print it preceded by '#'.  */
1673       {
1674         static int bits_set[8] = { 0, 1, 1, 2, 1, 2, 2, 3 };
1675         HOST_WIDE_INT xx = 1;
1676         HOST_WIDE_INT l;
1677
1678         if (CONST_INT_P (x))
1679           xx = INTVAL (x);
1680         else
1681           output_operand_lossage ("'B' operand is not constant");
1682
1683         /* GCC sign-extends masks with the MSB set, so we have to
1684            detect all the cases that differ only in sign extension
1685            beyond the bits we care about.  Normally, the predicates
1686            and constraints ensure that we have the right values.  This
1687            works correctly for valid masks.  */
1688         if (bits_set[xx & 7] <= 1)
1689           {
1690             /* Remove sign extension bits.  */
1691             if ((~xx & ~(HOST_WIDE_INT)0xff) == 0)
1692               xx &= 0xff;
1693             else if ((~xx & ~(HOST_WIDE_INT)0xffff) == 0)
1694               xx &= 0xffff;
1695             l = exact_log2 (xx);
1696           }
1697         else
1698           {
1699             /* Add sign extension bits.  */
1700             if ((xx & ~(HOST_WIDE_INT)0xff) == 0)
1701               xx |= ~(HOST_WIDE_INT)0xff;
1702             else if ((xx & ~(HOST_WIDE_INT)0xffff) == 0)
1703               xx |= ~(HOST_WIDE_INT)0xffff;
1704             l = exact_log2 (~xx);
1705           }
1706
1707         if (l == -1)
1708           output_operand_lossage ("'B' operand has multiple bits set");
1709
1710         fprintf (file, IMMEDIATE_PREFIX HOST_WIDE_INT_PRINT_DEC, l);
1711         return;
1712       }
1713
1714     case 'C':
1715       /* Print the symbol without a surrounding @fptr().  */
1716       if (GET_CODE (x) == SYMBOL_REF)
1717         assemble_name (file, XSTR (x, 0));
1718       else if (LABEL_P (x))
1719         output_asm_label (x);
1720       else
1721         xstormy16_print_operand_address (file, x);
1722       return;
1723
1724     case 'o':
1725     case 'O':
1726       /* Print the immediate operand less one, preceded by '#'.
1727          For 'O', negate it first.  */
1728       {
1729         HOST_WIDE_INT xx = 0;
1730
1731         if (CONST_INT_P (x))
1732           xx = INTVAL (x);
1733         else
1734           output_operand_lossage ("'o' operand is not constant");
1735
1736         if (code == 'O')
1737           xx = -xx;
1738
1739         fprintf (file, IMMEDIATE_PREFIX HOST_WIDE_INT_PRINT_DEC, xx - 1);
1740         return;
1741       }
1742
1743     case 'b':
1744       /* Print the shift mask for bp/bn.  */
1745       {
1746         HOST_WIDE_INT xx = 1;
1747         HOST_WIDE_INT l;
1748
1749         if (CONST_INT_P (x))
1750           xx = INTVAL (x);
1751         else
1752           output_operand_lossage ("'B' operand is not constant");
1753
1754         l = 7 - xx;
1755
1756         fputs (IMMEDIATE_PREFIX, file);
1757         fprintf (file, HOST_WIDE_INT_PRINT_DEC, l);
1758         return;
1759       }
1760
1761     case 0:
1762       /* Handled below.  */
1763       break;
1764
1765     default:
1766       output_operand_lossage ("xstormy16_print_operand: unknown code");
1767       return;
1768     }
1769
1770   switch (GET_CODE (x))
1771     {
1772     case REG:
1773       fputs (reg_names [REGNO (x)], file);
1774       break;
1775
1776     case MEM:
1777       xstormy16_print_operand_address (file, XEXP (x, 0));
1778       break;
1779
1780     default:
1781       /* Some kind of constant or label; an immediate operand,
1782          so prefix it with '#' for the assembler.  */
1783       fputs (IMMEDIATE_PREFIX, file);
1784       output_addr_const (file, x);
1785       break;
1786     }
1787
1788   return;
1789 }
1790 \f
1791 /* Expander for the `casesi' pattern.
1792    INDEX is the index of the switch statement.
1793    LOWER_BOUND is a CONST_INT that is the value of INDEX corresponding
1794      to the first table entry.
1795    RANGE is the number of table entries.
1796    TABLE is an ADDR_VEC that is the jump table.
1797    DEFAULT_LABEL is the address to branch to if INDEX is outside the
1798      range LOWER_BOUND to LOWER_BOUND + RANGE - 1.  */
1799
1800 void
1801 xstormy16_expand_casesi (rtx index, rtx lower_bound, rtx range,
1802                          rtx table, rtx default_label)
1803 {
1804   HOST_WIDE_INT range_i = INTVAL (range);
1805   rtx int_index;
1806
1807   /* This code uses 'br', so it can deal only with tables of size up to
1808      8192 entries.  */
1809   if (range_i >= 8192)
1810     sorry ("switch statement of size %lu entries too large",
1811            (unsigned long) range_i);
1812
1813   index = expand_binop (SImode, sub_optab, index, lower_bound, NULL_RTX, 0,
1814                         OPTAB_LIB_WIDEN);
1815   emit_cmp_and_jump_insns (index, range, GTU, NULL_RTX, SImode, 1,
1816                            default_label);
1817   int_index = gen_lowpart_common (HImode, index);
1818   emit_insn (gen_ashlhi3 (int_index, int_index, const2_rtx));
1819   emit_jump_insn (gen_tablejump_pcrel (int_index, table));
1820 }
1821
1822 /* Output an ADDR_VEC.  It is output as a sequence of 'jmpf'
1823    instructions, without label or alignment or any other special
1824    constructs.  We know that the previous instruction will be the
1825    `tablejump_pcrel' output above.
1826
1827    TODO: it might be nice to output 'br' instructions if they could
1828    all reach.  */
1829
1830 void
1831 xstormy16_output_addr_vec (FILE *file, rtx label ATTRIBUTE_UNUSED, rtx table)
1832 {
1833   int vlen, idx;
1834
1835   switch_to_section (current_function_section ());
1836
1837   vlen = XVECLEN (table, 0);
1838   for (idx = 0; idx < vlen; idx++)
1839     {
1840       fputs ("\tjmpf ", file);
1841       output_asm_label (XEXP (XVECEXP (table, 0, idx), 0));
1842       fputc ('\n', file);
1843     }
1844 }
1845 \f
1846 /* Expander for the `call' patterns.
1847    RETVAL is the RTL for the return register or NULL for void functions.
1848    DEST is the function to call, expressed as a MEM.
1849    COUNTER is ignored.  */
1850
1851 void
1852 xstormy16_expand_call (rtx retval, rtx dest, rtx counter)
1853 {
1854   rtx call, temp;
1855   enum machine_mode mode;
1856
1857   gcc_assert (MEM_P (dest));
1858   dest = XEXP (dest, 0);
1859
1860   if (! CONSTANT_P (dest) && ! REG_P (dest))
1861     dest = force_reg (Pmode, dest);
1862
1863   if (retval == NULL)
1864     mode = VOIDmode;
1865   else
1866     mode = GET_MODE (retval);
1867
1868   call = gen_rtx_CALL (mode, gen_rtx_MEM (FUNCTION_MODE, dest),
1869                        counter);
1870   if (retval)
1871     call = gen_rtx_SET (VOIDmode, retval, call);
1872
1873   if (! CONSTANT_P (dest))
1874     {
1875       temp = gen_reg_rtx (HImode);
1876       emit_move_insn (temp, const0_rtx);
1877     }
1878   else
1879     temp = const0_rtx;
1880
1881   call = gen_rtx_PARALLEL (VOIDmode, gen_rtvec (2, call,
1882                                                 gen_rtx_USE (VOIDmode, temp)));
1883   emit_call_insn (call);
1884 }
1885 \f
1886 /* Expanders for multiword computational operations.  */
1887
1888 /* Expander for arithmetic operations; emit insns to compute
1889
1890    (set DEST (CODE:MODE SRC0 SRC1))
1891
1892    When CODE is COMPARE, a branch template is generated
1893    (this saves duplicating code in xstormy16_split_cbranch).  */
1894
1895 void
1896 xstormy16_expand_arith (enum machine_mode mode, enum rtx_code code,
1897                         rtx dest, rtx src0, rtx src1)
1898 {
1899   int num_words = GET_MODE_BITSIZE (mode) / BITS_PER_WORD;
1900   int i;
1901   int firstloop = 1;
1902
1903   if (code == NEG)
1904     emit_move_insn (src0, const0_rtx);
1905
1906   for (i = 0; i < num_words; i++)
1907     {
1908       rtx w_src0, w_src1, w_dest;
1909       rtx insn;
1910
1911       w_src0 = simplify_gen_subreg (word_mode, src0, mode,
1912                                     i * UNITS_PER_WORD);
1913       w_src1 = simplify_gen_subreg (word_mode, src1, mode, i * UNITS_PER_WORD);
1914       w_dest = simplify_gen_subreg (word_mode, dest, mode, i * UNITS_PER_WORD);
1915
1916       switch (code)
1917         {
1918         case PLUS:
1919           if (firstloop
1920               && CONST_INT_P (w_src1)
1921               && INTVAL (w_src1) == 0)
1922             continue;
1923
1924           if (firstloop)
1925             insn = gen_addchi4 (w_dest, w_src0, w_src1);
1926           else
1927             insn = gen_addchi5 (w_dest, w_src0, w_src1);
1928           break;
1929
1930         case NEG:
1931         case MINUS:
1932         case COMPARE:
1933           if (code == COMPARE && i == num_words - 1)
1934             {
1935               rtx branch, sub, clobber, sub_1;
1936
1937               sub_1 = gen_rtx_MINUS (HImode, w_src0,
1938                                      gen_rtx_ZERO_EXTEND (HImode, gen_rtx_REG (BImode, CARRY_REGNUM)));
1939               sub = gen_rtx_SET (VOIDmode, w_dest,
1940                                  gen_rtx_MINUS (HImode, sub_1, w_src1));
1941               clobber = gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (BImode, CARRY_REGNUM));
1942               branch = gen_rtx_SET (VOIDmode, pc_rtx,
1943                                     gen_rtx_IF_THEN_ELSE (VOIDmode,
1944                                                           gen_rtx_EQ (HImode,
1945                                                                       sub_1,
1946                                                                       w_src1),
1947                                                           pc_rtx,
1948                                                           pc_rtx));
1949               insn = gen_rtx_PARALLEL (VOIDmode,
1950                                        gen_rtvec (3, branch, sub, clobber));
1951             }
1952           else if (firstloop
1953                    && code != COMPARE
1954                    && CONST_INT_P (w_src1)
1955                    && INTVAL (w_src1) == 0)
1956             continue;
1957           else if (firstloop)
1958             insn = gen_subchi4 (w_dest, w_src0, w_src1);
1959           else
1960             insn = gen_subchi5 (w_dest, w_src0, w_src1);
1961           break;
1962
1963         case IOR:
1964         case XOR:
1965         case AND:
1966           if (CONST_INT_P (w_src1)
1967               && INTVAL (w_src1) == -(code == AND))
1968             continue;
1969
1970           insn = gen_rtx_SET (VOIDmode, w_dest, gen_rtx_fmt_ee (code, mode,
1971                                                                 w_src0, w_src1));
1972           break;
1973
1974         case NOT:
1975           insn = gen_rtx_SET (VOIDmode, w_dest, gen_rtx_NOT (mode, w_src0));
1976           break;
1977
1978         default:
1979           gcc_unreachable ();
1980         }
1981
1982       firstloop = 0;
1983       emit (insn);
1984     }
1985
1986   /* If we emit nothing, try_split() will think we failed.  So emit
1987      something that does nothing and can be optimized away.  */
1988   if (firstloop)
1989     emit (gen_nop ());
1990 }
1991
1992 /* The shift operations are split at output time for constant values;
1993    variable-width shifts get handed off to a library routine.
1994
1995    Generate an output string to do (set X (CODE:MODE X SIZE_R))
1996    SIZE_R will be a CONST_INT, X will be a hard register.  */
1997
1998 const char *
1999 xstormy16_output_shift (enum machine_mode mode, enum rtx_code code,
2000                         rtx x, rtx size_r, rtx temp)
2001 {
2002   HOST_WIDE_INT size;
2003   const char *r0, *r1, *rt;
2004   static char r[64];
2005
2006   gcc_assert (CONST_INT_P (size_r)
2007               && REG_P (x)
2008               && mode == SImode);
2009
2010   size = INTVAL (size_r) & (GET_MODE_BITSIZE (mode) - 1);
2011
2012   if (size == 0)
2013     return "";
2014
2015   r0 = reg_names [REGNO (x)];
2016   r1 = reg_names [REGNO (x) + 1];
2017
2018   /* For shifts of size 1, we can use the rotate instructions.  */
2019   if (size == 1)
2020     {
2021       switch (code)
2022         {
2023         case ASHIFT:
2024           sprintf (r, "shl %s,#1 | rlc %s,#1", r0, r1);
2025           break;
2026         case ASHIFTRT:
2027           sprintf (r, "asr %s,#1 | rrc %s,#1", r1, r0);
2028           break;
2029         case LSHIFTRT:
2030           sprintf (r, "shr %s,#1 | rrc %s,#1", r1, r0);
2031           break;
2032         default:
2033           gcc_unreachable ();
2034         }
2035       return r;
2036     }
2037
2038   /* For large shifts, there are easy special cases.  */
2039   if (size == 16)
2040     {
2041       switch (code)
2042         {
2043         case ASHIFT:
2044           sprintf (r, "mov %s,%s | mov %s,#0", r1, r0, r0);
2045           break;
2046         case ASHIFTRT:
2047           sprintf (r, "mov %s,%s | asr %s,#15", r0, r1, r1);
2048           break;
2049         case LSHIFTRT:
2050           sprintf (r, "mov %s,%s | mov %s,#0", r0, r1, r1);
2051           break;
2052         default:
2053           gcc_unreachable ();
2054         }
2055       return r;
2056     }
2057   if (size > 16)
2058     {
2059       switch (code)
2060         {
2061         case ASHIFT:
2062           sprintf (r, "mov %s,%s | mov %s,#0 | shl %s,#%d",
2063                    r1, r0, r0, r1, (int) size - 16);
2064           break;
2065         case ASHIFTRT:
2066           sprintf (r, "mov %s,%s | asr %s,#15 | asr %s,#%d",
2067                    r0, r1, r1, r0, (int) size - 16);
2068           break;
2069         case LSHIFTRT:
2070           sprintf (r, "mov %s,%s | mov %s,#0 | shr %s,#%d",
2071                    r0, r1, r1, r0, (int) size - 16);
2072           break;
2073         default:
2074           gcc_unreachable ();
2075         }
2076       return r;
2077     }
2078
2079   /* For the rest, we have to do more work.  In particular, we
2080      need a temporary.  */
2081   rt = reg_names [REGNO (temp)];
2082   switch (code)
2083     {
2084     case ASHIFT:
2085       sprintf (r,
2086                "mov %s,%s | shl %s,#%d | shl %s,#%d | shr %s,#%d | or %s,%s",
2087                rt, r0, r0, (int) size, r1, (int) size, rt, (int) (16 - size),
2088                r1, rt);
2089       break;
2090     case ASHIFTRT:
2091       sprintf (r,
2092                "mov %s,%s | asr %s,#%d | shr %s,#%d | shl %s,#%d | or %s,%s",
2093                rt, r1, r1, (int) size, r0, (int) size, rt, (int) (16 - size),
2094                r0, rt);
2095       break;
2096     case LSHIFTRT:
2097       sprintf (r,
2098                "mov %s,%s | shr %s,#%d | shr %s,#%d | shl %s,#%d | or %s,%s",
2099                rt, r1, r1, (int) size, r0, (int) size, rt, (int) (16 - size),
2100                r0, rt);
2101       break;
2102     default:
2103       gcc_unreachable ();
2104     }
2105   return r;
2106 }
2107 \f
2108 /* Attribute handling.  */
2109
2110 /* Return nonzero if the function is an interrupt function.  */
2111
2112 int
2113 xstormy16_interrupt_function_p (void)
2114 {
2115   tree attributes;
2116
2117   /* The dwarf2 mechanism asks for INCOMING_FRAME_SP_OFFSET before
2118      any functions are declared, which is demonstrably wrong, but
2119      it is worked around here.  FIXME.  */
2120   if (!cfun)
2121     return 0;
2122
2123   attributes = TYPE_ATTRIBUTES (TREE_TYPE (current_function_decl));
2124   return lookup_attribute ("interrupt", attributes) != NULL_TREE;
2125 }
2126
2127 #undef  TARGET_ATTRIBUTE_TABLE
2128 #define TARGET_ATTRIBUTE_TABLE  xstormy16_attribute_table
2129
2130 static tree xstormy16_handle_interrupt_attribute
2131   (tree *, tree, tree, int, bool *);
2132 static tree xstormy16_handle_below100_attribute
2133   (tree *, tree, tree, int, bool *);
2134
2135 static const struct attribute_spec xstormy16_attribute_table[] =
2136 {
2137   /* name, min_len, max_len, decl_req, type_req, fn_type_req, handler.  */
2138   { "interrupt", 0, 0, false, true,  true,  xstormy16_handle_interrupt_attribute },
2139   { "BELOW100",  0, 0, false, false, false, xstormy16_handle_below100_attribute },
2140   { "below100",  0, 0, false, false, false, xstormy16_handle_below100_attribute },
2141   { NULL,        0, 0, false, false, false, NULL }
2142 };
2143
2144 /* Handle an "interrupt" attribute;
2145    arguments as in struct attribute_spec.handler.  */
2146
2147 static tree
2148 xstormy16_handle_interrupt_attribute (tree *node, tree name,
2149                                       tree args ATTRIBUTE_UNUSED,
2150                                       int flags ATTRIBUTE_UNUSED,
2151                                       bool *no_add_attrs)
2152 {
2153   if (TREE_CODE (*node) != FUNCTION_TYPE)
2154     {
2155       warning (OPT_Wattributes, "%qE attribute only applies to functions",
2156                name);
2157       *no_add_attrs = true;
2158     }
2159
2160   return NULL_TREE;
2161 }
2162
2163 /* Handle an "below" attribute;
2164    arguments as in struct attribute_spec.handler.  */
2165
2166 static tree
2167 xstormy16_handle_below100_attribute (tree *node,
2168                                      tree name ATTRIBUTE_UNUSED,
2169                                      tree args ATTRIBUTE_UNUSED,
2170                                      int flags ATTRIBUTE_UNUSED,
2171                                      bool *no_add_attrs)
2172 {
2173   if (TREE_CODE (*node) != VAR_DECL
2174       && TREE_CODE (*node) != POINTER_TYPE
2175       && TREE_CODE (*node) != TYPE_DECL)
2176     {
2177       warning (OPT_Wattributes,
2178                "%<__BELOW100__%> attribute only applies to variables");
2179       *no_add_attrs = true;
2180     }
2181   else if (args == NULL_TREE && TREE_CODE (*node) == VAR_DECL)
2182     {
2183       if (! (TREE_PUBLIC (*node) || TREE_STATIC (*node)))
2184         {
2185           warning (OPT_Wattributes, "__BELOW100__ attribute not allowed "
2186                    "with auto storage class");
2187           *no_add_attrs = true;
2188         }
2189     }
2190
2191   return NULL_TREE;
2192 }
2193 \f
2194 #undef  TARGET_INIT_BUILTINS
2195 #define TARGET_INIT_BUILTINS   xstormy16_init_builtins
2196 #undef  TARGET_EXPAND_BUILTIN
2197 #define TARGET_EXPAND_BUILTIN  xstormy16_expand_builtin
2198
2199 static struct
2200 {
2201   const char * name;
2202   int          md_code;
2203   const char * arg_ops;   /* 0..9, t for temp register, r for return value.  */
2204   const char * arg_types; /* s=short,l=long, upper case for unsigned.  */
2205 }
2206   s16builtins[] =
2207 {
2208   { "__sdivlh", CODE_FOR_sdivlh, "rt01", "sls" },
2209   { "__smodlh", CODE_FOR_sdivlh, "tr01", "sls" },
2210   { "__udivlh", CODE_FOR_udivlh, "rt01", "SLS" },
2211   { "__umodlh", CODE_FOR_udivlh, "tr01", "SLS" },
2212   { NULL, 0, NULL, NULL }
2213 };
2214
2215 static void
2216 xstormy16_init_builtins (void)
2217 {
2218   tree args, ret_type, arg;
2219   int i, a;
2220
2221   ret_type = void_type_node;
2222
2223   for (i = 0; s16builtins[i].name; i++)
2224     {
2225       args = void_list_node;
2226       for (a = strlen (s16builtins[i].arg_types) - 1; a >= 0; a--)
2227         {
2228           switch (s16builtins[i].arg_types[a])
2229             {
2230             case 's': arg = short_integer_type_node; break;
2231             case 'S': arg = short_unsigned_type_node; break;
2232             case 'l': arg = long_integer_type_node; break;
2233             case 'L': arg = long_unsigned_type_node; break;
2234             default: gcc_unreachable ();
2235             }
2236           if (a == 0)
2237             ret_type = arg;
2238           else
2239             args = tree_cons (NULL_TREE, arg, args);
2240         }
2241       add_builtin_function (s16builtins[i].name,
2242                             build_function_type (ret_type, args),
2243                             i, BUILT_IN_MD, NULL, NULL);
2244     }
2245 }
2246
2247 static rtx
2248 xstormy16_expand_builtin (tree exp, rtx target,
2249                           rtx subtarget ATTRIBUTE_UNUSED,
2250                           enum machine_mode mode ATTRIBUTE_UNUSED,
2251                           int ignore ATTRIBUTE_UNUSED)
2252 {
2253   rtx op[10], args[10], pat, copyto[10], retval = 0;
2254   tree fndecl, argtree;
2255   int i, a, o, code;
2256
2257   fndecl = TREE_OPERAND (TREE_OPERAND (exp, 0), 0);
2258   argtree = TREE_OPERAND (exp, 1);
2259   i = DECL_FUNCTION_CODE (fndecl);
2260   code = s16builtins[i].md_code;
2261
2262   for (a = 0; a < 10 && argtree; a++)
2263     {
2264       args[a] = expand_normal (TREE_VALUE (argtree));
2265       argtree = TREE_CHAIN (argtree);
2266     }
2267
2268   for (o = 0; s16builtins[i].arg_ops[o]; o++)
2269     {
2270       char ao = s16builtins[i].arg_ops[o];
2271       char c = insn_data[code].operand[o].constraint[0];
2272       enum machine_mode omode;
2273
2274       copyto[o] = 0;
2275
2276       omode = (enum machine_mode) insn_data[code].operand[o].mode;
2277       if (ao == 'r')
2278         op[o] = target ? target : gen_reg_rtx (omode);
2279       else if (ao == 't')
2280         op[o] = gen_reg_rtx (omode);
2281       else
2282         op[o] = args[(int) hex_value (ao)];
2283
2284       if (! (*insn_data[code].operand[o].predicate) (op[o], GET_MODE (op[o])))
2285         {
2286           if (c == '+' || c == '=')
2287             {
2288               copyto[o] = op[o];
2289               op[o] = gen_reg_rtx (omode);
2290             }
2291           else
2292             op[o] = copy_to_mode_reg (omode, op[o]);
2293         }
2294
2295       if (ao == 'r')
2296         retval = op[o];
2297     }
2298
2299   pat = GEN_FCN (code) (op[0], op[1], op[2], op[3], op[4],
2300                         op[5], op[6], op[7], op[8], op[9]);
2301   emit_insn (pat);
2302
2303   for (o = 0; s16builtins[i].arg_ops[o]; o++)
2304     if (copyto[o])
2305       {
2306         emit_move_insn (copyto[o], op[o]);
2307         if (op[o] == retval)
2308           retval = copyto[o];
2309       }
2310
2311   return retval;
2312 }
2313 \f
2314 /* Look for combinations of insns that can be converted to BN or BP
2315    opcodes.  This is, unfortunately, too complex to do with MD
2316    patterns.  */
2317
2318 static void
2319 combine_bnp (rtx insn)
2320 {
2321   int insn_code, regno, need_extend;
2322   unsigned int mask;
2323   rtx cond, reg, and_insn, load, qireg, mem;
2324   enum machine_mode load_mode = QImode;
2325   enum machine_mode and_mode = QImode;
2326   rtx shift = NULL_RTX;
2327
2328   insn_code = recog_memoized (insn);
2329   if (insn_code != CODE_FOR_cbranchhi
2330       && insn_code != CODE_FOR_cbranchhi_neg)
2331     return;
2332
2333   cond = XVECEXP (PATTERN (insn), 0, 0); /* set */
2334   cond = XEXP (cond, 1); /* if */
2335   cond = XEXP (cond, 0); /* cond */
2336   switch (GET_CODE (cond))
2337     {
2338     case NE:
2339     case EQ:
2340       need_extend = 0;
2341       break;
2342     case LT:
2343     case GE:
2344       need_extend = 1;
2345       break;
2346     default:
2347       return;
2348     }
2349
2350   reg = XEXP (cond, 0);
2351   if (! REG_P (reg))
2352     return;
2353   regno = REGNO (reg);
2354   if (XEXP (cond, 1) != const0_rtx)
2355     return;
2356   if (! find_regno_note (insn, REG_DEAD, regno))
2357     return;
2358   qireg = gen_rtx_REG (QImode, regno);
2359
2360   if (need_extend)
2361     {
2362       /* LT and GE conditionals should have a sign extend before
2363          them.  */
2364       for (and_insn = prev_real_insn (insn); and_insn;
2365            and_insn = prev_real_insn (and_insn))
2366         {
2367           int and_code = recog_memoized (and_insn);
2368
2369           if (and_code == CODE_FOR_extendqihi2
2370               && rtx_equal_p (SET_DEST (PATTERN (and_insn)), reg)
2371               && rtx_equal_p (XEXP (SET_SRC (PATTERN (and_insn)), 0), qireg))
2372             break;
2373
2374           if (and_code == CODE_FOR_movhi_internal
2375               && rtx_equal_p (SET_DEST (PATTERN (and_insn)), reg))
2376             {
2377               /* This is for testing bit 15.  */
2378               and_insn = insn;
2379               break;
2380             }
2381
2382           if (reg_mentioned_p (reg, and_insn))
2383             return;
2384
2385           if (GET_CODE (and_insn) != NOTE
2386               && GET_CODE (and_insn) != INSN)
2387             return;
2388         }
2389     }
2390   else
2391     {
2392       /* EQ and NE conditionals have an AND before them.  */
2393       for (and_insn = prev_real_insn (insn); and_insn;
2394            and_insn = prev_real_insn (and_insn))
2395         {
2396           if (recog_memoized (and_insn) == CODE_FOR_andhi3
2397               && rtx_equal_p (SET_DEST (PATTERN (and_insn)), reg)
2398               && rtx_equal_p (XEXP (SET_SRC (PATTERN (and_insn)), 0), reg))
2399             break;
2400
2401           if (reg_mentioned_p (reg, and_insn))
2402             return;
2403
2404           if (GET_CODE (and_insn) != NOTE
2405               && GET_CODE (and_insn) != INSN)
2406             return;
2407         }
2408
2409       if (and_insn)
2410         {
2411           /* Some mis-optimizations by GCC can generate a RIGHT-SHIFT
2412              followed by an AND like this:
2413
2414                (parallel [(set (reg:HI r7) (lshiftrt:HI (reg:HI r7) (const_int 3)))
2415                           (clobber (reg:BI carry))]
2416
2417                (set (reg:HI r7) (and:HI (reg:HI r7) (const_int 1)))
2418
2419              Attempt to detect this here.  */
2420           for (shift = prev_real_insn (and_insn); shift;
2421                shift = prev_real_insn (shift))
2422             {
2423               if (recog_memoized (shift) == CODE_FOR_lshrhi3
2424                   && rtx_equal_p (SET_DEST (XVECEXP (PATTERN (shift), 0, 0)), reg)
2425                   && rtx_equal_p (XEXP (SET_SRC (XVECEXP (PATTERN (shift), 0, 0)), 0), reg))
2426                 break;
2427
2428               if (reg_mentioned_p (reg, shift)
2429                   || (GET_CODE (shift) != NOTE
2430                       && GET_CODE (shift) != INSN))
2431                 {
2432                   shift = NULL_RTX;
2433                   break;
2434                 }
2435             }
2436         }
2437     }
2438   if (!and_insn)
2439     return;
2440
2441   for (load = shift ? prev_real_insn (shift) : prev_real_insn (and_insn);
2442        load;
2443        load = prev_real_insn (load))
2444     {
2445       int load_code = recog_memoized (load);
2446
2447       if (load_code == CODE_FOR_movhi_internal
2448           && rtx_equal_p (SET_DEST (PATTERN (load)), reg)
2449           && xstormy16_below100_operand (SET_SRC (PATTERN (load)), HImode)
2450           && ! MEM_VOLATILE_P (SET_SRC (PATTERN (load))))
2451         {
2452           load_mode = HImode;
2453           break;
2454         }
2455
2456       if (load_code == CODE_FOR_movqi_internal
2457           && rtx_equal_p (SET_DEST (PATTERN (load)), qireg)
2458           && xstormy16_below100_operand (SET_SRC (PATTERN (load)), QImode))
2459         {
2460           load_mode = QImode;
2461           break;
2462         }
2463
2464       if (load_code == CODE_FOR_zero_extendqihi2
2465           && rtx_equal_p (SET_DEST (PATTERN (load)), reg)
2466           && xstormy16_below100_operand (XEXP (SET_SRC (PATTERN (load)), 0), QImode))
2467         {
2468           load_mode = QImode;
2469           and_mode = HImode;
2470           break;
2471         }
2472
2473       if (reg_mentioned_p (reg, load))
2474         return;
2475
2476       if (GET_CODE (load) != NOTE
2477           && GET_CODE (load) != INSN)
2478         return;
2479     }
2480   if (!load)
2481     return;
2482
2483   mem = SET_SRC (PATTERN (load));
2484
2485   if (need_extend)
2486     {
2487       mask = (load_mode == HImode) ? 0x8000 : 0x80;
2488
2489       /* If the mem includes a zero-extend operation and we are
2490          going to generate a sign-extend operation then move the
2491          mem inside the zero-extend.  */
2492       if (GET_CODE (mem) == ZERO_EXTEND)
2493         mem = XEXP (mem, 0);
2494     }
2495   else
2496     {
2497       if (!xstormy16_onebit_set_operand (XEXP (SET_SRC (PATTERN (and_insn)), 1),
2498                                          load_mode))
2499         return;
2500
2501       mask = (int) INTVAL (XEXP (SET_SRC (PATTERN (and_insn)), 1));
2502
2503       if (shift)
2504         mask <<= INTVAL (XEXP (SET_SRC (XVECEXP (PATTERN (shift), 0, 0)), 1));
2505     }
2506
2507   if (load_mode == HImode)
2508     {
2509       rtx addr = XEXP (mem, 0);
2510
2511       if (! (mask & 0xff))
2512         {
2513           addr = plus_constant (addr, 1);
2514           mask >>= 8;
2515         }
2516       mem = gen_rtx_MEM (QImode, addr);
2517     }
2518
2519   if (need_extend)
2520     XEXP (cond, 0) = gen_rtx_SIGN_EXTEND (HImode, mem);
2521   else
2522     XEXP (cond, 0) = gen_rtx_AND (and_mode, mem, GEN_INT (mask));
2523
2524   INSN_CODE (insn) = -1;
2525   delete_insn (load);
2526
2527   if (and_insn != insn)
2528     delete_insn (and_insn);
2529
2530   if (shift != NULL_RTX)
2531     delete_insn (shift);
2532 }
2533
2534 static void
2535 xstormy16_reorg (void)
2536 {
2537   rtx insn;
2538
2539   for (insn = get_insns (); insn; insn = NEXT_INSN (insn))
2540     {
2541       if (! JUMP_P (insn))
2542         continue;
2543       combine_bnp (insn);
2544     }
2545 }
2546 \f
2547 /* Worker function for TARGET_RETURN_IN_MEMORY.  */
2548
2549 static bool
2550 xstormy16_return_in_memory (const_tree type, const_tree fntype ATTRIBUTE_UNUSED)
2551 {
2552   const HOST_WIDE_INT size = int_size_in_bytes (type);
2553   return (size == -1 || size > UNITS_PER_WORD * NUM_ARGUMENT_REGISTERS);
2554 }
2555 \f
2556 /* Implement TARGET_OPTION_OPTIMIZATION_TABLE.  */
2557 static const struct default_options xstorym16_option_optimization_table[] =
2558   {
2559     { OPT_LEVELS_1_PLUS, OPT_fomit_frame_pointer, NULL, 1 },
2560     { OPT_LEVELS_NONE, 0, NULL, 0 }
2561   };
2562 \f
2563 #undef  TARGET_ASM_ALIGNED_HI_OP
2564 #define TARGET_ASM_ALIGNED_HI_OP "\t.hword\t"
2565 #undef  TARGET_ASM_ALIGNED_SI_OP
2566 #define TARGET_ASM_ALIGNED_SI_OP "\t.word\t"
2567 #undef  TARGET_ENCODE_SECTION_INFO
2568 #define TARGET_ENCODE_SECTION_INFO xstormy16_encode_section_info
2569
2570 /* Select_section doesn't handle .bss_below100.  */
2571 #undef  TARGET_HAVE_SWITCHABLE_BSS_SECTIONS
2572 #define TARGET_HAVE_SWITCHABLE_BSS_SECTIONS false
2573
2574 #undef  TARGET_ASM_OUTPUT_MI_THUNK
2575 #define TARGET_ASM_OUTPUT_MI_THUNK xstormy16_asm_output_mi_thunk
2576 #undef  TARGET_ASM_CAN_OUTPUT_MI_THUNK
2577 #define TARGET_ASM_CAN_OUTPUT_MI_THUNK default_can_output_mi_thunk_no_vcall
2578
2579 #undef  TARGET_RTX_COSTS
2580 #define TARGET_RTX_COSTS xstormy16_rtx_costs
2581 #undef  TARGET_ADDRESS_COST
2582 #define TARGET_ADDRESS_COST xstormy16_address_cost
2583
2584 #undef  TARGET_BUILD_BUILTIN_VA_LIST
2585 #define TARGET_BUILD_BUILTIN_VA_LIST xstormy16_build_builtin_va_list
2586 #undef  TARGET_EXPAND_BUILTIN_VA_START
2587 #define TARGET_EXPAND_BUILTIN_VA_START xstormy16_expand_builtin_va_start
2588 #undef  TARGET_GIMPLIFY_VA_ARG_EXPR
2589 #define TARGET_GIMPLIFY_VA_ARG_EXPR xstormy16_gimplify_va_arg_expr
2590
2591 #undef  TARGET_PROMOTE_FUNCTION_MODE
2592 #define TARGET_PROMOTE_FUNCTION_MODE default_promote_function_mode_always_promote
2593 #undef  TARGET_PROMOTE_PROTOTYPES
2594 #define TARGET_PROMOTE_PROTOTYPES hook_bool_const_tree_true
2595
2596 #undef  TARGET_FUNCTION_ARG
2597 #define TARGET_FUNCTION_ARG xstormy16_function_arg
2598 #undef  TARGET_FUNCTION_ARG_ADVANCE
2599 #define TARGET_FUNCTION_ARG_ADVANCE xstormy16_function_arg_advance
2600
2601 #undef  TARGET_RETURN_IN_MEMORY
2602 #define TARGET_RETURN_IN_MEMORY xstormy16_return_in_memory
2603
2604 #undef  TARGET_MACHINE_DEPENDENT_REORG
2605 #define TARGET_MACHINE_DEPENDENT_REORG xstormy16_reorg
2606
2607 #undef TARGET_LEGITIMATE_ADDRESS_P
2608 #define TARGET_LEGITIMATE_ADDRESS_P     xstormy16_legitimate_address_p
2609 #undef TARGET_MODE_DEPENDENT_ADDRESS_P
2610 #define TARGET_MODE_DEPENDENT_ADDRESS_P xstormy16_mode_dependent_address_p
2611
2612 #undef TARGET_CAN_ELIMINATE
2613 #define TARGET_CAN_ELIMINATE xstormy16_can_eliminate
2614
2615 #undef TARGET_TRAMPOLINE_INIT
2616 #define TARGET_TRAMPOLINE_INIT xstormy16_trampoline_init
2617
2618 #undef TARGET_OPTION_OPTIMIZATION_TABLE
2619 #define TARGET_OPTION_OPTIMIZATION_TABLE xstorym16_option_optimization_table
2620
2621 struct gcc_target targetm = TARGET_INITIALIZER;
2622
2623 #include "gt-stormy16.h"