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