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