OSDN Git Service

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