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