OSDN Git Service

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