1*c87b03e5Sespie /* Xstormy16 target functions.
2*c87b03e5Sespie    Copyright (C) 1997, 1998, 1999, 2000, 2001, 2002
3*c87b03e5Sespie    Free Software Foundation, Inc.
4*c87b03e5Sespie    Contributed by Red Hat, Inc.
5*c87b03e5Sespie 
6*c87b03e5Sespie This file is part of GNU CC.
7*c87b03e5Sespie 
8*c87b03e5Sespie GNU CC is free software; you can redistribute it and/or modify
9*c87b03e5Sespie it under the terms of the GNU General Public License as published by
10*c87b03e5Sespie the Free Software Foundation; either version 2, or (at your option)
11*c87b03e5Sespie any later version.
12*c87b03e5Sespie 
13*c87b03e5Sespie GNU CC is distributed in the hope that it will be useful,
14*c87b03e5Sespie but WITHOUT ANY WARRANTY; without even the implied warranty of
15*c87b03e5Sespie MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16*c87b03e5Sespie GNU General Public License for more details.
17*c87b03e5Sespie 
18*c87b03e5Sespie You should have received a copy of the GNU General Public License
19*c87b03e5Sespie along with GNU CC; see the file COPYING.  If not, write to
20*c87b03e5Sespie the Free Software Foundation, 59 Temple Place - Suite 330,
21*c87b03e5Sespie Boston, MA 02111-1307, USA.  */
22*c87b03e5Sespie 
23*c87b03e5Sespie #include "config.h"
24*c87b03e5Sespie #include "system.h"
25*c87b03e5Sespie #include "rtl.h"
26*c87b03e5Sespie #include "regs.h"
27*c87b03e5Sespie #include "hard-reg-set.h"
28*c87b03e5Sespie #include "real.h"
29*c87b03e5Sespie #include "insn-config.h"
30*c87b03e5Sespie #include "conditions.h"
31*c87b03e5Sespie #include "insn-flags.h"
32*c87b03e5Sespie #include "output.h"
33*c87b03e5Sespie #include "insn-attr.h"
34*c87b03e5Sespie #include "flags.h"
35*c87b03e5Sespie #include "recog.h"
36*c87b03e5Sespie #include "toplev.h"
37*c87b03e5Sespie #include "obstack.h"
38*c87b03e5Sespie #include "tree.h"
39*c87b03e5Sespie #include "expr.h"
40*c87b03e5Sespie #include "optabs.h"
41*c87b03e5Sespie #include "output.h"
42*c87b03e5Sespie #include "except.h"
43*c87b03e5Sespie #include "function.h"
44*c87b03e5Sespie #include "target.h"
45*c87b03e5Sespie #include "target-def.h"
46*c87b03e5Sespie #include "tm_p.h"
47*c87b03e5Sespie #include "langhooks.h"
48*c87b03e5Sespie 
49*c87b03e5Sespie static rtx emit_addhi3_postreload PARAMS ((rtx, rtx, rtx));
50*c87b03e5Sespie static void xstormy16_asm_out_constructor PARAMS ((rtx, int));
51*c87b03e5Sespie static void xstormy16_asm_out_destructor PARAMS ((rtx, int));
52*c87b03e5Sespie static void xstormy16_encode_section_info PARAMS ((tree, int));
53*c87b03e5Sespie static void xstormy16_asm_output_mi_thunk PARAMS ((FILE *, tree, HOST_WIDE_INT,
54*c87b03e5Sespie 						   HOST_WIDE_INT, tree));
55*c87b03e5Sespie 
56*c87b03e5Sespie static void xstormy16_init_builtins PARAMS ((void));
57*c87b03e5Sespie static rtx xstormy16_expand_builtin PARAMS ((tree, rtx, rtx, enum machine_mode, int));
58*c87b03e5Sespie 
59*c87b03e5Sespie /* Define the information needed to generate branch and scc insns.  This is
60*c87b03e5Sespie    stored from the compare operation.  */
61*c87b03e5Sespie struct rtx_def * xstormy16_compare_op0;
62*c87b03e5Sespie struct rtx_def * xstormy16_compare_op1;
63*c87b03e5Sespie 
64*c87b03e5Sespie /* Return 1 if this is a LT, GE, LTU, or GEU operator.  */
65*c87b03e5Sespie 
66*c87b03e5Sespie int
xstormy16_ineqsi_operator(op,mode)67*c87b03e5Sespie xstormy16_ineqsi_operator (op, mode)
68*c87b03e5Sespie     register rtx op;
69*c87b03e5Sespie     enum machine_mode mode;
70*c87b03e5Sespie {
71*c87b03e5Sespie   enum rtx_code code = GET_CODE (op);
72*c87b03e5Sespie 
73*c87b03e5Sespie   return ((mode == VOIDmode || GET_MODE (op) == mode)
74*c87b03e5Sespie 	  && (code == LT || code == GE || code == LTU || code == GEU));
75*c87b03e5Sespie }
76*c87b03e5Sespie 
77*c87b03e5Sespie /* Return 1 if this is an EQ or NE operator.  */
78*c87b03e5Sespie 
79*c87b03e5Sespie int
equality_operator(op,mode)80*c87b03e5Sespie equality_operator (op, mode)
81*c87b03e5Sespie     register rtx op;
82*c87b03e5Sespie     enum machine_mode mode;
83*c87b03e5Sespie {
84*c87b03e5Sespie   return ((mode == VOIDmode || GET_MODE (op) == mode)
85*c87b03e5Sespie 	  && (GET_CODE (op) == EQ || GET_CODE (op) == NE));
86*c87b03e5Sespie }
87*c87b03e5Sespie 
88*c87b03e5Sespie /* Return 1 if this is a comparison operator but not an EQ or NE operator.  */
89*c87b03e5Sespie 
90*c87b03e5Sespie int
inequality_operator(op,mode)91*c87b03e5Sespie inequality_operator (op, mode)
92*c87b03e5Sespie     register rtx op;
93*c87b03e5Sespie     enum machine_mode mode;
94*c87b03e5Sespie {
95*c87b03e5Sespie   return comparison_operator (op, mode) && ! equality_operator (op, mode);
96*c87b03e5Sespie }
97*c87b03e5Sespie 
98*c87b03e5Sespie /* Branches are handled as follows:
99*c87b03e5Sespie 
100*c87b03e5Sespie    1. HImode compare-and-branches.  The machine supports these
101*c87b03e5Sespie       natively, so the appropriate pattern is emitted directly.
102*c87b03e5Sespie 
103*c87b03e5Sespie    2. SImode EQ and NE.  These are emitted as pairs of HImode
104*c87b03e5Sespie       compare-and-branches.
105*c87b03e5Sespie 
106*c87b03e5Sespie    3. SImode LT, GE, LTU and GEU.  These are emitted as a sequence
107*c87b03e5Sespie       of a SImode subtract followed by a branch (not a compare-and-branch),
108*c87b03e5Sespie       like this:
109*c87b03e5Sespie       sub
110*c87b03e5Sespie       sbc
111*c87b03e5Sespie       blt
112*c87b03e5Sespie 
113*c87b03e5Sespie    4. SImode GT, LE, GTU, LEU.  These are emitted as a sequence like:
114*c87b03e5Sespie       sub
115*c87b03e5Sespie       sbc
116*c87b03e5Sespie       blt
117*c87b03e5Sespie       or
118*c87b03e5Sespie       bne
119*c87b03e5Sespie */
120*c87b03e5Sespie 
121*c87b03e5Sespie /* Emit a branch of kind CODE to location LOC.  */
122*c87b03e5Sespie 
123*c87b03e5Sespie void
xstormy16_emit_cbranch(code,loc)124*c87b03e5Sespie xstormy16_emit_cbranch (code, loc)
125*c87b03e5Sespie      enum rtx_code code;
126*c87b03e5Sespie      rtx loc;
127*c87b03e5Sespie {
128*c87b03e5Sespie   rtx op0 = xstormy16_compare_op0;
129*c87b03e5Sespie   rtx op1 = xstormy16_compare_op1;
130*c87b03e5Sespie   rtx condition_rtx, loc_ref, branch, cy_clobber;
131*c87b03e5Sespie   rtvec vec;
132*c87b03e5Sespie   enum machine_mode mode;
133*c87b03e5Sespie 
134*c87b03e5Sespie   mode = GET_MODE (op0);
135*c87b03e5Sespie   if (mode != HImode && mode != SImode)
136*c87b03e5Sespie     abort ();
137*c87b03e5Sespie 
138*c87b03e5Sespie   if (mode == SImode
139*c87b03e5Sespie       && (code == GT || code == LE || code == GTU || code == LEU))
140*c87b03e5Sespie     {
141*c87b03e5Sespie       int unsigned_p = (code == GTU || code == LEU);
142*c87b03e5Sespie       int gt_p = (code == GT || code == GTU);
143*c87b03e5Sespie       rtx lab = NULL_RTX;
144*c87b03e5Sespie 
145*c87b03e5Sespie       if (gt_p)
146*c87b03e5Sespie 	lab = gen_label_rtx ();
147*c87b03e5Sespie       xstormy16_emit_cbranch (unsigned_p ? LTU : LT, gt_p ? lab : loc);
148*c87b03e5Sespie       /* This should be generated as a comparison against the temporary
149*c87b03e5Sespie 	 created by the previous insn, but reload can't handle that.  */
150*c87b03e5Sespie       xstormy16_emit_cbranch (gt_p ? NE : EQ, loc);
151*c87b03e5Sespie       if (gt_p)
152*c87b03e5Sespie 	emit_label (lab);
153*c87b03e5Sespie       return;
154*c87b03e5Sespie     }
155*c87b03e5Sespie   else if (mode == SImode
156*c87b03e5Sespie 	   && (code == NE || code == EQ)
157*c87b03e5Sespie 	   && op1 != const0_rtx)
158*c87b03e5Sespie     {
159*c87b03e5Sespie       rtx lab = NULL_RTX;
160*c87b03e5Sespie       int num_words = GET_MODE_BITSIZE (mode) / BITS_PER_WORD;
161*c87b03e5Sespie       int i;
162*c87b03e5Sespie 
163*c87b03e5Sespie       if (code == EQ)
164*c87b03e5Sespie 	lab = gen_label_rtx ();
165*c87b03e5Sespie 
166*c87b03e5Sespie       for (i = 0; i < num_words - 1; i++)
167*c87b03e5Sespie 	{
168*c87b03e5Sespie 	  xstormy16_compare_op0 = simplify_gen_subreg (word_mode, op0, mode,
169*c87b03e5Sespie 						      i * UNITS_PER_WORD);
170*c87b03e5Sespie 	  xstormy16_compare_op1 = simplify_gen_subreg (word_mode, op1, mode,
171*c87b03e5Sespie 						      i * UNITS_PER_WORD);
172*c87b03e5Sespie 	  xstormy16_emit_cbranch (NE, code == EQ ? lab : loc);
173*c87b03e5Sespie 	}
174*c87b03e5Sespie       xstormy16_compare_op0 = simplify_gen_subreg (word_mode, op0, mode,
175*c87b03e5Sespie 						  i * UNITS_PER_WORD);
176*c87b03e5Sespie       xstormy16_compare_op1 = simplify_gen_subreg (word_mode, op1, mode,
177*c87b03e5Sespie 						  i * UNITS_PER_WORD);
178*c87b03e5Sespie       xstormy16_emit_cbranch (code, loc);
179*c87b03e5Sespie 
180*c87b03e5Sespie       if (code == EQ)
181*c87b03e5Sespie 	emit_label (lab);
182*c87b03e5Sespie       return;
183*c87b03e5Sespie     }
184*c87b03e5Sespie 
185*c87b03e5Sespie   /* We can't allow reload to try to generate any reload after a branch,
186*c87b03e5Sespie      so when some register must match we must make the temporary ourselves.  */
187*c87b03e5Sespie   if (mode != HImode)
188*c87b03e5Sespie     {
189*c87b03e5Sespie       rtx tmp;
190*c87b03e5Sespie       tmp = gen_reg_rtx (mode);
191*c87b03e5Sespie       emit_move_insn (tmp, op0);
192*c87b03e5Sespie       op0 = tmp;
193*c87b03e5Sespie     }
194*c87b03e5Sespie 
195*c87b03e5Sespie   condition_rtx = gen_rtx (code, mode, op0, op1);
196*c87b03e5Sespie   loc_ref = gen_rtx_LABEL_REF (VOIDmode, loc);
197*c87b03e5Sespie   branch = gen_rtx_SET (VOIDmode, pc_rtx,
198*c87b03e5Sespie 			gen_rtx_IF_THEN_ELSE (VOIDmode, condition_rtx,
199*c87b03e5Sespie 					      loc_ref, pc_rtx));
200*c87b03e5Sespie 
201*c87b03e5Sespie   cy_clobber = gen_rtx_CLOBBER (VOIDmode, gen_rtx_SCRATCH (BImode));
202*c87b03e5Sespie 
203*c87b03e5Sespie   if (mode == HImode)
204*c87b03e5Sespie     vec = gen_rtvec (2, branch, cy_clobber);
205*c87b03e5Sespie   else if (code == NE || code == EQ)
206*c87b03e5Sespie     vec = gen_rtvec (2, branch, gen_rtx_CLOBBER (VOIDmode, op0));
207*c87b03e5Sespie   else
208*c87b03e5Sespie     {
209*c87b03e5Sespie       rtx sub;
210*c87b03e5Sespie #if 0
211*c87b03e5Sespie       sub = gen_rtx_SET (VOIDmode, op0, gen_rtx_MINUS (SImode, op0, op1));
212*c87b03e5Sespie #else
213*c87b03e5Sespie       sub = gen_rtx_CLOBBER (SImode, op0);
214*c87b03e5Sespie #endif
215*c87b03e5Sespie       vec = gen_rtvec (3, branch, sub, cy_clobber);
216*c87b03e5Sespie     }
217*c87b03e5Sespie 
218*c87b03e5Sespie   emit_jump_insn (gen_rtx_PARALLEL (VOIDmode, vec));
219*c87b03e5Sespie }
220*c87b03e5Sespie 
221*c87b03e5Sespie /* Take a SImode conditional branch, one of GT/LE/GTU/LEU, and split
222*c87b03e5Sespie    the arithmetic operation.  Most of the work is done by
223*c87b03e5Sespie    xstormy16_expand_arith.  */
224*c87b03e5Sespie 
225*c87b03e5Sespie void
xstormy16_split_cbranch(mode,label,comparison,dest,carry)226*c87b03e5Sespie xstormy16_split_cbranch (mode, label, comparison, dest, carry)
227*c87b03e5Sespie      enum machine_mode mode;
228*c87b03e5Sespie      rtx label;
229*c87b03e5Sespie      rtx comparison;
230*c87b03e5Sespie      rtx dest;
231*c87b03e5Sespie      rtx carry;
232*c87b03e5Sespie {
233*c87b03e5Sespie   rtx op0 = XEXP (comparison, 0);
234*c87b03e5Sespie   rtx op1 = XEXP (comparison, 1);
235*c87b03e5Sespie   rtx seq, last_insn;
236*c87b03e5Sespie   rtx compare;
237*c87b03e5Sespie 
238*c87b03e5Sespie   start_sequence ();
239*c87b03e5Sespie   xstormy16_expand_arith (mode, COMPARE, dest, op0, op1, carry);
240*c87b03e5Sespie   seq = get_insns ();
241*c87b03e5Sespie   end_sequence ();
242*c87b03e5Sespie 
243*c87b03e5Sespie   if (! INSN_P (seq))
244*c87b03e5Sespie     abort ();
245*c87b03e5Sespie 
246*c87b03e5Sespie   last_insn = seq;
247*c87b03e5Sespie   while (NEXT_INSN (last_insn) != NULL_RTX)
248*c87b03e5Sespie     last_insn = NEXT_INSN (last_insn);
249*c87b03e5Sespie 
250*c87b03e5Sespie   compare = SET_SRC (XVECEXP (PATTERN (last_insn), 0, 0));
251*c87b03e5Sespie   PUT_CODE (XEXP (compare, 0), GET_CODE (comparison));
252*c87b03e5Sespie   XEXP (compare, 1) = gen_rtx_LABEL_REF (VOIDmode, label);
253*c87b03e5Sespie   emit_insn (seq);
254*c87b03e5Sespie }
255*c87b03e5Sespie 
256*c87b03e5Sespie 
257*c87b03e5Sespie /* Return the string to output a conditional branch to LABEL, which is
258*c87b03e5Sespie    the operand number of the label.
259*c87b03e5Sespie 
260*c87b03e5Sespie    OP is the conditional expression, or NULL for branch-always.
261*c87b03e5Sespie 
262*c87b03e5Sespie    REVERSED is nonzero if we should reverse the sense of the comparison.
263*c87b03e5Sespie 
264*c87b03e5Sespie    INSN is the insn.  */
265*c87b03e5Sespie 
266*c87b03e5Sespie char *
xstormy16_output_cbranch_hi(op,label,reversed,insn)267*c87b03e5Sespie xstormy16_output_cbranch_hi (op, label, reversed, insn)
268*c87b03e5Sespie      rtx op;
269*c87b03e5Sespie      const char * label;
270*c87b03e5Sespie      int reversed;
271*c87b03e5Sespie      rtx insn;
272*c87b03e5Sespie {
273*c87b03e5Sespie   static char string[64];
274*c87b03e5Sespie   int need_longbranch = (op != NULL_RTX
275*c87b03e5Sespie 			 ? get_attr_length (insn) == 8
276*c87b03e5Sespie 			 : get_attr_length (insn) == 4);
277*c87b03e5Sespie   int really_reversed = reversed ^ need_longbranch;
278*c87b03e5Sespie   const char *ccode;
279*c87b03e5Sespie   const char *template;
280*c87b03e5Sespie   const char *operands;
281*c87b03e5Sespie   enum rtx_code code;
282*c87b03e5Sespie 
283*c87b03e5Sespie   if (! op)
284*c87b03e5Sespie     {
285*c87b03e5Sespie       if (need_longbranch)
286*c87b03e5Sespie 	ccode = "jmpf";
287*c87b03e5Sespie       else
288*c87b03e5Sespie 	ccode = "br";
289*c87b03e5Sespie       sprintf (string, "%s %s", ccode, label);
290*c87b03e5Sespie       return string;
291*c87b03e5Sespie     }
292*c87b03e5Sespie 
293*c87b03e5Sespie   code = GET_CODE (op);
294*c87b03e5Sespie 
295*c87b03e5Sespie   if (GET_CODE (XEXP (op, 0)) != REG)
296*c87b03e5Sespie     {
297*c87b03e5Sespie       code = swap_condition (code);
298*c87b03e5Sespie       operands = "%3,%2";
299*c87b03e5Sespie     }
300*c87b03e5Sespie   else
301*c87b03e5Sespie       operands = "%2,%3";
302*c87b03e5Sespie 
303*c87b03e5Sespie   /* Work out which way this really branches.  */
304*c87b03e5Sespie   if (really_reversed)
305*c87b03e5Sespie     code = reverse_condition (code);
306*c87b03e5Sespie 
307*c87b03e5Sespie   switch (code)
308*c87b03e5Sespie     {
309*c87b03e5Sespie     case EQ:   ccode = "z";   break;
310*c87b03e5Sespie     case NE:   ccode = "nz";  break;
311*c87b03e5Sespie     case GE:   ccode = "ge";  break;
312*c87b03e5Sespie     case LT:   ccode = "lt";  break;
313*c87b03e5Sespie     case GT:   ccode = "gt";  break;
314*c87b03e5Sespie     case LE:   ccode = "le";  break;
315*c87b03e5Sespie     case GEU:  ccode = "nc";  break;
316*c87b03e5Sespie     case LTU:  ccode = "c";   break;
317*c87b03e5Sespie     case GTU:  ccode = "hi";  break;
318*c87b03e5Sespie     case LEU:  ccode = "ls";  break;
319*c87b03e5Sespie 
320*c87b03e5Sespie     default:
321*c87b03e5Sespie       abort ();
322*c87b03e5Sespie     }
323*c87b03e5Sespie 
324*c87b03e5Sespie   if (need_longbranch)
325*c87b03e5Sespie     template = "b%s %s,.+8 | jmpf %s";
326*c87b03e5Sespie   else
327*c87b03e5Sespie     template = "b%s %s,%s";
328*c87b03e5Sespie   sprintf (string, template, ccode, operands, label);
329*c87b03e5Sespie 
330*c87b03e5Sespie   return string;
331*c87b03e5Sespie }
332*c87b03e5Sespie 
333*c87b03e5Sespie /* Return the string to output a conditional branch to LABEL, which is
334*c87b03e5Sespie    the operand number of the label, but suitable for the tail of a
335*c87b03e5Sespie    SImode branch.
336*c87b03e5Sespie 
337*c87b03e5Sespie    OP is the conditional expression (OP is never NULL_RTX).
338*c87b03e5Sespie 
339*c87b03e5Sespie    REVERSED is nonzero if we should reverse the sense of the comparison.
340*c87b03e5Sespie 
341*c87b03e5Sespie    INSN is the insn.  */
342*c87b03e5Sespie 
343*c87b03e5Sespie char *
xstormy16_output_cbranch_si(op,label,reversed,insn)344*c87b03e5Sespie xstormy16_output_cbranch_si (op, label, reversed, insn)
345*c87b03e5Sespie      rtx op;
346*c87b03e5Sespie      const char * label;
347*c87b03e5Sespie      int reversed;
348*c87b03e5Sespie      rtx insn;
349*c87b03e5Sespie {
350*c87b03e5Sespie   static char string[64];
351*c87b03e5Sespie   int need_longbranch = get_attr_length (insn) >= 8;
352*c87b03e5Sespie   int really_reversed = reversed ^ need_longbranch;
353*c87b03e5Sespie   const char *ccode;
354*c87b03e5Sespie   const char *template;
355*c87b03e5Sespie   char prevop[16];
356*c87b03e5Sespie   enum rtx_code code;
357*c87b03e5Sespie 
358*c87b03e5Sespie   code = GET_CODE (op);
359*c87b03e5Sespie 
360*c87b03e5Sespie   /* Work out which way this really branches.  */
361*c87b03e5Sespie   if (really_reversed)
362*c87b03e5Sespie     code = reverse_condition (code);
363*c87b03e5Sespie 
364*c87b03e5Sespie   switch (code)
365*c87b03e5Sespie     {
366*c87b03e5Sespie     case EQ:   ccode = "z";   break;
367*c87b03e5Sespie     case NE:   ccode = "nz";  break;
368*c87b03e5Sespie     case GE:   ccode = "ge";  break;
369*c87b03e5Sespie     case LT:   ccode = "lt";  break;
370*c87b03e5Sespie     case GEU:  ccode = "nc";  break;
371*c87b03e5Sespie     case LTU:  ccode = "c";   break;
372*c87b03e5Sespie 
373*c87b03e5Sespie       /* The missing codes above should never be generated.  */
374*c87b03e5Sespie     default:
375*c87b03e5Sespie       abort ();
376*c87b03e5Sespie     }
377*c87b03e5Sespie 
378*c87b03e5Sespie   switch (code)
379*c87b03e5Sespie     {
380*c87b03e5Sespie     case EQ: case NE:
381*c87b03e5Sespie       {
382*c87b03e5Sespie 	int regnum;
383*c87b03e5Sespie 
384*c87b03e5Sespie 	if (GET_CODE (XEXP (op, 0)) != REG)
385*c87b03e5Sespie 	  abort ();
386*c87b03e5Sespie 
387*c87b03e5Sespie 	regnum = REGNO (XEXP (op, 0));
388*c87b03e5Sespie 	sprintf (prevop, "or %s,%s", reg_names[regnum], reg_names[regnum+1]);
389*c87b03e5Sespie       }
390*c87b03e5Sespie       break;
391*c87b03e5Sespie 
392*c87b03e5Sespie     case GE: case LT: case GEU: case LTU:
393*c87b03e5Sespie       strcpy (prevop, "sbc %2,%3");
394*c87b03e5Sespie       break;
395*c87b03e5Sespie 
396*c87b03e5Sespie     default:
397*c87b03e5Sespie       abort ();
398*c87b03e5Sespie     }
399*c87b03e5Sespie 
400*c87b03e5Sespie   if (need_longbranch)
401*c87b03e5Sespie     template = "%s | b%s .+6 | jmpf %s";
402*c87b03e5Sespie   else
403*c87b03e5Sespie     template = "%s | b%s %s";
404*c87b03e5Sespie   sprintf (string, template, prevop, ccode, label);
405*c87b03e5Sespie 
406*c87b03e5Sespie   return string;
407*c87b03e5Sespie }
408*c87b03e5Sespie 
409*c87b03e5Sespie /* Many machines have some registers that cannot be copied directly to or from
410*c87b03e5Sespie    memory or even from other types of registers.  An example is the `MQ'
411*c87b03e5Sespie    register, which on most machines, can only be copied to or from general
412*c87b03e5Sespie    registers, but not memory.  Some machines allow copying all registers to and
413*c87b03e5Sespie    from memory, but require a scratch register for stores to some memory
414*c87b03e5Sespie    locations (e.g., those with symbolic address on the RT, and those with
415*c87b03e5Sespie    certain symbolic address on the SPARC when compiling PIC).  In some cases,
416*c87b03e5Sespie    both an intermediate and a scratch register are required.
417*c87b03e5Sespie 
418*c87b03e5Sespie    You should define these macros to indicate to the reload phase that it may
419*c87b03e5Sespie    need to allocate at least one register for a reload in addition to the
420*c87b03e5Sespie    register to contain the data.  Specifically, if copying X to a register
421*c87b03e5Sespie    CLASS in MODE requires an intermediate register, you should define
422*c87b03e5Sespie    `SECONDARY_INPUT_RELOAD_CLASS' to return the largest register class all of
423*c87b03e5Sespie    whose registers can be used as intermediate registers or scratch registers.
424*c87b03e5Sespie 
425*c87b03e5Sespie    If copying a register CLASS in MODE to X requires an intermediate or scratch
426*c87b03e5Sespie    register, `SECONDARY_OUTPUT_RELOAD_CLASS' should be defined to return the
427*c87b03e5Sespie    largest register class required.  If the requirements for input and output
428*c87b03e5Sespie    reloads are the same, the macro `SECONDARY_RELOAD_CLASS' should be used
429*c87b03e5Sespie    instead of defining both macros identically.
430*c87b03e5Sespie 
431*c87b03e5Sespie    The values returned by these macros are often `GENERAL_REGS'.  Return
432*c87b03e5Sespie    `NO_REGS' if no spare register is needed; i.e., if X can be directly copied
433*c87b03e5Sespie    to or from a register of CLASS in MODE without requiring a scratch register.
434*c87b03e5Sespie    Do not define this macro if it would always return `NO_REGS'.
435*c87b03e5Sespie 
436*c87b03e5Sespie    If a scratch register is required (either with or without an intermediate
437*c87b03e5Sespie    register), you should define patterns for `reload_inM' or `reload_outM', as
438*c87b03e5Sespie    required..  These patterns, which will normally be implemented with a
439*c87b03e5Sespie    `define_expand', should be similar to the `movM' patterns, except that
440*c87b03e5Sespie    operand 2 is the scratch register.
441*c87b03e5Sespie 
442*c87b03e5Sespie    Define constraints for the reload register and scratch register that contain
443*c87b03e5Sespie    a single register class.  If the original reload register (whose class is
444*c87b03e5Sespie    CLASS) can meet the constraint given in the pattern, the value returned by
445*c87b03e5Sespie    these macros is used for the class of the scratch register.  Otherwise, two
446*c87b03e5Sespie    additional reload registers are required.  Their classes are obtained from
447*c87b03e5Sespie    the constraints in the insn pattern.
448*c87b03e5Sespie 
449*c87b03e5Sespie    X might be a pseudo-register or a `subreg' of a pseudo-register, which could
450*c87b03e5Sespie    either be in a hard register or in memory.  Use `true_regnum' to find out;
451*c87b03e5Sespie    it will return -1 if the pseudo is in memory and the hard register number if
452*c87b03e5Sespie    it is in a register.
453*c87b03e5Sespie 
454*c87b03e5Sespie    These macros should not be used in the case where a particular class of
455*c87b03e5Sespie    registers can only be copied to memory and not to another class of
456*c87b03e5Sespie    registers.  In that case, secondary reload registers are not needed and
457*c87b03e5Sespie    would not be helpful.  Instead, a stack location must be used to perform the
458*c87b03e5Sespie    copy and the `movM' pattern should use memory as an intermediate storage.
459*c87b03e5Sespie    This case often occurs between floating-point and general registers.  */
460*c87b03e5Sespie 
461*c87b03e5Sespie enum reg_class
xstormy16_secondary_reload_class(class,mode,x)462*c87b03e5Sespie xstormy16_secondary_reload_class (class, mode, x)
463*c87b03e5Sespie      enum reg_class class;
464*c87b03e5Sespie      enum machine_mode mode;
465*c87b03e5Sespie      rtx x;
466*c87b03e5Sespie {
467*c87b03e5Sespie   /* This chip has the interesting property that only the first eight
468*c87b03e5Sespie      registers can be moved to/from memory.  */
469*c87b03e5Sespie   if ((GET_CODE (x) == MEM
470*c87b03e5Sespie        || ((GET_CODE (x) == SUBREG || GET_CODE (x) == REG)
471*c87b03e5Sespie 	   && (true_regnum (x) == -1
472*c87b03e5Sespie 	       || true_regnum (x) >= FIRST_PSEUDO_REGISTER)))
473*c87b03e5Sespie       && ! reg_class_subset_p (class, EIGHT_REGS))
474*c87b03e5Sespie     return EIGHT_REGS;
475*c87b03e5Sespie 
476*c87b03e5Sespie   /* When reloading a PLUS, the carry register will be required
477*c87b03e5Sespie      unless the inc or dec instructions can be used.  */
478*c87b03e5Sespie   if (xstormy16_carry_plus_operand (x, mode))
479*c87b03e5Sespie     return CARRY_REGS;
480*c87b03e5Sespie 
481*c87b03e5Sespie   return NO_REGS;
482*c87b03e5Sespie }
483*c87b03e5Sespie 
484*c87b03e5Sespie /* Recognize a PLUS that needs the carry register.  */
485*c87b03e5Sespie int
xstormy16_carry_plus_operand(x,mode)486*c87b03e5Sespie xstormy16_carry_plus_operand (x, mode)
487*c87b03e5Sespie      rtx x;
488*c87b03e5Sespie      enum machine_mode mode ATTRIBUTE_UNUSED;
489*c87b03e5Sespie {
490*c87b03e5Sespie   return (GET_CODE (x) == PLUS
491*c87b03e5Sespie 	  && GET_CODE (XEXP (x, 1)) == CONST_INT
492*c87b03e5Sespie 	  && (INTVAL (XEXP (x, 1)) < -4 || INTVAL (XEXP (x, 1)) > 4));
493*c87b03e5Sespie }
494*c87b03e5Sespie 
495*c87b03e5Sespie 
496*c87b03e5Sespie enum reg_class
xstormy16_preferred_reload_class(x,class)497*c87b03e5Sespie xstormy16_preferred_reload_class (x, class)
498*c87b03e5Sespie      enum reg_class class;
499*c87b03e5Sespie      rtx x;
500*c87b03e5Sespie {
501*c87b03e5Sespie   if (class == GENERAL_REGS
502*c87b03e5Sespie       && GET_CODE (x) == MEM)
503*c87b03e5Sespie     return EIGHT_REGS;
504*c87b03e5Sespie 
505*c87b03e5Sespie   return class;
506*c87b03e5Sespie }
507*c87b03e5Sespie 
508*c87b03e5Sespie #define LEGITIMATE_ADDRESS_INTEGER_P(X, OFFSET)				\
509*c87b03e5Sespie  (GET_CODE (X) == CONST_INT						\
510*c87b03e5Sespie   && (unsigned HOST_WIDE_INT) (INTVAL (X) + (OFFSET) + 2048) < 4096)
511*c87b03e5Sespie 
512*c87b03e5Sespie #define LEGITIMATE_ADDRESS_CONST_INT_P(X, OFFSET)			 \
513*c87b03e5Sespie  (GET_CODE (X) == CONST_INT						 \
514*c87b03e5Sespie   && INTVAL (X) + (OFFSET) >= 0						 \
515*c87b03e5Sespie   && INTVAL (X) + (OFFSET) < 0x8000					 \
516*c87b03e5Sespie   && (INTVAL (X) + (OFFSET) < 0x100 || INTVAL (X) + (OFFSET) >= 0x7F00))
517*c87b03e5Sespie 
518*c87b03e5Sespie int
xstormy16_legitimate_address_p(mode,x,strict)519*c87b03e5Sespie xstormy16_legitimate_address_p (mode, x, strict)
520*c87b03e5Sespie      enum machine_mode mode ATTRIBUTE_UNUSED;
521*c87b03e5Sespie      rtx x;
522*c87b03e5Sespie      int strict;
523*c87b03e5Sespie {
524*c87b03e5Sespie   if (LEGITIMATE_ADDRESS_CONST_INT_P (x, 0))
525*c87b03e5Sespie     return 1;
526*c87b03e5Sespie 
527*c87b03e5Sespie   if (GET_CODE (x) == PLUS
528*c87b03e5Sespie       && LEGITIMATE_ADDRESS_INTEGER_P (XEXP (x, 1), 0))
529*c87b03e5Sespie     x = XEXP (x, 0);
530*c87b03e5Sespie 
531*c87b03e5Sespie   if (GET_CODE (x) == POST_INC
532*c87b03e5Sespie       || GET_CODE (x) == PRE_DEC)
533*c87b03e5Sespie     x = XEXP (x, 0);
534*c87b03e5Sespie 
535*c87b03e5Sespie   if (GET_CODE (x) == REG && REGNO_OK_FOR_BASE_P (REGNO (x))
536*c87b03e5Sespie       && (! strict || REGNO (x) < FIRST_PSEUDO_REGISTER))
537*c87b03e5Sespie     return 1;
538*c87b03e5Sespie 
539*c87b03e5Sespie   return 0;
540*c87b03e5Sespie }
541*c87b03e5Sespie 
542*c87b03e5Sespie /* Return nonzero if memory address X (an RTX) can have different
543*c87b03e5Sespie    meanings depending on the machine mode of the memory reference it
544*c87b03e5Sespie    is used for or if the address is valid for some modes but not
545*c87b03e5Sespie    others.
546*c87b03e5Sespie 
547*c87b03e5Sespie    Autoincrement and autodecrement addresses typically have mode-dependent
548*c87b03e5Sespie    effects because the amount of the increment or decrement is the size of the
549*c87b03e5Sespie    operand being addressed.  Some machines have other mode-dependent addresses.
550*c87b03e5Sespie    Many RISC machines have no mode-dependent addresses.
551*c87b03e5Sespie 
552*c87b03e5Sespie    You may assume that ADDR is a valid address for the machine.
553*c87b03e5Sespie 
554*c87b03e5Sespie    On this chip, this is true if the address is valid with an offset
555*c87b03e5Sespie    of 0 but not of 6, because in that case it cannot be used as an
556*c87b03e5Sespie    address for DImode or DFmode, or if the address is a post-increment
557*c87b03e5Sespie    or pre-decrement address.  */
558*c87b03e5Sespie int
xstormy16_mode_dependent_address_p(x)559*c87b03e5Sespie xstormy16_mode_dependent_address_p (x)
560*c87b03e5Sespie      rtx x;
561*c87b03e5Sespie {
562*c87b03e5Sespie   if (LEGITIMATE_ADDRESS_CONST_INT_P (x, 0)
563*c87b03e5Sespie       && ! LEGITIMATE_ADDRESS_CONST_INT_P (x, 6))
564*c87b03e5Sespie     return 1;
565*c87b03e5Sespie 
566*c87b03e5Sespie   if (GET_CODE (x) == PLUS
567*c87b03e5Sespie       && LEGITIMATE_ADDRESS_INTEGER_P (XEXP (x, 1), 0)
568*c87b03e5Sespie       && ! LEGITIMATE_ADDRESS_INTEGER_P (XEXP (x, 1), 6))
569*c87b03e5Sespie     return 1;
570*c87b03e5Sespie 
571*c87b03e5Sespie   if (GET_CODE (x) == PLUS)
572*c87b03e5Sespie     x = XEXP (x, 0);
573*c87b03e5Sespie 
574*c87b03e5Sespie   if (GET_CODE (x) == POST_INC
575*c87b03e5Sespie       || GET_CODE (x) == PRE_DEC)
576*c87b03e5Sespie     return 1;
577*c87b03e5Sespie 
578*c87b03e5Sespie   return 0;
579*c87b03e5Sespie }
580*c87b03e5Sespie 
581*c87b03e5Sespie /* A C expression that defines the optional machine-dependent constraint
582*c87b03e5Sespie    letters (`Q', `R', `S', `T', `U') that can be used to segregate specific
583*c87b03e5Sespie    types of operands, usually memory references, for the target machine.
584*c87b03e5Sespie    Normally this macro will not be defined.  If it is required for a particular
585*c87b03e5Sespie    target machine, it should return 1 if VALUE corresponds to the operand type
586*c87b03e5Sespie    represented by the constraint letter C.  If C is not defined as an extra
587*c87b03e5Sespie    constraint, the value returned should be 0 regardless of VALUE.  */
588*c87b03e5Sespie int
xstormy16_extra_constraint_p(x,c)589*c87b03e5Sespie xstormy16_extra_constraint_p (x, c)
590*c87b03e5Sespie      rtx x;
591*c87b03e5Sespie      int c;
592*c87b03e5Sespie {
593*c87b03e5Sespie   switch (c)
594*c87b03e5Sespie     {
595*c87b03e5Sespie       /* 'Q' is for pushes.  */
596*c87b03e5Sespie     case 'Q':
597*c87b03e5Sespie       return (GET_CODE (x) == MEM
598*c87b03e5Sespie 	      && GET_CODE (XEXP (x, 0)) == POST_INC
599*c87b03e5Sespie 	      && XEXP (XEXP (x, 0), 0) == stack_pointer_rtx);
600*c87b03e5Sespie 
601*c87b03e5Sespie       /* 'R' is for pops.  */
602*c87b03e5Sespie     case 'R':
603*c87b03e5Sespie       return (GET_CODE (x) == MEM
604*c87b03e5Sespie 	      && GET_CODE (XEXP (x, 0)) == PRE_DEC
605*c87b03e5Sespie 	      && XEXP (XEXP (x, 0), 0) == stack_pointer_rtx);
606*c87b03e5Sespie 
607*c87b03e5Sespie       /* 'S' is for immediate memory addresses.  */
608*c87b03e5Sespie     case 'S':
609*c87b03e5Sespie       return (GET_CODE (x) == MEM
610*c87b03e5Sespie 	      && GET_CODE (XEXP (x, 0)) == CONST_INT
611*c87b03e5Sespie 	      && xstormy16_legitimate_address_p (VOIDmode, XEXP (x, 0), 0));
612*c87b03e5Sespie 
613*c87b03e5Sespie       /* 'T' is for Rx.  */
614*c87b03e5Sespie     case 'T':
615*c87b03e5Sespie       /* Not implemented yet.  */
616*c87b03e5Sespie       return 0;
617*c87b03e5Sespie 
618*c87b03e5Sespie       /* 'U' is for CONST_INT values not between 2 and 15 inclusive,
619*c87b03e5Sespie 	 for allocating a scratch register for 32-bit shifts.  */
620*c87b03e5Sespie     case 'U':
621*c87b03e5Sespie       return (GET_CODE (x) == CONST_INT
622*c87b03e5Sespie 	      && (INTVAL (x) < 2 || INTVAL (x) > 15));
623*c87b03e5Sespie 
624*c87b03e5Sespie     default:
625*c87b03e5Sespie       return 0;
626*c87b03e5Sespie     }
627*c87b03e5Sespie }
628*c87b03e5Sespie 
629*c87b03e5Sespie int
short_memory_operand(x,mode)630*c87b03e5Sespie short_memory_operand (x, mode)
631*c87b03e5Sespie      rtx x;
632*c87b03e5Sespie      enum machine_mode mode;
633*c87b03e5Sespie {
634*c87b03e5Sespie   if (! memory_operand (x, mode))
635*c87b03e5Sespie     return 0;
636*c87b03e5Sespie   return (GET_CODE (XEXP (x, 0)) != PLUS);
637*c87b03e5Sespie }
638*c87b03e5Sespie 
639*c87b03e5Sespie int
nonimmediate_nonstack_operand(op,mode)640*c87b03e5Sespie nonimmediate_nonstack_operand (op, mode)
641*c87b03e5Sespie      rtx op;
642*c87b03e5Sespie      enum machine_mode mode;
643*c87b03e5Sespie {
644*c87b03e5Sespie   /* 'Q' is for pushes, 'R' for pops.  */
645*c87b03e5Sespie   return (nonimmediate_operand (op, mode)
646*c87b03e5Sespie 	  && ! xstormy16_extra_constraint_p (op, 'Q')
647*c87b03e5Sespie 	  && ! xstormy16_extra_constraint_p (op, 'R'));
648*c87b03e5Sespie }
649*c87b03e5Sespie 
650*c87b03e5Sespie /* Splitter for the 'move' patterns, for modes not directly implemeted
651*c87b03e5Sespie    by hardware.  Emit insns to copy a value of mode MODE from SRC to
652*c87b03e5Sespie    DEST.
653*c87b03e5Sespie 
654*c87b03e5Sespie    This function is only called when reload_completed.
655*c87b03e5Sespie    */
656*c87b03e5Sespie 
657*c87b03e5Sespie void
xstormy16_split_move(mode,dest,src)658*c87b03e5Sespie xstormy16_split_move (mode, dest, src)
659*c87b03e5Sespie      enum machine_mode mode;
660*c87b03e5Sespie      rtx dest;
661*c87b03e5Sespie      rtx src;
662*c87b03e5Sespie {
663*c87b03e5Sespie   int num_words = GET_MODE_BITSIZE (mode) / BITS_PER_WORD;
664*c87b03e5Sespie   int direction, end, i;
665*c87b03e5Sespie   int src_modifies = 0;
666*c87b03e5Sespie   int dest_modifies = 0;
667*c87b03e5Sespie   int src_volatile = 0;
668*c87b03e5Sespie   int dest_volatile = 0;
669*c87b03e5Sespie   rtx mem_operand;
670*c87b03e5Sespie   rtx auto_inc_reg_rtx = NULL_RTX;
671*c87b03e5Sespie 
672*c87b03e5Sespie   /* Check initial conditions.  */
673*c87b03e5Sespie   if (! reload_completed
674*c87b03e5Sespie       || mode == QImode || mode == HImode
675*c87b03e5Sespie       || ! nonimmediate_operand (dest, mode)
676*c87b03e5Sespie       || ! general_operand (src, mode))
677*c87b03e5Sespie     abort ();
678*c87b03e5Sespie 
679*c87b03e5Sespie   /* This case is not supported below, and shouldn't be generated.  */
680*c87b03e5Sespie   if (GET_CODE (dest) == MEM
681*c87b03e5Sespie       && GET_CODE (src) == MEM)
682*c87b03e5Sespie     abort ();
683*c87b03e5Sespie 
684*c87b03e5Sespie   /* This case is very very bad after reload, so trap it now.  */
685*c87b03e5Sespie   if (GET_CODE (dest) == SUBREG
686*c87b03e5Sespie       || GET_CODE (src) == SUBREG)
687*c87b03e5Sespie     abort ();
688*c87b03e5Sespie 
689*c87b03e5Sespie   /* The general idea is to copy by words, offsetting the source and
690*c87b03e5Sespie      destination.  Normally the least-significant word will be copied
691*c87b03e5Sespie      first, but for pre-dec operations it's better to copy the
692*c87b03e5Sespie      most-significant word first.  Only one operand can be a pre-dec
693*c87b03e5Sespie      or post-inc operand.
694*c87b03e5Sespie 
695*c87b03e5Sespie      It's also possible that the copy overlaps so that the direction
696*c87b03e5Sespie      must be reversed.  */
697*c87b03e5Sespie   direction = 1;
698*c87b03e5Sespie 
699*c87b03e5Sespie   if (GET_CODE (dest) == MEM)
700*c87b03e5Sespie     {
701*c87b03e5Sespie       mem_operand = XEXP (dest, 0);
702*c87b03e5Sespie       dest_modifies = side_effects_p (mem_operand);
703*c87b03e5Sespie       if (auto_inc_p (mem_operand))
704*c87b03e5Sespie         auto_inc_reg_rtx = XEXP (mem_operand, 0);
705*c87b03e5Sespie       dest_volatile = MEM_VOLATILE_P (dest);
706*c87b03e5Sespie       if (dest_volatile)
707*c87b03e5Sespie 	{
708*c87b03e5Sespie 	  dest = copy_rtx (dest);
709*c87b03e5Sespie 	  MEM_VOLATILE_P (dest) = 0;
710*c87b03e5Sespie 	}
711*c87b03e5Sespie     }
712*c87b03e5Sespie   else if (GET_CODE (src) == MEM)
713*c87b03e5Sespie     {
714*c87b03e5Sespie       mem_operand = XEXP (src, 0);
715*c87b03e5Sespie       src_modifies = side_effects_p (mem_operand);
716*c87b03e5Sespie       if (auto_inc_p (mem_operand))
717*c87b03e5Sespie         auto_inc_reg_rtx = XEXP (mem_operand, 0);
718*c87b03e5Sespie       src_volatile = MEM_VOLATILE_P (src);
719*c87b03e5Sespie       if (src_volatile)
720*c87b03e5Sespie 	{
721*c87b03e5Sespie 	  src = copy_rtx (src);
722*c87b03e5Sespie 	  MEM_VOLATILE_P (src) = 0;
723*c87b03e5Sespie 	}
724*c87b03e5Sespie     }
725*c87b03e5Sespie   else
726*c87b03e5Sespie     mem_operand = NULL_RTX;
727*c87b03e5Sespie 
728*c87b03e5Sespie   if (mem_operand == NULL_RTX)
729*c87b03e5Sespie     {
730*c87b03e5Sespie       if (GET_CODE (src) == REG
731*c87b03e5Sespie 	  && GET_CODE (dest) == REG
732*c87b03e5Sespie 	  && reg_overlap_mentioned_p (dest, src)
733*c87b03e5Sespie 	  && REGNO (dest) > REGNO (src))
734*c87b03e5Sespie 	direction = -1;
735*c87b03e5Sespie     }
736*c87b03e5Sespie   else if (GET_CODE (mem_operand) == PRE_DEC
737*c87b03e5Sespie       || (GET_CODE (mem_operand) == PLUS
738*c87b03e5Sespie 	  && GET_CODE (XEXP (mem_operand, 0)) == PRE_DEC))
739*c87b03e5Sespie     direction = -1;
740*c87b03e5Sespie   else if (GET_CODE (src) == MEM
741*c87b03e5Sespie 	   && reg_overlap_mentioned_p (dest, src))
742*c87b03e5Sespie     {
743*c87b03e5Sespie       int regno;
744*c87b03e5Sespie       if (GET_CODE (dest) != REG)
745*c87b03e5Sespie 	abort ();
746*c87b03e5Sespie       regno = REGNO (dest);
747*c87b03e5Sespie 
748*c87b03e5Sespie       if (! refers_to_regno_p (regno, regno + num_words, mem_operand, 0))
749*c87b03e5Sespie 	abort ();
750*c87b03e5Sespie 
751*c87b03e5Sespie       if (refers_to_regno_p (regno, regno + 1, mem_operand, 0))
752*c87b03e5Sespie 	direction = -1;
753*c87b03e5Sespie       else if (refers_to_regno_p (regno + num_words - 1, regno + num_words,
754*c87b03e5Sespie 				  mem_operand, 0))
755*c87b03e5Sespie 	direction = 1;
756*c87b03e5Sespie       else
757*c87b03e5Sespie 	/* This means something like
758*c87b03e5Sespie 	   (set (reg:DI r0) (mem:DI (reg:HI r1)))
759*c87b03e5Sespie 	   which we'd need to support by doing the set of the second word
760*c87b03e5Sespie 	   last.  */
761*c87b03e5Sespie 	abort ();
762*c87b03e5Sespie     }
763*c87b03e5Sespie 
764*c87b03e5Sespie   end = direction < 0 ? -1 : num_words;
765*c87b03e5Sespie   for (i = direction < 0 ? num_words - 1 : 0; i != end; i += direction)
766*c87b03e5Sespie     {
767*c87b03e5Sespie       rtx w_src, w_dest, insn;
768*c87b03e5Sespie 
769*c87b03e5Sespie       if (src_modifies)
770*c87b03e5Sespie 	w_src = gen_rtx_MEM (word_mode, mem_operand);
771*c87b03e5Sespie       else
772*c87b03e5Sespie 	w_src = simplify_gen_subreg (word_mode, src, mode, i * UNITS_PER_WORD);
773*c87b03e5Sespie       if (src_volatile)
774*c87b03e5Sespie 	MEM_VOLATILE_P (w_src) = 1;
775*c87b03e5Sespie       if (dest_modifies)
776*c87b03e5Sespie 	w_dest = gen_rtx_MEM (word_mode, mem_operand);
777*c87b03e5Sespie       else
778*c87b03e5Sespie 	w_dest = simplify_gen_subreg (word_mode, dest, mode,
779*c87b03e5Sespie 				      i * UNITS_PER_WORD);
780*c87b03e5Sespie       if (dest_volatile)
781*c87b03e5Sespie 	MEM_VOLATILE_P (w_dest) = 1;
782*c87b03e5Sespie 
783*c87b03e5Sespie       /* The simplify_subreg calls must always be able to simplify.  */
784*c87b03e5Sespie       if (GET_CODE (w_src) == SUBREG
785*c87b03e5Sespie 	  || GET_CODE (w_dest) == SUBREG)
786*c87b03e5Sespie 	abort ();
787*c87b03e5Sespie 
788*c87b03e5Sespie       insn = emit_insn (gen_rtx_SET (VOIDmode, w_dest, w_src));
789*c87b03e5Sespie       if (auto_inc_reg_rtx)
790*c87b03e5Sespie         REG_NOTES (insn) = alloc_EXPR_LIST (REG_INC,
791*c87b03e5Sespie                                             auto_inc_reg_rtx,
792*c87b03e5Sespie 					    REG_NOTES (insn));
793*c87b03e5Sespie     }
794*c87b03e5Sespie }
795*c87b03e5Sespie 
796*c87b03e5Sespie /* Expander for the 'move' patterns.  Emit insns to copy a value of
797*c87b03e5Sespie    mode MODE from SRC to DEST.  */
798*c87b03e5Sespie 
799*c87b03e5Sespie void
xstormy16_expand_move(mode,dest,src)800*c87b03e5Sespie xstormy16_expand_move (mode, dest, src)
801*c87b03e5Sespie      enum machine_mode mode;
802*c87b03e5Sespie      rtx dest;
803*c87b03e5Sespie      rtx src;
804*c87b03e5Sespie {
805*c87b03e5Sespie   /* There are only limited immediate-to-memory move instructions.  */
806*c87b03e5Sespie   if (! reload_in_progress
807*c87b03e5Sespie       && ! reload_completed
808*c87b03e5Sespie       && GET_CODE (dest) == MEM
809*c87b03e5Sespie       && (GET_CODE (XEXP (dest, 0)) != CONST_INT
810*c87b03e5Sespie 	  || ! xstormy16_legitimate_address_p (mode, XEXP (dest, 0), 0))
811*c87b03e5Sespie       && GET_CODE (src) != REG
812*c87b03e5Sespie       && GET_CODE (src) != SUBREG)
813*c87b03e5Sespie     src = copy_to_mode_reg (mode, src);
814*c87b03e5Sespie 
815*c87b03e5Sespie   /* Don't emit something we would immediately split.  */
816*c87b03e5Sespie   if (reload_completed
817*c87b03e5Sespie       && mode != HImode && mode != QImode)
818*c87b03e5Sespie     {
819*c87b03e5Sespie       xstormy16_split_move (mode, dest, src);
820*c87b03e5Sespie       return;
821*c87b03e5Sespie     }
822*c87b03e5Sespie 
823*c87b03e5Sespie   emit_insn (gen_rtx_SET (VOIDmode, dest, src));
824*c87b03e5Sespie }
825*c87b03e5Sespie 
826*c87b03e5Sespie 
827*c87b03e5Sespie /* Stack Layout:
828*c87b03e5Sespie 
829*c87b03e5Sespie    The stack is laid out as follows:
830*c87b03e5Sespie 
831*c87b03e5Sespie SP->
832*c87b03e5Sespie FP->	Local variables
833*c87b03e5Sespie 	Register save area (up to 4 words)
834*c87b03e5Sespie 	Argument register save area for stdarg (NUM_ARGUMENT_REGISTERS words)
835*c87b03e5Sespie 
836*c87b03e5Sespie AP->	Return address (two words)
837*c87b03e5Sespie 	9th procedure parameter word
838*c87b03e5Sespie 	10th procedure parameter word
839*c87b03e5Sespie 	...
840*c87b03e5Sespie 	last procedure parameter word
841*c87b03e5Sespie 
842*c87b03e5Sespie   The frame pointer location is tuned to make it most likely that all
843*c87b03e5Sespie   parameters and local variables can be accessed using a load-indexed
844*c87b03e5Sespie   instruction.  */
845*c87b03e5Sespie 
846*c87b03e5Sespie /* A structure to describe the layout.  */
847*c87b03e5Sespie struct xstormy16_stack_layout
848*c87b03e5Sespie {
849*c87b03e5Sespie   /* Size of the topmost three items on the stack.  */
850*c87b03e5Sespie   int locals_size;
851*c87b03e5Sespie   int register_save_size;
852*c87b03e5Sespie   int stdarg_save_size;
853*c87b03e5Sespie   /* Sum of the above items.  */
854*c87b03e5Sespie   int frame_size;
855*c87b03e5Sespie   /* Various offsets.  */
856*c87b03e5Sespie   int first_local_minus_ap;
857*c87b03e5Sespie   int sp_minus_fp;
858*c87b03e5Sespie   int fp_minus_ap;
859*c87b03e5Sespie };
860*c87b03e5Sespie 
861*c87b03e5Sespie /* Does REGNO need to be saved?  */
862*c87b03e5Sespie #define REG_NEEDS_SAVE(REGNUM, IFUN)					\
863*c87b03e5Sespie   ((regs_ever_live[REGNUM] && ! call_used_regs[REGNUM])			\
864*c87b03e5Sespie    || (IFUN && ! fixed_regs[REGNUM] && call_used_regs[REGNUM]		\
865*c87b03e5Sespie        && (regs_ever_live[REGNUM] || ! current_function_is_leaf)))
866*c87b03e5Sespie 
867*c87b03e5Sespie /* Compute the stack layout.  */
868*c87b03e5Sespie struct xstormy16_stack_layout
xstormy16_compute_stack_layout()869*c87b03e5Sespie xstormy16_compute_stack_layout ()
870*c87b03e5Sespie {
871*c87b03e5Sespie   struct xstormy16_stack_layout layout;
872*c87b03e5Sespie   int regno;
873*c87b03e5Sespie   const int ifun = xstormy16_interrupt_function_p ();
874*c87b03e5Sespie 
875*c87b03e5Sespie   layout.locals_size = get_frame_size ();
876*c87b03e5Sespie 
877*c87b03e5Sespie   layout.register_save_size = 0;
878*c87b03e5Sespie   for (regno = 0; regno < FIRST_PSEUDO_REGISTER; regno++)
879*c87b03e5Sespie     if (REG_NEEDS_SAVE (regno, ifun))
880*c87b03e5Sespie       layout.register_save_size += UNITS_PER_WORD;
881*c87b03e5Sespie 
882*c87b03e5Sespie   if (current_function_stdarg)
883*c87b03e5Sespie     layout.stdarg_save_size = NUM_ARGUMENT_REGISTERS * UNITS_PER_WORD;
884*c87b03e5Sespie   else
885*c87b03e5Sespie     layout.stdarg_save_size = 0;
886*c87b03e5Sespie 
887*c87b03e5Sespie   layout.frame_size = (layout.locals_size
888*c87b03e5Sespie 		       + layout.register_save_size
889*c87b03e5Sespie 		       + layout.stdarg_save_size);
890*c87b03e5Sespie 
891*c87b03e5Sespie   if (current_function_args_size <= 2048 && current_function_args_size != -1)
892*c87b03e5Sespie     {
893*c87b03e5Sespie       if (layout.frame_size + INCOMING_FRAME_SP_OFFSET
894*c87b03e5Sespie 	  + current_function_args_size <= 2048)
895*c87b03e5Sespie 	layout.fp_minus_ap = layout.frame_size + INCOMING_FRAME_SP_OFFSET;
896*c87b03e5Sespie       else
897*c87b03e5Sespie 	layout.fp_minus_ap = 2048 - current_function_args_size;
898*c87b03e5Sespie     }
899*c87b03e5Sespie   else
900*c87b03e5Sespie     layout.fp_minus_ap = (layout.stdarg_save_size
901*c87b03e5Sespie 			  + layout.register_save_size
902*c87b03e5Sespie 			  + INCOMING_FRAME_SP_OFFSET);
903*c87b03e5Sespie   layout.sp_minus_fp = (layout.frame_size + INCOMING_FRAME_SP_OFFSET
904*c87b03e5Sespie 			- layout.fp_minus_ap);
905*c87b03e5Sespie   layout.first_local_minus_ap = layout.sp_minus_fp - layout.locals_size;
906*c87b03e5Sespie   return layout;
907*c87b03e5Sespie }
908*c87b03e5Sespie 
909*c87b03e5Sespie /* Determine how all the special registers get eliminated.  */
910*c87b03e5Sespie int
xstormy16_initial_elimination_offset(from,to)911*c87b03e5Sespie xstormy16_initial_elimination_offset (from, to)
912*c87b03e5Sespie      int from, to;
913*c87b03e5Sespie {
914*c87b03e5Sespie   struct xstormy16_stack_layout layout;
915*c87b03e5Sespie   int result;
916*c87b03e5Sespie 
917*c87b03e5Sespie   layout = xstormy16_compute_stack_layout ();
918*c87b03e5Sespie 
919*c87b03e5Sespie   if (from == FRAME_POINTER_REGNUM && to == HARD_FRAME_POINTER_REGNUM)
920*c87b03e5Sespie     result = layout.sp_minus_fp - layout.locals_size;
921*c87b03e5Sespie   else if (from == FRAME_POINTER_REGNUM && to == STACK_POINTER_REGNUM)
922*c87b03e5Sespie     result = -layout.locals_size;
923*c87b03e5Sespie   else if (from == ARG_POINTER_REGNUM && to == HARD_FRAME_POINTER_REGNUM)
924*c87b03e5Sespie     result = -layout.fp_minus_ap;
925*c87b03e5Sespie   else if (from == ARG_POINTER_REGNUM && to == STACK_POINTER_REGNUM)
926*c87b03e5Sespie     result = -(layout.sp_minus_fp + layout.fp_minus_ap);
927*c87b03e5Sespie   else
928*c87b03e5Sespie     abort ();
929*c87b03e5Sespie 
930*c87b03e5Sespie   return result;
931*c87b03e5Sespie }
932*c87b03e5Sespie 
933*c87b03e5Sespie static rtx
emit_addhi3_postreload(dest,src0,src1)934*c87b03e5Sespie emit_addhi3_postreload (dest, src0, src1)
935*c87b03e5Sespie      rtx dest;
936*c87b03e5Sespie      rtx src0;
937*c87b03e5Sespie      rtx src1;
938*c87b03e5Sespie {
939*c87b03e5Sespie   rtx set, clobber, insn;
940*c87b03e5Sespie 
941*c87b03e5Sespie   set = gen_rtx_SET (VOIDmode, dest, gen_rtx_PLUS (HImode, src0, src1));
942*c87b03e5Sespie   clobber = gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (BImode, 16));
943*c87b03e5Sespie   insn = emit_insn (gen_rtx_PARALLEL (VOIDmode, gen_rtvec (2, set, clobber)));
944*c87b03e5Sespie   return insn;
945*c87b03e5Sespie }
946*c87b03e5Sespie 
947*c87b03e5Sespie /* Called after register allocation to add any instructions needed for
948*c87b03e5Sespie    the prologue.  Using a prologue insn is favored compared to putting
949*c87b03e5Sespie    all of the instructions in the TARGET_ASM_FUNCTION_PROLOGUE macro,
950*c87b03e5Sespie    since it allows the scheduler to intermix instructions with the
951*c87b03e5Sespie    saves of the caller saved registers.  In some cases, it might be
952*c87b03e5Sespie    necessary to emit a barrier instruction as the last insn to prevent
953*c87b03e5Sespie    such scheduling.
954*c87b03e5Sespie 
955*c87b03e5Sespie    Also any insns generated here should have RTX_FRAME_RELATED_P(insn) = 1
956*c87b03e5Sespie    so that the debug info generation code can handle them properly.  */
957*c87b03e5Sespie void
xstormy16_expand_prologue()958*c87b03e5Sespie xstormy16_expand_prologue ()
959*c87b03e5Sespie {
960*c87b03e5Sespie   struct xstormy16_stack_layout layout;
961*c87b03e5Sespie   int regno;
962*c87b03e5Sespie   rtx insn;
963*c87b03e5Sespie   rtx mem_push_rtx;
964*c87b03e5Sespie   rtx mem_fake_push_rtx;
965*c87b03e5Sespie   const int ifun = xstormy16_interrupt_function_p ();
966*c87b03e5Sespie 
967*c87b03e5Sespie   mem_push_rtx = gen_rtx_POST_INC (Pmode, stack_pointer_rtx);
968*c87b03e5Sespie   mem_push_rtx = gen_rtx_MEM (HImode, mem_push_rtx);
969*c87b03e5Sespie   mem_fake_push_rtx = gen_rtx_PRE_INC (Pmode, stack_pointer_rtx);
970*c87b03e5Sespie   mem_fake_push_rtx = gen_rtx_MEM (HImode, mem_fake_push_rtx);
971*c87b03e5Sespie 
972*c87b03e5Sespie   layout = xstormy16_compute_stack_layout ();
973*c87b03e5Sespie 
974*c87b03e5Sespie   /* Save the argument registers if necessary.  */
975*c87b03e5Sespie   if (layout.stdarg_save_size)
976*c87b03e5Sespie     for (regno = FIRST_ARGUMENT_REGISTER;
977*c87b03e5Sespie 	 regno < FIRST_ARGUMENT_REGISTER + NUM_ARGUMENT_REGISTERS;
978*c87b03e5Sespie 	 regno++)
979*c87b03e5Sespie       {
980*c87b03e5Sespie 	rtx reg = gen_rtx_REG (HImode, regno);
981*c87b03e5Sespie 	insn = emit_move_insn (mem_push_rtx, reg);
982*c87b03e5Sespie 	RTX_FRAME_RELATED_P (insn) = 1;
983*c87b03e5Sespie 	REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_FRAME_RELATED_EXPR,
984*c87b03e5Sespie 					      gen_rtx_SET (VOIDmode,
985*c87b03e5Sespie 							   mem_fake_push_rtx,
986*c87b03e5Sespie 							   reg),
987*c87b03e5Sespie 					      REG_NOTES (insn));
988*c87b03e5Sespie       }
989*c87b03e5Sespie 
990*c87b03e5Sespie   /* Push each of the registers to save.  */
991*c87b03e5Sespie   for (regno = 0; regno < FIRST_PSEUDO_REGISTER; regno++)
992*c87b03e5Sespie     if (REG_NEEDS_SAVE (regno, ifun))
993*c87b03e5Sespie       {
994*c87b03e5Sespie 	rtx reg = gen_rtx_REG (HImode, regno);
995*c87b03e5Sespie 	insn = emit_move_insn (mem_push_rtx, reg);
996*c87b03e5Sespie 	RTX_FRAME_RELATED_P (insn) = 1;
997*c87b03e5Sespie 	REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_FRAME_RELATED_EXPR,
998*c87b03e5Sespie 					      gen_rtx_SET (VOIDmode,
999*c87b03e5Sespie 							   mem_fake_push_rtx,
1000*c87b03e5Sespie 							   reg),
1001*c87b03e5Sespie 					      REG_NOTES (insn));
1002*c87b03e5Sespie       }
1003*c87b03e5Sespie 
1004*c87b03e5Sespie   /* It's just possible that the SP here might be what we need for
1005*c87b03e5Sespie      the new FP...  */
1006*c87b03e5Sespie   if (frame_pointer_needed && layout.sp_minus_fp == layout.locals_size)
1007*c87b03e5Sespie     {
1008*c87b03e5Sespie       insn = emit_move_insn (hard_frame_pointer_rtx, stack_pointer_rtx);
1009*c87b03e5Sespie       RTX_FRAME_RELATED_P (insn) = 1;
1010*c87b03e5Sespie     }
1011*c87b03e5Sespie 
1012*c87b03e5Sespie   /* Allocate space for local variables.  */
1013*c87b03e5Sespie   if (layout.locals_size)
1014*c87b03e5Sespie     {
1015*c87b03e5Sespie       insn = emit_addhi3_postreload (stack_pointer_rtx, stack_pointer_rtx,
1016*c87b03e5Sespie 				     GEN_INT (layout.locals_size));
1017*c87b03e5Sespie       RTX_FRAME_RELATED_P (insn) = 1;
1018*c87b03e5Sespie     }
1019*c87b03e5Sespie 
1020*c87b03e5Sespie   /* Set up the frame pointer, if required.  */
1021*c87b03e5Sespie   if (frame_pointer_needed && layout.sp_minus_fp != layout.locals_size)
1022*c87b03e5Sespie     {
1023*c87b03e5Sespie       insn = emit_move_insn (hard_frame_pointer_rtx, stack_pointer_rtx);
1024*c87b03e5Sespie       RTX_FRAME_RELATED_P (insn) = 1;
1025*c87b03e5Sespie       if (layout.sp_minus_fp)
1026*c87b03e5Sespie 	{
1027*c87b03e5Sespie 	  insn = emit_addhi3_postreload (hard_frame_pointer_rtx,
1028*c87b03e5Sespie 					 hard_frame_pointer_rtx,
1029*c87b03e5Sespie 					 GEN_INT (-layout.sp_minus_fp));
1030*c87b03e5Sespie 	  RTX_FRAME_RELATED_P (insn) = 1;
1031*c87b03e5Sespie 	}
1032*c87b03e5Sespie     }
1033*c87b03e5Sespie }
1034*c87b03e5Sespie 
1035*c87b03e5Sespie /* Do we need an epilogue at all?  */
1036*c87b03e5Sespie int
direct_return()1037*c87b03e5Sespie direct_return ()
1038*c87b03e5Sespie {
1039*c87b03e5Sespie   return (reload_completed
1040*c87b03e5Sespie 	  && xstormy16_compute_stack_layout ().frame_size == 0);
1041*c87b03e5Sespie }
1042*c87b03e5Sespie 
1043*c87b03e5Sespie /* Called after register allocation to add any instructions needed for
1044*c87b03e5Sespie    the epilogue.  Using an epilogue insn is favored compared to putting
1045*c87b03e5Sespie    all of the instructions in the TARGET_ASM_FUNCTION_PROLOGUE macro,
1046*c87b03e5Sespie    since it allows the scheduler to intermix instructions with the
1047*c87b03e5Sespie    saves of the caller saved registers.  In some cases, it might be
1048*c87b03e5Sespie    necessary to emit a barrier instruction as the last insn to prevent
1049*c87b03e5Sespie    such scheduling.  */
1050*c87b03e5Sespie 
1051*c87b03e5Sespie void
xstormy16_expand_epilogue()1052*c87b03e5Sespie xstormy16_expand_epilogue ()
1053*c87b03e5Sespie {
1054*c87b03e5Sespie   struct xstormy16_stack_layout layout;
1055*c87b03e5Sespie   rtx mem_pop_rtx;
1056*c87b03e5Sespie   int regno;
1057*c87b03e5Sespie   const int ifun = xstormy16_interrupt_function_p ();
1058*c87b03e5Sespie 
1059*c87b03e5Sespie   mem_pop_rtx = gen_rtx_PRE_DEC (Pmode, stack_pointer_rtx);
1060*c87b03e5Sespie   mem_pop_rtx = gen_rtx_MEM (HImode, mem_pop_rtx);
1061*c87b03e5Sespie 
1062*c87b03e5Sespie   layout = xstormy16_compute_stack_layout ();
1063*c87b03e5Sespie 
1064*c87b03e5Sespie   /* Pop the stack for the locals.  */
1065*c87b03e5Sespie   if (layout.locals_size)
1066*c87b03e5Sespie     {
1067*c87b03e5Sespie       if (frame_pointer_needed && layout.sp_minus_fp == layout.locals_size)
1068*c87b03e5Sespie 	emit_move_insn (stack_pointer_rtx, hard_frame_pointer_rtx);
1069*c87b03e5Sespie       else
1070*c87b03e5Sespie 	emit_addhi3_postreload (stack_pointer_rtx, stack_pointer_rtx,
1071*c87b03e5Sespie 				GEN_INT (- layout.locals_size));
1072*c87b03e5Sespie     }
1073*c87b03e5Sespie 
1074*c87b03e5Sespie   /* Restore any call-saved registers.  */
1075*c87b03e5Sespie   for (regno = FIRST_PSEUDO_REGISTER - 1; regno >= 0; regno--)
1076*c87b03e5Sespie     if (REG_NEEDS_SAVE (regno, ifun))
1077*c87b03e5Sespie       emit_move_insn (gen_rtx_REG (HImode, regno), mem_pop_rtx);
1078*c87b03e5Sespie 
1079*c87b03e5Sespie   /* Pop the stack for the stdarg save area.  */
1080*c87b03e5Sespie   if (layout.stdarg_save_size)
1081*c87b03e5Sespie     emit_addhi3_postreload (stack_pointer_rtx, stack_pointer_rtx,
1082*c87b03e5Sespie 			    GEN_INT (- layout.stdarg_save_size));
1083*c87b03e5Sespie 
1084*c87b03e5Sespie   /* Return.  */
1085*c87b03e5Sespie   if (ifun)
1086*c87b03e5Sespie     emit_jump_insn (gen_return_internal_interrupt ());
1087*c87b03e5Sespie   else
1088*c87b03e5Sespie     emit_jump_insn (gen_return_internal ());
1089*c87b03e5Sespie }
1090*c87b03e5Sespie 
1091*c87b03e5Sespie int
xstormy16_epilogue_uses(regno)1092*c87b03e5Sespie xstormy16_epilogue_uses (regno)
1093*c87b03e5Sespie      int regno;
1094*c87b03e5Sespie {
1095*c87b03e5Sespie   if (reload_completed && call_used_regs[regno])
1096*c87b03e5Sespie     {
1097*c87b03e5Sespie       const int ifun = xstormy16_interrupt_function_p ();
1098*c87b03e5Sespie       return REG_NEEDS_SAVE (regno, ifun);
1099*c87b03e5Sespie     }
1100*c87b03e5Sespie   return 0;
1101*c87b03e5Sespie }
1102*c87b03e5Sespie 
1103*c87b03e5Sespie /* Return an updated summarizer variable CUM to advance past an
1104*c87b03e5Sespie    argument in the argument list.  The values MODE, TYPE and NAMED
1105*c87b03e5Sespie    describe that argument.  Once this is done, the variable CUM is
1106*c87b03e5Sespie    suitable for analyzing the *following* argument with
1107*c87b03e5Sespie    `FUNCTION_ARG', etc.
1108*c87b03e5Sespie 
1109*c87b03e5Sespie    This function need not do anything if the argument in question was
1110*c87b03e5Sespie    passed on the stack.  The compiler knows how to track the amount of
1111*c87b03e5Sespie    stack space used for arguments without any special help.  However,
1112*c87b03e5Sespie    it makes life easier for xstormy16_build_va_list if it does update
1113*c87b03e5Sespie    the word count.  */
1114*c87b03e5Sespie CUMULATIVE_ARGS
xstormy16_function_arg_advance(cum,mode,type,named)1115*c87b03e5Sespie xstormy16_function_arg_advance (cum, mode, type, named)
1116*c87b03e5Sespie      CUMULATIVE_ARGS cum;
1117*c87b03e5Sespie      enum machine_mode mode;
1118*c87b03e5Sespie      tree type;
1119*c87b03e5Sespie      int named ATTRIBUTE_UNUSED;
1120*c87b03e5Sespie {
1121*c87b03e5Sespie   /* If an argument would otherwise be passed partially in registers,
1122*c87b03e5Sespie      and partially on the stack, the whole of it is passed on the
1123*c87b03e5Sespie      stack.  */
1124*c87b03e5Sespie   if (cum < NUM_ARGUMENT_REGISTERS
1125*c87b03e5Sespie       && cum + XSTORMY16_WORD_SIZE (type, mode) > NUM_ARGUMENT_REGISTERS)
1126*c87b03e5Sespie     cum = NUM_ARGUMENT_REGISTERS;
1127*c87b03e5Sespie 
1128*c87b03e5Sespie   cum += XSTORMY16_WORD_SIZE (type, mode);
1129*c87b03e5Sespie 
1130*c87b03e5Sespie   return cum;
1131*c87b03e5Sespie }
1132*c87b03e5Sespie 
1133*c87b03e5Sespie /* Do any needed setup for a variadic function.  CUM has not been updated
1134*c87b03e5Sespie    for the last named argument which has type TYPE and mode MODE.  */
1135*c87b03e5Sespie void
xstormy16_setup_incoming_varargs(cum,int_mode,type,pretend_size)1136*c87b03e5Sespie xstormy16_setup_incoming_varargs (cum, int_mode, type, pretend_size)
1137*c87b03e5Sespie      CUMULATIVE_ARGS cum ATTRIBUTE_UNUSED;
1138*c87b03e5Sespie      int             int_mode ATTRIBUTE_UNUSED;
1139*c87b03e5Sespie      tree            type ATTRIBUTE_UNUSED;
1140*c87b03e5Sespie      int *           pretend_size ATTRIBUTE_UNUSED;
1141*c87b03e5Sespie {
1142*c87b03e5Sespie }
1143*c87b03e5Sespie 
1144*c87b03e5Sespie /* Build the va_list type.
1145*c87b03e5Sespie 
1146*c87b03e5Sespie    For this chip, va_list is a record containing a counter and a pointer.
1147*c87b03e5Sespie    The counter is of type 'int' and indicates how many bytes
1148*c87b03e5Sespie    have been used to date.  The pointer indicates the stack position
1149*c87b03e5Sespie    for arguments that have not been passed in registers.
1150*c87b03e5Sespie    To keep the layout nice, the pointer is first in the structure.  */
1151*c87b03e5Sespie 
1152*c87b03e5Sespie tree
xstormy16_build_va_list()1153*c87b03e5Sespie xstormy16_build_va_list ()
1154*c87b03e5Sespie {
1155*c87b03e5Sespie   tree f_1, f_2, record, type_decl;
1156*c87b03e5Sespie 
1157*c87b03e5Sespie   record = (*lang_hooks.types.make_type) (RECORD_TYPE);
1158*c87b03e5Sespie   type_decl = build_decl (TYPE_DECL, get_identifier ("__va_list_tag"), record);
1159*c87b03e5Sespie 
1160*c87b03e5Sespie   f_1 = build_decl (FIELD_DECL, get_identifier ("base"),
1161*c87b03e5Sespie 		      ptr_type_node);
1162*c87b03e5Sespie   f_2 = build_decl (FIELD_DECL, get_identifier ("count"),
1163*c87b03e5Sespie 		      unsigned_type_node);
1164*c87b03e5Sespie 
1165*c87b03e5Sespie   DECL_FIELD_CONTEXT (f_1) = record;
1166*c87b03e5Sespie   DECL_FIELD_CONTEXT (f_2) = record;
1167*c87b03e5Sespie 
1168*c87b03e5Sespie   TREE_CHAIN (record) = type_decl;
1169*c87b03e5Sespie   TYPE_NAME (record) = type_decl;
1170*c87b03e5Sespie   TYPE_FIELDS (record) = f_1;
1171*c87b03e5Sespie   TREE_CHAIN (f_1) = f_2;
1172*c87b03e5Sespie 
1173*c87b03e5Sespie   layout_type (record);
1174*c87b03e5Sespie 
1175*c87b03e5Sespie   return record;
1176*c87b03e5Sespie }
1177*c87b03e5Sespie 
1178*c87b03e5Sespie /* Implement the stdarg/varargs va_start macro.  STDARG_P is nonzero if this
1179*c87b03e5Sespie    is stdarg.h instead of varargs.h.  VALIST is the tree of the va_list
1180*c87b03e5Sespie    variable to initialize.  NEXTARG is the machine independent notion of the
1181*c87b03e5Sespie    'next' argument after the variable arguments.  */
1182*c87b03e5Sespie void
xstormy16_expand_builtin_va_start(valist,nextarg)1183*c87b03e5Sespie xstormy16_expand_builtin_va_start (valist, nextarg)
1184*c87b03e5Sespie      tree valist;
1185*c87b03e5Sespie      rtx nextarg ATTRIBUTE_UNUSED;
1186*c87b03e5Sespie {
1187*c87b03e5Sespie   tree f_base, f_count;
1188*c87b03e5Sespie   tree base, count;
1189*c87b03e5Sespie   tree t;
1190*c87b03e5Sespie 
1191*c87b03e5Sespie   if (xstormy16_interrupt_function_p ())
1192*c87b03e5Sespie     error ("cannot use va_start in interrupt function");
1193*c87b03e5Sespie 
1194*c87b03e5Sespie   f_base = TYPE_FIELDS (va_list_type_node);
1195*c87b03e5Sespie   f_count = TREE_CHAIN (f_base);
1196*c87b03e5Sespie 
1197*c87b03e5Sespie   base = build (COMPONENT_REF, TREE_TYPE (f_base), valist, f_base);
1198*c87b03e5Sespie   count = build (COMPONENT_REF, TREE_TYPE (f_count), valist, f_count);
1199*c87b03e5Sespie 
1200*c87b03e5Sespie   t = make_tree (TREE_TYPE (base), virtual_incoming_args_rtx);
1201*c87b03e5Sespie   t = build (PLUS_EXPR, TREE_TYPE (base), t,
1202*c87b03e5Sespie 	     build_int_2 (INCOMING_FRAME_SP_OFFSET, 0));
1203*c87b03e5Sespie   t = build (MODIFY_EXPR, TREE_TYPE (base), base, t);
1204*c87b03e5Sespie   TREE_SIDE_EFFECTS (t) = 1;
1205*c87b03e5Sespie   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
1206*c87b03e5Sespie 
1207*c87b03e5Sespie   t = build (MODIFY_EXPR, TREE_TYPE (count), count,
1208*c87b03e5Sespie 	     build_int_2 (current_function_args_info * UNITS_PER_WORD, 0));
1209*c87b03e5Sespie   TREE_SIDE_EFFECTS (t) = 1;
1210*c87b03e5Sespie   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
1211*c87b03e5Sespie }
1212*c87b03e5Sespie 
1213*c87b03e5Sespie /* Implement the stdarg/varargs va_arg macro.  VALIST is the variable
1214*c87b03e5Sespie    of type va_list as a tree, TYPE is the type passed to va_arg.
1215*c87b03e5Sespie    Note:  This algorithm is documented in stormy-abi.  */
1216*c87b03e5Sespie 
1217*c87b03e5Sespie rtx
xstormy16_expand_builtin_va_arg(valist,type)1218*c87b03e5Sespie xstormy16_expand_builtin_va_arg (valist, type)
1219*c87b03e5Sespie      tree valist;
1220*c87b03e5Sespie      tree type;
1221*c87b03e5Sespie {
1222*c87b03e5Sespie   tree f_base, f_count;
1223*c87b03e5Sespie   tree base, count;
1224*c87b03e5Sespie   rtx count_rtx, addr_rtx, r;
1225*c87b03e5Sespie   rtx lab_gotaddr, lab_fromstack;
1226*c87b03e5Sespie   tree t;
1227*c87b03e5Sespie   int size, size_of_reg_args;
1228*c87b03e5Sespie   tree size_tree, count_plus_size;
1229*c87b03e5Sespie   rtx count_plus_size_rtx;
1230*c87b03e5Sespie 
1231*c87b03e5Sespie   f_base = TYPE_FIELDS (va_list_type_node);
1232*c87b03e5Sespie   f_count = TREE_CHAIN (f_base);
1233*c87b03e5Sespie 
1234*c87b03e5Sespie   base = build (COMPONENT_REF, TREE_TYPE (f_base), valist, f_base);
1235*c87b03e5Sespie   count = build (COMPONENT_REF, TREE_TYPE (f_count), valist, f_count);
1236*c87b03e5Sespie 
1237*c87b03e5Sespie   size = PUSH_ROUNDING (int_size_in_bytes (type));
1238*c87b03e5Sespie   size_tree = round_up (size_in_bytes (type), UNITS_PER_WORD);
1239*c87b03e5Sespie 
1240*c87b03e5Sespie   size_of_reg_args = NUM_ARGUMENT_REGISTERS * UNITS_PER_WORD;
1241*c87b03e5Sespie 
1242*c87b03e5Sespie   count_rtx = expand_expr (count, NULL_RTX, HImode, EXPAND_NORMAL);
1243*c87b03e5Sespie   lab_gotaddr = gen_label_rtx ();
1244*c87b03e5Sespie   lab_fromstack = gen_label_rtx ();
1245*c87b03e5Sespie   addr_rtx = gen_reg_rtx (Pmode);
1246*c87b03e5Sespie 
1247*c87b03e5Sespie   count_plus_size = build (PLUS_EXPR, TREE_TYPE (count), count, size_tree);
1248*c87b03e5Sespie   count_plus_size_rtx = expand_expr (count_plus_size, NULL_RTX, HImode, EXPAND_NORMAL);
1249*c87b03e5Sespie   emit_cmp_and_jump_insns (count_plus_size_rtx, GEN_INT (size_of_reg_args),
1250*c87b03e5Sespie 			   GTU, const1_rtx, HImode, 1, lab_fromstack);
1251*c87b03e5Sespie 
1252*c87b03e5Sespie   t = build (PLUS_EXPR, ptr_type_node, base, count);
1253*c87b03e5Sespie   r = expand_expr (t, addr_rtx, Pmode, EXPAND_NORMAL);
1254*c87b03e5Sespie   if (r != addr_rtx)
1255*c87b03e5Sespie     emit_move_insn (addr_rtx, r);
1256*c87b03e5Sespie 
1257*c87b03e5Sespie   emit_jump_insn (gen_jump (lab_gotaddr));
1258*c87b03e5Sespie   emit_barrier ();
1259*c87b03e5Sespie   emit_label (lab_fromstack);
1260*c87b03e5Sespie 
1261*c87b03e5Sespie   /* Arguments larger than a word might need to skip over some
1262*c87b03e5Sespie      registers, since arguments are either passed entirely in
1263*c87b03e5Sespie      registers or entirely on the stack.  */
1264*c87b03e5Sespie   if (size > 2 || size < 0)
1265*c87b03e5Sespie     {
1266*c87b03e5Sespie       rtx lab_notransition = gen_label_rtx ();
1267*c87b03e5Sespie       emit_cmp_and_jump_insns (count_rtx, GEN_INT (NUM_ARGUMENT_REGISTERS
1268*c87b03e5Sespie 						   * UNITS_PER_WORD),
1269*c87b03e5Sespie 			       GEU, const1_rtx, HImode, 1, lab_notransition);
1270*c87b03e5Sespie 
1271*c87b03e5Sespie       t = build (MODIFY_EXPR, TREE_TYPE (count), count,
1272*c87b03e5Sespie 		 build_int_2 (NUM_ARGUMENT_REGISTERS * UNITS_PER_WORD, 0));
1273*c87b03e5Sespie       TREE_SIDE_EFFECTS (t) = 1;
1274*c87b03e5Sespie       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
1275*c87b03e5Sespie 
1276*c87b03e5Sespie       emit_label (lab_notransition);
1277*c87b03e5Sespie     }
1278*c87b03e5Sespie 
1279*c87b03e5Sespie   t = build (PLUS_EXPR, sizetype, size_tree,
1280*c87b03e5Sespie 	     build_int_2 ((- NUM_ARGUMENT_REGISTERS * UNITS_PER_WORD
1281*c87b03e5Sespie 			   + INCOMING_FRAME_SP_OFFSET),
1282*c87b03e5Sespie 			  -1));
1283*c87b03e5Sespie   t = build (PLUS_EXPR, TREE_TYPE (count), count, fold (t));
1284*c87b03e5Sespie   t = build (MINUS_EXPR, TREE_TYPE (base), base, t);
1285*c87b03e5Sespie   r = expand_expr (t, addr_rtx, Pmode, EXPAND_NORMAL);
1286*c87b03e5Sespie   if (r != addr_rtx)
1287*c87b03e5Sespie     emit_move_insn (addr_rtx, r);
1288*c87b03e5Sespie 
1289*c87b03e5Sespie   emit_label (lab_gotaddr);
1290*c87b03e5Sespie 
1291*c87b03e5Sespie   count_plus_size = build (PLUS_EXPR, TREE_TYPE (count), count, size_tree);
1292*c87b03e5Sespie   t = build (MODIFY_EXPR, TREE_TYPE (count), count, count_plus_size);
1293*c87b03e5Sespie   TREE_SIDE_EFFECTS (t) = 1;
1294*c87b03e5Sespie   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
1295*c87b03e5Sespie 
1296*c87b03e5Sespie   return addr_rtx;
1297*c87b03e5Sespie }
1298*c87b03e5Sespie 
1299*c87b03e5Sespie /* Initialize the variable parts of a trampoline.  ADDR is an RTX for
1300*c87b03e5Sespie    the address of the trampoline; FNADDR is an RTX for the address of
1301*c87b03e5Sespie    the nested function; STATIC_CHAIN is an RTX for the static chain
1302*c87b03e5Sespie    value that should be passed to the function when it is called.  */
1303*c87b03e5Sespie void
xstormy16_initialize_trampoline(addr,fnaddr,static_chain)1304*c87b03e5Sespie xstormy16_initialize_trampoline (addr, fnaddr, static_chain)
1305*c87b03e5Sespie      rtx addr;
1306*c87b03e5Sespie      rtx fnaddr;
1307*c87b03e5Sespie      rtx static_chain;
1308*c87b03e5Sespie {
1309*c87b03e5Sespie   rtx reg_addr = gen_reg_rtx (Pmode);
1310*c87b03e5Sespie   rtx temp = gen_reg_rtx (HImode);
1311*c87b03e5Sespie   rtx reg_fnaddr = gen_reg_rtx (HImode);
1312*c87b03e5Sespie   rtx reg_addr_mem;
1313*c87b03e5Sespie 
1314*c87b03e5Sespie   reg_addr_mem = gen_rtx_MEM (HImode, reg_addr);
1315*c87b03e5Sespie 
1316*c87b03e5Sespie   emit_move_insn (reg_addr, addr);
1317*c87b03e5Sespie   emit_move_insn (temp, GEN_INT (0x3130 | STATIC_CHAIN_REGNUM));
1318*c87b03e5Sespie   emit_move_insn (reg_addr_mem, temp);
1319*c87b03e5Sespie   emit_insn (gen_addhi3 (reg_addr, reg_addr, const2_rtx));
1320*c87b03e5Sespie   emit_move_insn (temp, static_chain);
1321*c87b03e5Sespie   emit_move_insn (reg_addr_mem, temp);
1322*c87b03e5Sespie   emit_insn (gen_addhi3 (reg_addr, reg_addr, const2_rtx));
1323*c87b03e5Sespie   emit_move_insn (reg_fnaddr, fnaddr);
1324*c87b03e5Sespie   emit_move_insn (temp, reg_fnaddr);
1325*c87b03e5Sespie   emit_insn (gen_andhi3 (temp, temp, GEN_INT (0xFF)));
1326*c87b03e5Sespie   emit_insn (gen_iorhi3 (temp, temp, GEN_INT (0x0200)));
1327*c87b03e5Sespie   emit_move_insn (reg_addr_mem, temp);
1328*c87b03e5Sespie   emit_insn (gen_addhi3 (reg_addr, reg_addr, const2_rtx));
1329*c87b03e5Sespie   emit_insn (gen_lshrhi3 (reg_fnaddr, reg_fnaddr, GEN_INT (8)));
1330*c87b03e5Sespie   emit_move_insn (reg_addr_mem, reg_fnaddr);
1331*c87b03e5Sespie }
1332*c87b03e5Sespie 
1333*c87b03e5Sespie /* Create an RTX representing the place where a function returns a
1334*c87b03e5Sespie    value of data type VALTYPE.  VALTYPE is a tree node representing a
1335*c87b03e5Sespie    data type.  Write `TYPE_MODE (VALTYPE)' to get the machine mode
1336*c87b03e5Sespie    used to represent that type.  On many machines, only the mode is
1337*c87b03e5Sespie    relevant.  (Actually, on most machines, scalar values are returned
1338*c87b03e5Sespie    in the same place regardless of mode).
1339*c87b03e5Sespie 
1340*c87b03e5Sespie    If `PROMOTE_FUNCTION_RETURN' is defined, you must apply the same promotion
1341*c87b03e5Sespie    rules specified in `PROMOTE_MODE' if VALTYPE is a scalar type.
1342*c87b03e5Sespie 
1343*c87b03e5Sespie    If the precise function being called is known, FUNC is a tree node
1344*c87b03e5Sespie    (`FUNCTION_DECL') for it; otherwise, FUNC is a null pointer.  This makes it
1345*c87b03e5Sespie    possible to use a different value-returning convention for specific
1346*c87b03e5Sespie    functions when all their calls are known.
1347*c87b03e5Sespie 
1348*c87b03e5Sespie    `FUNCTION_VALUE' is not used for return vales with aggregate data types,
1349*c87b03e5Sespie    because these are returned in another way.  See `STRUCT_VALUE_REGNUM' and
1350*c87b03e5Sespie    related macros.  */
1351*c87b03e5Sespie rtx
xstormy16_function_value(valtype,func)1352*c87b03e5Sespie xstormy16_function_value (valtype, func)
1353*c87b03e5Sespie      tree valtype;
1354*c87b03e5Sespie      tree func ATTRIBUTE_UNUSED;
1355*c87b03e5Sespie {
1356*c87b03e5Sespie   enum machine_mode mode;
1357*c87b03e5Sespie   mode = TYPE_MODE (valtype);
1358*c87b03e5Sespie   PROMOTE_MODE (mode, 0, valtype);
1359*c87b03e5Sespie   return gen_rtx_REG (mode, RETURN_VALUE_REGNUM);
1360*c87b03e5Sespie }
1361*c87b03e5Sespie 
1362*c87b03e5Sespie /* A C compound statement that outputs the assembler code for a thunk function,
1363*c87b03e5Sespie    used to implement C++ virtual function calls with multiple inheritance.  The
1364*c87b03e5Sespie    thunk acts as a wrapper around a virtual function, adjusting the implicit
1365*c87b03e5Sespie    object parameter before handing control off to the real function.
1366*c87b03e5Sespie 
1367*c87b03e5Sespie    First, emit code to add the integer DELTA to the location that contains the
1368*c87b03e5Sespie    incoming first argument.  Assume that this argument contains a pointer, and
1369*c87b03e5Sespie    is the one used to pass the `this' pointer in C++.  This is the incoming
1370*c87b03e5Sespie    argument *before* the function prologue, e.g. `%o0' on a sparc.  The
1371*c87b03e5Sespie    addition must preserve the values of all other incoming arguments.
1372*c87b03e5Sespie 
1373*c87b03e5Sespie    After the addition, emit code to jump to FUNCTION, which is a
1374*c87b03e5Sespie    `FUNCTION_DECL'.  This is a direct pure jump, not a call, and does not touch
1375*c87b03e5Sespie    the return address.  Hence returning from FUNCTION will return to whoever
1376*c87b03e5Sespie    called the current `thunk'.
1377*c87b03e5Sespie 
1378*c87b03e5Sespie    The effect must be as if @var{function} had been called directly
1379*c87b03e5Sespie    with the adjusted first argument.  This macro is responsible for
1380*c87b03e5Sespie    emitting all of the code for a thunk function;
1381*c87b03e5Sespie    TARGET_ASM_FUNCTION_PROLOGUE and TARGET_ASM_FUNCTION_EPILOGUE are
1382*c87b03e5Sespie    not invoked.
1383*c87b03e5Sespie 
1384*c87b03e5Sespie    The THUNK_FNDECL is redundant.  (DELTA and FUNCTION have already been
1385*c87b03e5Sespie    extracted from it.)  It might possibly be useful on some targets, but
1386*c87b03e5Sespie    probably not.  */
1387*c87b03e5Sespie 
1388*c87b03e5Sespie static void
xstormy16_asm_output_mi_thunk(file,thunk_fndecl,delta,vcall_offset,function)1389*c87b03e5Sespie xstormy16_asm_output_mi_thunk (file, thunk_fndecl, delta,
1390*c87b03e5Sespie 			       vcall_offset, function)
1391*c87b03e5Sespie      FILE *file;
1392*c87b03e5Sespie      tree thunk_fndecl ATTRIBUTE_UNUSED;
1393*c87b03e5Sespie      HOST_WIDE_INT delta;
1394*c87b03e5Sespie      HOST_WIDE_INT vcall_offset ATTRIBUTE_UNUSED;
1395*c87b03e5Sespie      tree function;
1396*c87b03e5Sespie {
1397*c87b03e5Sespie   int regnum = FIRST_ARGUMENT_REGISTER;
1398*c87b03e5Sespie 
1399*c87b03e5Sespie   /* There might be a hidden first argument for a returned structure.  */
1400*c87b03e5Sespie   if (aggregate_value_p (TREE_TYPE (TREE_TYPE (function))))
1401*c87b03e5Sespie     regnum += 1;
1402*c87b03e5Sespie 
1403*c87b03e5Sespie   fprintf (file, "\tadd %s,#0x%x\n", reg_names[regnum], (int) delta & 0xFFFF);
1404*c87b03e5Sespie   fputs ("\tjmpf ", file);
1405*c87b03e5Sespie   assemble_name (file, XSTR (XEXP (DECL_RTL (function), 0), 0));
1406*c87b03e5Sespie   putc ('\n', file);
1407*c87b03e5Sespie }
1408*c87b03e5Sespie 
1409*c87b03e5Sespie /* Mark functions with SYMBOL_REF_FLAG.  */
1410*c87b03e5Sespie 
1411*c87b03e5Sespie static void
xstormy16_encode_section_info(decl,first)1412*c87b03e5Sespie xstormy16_encode_section_info (decl, first)
1413*c87b03e5Sespie      tree decl;
1414*c87b03e5Sespie      int first ATTRIBUTE_UNUSED;
1415*c87b03e5Sespie {
1416*c87b03e5Sespie   if (TREE_CODE (decl) == FUNCTION_DECL)
1417*c87b03e5Sespie     SYMBOL_REF_FLAG (XEXP (DECL_RTL (decl), 0)) = 1;
1418*c87b03e5Sespie }
1419*c87b03e5Sespie 
1420*c87b03e5Sespie /* Output constructors and destructors.  Just like
1421*c87b03e5Sespie    default_named_section_asm_out_* but don't set the sections writable.  */
1422*c87b03e5Sespie #undef TARGET_ASM_CONSTRUCTOR
1423*c87b03e5Sespie #define TARGET_ASM_CONSTRUCTOR xstormy16_asm_out_constructor
1424*c87b03e5Sespie #undef TARGET_ASM_DESTRUCTOR
1425*c87b03e5Sespie #define TARGET_ASM_DESTRUCTOR xstormy16_asm_out_destructor
1426*c87b03e5Sespie 
1427*c87b03e5Sespie static void
xstormy16_asm_out_destructor(symbol,priority)1428*c87b03e5Sespie xstormy16_asm_out_destructor (symbol, priority)
1429*c87b03e5Sespie      rtx symbol;
1430*c87b03e5Sespie      int priority;
1431*c87b03e5Sespie {
1432*c87b03e5Sespie   const char *section = ".dtors";
1433*c87b03e5Sespie   char buf[16];
1434*c87b03e5Sespie 
1435*c87b03e5Sespie   /* ??? This only works reliably with the GNU linker.   */
1436*c87b03e5Sespie   if (priority != DEFAULT_INIT_PRIORITY)
1437*c87b03e5Sespie     {
1438*c87b03e5Sespie       sprintf (buf, ".dtors.%.5u",
1439*c87b03e5Sespie 	       /* Invert the numbering so the linker puts us in the proper
1440*c87b03e5Sespie 		  order; constructors are run from right to left, and the
1441*c87b03e5Sespie 		  linker sorts in increasing order.  */
1442*c87b03e5Sespie 	       MAX_INIT_PRIORITY - priority);
1443*c87b03e5Sespie       section = buf;
1444*c87b03e5Sespie     }
1445*c87b03e5Sespie 
1446*c87b03e5Sespie   named_section_flags (section, 0);
1447*c87b03e5Sespie   assemble_align (POINTER_SIZE);
1448*c87b03e5Sespie   assemble_integer (symbol, POINTER_SIZE / BITS_PER_UNIT, POINTER_SIZE, 1);
1449*c87b03e5Sespie }
1450*c87b03e5Sespie 
1451*c87b03e5Sespie static void
xstormy16_asm_out_constructor(symbol,priority)1452*c87b03e5Sespie xstormy16_asm_out_constructor (symbol, priority)
1453*c87b03e5Sespie      rtx symbol;
1454*c87b03e5Sespie      int priority;
1455*c87b03e5Sespie {
1456*c87b03e5Sespie   const char *section = ".ctors";
1457*c87b03e5Sespie   char buf[16];
1458*c87b03e5Sespie 
1459*c87b03e5Sespie   /* ??? This only works reliably with the GNU linker.   */
1460*c87b03e5Sespie   if (priority != DEFAULT_INIT_PRIORITY)
1461*c87b03e5Sespie     {
1462*c87b03e5Sespie       sprintf (buf, ".ctors.%.5u",
1463*c87b03e5Sespie 	       /* Invert the numbering so the linker puts us in the proper
1464*c87b03e5Sespie 		  order; constructors are run from right to left, and the
1465*c87b03e5Sespie 		  linker sorts in increasing order.  */
1466*c87b03e5Sespie 	       MAX_INIT_PRIORITY - priority);
1467*c87b03e5Sespie       section = buf;
1468*c87b03e5Sespie     }
1469*c87b03e5Sespie 
1470*c87b03e5Sespie   named_section_flags (section, 0);
1471*c87b03e5Sespie   assemble_align (POINTER_SIZE);
1472*c87b03e5Sespie   assemble_integer (symbol, POINTER_SIZE / BITS_PER_UNIT, POINTER_SIZE, 1);
1473*c87b03e5Sespie }
1474*c87b03e5Sespie 
1475*c87b03e5Sespie /* Print a memory address as an operand to reference that memory location.  */
1476*c87b03e5Sespie void
xstormy16_print_operand_address(file,address)1477*c87b03e5Sespie xstormy16_print_operand_address (file, address)
1478*c87b03e5Sespie      FILE * file;
1479*c87b03e5Sespie      rtx    address;
1480*c87b03e5Sespie {
1481*c87b03e5Sespie   HOST_WIDE_INT offset;
1482*c87b03e5Sespie   int pre_dec, post_inc;
1483*c87b03e5Sespie 
1484*c87b03e5Sespie   /* There are a few easy cases.  */
1485*c87b03e5Sespie   if (GET_CODE (address) == CONST_INT)
1486*c87b03e5Sespie     {
1487*c87b03e5Sespie       fprintf (file, HOST_WIDE_INT_PRINT_DEC, INTVAL (address) & 0xFFFF);
1488*c87b03e5Sespie       return;
1489*c87b03e5Sespie     }
1490*c87b03e5Sespie 
1491*c87b03e5Sespie   if (CONSTANT_P (address) || GET_CODE (address) == CODE_LABEL)
1492*c87b03e5Sespie     {
1493*c87b03e5Sespie       output_addr_const (file, address);
1494*c87b03e5Sespie       return;
1495*c87b03e5Sespie     }
1496*c87b03e5Sespie 
1497*c87b03e5Sespie   /* Otherwise, it's hopefully something of the form
1498*c87b03e5Sespie      (plus:HI (pre_dec:HI (reg:HI ...)) (const_int ...))
1499*c87b03e5Sespie   */
1500*c87b03e5Sespie 
1501*c87b03e5Sespie   if (GET_CODE (address) == PLUS)
1502*c87b03e5Sespie     {
1503*c87b03e5Sespie       if (GET_CODE (XEXP (address, 1)) != CONST_INT)
1504*c87b03e5Sespie 	abort ();
1505*c87b03e5Sespie       offset = INTVAL (XEXP (address, 1));
1506*c87b03e5Sespie       address = XEXP (address, 0);
1507*c87b03e5Sespie     }
1508*c87b03e5Sespie   else
1509*c87b03e5Sespie     offset = 0;
1510*c87b03e5Sespie 
1511*c87b03e5Sespie   pre_dec = (GET_CODE (address) == PRE_DEC);
1512*c87b03e5Sespie   post_inc = (GET_CODE (address) == POST_INC);
1513*c87b03e5Sespie   if (pre_dec || post_inc)
1514*c87b03e5Sespie     address = XEXP (address, 0);
1515*c87b03e5Sespie 
1516*c87b03e5Sespie   if (GET_CODE (address) != REG)
1517*c87b03e5Sespie     abort ();
1518*c87b03e5Sespie 
1519*c87b03e5Sespie   fputc ('(', file);
1520*c87b03e5Sespie   if (pre_dec)
1521*c87b03e5Sespie     fputs ("--", file);
1522*c87b03e5Sespie   fputs (reg_names [REGNO (address)], file);
1523*c87b03e5Sespie   if (post_inc)
1524*c87b03e5Sespie     fputs ("++", file);
1525*c87b03e5Sespie   if (offset != 0)
1526*c87b03e5Sespie     {
1527*c87b03e5Sespie       fputc (',', file);
1528*c87b03e5Sespie       fprintf (file, HOST_WIDE_INT_PRINT_DEC, offset);
1529*c87b03e5Sespie     }
1530*c87b03e5Sespie   fputc (')', file);
1531*c87b03e5Sespie }
1532*c87b03e5Sespie 
1533*c87b03e5Sespie /* Print an operand to an assembler instruction.  */
1534*c87b03e5Sespie void
xstormy16_print_operand(file,x,code)1535*c87b03e5Sespie xstormy16_print_operand (file, x, code)
1536*c87b03e5Sespie      FILE * file;
1537*c87b03e5Sespie      rtx    x;
1538*c87b03e5Sespie      int    code;
1539*c87b03e5Sespie {
1540*c87b03e5Sespie   switch (code)
1541*c87b03e5Sespie     {
1542*c87b03e5Sespie     case 'B':
1543*c87b03e5Sespie 	/* There is either one bit set, or one bit clear, in X.
1544*c87b03e5Sespie 	   Print it preceded by '#'.  */
1545*c87b03e5Sespie       {
1546*c87b03e5Sespie 	HOST_WIDE_INT xx = 1;
1547*c87b03e5Sespie 	HOST_WIDE_INT l;
1548*c87b03e5Sespie 
1549*c87b03e5Sespie 	if (GET_CODE (x) == CONST_INT)
1550*c87b03e5Sespie 	  xx = INTVAL (x);
1551*c87b03e5Sespie 	else
1552*c87b03e5Sespie 	  output_operand_lossage ("`B' operand is not constant");
1553*c87b03e5Sespie 
1554*c87b03e5Sespie 	l = exact_log2 (xx);
1555*c87b03e5Sespie 	if (l == -1)
1556*c87b03e5Sespie 	  l = exact_log2 (~xx);
1557*c87b03e5Sespie 	if (l == -1)
1558*c87b03e5Sespie 	  output_operand_lossage ("`B' operand has multiple bits set");
1559*c87b03e5Sespie 
1560*c87b03e5Sespie 	fputs (IMMEDIATE_PREFIX, file);
1561*c87b03e5Sespie 	fprintf (file, HOST_WIDE_INT_PRINT_DEC, l);
1562*c87b03e5Sespie 	return;
1563*c87b03e5Sespie       }
1564*c87b03e5Sespie 
1565*c87b03e5Sespie     case 'C':
1566*c87b03e5Sespie       /* Print the symbol without a surrounding @fptr().  */
1567*c87b03e5Sespie       if (GET_CODE (x) == SYMBOL_REF)
1568*c87b03e5Sespie 	assemble_name (file, XSTR (x, 0));
1569*c87b03e5Sespie       else if (GET_CODE (x) == LABEL_REF)
1570*c87b03e5Sespie 	output_asm_label (x);
1571*c87b03e5Sespie       else
1572*c87b03e5Sespie 	xstormy16_print_operand_address (file, x);
1573*c87b03e5Sespie       return;
1574*c87b03e5Sespie 
1575*c87b03e5Sespie     case 'o':
1576*c87b03e5Sespie     case 'O':
1577*c87b03e5Sespie       /* Print the immediate operand less one, preceded by '#'.
1578*c87b03e5Sespie          For 'O', negate it first.  */
1579*c87b03e5Sespie       {
1580*c87b03e5Sespie 	HOST_WIDE_INT xx = 0;
1581*c87b03e5Sespie 
1582*c87b03e5Sespie 	if (GET_CODE (x) == CONST_INT)
1583*c87b03e5Sespie 	  xx = INTVAL (x);
1584*c87b03e5Sespie 	else
1585*c87b03e5Sespie 	  output_operand_lossage ("`o' operand is not constant");
1586*c87b03e5Sespie 
1587*c87b03e5Sespie 	if (code == 'O')
1588*c87b03e5Sespie 	  xx = -xx;
1589*c87b03e5Sespie 
1590*c87b03e5Sespie 	fputs (IMMEDIATE_PREFIX, file);
1591*c87b03e5Sespie 	fprintf (file, HOST_WIDE_INT_PRINT_DEC, xx - 1);
1592*c87b03e5Sespie 	return;
1593*c87b03e5Sespie       }
1594*c87b03e5Sespie 
1595*c87b03e5Sespie     case 0:
1596*c87b03e5Sespie       /* Handled below.  */
1597*c87b03e5Sespie       break;
1598*c87b03e5Sespie 
1599*c87b03e5Sespie     default:
1600*c87b03e5Sespie       output_operand_lossage ("xstormy16_print_operand: unknown code");
1601*c87b03e5Sespie       return;
1602*c87b03e5Sespie     }
1603*c87b03e5Sespie 
1604*c87b03e5Sespie   switch (GET_CODE (x))
1605*c87b03e5Sespie     {
1606*c87b03e5Sespie     case REG:
1607*c87b03e5Sespie       fputs (reg_names [REGNO (x)], file);
1608*c87b03e5Sespie       break;
1609*c87b03e5Sespie 
1610*c87b03e5Sespie     case MEM:
1611*c87b03e5Sespie       xstormy16_print_operand_address (file, XEXP (x, 0));
1612*c87b03e5Sespie       break;
1613*c87b03e5Sespie 
1614*c87b03e5Sespie     default:
1615*c87b03e5Sespie       /* Some kind of constant or label; an immediate operand,
1616*c87b03e5Sespie          so prefix it with '#' for the assembler.  */
1617*c87b03e5Sespie       fputs (IMMEDIATE_PREFIX, file);
1618*c87b03e5Sespie       output_addr_const (file, x);
1619*c87b03e5Sespie       break;
1620*c87b03e5Sespie     }
1621*c87b03e5Sespie 
1622*c87b03e5Sespie   return;
1623*c87b03e5Sespie }
1624*c87b03e5Sespie 
1625*c87b03e5Sespie 
1626*c87b03e5Sespie /* Expander for the `casesi' pattern.
1627*c87b03e5Sespie    INDEX is the index of the switch statement.
1628*c87b03e5Sespie    LOWER_BOUND is a CONST_INT that is the value of INDEX corresponding
1629*c87b03e5Sespie      to the first table entry.
1630*c87b03e5Sespie    RANGE is the number of table entries.
1631*c87b03e5Sespie    TABLE is an ADDR_VEC that is the jump table.
1632*c87b03e5Sespie    DEFAULT_LABEL is the address to branch to if INDEX is outside the
1633*c87b03e5Sespie      range LOWER_BOUND to LOWER_BOUND+RANGE-1.
1634*c87b03e5Sespie */
1635*c87b03e5Sespie 
1636*c87b03e5Sespie void
xstormy16_expand_casesi(index,lower_bound,range,table,default_label)1637*c87b03e5Sespie xstormy16_expand_casesi (index, lower_bound, range, table, default_label)
1638*c87b03e5Sespie      rtx index;
1639*c87b03e5Sespie      rtx lower_bound;
1640*c87b03e5Sespie      rtx range;
1641*c87b03e5Sespie      rtx table;
1642*c87b03e5Sespie      rtx default_label;
1643*c87b03e5Sespie {
1644*c87b03e5Sespie   HOST_WIDE_INT range_i = INTVAL (range);
1645*c87b03e5Sespie   rtx int_index;
1646*c87b03e5Sespie 
1647*c87b03e5Sespie   /* This code uses 'br', so it can deal only with tables of size up to
1648*c87b03e5Sespie      8192 entries.  */
1649*c87b03e5Sespie   if (range_i >= 8192)
1650*c87b03e5Sespie     sorry ("switch statement of size %lu entries too large",
1651*c87b03e5Sespie 	   (unsigned long) range_i);
1652*c87b03e5Sespie 
1653*c87b03e5Sespie   index = expand_binop (SImode, sub_optab, index, lower_bound, NULL_RTX, 0,
1654*c87b03e5Sespie 			OPTAB_LIB_WIDEN);
1655*c87b03e5Sespie   emit_cmp_and_jump_insns (index, range, GTU, NULL_RTX, SImode, 1,
1656*c87b03e5Sespie 			   default_label);
1657*c87b03e5Sespie   int_index = gen_lowpart_common (HImode, index);
1658*c87b03e5Sespie   emit_insn (gen_ashlhi3 (int_index, int_index, GEN_INT (2)));
1659*c87b03e5Sespie   emit_jump_insn (gen_tablejump_pcrel (int_index, table));
1660*c87b03e5Sespie }
1661*c87b03e5Sespie 
1662*c87b03e5Sespie /* Output an ADDR_VEC.  It is output as a sequence of 'jmpf'
1663*c87b03e5Sespie    instructions, without label or alignment or any other special
1664*c87b03e5Sespie    constructs.  We know that the previous instruction will be the
1665*c87b03e5Sespie    `tablejump_pcrel' output above.
1666*c87b03e5Sespie 
1667*c87b03e5Sespie    TODO: it might be nice to output 'br' instructions if they could
1668*c87b03e5Sespie    all reach.  */
1669*c87b03e5Sespie 
1670*c87b03e5Sespie void
xstormy16_output_addr_vec(file,label,table)1671*c87b03e5Sespie xstormy16_output_addr_vec (file, label, table)
1672*c87b03e5Sespie      FILE *file;
1673*c87b03e5Sespie      rtx label ATTRIBUTE_UNUSED;
1674*c87b03e5Sespie      rtx table;
1675*c87b03e5Sespie {
1676*c87b03e5Sespie   int vlen, idx;
1677*c87b03e5Sespie 
1678*c87b03e5Sespie   function_section (current_function_decl);
1679*c87b03e5Sespie 
1680*c87b03e5Sespie   vlen = XVECLEN (table, 0);
1681*c87b03e5Sespie   for (idx = 0; idx < vlen; idx++)
1682*c87b03e5Sespie     {
1683*c87b03e5Sespie       fputs ("\tjmpf ", file);
1684*c87b03e5Sespie       output_asm_label (XEXP (XVECEXP (table, 0, idx), 0));
1685*c87b03e5Sespie       fputc ('\n', file);
1686*c87b03e5Sespie     }
1687*c87b03e5Sespie }
1688*c87b03e5Sespie 
1689*c87b03e5Sespie 
1690*c87b03e5Sespie /* Expander for the `call' patterns.
1691*c87b03e5Sespie    INDEX is the index of the switch statement.
1692*c87b03e5Sespie    LOWER_BOUND is a CONST_INT that is the value of INDEX corresponding
1693*c87b03e5Sespie      to the first table entry.
1694*c87b03e5Sespie    RANGE is the number of table entries.
1695*c87b03e5Sespie    TABLE is an ADDR_VEC that is the jump table.
1696*c87b03e5Sespie    DEFAULT_LABEL is the address to branch to if INDEX is outside the
1697*c87b03e5Sespie      range LOWER_BOUND to LOWER_BOUND+RANGE-1.
1698*c87b03e5Sespie */
1699*c87b03e5Sespie 
1700*c87b03e5Sespie void
xstormy16_expand_call(retval,dest,counter)1701*c87b03e5Sespie xstormy16_expand_call (retval, dest, counter)
1702*c87b03e5Sespie      rtx retval;
1703*c87b03e5Sespie      rtx dest;
1704*c87b03e5Sespie      rtx counter;
1705*c87b03e5Sespie {
1706*c87b03e5Sespie   rtx call, temp;
1707*c87b03e5Sespie   enum machine_mode mode;
1708*c87b03e5Sespie 
1709*c87b03e5Sespie   if (GET_CODE (dest) != MEM)
1710*c87b03e5Sespie     abort ();
1711*c87b03e5Sespie   dest = XEXP (dest, 0);
1712*c87b03e5Sespie 
1713*c87b03e5Sespie   if (! CONSTANT_P (dest)
1714*c87b03e5Sespie       && GET_CODE (dest) != REG)
1715*c87b03e5Sespie     dest = force_reg (Pmode, dest);
1716*c87b03e5Sespie 
1717*c87b03e5Sespie   if (retval == NULL)
1718*c87b03e5Sespie     mode = VOIDmode;
1719*c87b03e5Sespie   else
1720*c87b03e5Sespie     mode = GET_MODE (retval);
1721*c87b03e5Sespie 
1722*c87b03e5Sespie   call = gen_rtx_CALL (mode, gen_rtx_MEM (FUNCTION_MODE, dest),
1723*c87b03e5Sespie 		       counter);
1724*c87b03e5Sespie   if (retval)
1725*c87b03e5Sespie     call = gen_rtx_SET (VOIDmode, retval, call);
1726*c87b03e5Sespie 
1727*c87b03e5Sespie   if (! CONSTANT_P (dest))
1728*c87b03e5Sespie     {
1729*c87b03e5Sespie       temp = gen_reg_rtx (HImode);
1730*c87b03e5Sespie       emit_move_insn (temp, const0_rtx);
1731*c87b03e5Sespie     }
1732*c87b03e5Sespie   else
1733*c87b03e5Sespie     temp = const0_rtx;
1734*c87b03e5Sespie 
1735*c87b03e5Sespie   call = gen_rtx_PARALLEL (VOIDmode, gen_rtvec (2, call,
1736*c87b03e5Sespie 						gen_rtx_USE (VOIDmode, temp)));
1737*c87b03e5Sespie   emit_call_insn (call);
1738*c87b03e5Sespie }
1739*c87b03e5Sespie 
1740*c87b03e5Sespie /* Expanders for multiword computational operations.  */
1741*c87b03e5Sespie 
1742*c87b03e5Sespie /* Expander for arithmetic operations; emit insns to compute
1743*c87b03e5Sespie 
1744*c87b03e5Sespie    (set DEST (CODE:MODE SRC0 SRC1))
1745*c87b03e5Sespie 
1746*c87b03e5Sespie    using CARRY as a temporary.  When CODE is COMPARE, a branch
1747*c87b03e5Sespie    template is generated (this saves duplicating code in
1748*c87b03e5Sespie    xstormy16_split_cbranch).  */
1749*c87b03e5Sespie 
1750*c87b03e5Sespie void
xstormy16_expand_arith(mode,code,dest,src0,src1,carry)1751*c87b03e5Sespie xstormy16_expand_arith (mode, code, dest, src0, src1, carry)
1752*c87b03e5Sespie      enum machine_mode mode;
1753*c87b03e5Sespie      enum rtx_code code;
1754*c87b03e5Sespie      rtx dest;
1755*c87b03e5Sespie      rtx src0;
1756*c87b03e5Sespie      rtx src1;
1757*c87b03e5Sespie      rtx carry;
1758*c87b03e5Sespie {
1759*c87b03e5Sespie   int num_words = GET_MODE_BITSIZE (mode) / BITS_PER_WORD;
1760*c87b03e5Sespie   int i;
1761*c87b03e5Sespie   int firstloop = 1;
1762*c87b03e5Sespie 
1763*c87b03e5Sespie   if (code == NEG)
1764*c87b03e5Sespie     {
1765*c87b03e5Sespie       rtx zero_reg = gen_reg_rtx (word_mode);
1766*c87b03e5Sespie       emit_move_insn (zero_reg, src0);
1767*c87b03e5Sespie       src0 = zero_reg;
1768*c87b03e5Sespie     }
1769*c87b03e5Sespie 
1770*c87b03e5Sespie   for (i = 0; i < num_words; i++)
1771*c87b03e5Sespie     {
1772*c87b03e5Sespie       rtx w_src0, w_src1, w_dest;
1773*c87b03e5Sespie       rtx insn;
1774*c87b03e5Sespie 
1775*c87b03e5Sespie       if (code == NEG)
1776*c87b03e5Sespie 	w_src0 = src0;
1777*c87b03e5Sespie       else
1778*c87b03e5Sespie 	w_src0 = simplify_gen_subreg (word_mode, src0, mode,
1779*c87b03e5Sespie 				      i * UNITS_PER_WORD);
1780*c87b03e5Sespie       w_src1 = simplify_gen_subreg (word_mode, src1, mode, i * UNITS_PER_WORD);
1781*c87b03e5Sespie       w_dest = simplify_gen_subreg (word_mode, dest, mode, i * UNITS_PER_WORD);
1782*c87b03e5Sespie 
1783*c87b03e5Sespie       switch (code)
1784*c87b03e5Sespie 	{
1785*c87b03e5Sespie 	case PLUS:
1786*c87b03e5Sespie 	  if (firstloop
1787*c87b03e5Sespie 	      && GET_CODE (w_src1) == CONST_INT && INTVAL (w_src1) == 0)
1788*c87b03e5Sespie 	    continue;
1789*c87b03e5Sespie 
1790*c87b03e5Sespie 	  if (firstloop)
1791*c87b03e5Sespie 	    insn = gen_addchi4 (w_dest, w_src0, w_src1, carry);
1792*c87b03e5Sespie 	  else
1793*c87b03e5Sespie 	    insn = gen_addchi5 (w_dest, w_src0, w_src1, carry, carry);
1794*c87b03e5Sespie 	  break;
1795*c87b03e5Sespie 
1796*c87b03e5Sespie 	case NEG:
1797*c87b03e5Sespie 	case MINUS:
1798*c87b03e5Sespie 	case COMPARE:
1799*c87b03e5Sespie 	  if (code == COMPARE && i == num_words - 1)
1800*c87b03e5Sespie 	    {
1801*c87b03e5Sespie 	      rtx branch, sub, clobber, sub_1;
1802*c87b03e5Sespie 
1803*c87b03e5Sespie 	      sub_1 = gen_rtx_MINUS (HImode, w_src0,
1804*c87b03e5Sespie 				     gen_rtx_ZERO_EXTEND (HImode, carry));
1805*c87b03e5Sespie 	      sub = gen_rtx_SET (VOIDmode, w_dest,
1806*c87b03e5Sespie 				 gen_rtx_MINUS (HImode, sub_1, w_src1));
1807*c87b03e5Sespie 	      clobber = gen_rtx_CLOBBER (VOIDmode, carry);
1808*c87b03e5Sespie 	      branch = gen_rtx_SET (VOIDmode, pc_rtx,
1809*c87b03e5Sespie 				    gen_rtx_IF_THEN_ELSE (VOIDmode,
1810*c87b03e5Sespie 							  gen_rtx_EQ (HImode,
1811*c87b03e5Sespie 								      sub_1,
1812*c87b03e5Sespie 								      w_src1),
1813*c87b03e5Sespie 							  pc_rtx,
1814*c87b03e5Sespie 							  pc_rtx));
1815*c87b03e5Sespie 	      insn = gen_rtx_PARALLEL (VOIDmode,
1816*c87b03e5Sespie 				       gen_rtvec (3, branch, sub, clobber));
1817*c87b03e5Sespie 	    }
1818*c87b03e5Sespie 	  else if (firstloop
1819*c87b03e5Sespie 		   && code != COMPARE
1820*c87b03e5Sespie 		   && GET_CODE (w_src1) == CONST_INT && INTVAL (w_src1) == 0)
1821*c87b03e5Sespie 	    continue;
1822*c87b03e5Sespie 	  else if (firstloop)
1823*c87b03e5Sespie 	    insn = gen_subchi4 (w_dest, w_src0, w_src1, carry);
1824*c87b03e5Sespie 	  else
1825*c87b03e5Sespie 	    insn = gen_subchi5 (w_dest, w_src0, w_src1, carry, carry);
1826*c87b03e5Sespie 	  break;
1827*c87b03e5Sespie 
1828*c87b03e5Sespie 	case IOR:
1829*c87b03e5Sespie 	case XOR:
1830*c87b03e5Sespie 	case AND:
1831*c87b03e5Sespie 	  if (GET_CODE (w_src1) == CONST_INT
1832*c87b03e5Sespie 	      && INTVAL (w_src1) == -(code == AND))
1833*c87b03e5Sespie 	    continue;
1834*c87b03e5Sespie 
1835*c87b03e5Sespie 	  insn = gen_rtx_SET (VOIDmode, w_dest, gen_rtx (code, mode,
1836*c87b03e5Sespie 							 w_src0, w_src1));
1837*c87b03e5Sespie 	  break;
1838*c87b03e5Sespie 
1839*c87b03e5Sespie 	case NOT:
1840*c87b03e5Sespie 	  insn = gen_rtx_SET (VOIDmode, w_dest, gen_rtx_NOT (mode, w_src0));
1841*c87b03e5Sespie 	  break;
1842*c87b03e5Sespie 
1843*c87b03e5Sespie 	default:
1844*c87b03e5Sespie 	  abort ();
1845*c87b03e5Sespie 	}
1846*c87b03e5Sespie 
1847*c87b03e5Sespie       firstloop = 0;
1848*c87b03e5Sespie       emit (insn);
1849*c87b03e5Sespie     }
1850*c87b03e5Sespie }
1851*c87b03e5Sespie 
1852*c87b03e5Sespie /* Return 1 if OP is a shift operator.  */
1853*c87b03e5Sespie 
1854*c87b03e5Sespie int
shift_operator(op,mode)1855*c87b03e5Sespie shift_operator (op, mode)
1856*c87b03e5Sespie      register rtx op;
1857*c87b03e5Sespie      enum machine_mode mode ATTRIBUTE_UNUSED;
1858*c87b03e5Sespie {
1859*c87b03e5Sespie   enum rtx_code code = GET_CODE (op);
1860*c87b03e5Sespie 
1861*c87b03e5Sespie   return (code == ASHIFT
1862*c87b03e5Sespie 	  || code == ASHIFTRT
1863*c87b03e5Sespie 	  || code == LSHIFTRT);
1864*c87b03e5Sespie }
1865*c87b03e5Sespie 
1866*c87b03e5Sespie /* The shift operations are split at output time for constant values;
1867*c87b03e5Sespie    variable-width shifts get handed off to a library routine.
1868*c87b03e5Sespie 
1869*c87b03e5Sespie    Generate an output string to do (set X (CODE:MODE X SIZE_R))
1870*c87b03e5Sespie    SIZE_R will be a CONST_INT, X will be a hard register.  */
1871*c87b03e5Sespie 
1872*c87b03e5Sespie const char *
xstormy16_output_shift(mode,code,x,size_r,temp)1873*c87b03e5Sespie xstormy16_output_shift (mode, code, x, size_r, temp)
1874*c87b03e5Sespie      enum machine_mode mode;
1875*c87b03e5Sespie      enum rtx_code code;
1876*c87b03e5Sespie      rtx x;
1877*c87b03e5Sespie      rtx size_r;
1878*c87b03e5Sespie      rtx temp;
1879*c87b03e5Sespie {
1880*c87b03e5Sespie   HOST_WIDE_INT size;
1881*c87b03e5Sespie   const char *r0, *r1, *rt;
1882*c87b03e5Sespie   static char r[64];
1883*c87b03e5Sespie 
1884*c87b03e5Sespie   if (GET_CODE (size_r) != CONST_INT
1885*c87b03e5Sespie       || GET_CODE (x) != REG
1886*c87b03e5Sespie       || mode != SImode)
1887*c87b03e5Sespie     abort ();
1888*c87b03e5Sespie   size = INTVAL (size_r) & (GET_MODE_BITSIZE (mode) - 1);
1889*c87b03e5Sespie 
1890*c87b03e5Sespie   if (size == 0)
1891*c87b03e5Sespie     return "";
1892*c87b03e5Sespie 
1893*c87b03e5Sespie   r0 = reg_names [REGNO (x)];
1894*c87b03e5Sespie   r1 = reg_names [REGNO (x) + 1];
1895*c87b03e5Sespie 
1896*c87b03e5Sespie   /* For shifts of size 1, we can use the rotate instructions.  */
1897*c87b03e5Sespie   if (size == 1)
1898*c87b03e5Sespie     {
1899*c87b03e5Sespie       switch (code)
1900*c87b03e5Sespie 	{
1901*c87b03e5Sespie 	case ASHIFT:
1902*c87b03e5Sespie 	  sprintf (r, "shl %s,#1 | rlc %s,#1", r0, r1);
1903*c87b03e5Sespie 	  break;
1904*c87b03e5Sespie 	case ASHIFTRT:
1905*c87b03e5Sespie 	  sprintf (r, "asr %s,#1 | rrc %s,#1", r1, r0);
1906*c87b03e5Sespie 	  break;
1907*c87b03e5Sespie 	case LSHIFTRT:
1908*c87b03e5Sespie 	  sprintf (r, "shr %s,#1 | rrc %s,#1", r1, r0);
1909*c87b03e5Sespie 	  break;
1910*c87b03e5Sespie 	default:
1911*c87b03e5Sespie 	  abort ();
1912*c87b03e5Sespie 	}
1913*c87b03e5Sespie       return r;
1914*c87b03e5Sespie     }
1915*c87b03e5Sespie 
1916*c87b03e5Sespie   /* For large shifts, there are easy special cases.  */
1917*c87b03e5Sespie   if (size == 16)
1918*c87b03e5Sespie     {
1919*c87b03e5Sespie       switch (code)
1920*c87b03e5Sespie 	{
1921*c87b03e5Sespie 	case ASHIFT:
1922*c87b03e5Sespie 	  sprintf (r, "mov %s,%s | mov %s,#0", r1, r0, r0);
1923*c87b03e5Sespie 	  break;
1924*c87b03e5Sespie 	case ASHIFTRT:
1925*c87b03e5Sespie 	  sprintf (r, "mov %s,%s | asr %s,#15", r0, r1, r1);
1926*c87b03e5Sespie 	  break;
1927*c87b03e5Sespie 	case LSHIFTRT:
1928*c87b03e5Sespie 	  sprintf (r, "mov %s,%s | mov %s,#0", r0, r1, r1);
1929*c87b03e5Sespie 	  break;
1930*c87b03e5Sespie 	default:
1931*c87b03e5Sespie 	  abort ();
1932*c87b03e5Sespie 	}
1933*c87b03e5Sespie       return r;
1934*c87b03e5Sespie     }
1935*c87b03e5Sespie   if (size > 16)
1936*c87b03e5Sespie     {
1937*c87b03e5Sespie       switch (code)
1938*c87b03e5Sespie 	{
1939*c87b03e5Sespie 	case ASHIFT:
1940*c87b03e5Sespie 	  sprintf (r, "mov %s,%s | mov %s,#0 | shl %s,#%d",
1941*c87b03e5Sespie 		   r1, r0, r0, r1, (int) size - 16);
1942*c87b03e5Sespie 	  break;
1943*c87b03e5Sespie 	case ASHIFTRT:
1944*c87b03e5Sespie 	  sprintf (r, "mov %s,%s | asr %s,#15 | asr %s,#%d",
1945*c87b03e5Sespie 		   r0, r1, r1, r0, (int) size - 16);
1946*c87b03e5Sespie 	  break;
1947*c87b03e5Sespie 	case LSHIFTRT:
1948*c87b03e5Sespie 	  sprintf (r, "mov %s,%s | mov %s,#0 | shr %s,#%d",
1949*c87b03e5Sespie 		   r0, r1, r1, r0, (int) size - 16);
1950*c87b03e5Sespie 	  break;
1951*c87b03e5Sespie 	default:
1952*c87b03e5Sespie 	  abort ();
1953*c87b03e5Sespie 	}
1954*c87b03e5Sespie       return r;
1955*c87b03e5Sespie     }
1956*c87b03e5Sespie 
1957*c87b03e5Sespie   /* For the rest, we have to do more work.  In particular, we
1958*c87b03e5Sespie      need a temporary.  */
1959*c87b03e5Sespie   rt = reg_names [REGNO (temp)];
1960*c87b03e5Sespie   switch (code)
1961*c87b03e5Sespie     {
1962*c87b03e5Sespie     case ASHIFT:
1963*c87b03e5Sespie       sprintf (r,
1964*c87b03e5Sespie 	       "mov %s,%s | shl %s,#%d | shl %s,#%d | shr %s,#%d | or %s,%s",
1965*c87b03e5Sespie 	       rt, r0, r0, (int) size, r1, (int) size, rt, (int) 16-size,
1966*c87b03e5Sespie 	       r1, rt);
1967*c87b03e5Sespie       break;
1968*c87b03e5Sespie     case ASHIFTRT:
1969*c87b03e5Sespie       sprintf (r,
1970*c87b03e5Sespie 	       "mov %s,%s | asr %s,#%d | shr %s,#%d | shl %s,#%d | or %s,%s",
1971*c87b03e5Sespie 	       rt, r1, r1, (int) size, r0, (int) size, rt, (int) 16-size,
1972*c87b03e5Sespie 	       r0, rt);
1973*c87b03e5Sespie       break;
1974*c87b03e5Sespie     case LSHIFTRT:
1975*c87b03e5Sespie       sprintf (r,
1976*c87b03e5Sespie 	       "mov %s,%s | shr %s,#%d | shr %s,#%d | shl %s,#%d | or %s,%s",
1977*c87b03e5Sespie 	       rt, r1, r1, (int) size, r0, (int) size, rt, (int) 16-size,
1978*c87b03e5Sespie 	       r0, rt);
1979*c87b03e5Sespie       break;
1980*c87b03e5Sespie     default:
1981*c87b03e5Sespie       abort ();
1982*c87b03e5Sespie     }
1983*c87b03e5Sespie   return r;
1984*c87b03e5Sespie }
1985*c87b03e5Sespie 
1986*c87b03e5Sespie /* Attribute handling.  */
1987*c87b03e5Sespie 
1988*c87b03e5Sespie /* Return nonzero if the function is an interrupt function.  */
1989*c87b03e5Sespie int
xstormy16_interrupt_function_p()1990*c87b03e5Sespie xstormy16_interrupt_function_p ()
1991*c87b03e5Sespie {
1992*c87b03e5Sespie   tree attributes;
1993*c87b03e5Sespie 
1994*c87b03e5Sespie   /* The dwarf2 mechanism asks for INCOMING_FRAME_SP_OFFSET before
1995*c87b03e5Sespie      any functions are declared, which is demonstrably wrong, but
1996*c87b03e5Sespie      it is worked around here.  FIXME.  */
1997*c87b03e5Sespie   if (!cfun)
1998*c87b03e5Sespie     return 0;
1999*c87b03e5Sespie 
2000*c87b03e5Sespie   attributes = TYPE_ATTRIBUTES (TREE_TYPE (current_function_decl));
2001*c87b03e5Sespie   return lookup_attribute ("interrupt", attributes) != NULL_TREE;
2002*c87b03e5Sespie }
2003*c87b03e5Sespie 
2004*c87b03e5Sespie #undef TARGET_ATTRIBUTE_TABLE
2005*c87b03e5Sespie #define TARGET_ATTRIBUTE_TABLE xstormy16_attribute_table
2006*c87b03e5Sespie static tree xstormy16_handle_interrupt_attribute PARAMS ((tree *, tree, tree, int, bool *));
2007*c87b03e5Sespie static const struct attribute_spec xstormy16_attribute_table[] =
2008*c87b03e5Sespie {
2009*c87b03e5Sespie   /* { name, min_len, max_len, decl_req, type_req, fn_type_req, handler } */
2010*c87b03e5Sespie   { "interrupt", 0, 0, false, true,  true,  xstormy16_handle_interrupt_attribute },
2011*c87b03e5Sespie   { NULL,        0, 0, false, false, false, NULL }
2012*c87b03e5Sespie };
2013*c87b03e5Sespie 
2014*c87b03e5Sespie /* Handle an "interrupt" attribute;
2015*c87b03e5Sespie    arguments as in struct attribute_spec.handler.  */
2016*c87b03e5Sespie static tree
xstormy16_handle_interrupt_attribute(node,name,args,flags,no_add_attrs)2017*c87b03e5Sespie xstormy16_handle_interrupt_attribute (node, name, args, flags, no_add_attrs)
2018*c87b03e5Sespie      tree *node;
2019*c87b03e5Sespie      tree name;
2020*c87b03e5Sespie      tree args ATTRIBUTE_UNUSED;
2021*c87b03e5Sespie      int flags ATTRIBUTE_UNUSED;
2022*c87b03e5Sespie      bool *no_add_attrs;
2023*c87b03e5Sespie {
2024*c87b03e5Sespie   if (TREE_CODE (*node) != FUNCTION_TYPE)
2025*c87b03e5Sespie     {
2026*c87b03e5Sespie       warning ("`%s' attribute only applies to functions",
2027*c87b03e5Sespie 	       IDENTIFIER_POINTER (name));
2028*c87b03e5Sespie       *no_add_attrs = true;
2029*c87b03e5Sespie     }
2030*c87b03e5Sespie 
2031*c87b03e5Sespie   return NULL_TREE;
2032*c87b03e5Sespie }
2033*c87b03e5Sespie 
2034*c87b03e5Sespie #undef TARGET_INIT_BUILTINS
2035*c87b03e5Sespie #define TARGET_INIT_BUILTINS xstormy16_init_builtins
2036*c87b03e5Sespie #undef TARGET_EXPAND_BUILTIN
2037*c87b03e5Sespie #define TARGET_EXPAND_BUILTIN xstormy16_expand_builtin
2038*c87b03e5Sespie 
2039*c87b03e5Sespie static struct {
2040*c87b03e5Sespie   const char *name;
2041*c87b03e5Sespie   int md_code;
2042*c87b03e5Sespie   const char *arg_ops; /* 0..9, t for temp register, r for return value */
2043*c87b03e5Sespie   const char *arg_types; /* s=short,l=long, upper case for unsigned */
2044*c87b03e5Sespie } s16builtins[] = {
2045*c87b03e5Sespie   { "__sdivlh", CODE_FOR_sdivlh, "rt01", "sls" },
2046*c87b03e5Sespie   { "__smodlh", CODE_FOR_sdivlh, "tr01", "sls" },
2047*c87b03e5Sespie   { "__udivlh", CODE_FOR_udivlh, "rt01", "SLS" },
2048*c87b03e5Sespie   { "__umodlh", CODE_FOR_udivlh, "tr01", "SLS" },
2049*c87b03e5Sespie   { 0, 0, 0, 0 }
2050*c87b03e5Sespie };
2051*c87b03e5Sespie 
2052*c87b03e5Sespie static void
xstormy16_init_builtins()2053*c87b03e5Sespie xstormy16_init_builtins ()
2054*c87b03e5Sespie {
2055*c87b03e5Sespie   tree args, ret_type, arg;
2056*c87b03e5Sespie   int i, a;
2057*c87b03e5Sespie 
2058*c87b03e5Sespie   ret_type = void_type_node;
2059*c87b03e5Sespie 
2060*c87b03e5Sespie   for (i=0; s16builtins[i].name; i++)
2061*c87b03e5Sespie     {
2062*c87b03e5Sespie       args = void_list_node;
2063*c87b03e5Sespie       for (a=strlen (s16builtins[i].arg_types)-1; a>=0; a--)
2064*c87b03e5Sespie 	{
2065*c87b03e5Sespie 	  switch (s16builtins[i].arg_types[a])
2066*c87b03e5Sespie 	    {
2067*c87b03e5Sespie 	    case 's': arg = short_integer_type_node; break;
2068*c87b03e5Sespie 	    case 'S': arg = short_unsigned_type_node; break;
2069*c87b03e5Sespie 	    case 'l': arg = long_integer_type_node; break;
2070*c87b03e5Sespie 	    case 'L': arg = long_unsigned_type_node; break;
2071*c87b03e5Sespie 	    default: abort();
2072*c87b03e5Sespie 	    }
2073*c87b03e5Sespie 	  if (a == 0)
2074*c87b03e5Sespie 	    ret_type = arg;
2075*c87b03e5Sespie 	  else
2076*c87b03e5Sespie 	    args = tree_cons (NULL_TREE, arg, args);
2077*c87b03e5Sespie 	}
2078*c87b03e5Sespie       builtin_function (s16builtins[i].name,
2079*c87b03e5Sespie 			build_function_type (ret_type, args),
2080*c87b03e5Sespie 			i, BUILT_IN_MD, NULL, NULL);
2081*c87b03e5Sespie     }
2082*c87b03e5Sespie }
2083*c87b03e5Sespie 
2084*c87b03e5Sespie static rtx
xstormy16_expand_builtin(exp,target,subtarget,mode,ignore)2085*c87b03e5Sespie xstormy16_expand_builtin(exp, target, subtarget, mode, ignore)
2086*c87b03e5Sespie      tree exp;
2087*c87b03e5Sespie      rtx target;
2088*c87b03e5Sespie      rtx subtarget ATTRIBUTE_UNUSED;
2089*c87b03e5Sespie      enum machine_mode mode ATTRIBUTE_UNUSED;
2090*c87b03e5Sespie      int ignore ATTRIBUTE_UNUSED;
2091*c87b03e5Sespie {
2092*c87b03e5Sespie   rtx op[10], args[10], pat, copyto[10], retval = 0;
2093*c87b03e5Sespie   tree fndecl, argtree;
2094*c87b03e5Sespie   int i, a, o, code;
2095*c87b03e5Sespie 
2096*c87b03e5Sespie   fndecl = TREE_OPERAND (TREE_OPERAND (exp, 0), 0);
2097*c87b03e5Sespie   argtree = TREE_OPERAND (exp, 1);
2098*c87b03e5Sespie   i = DECL_FUNCTION_CODE (fndecl);
2099*c87b03e5Sespie   code = s16builtins[i].md_code;
2100*c87b03e5Sespie 
2101*c87b03e5Sespie   for (a = 0; a < 10 && argtree; a++)
2102*c87b03e5Sespie     {
2103*c87b03e5Sespie       args[a] = expand_expr (TREE_VALUE (argtree), NULL_RTX, VOIDmode, 0);
2104*c87b03e5Sespie       argtree = TREE_CHAIN (argtree);
2105*c87b03e5Sespie     }
2106*c87b03e5Sespie 
2107*c87b03e5Sespie   for (o = 0; s16builtins[i].arg_ops[o]; o++)
2108*c87b03e5Sespie     {
2109*c87b03e5Sespie       char ao = s16builtins[i].arg_ops[o];
2110*c87b03e5Sespie       char c = insn_data[code].operand[o].constraint[0];
2111*c87b03e5Sespie       int omode;
2112*c87b03e5Sespie 
2113*c87b03e5Sespie       copyto[o] = 0;
2114*c87b03e5Sespie 
2115*c87b03e5Sespie       omode = insn_data[code].operand[o].mode;
2116*c87b03e5Sespie       if (ao == 'r')
2117*c87b03e5Sespie 	op[o] = target ? target : gen_reg_rtx (omode);
2118*c87b03e5Sespie       else if (ao == 't')
2119*c87b03e5Sespie 	op[o] = gen_reg_rtx (omode);
2120*c87b03e5Sespie       else
2121*c87b03e5Sespie 	op[o] = args[(int) hex_value (ao)];
2122*c87b03e5Sespie 
2123*c87b03e5Sespie       if (! (*insn_data[code].operand[o].predicate) (op[o], GET_MODE (op[o])))
2124*c87b03e5Sespie 	{
2125*c87b03e5Sespie 	  if (c == '+' || c == '=')
2126*c87b03e5Sespie 	    {
2127*c87b03e5Sespie 	      copyto[o] = op[o];
2128*c87b03e5Sespie 	      op[o] = gen_reg_rtx (omode);
2129*c87b03e5Sespie 	    }
2130*c87b03e5Sespie 	  else
2131*c87b03e5Sespie 	    op[o] = copy_to_mode_reg (omode, op[o]);
2132*c87b03e5Sespie 	}
2133*c87b03e5Sespie 
2134*c87b03e5Sespie       if (ao == 'r')
2135*c87b03e5Sespie 	retval = op[o];
2136*c87b03e5Sespie     }
2137*c87b03e5Sespie 
2138*c87b03e5Sespie   pat = GEN_FCN (code) (op[0], op[1], op[2], op[3], op[4],
2139*c87b03e5Sespie 			op[5], op[6], op[7], op[8], op[9]);
2140*c87b03e5Sespie   emit_insn (pat);
2141*c87b03e5Sespie 
2142*c87b03e5Sespie   for (o = 0; s16builtins[i].arg_ops[o]; o++)
2143*c87b03e5Sespie     if (copyto[o])
2144*c87b03e5Sespie       {
2145*c87b03e5Sespie 	emit_move_insn (copyto[o], op[o]);
2146*c87b03e5Sespie 	if (op[o] == retval)
2147*c87b03e5Sespie 	  retval = copyto[o];
2148*c87b03e5Sespie       }
2149*c87b03e5Sespie 
2150*c87b03e5Sespie   return retval;
2151*c87b03e5Sespie }
2152*c87b03e5Sespie 
2153*c87b03e5Sespie 
2154*c87b03e5Sespie #undef TARGET_ASM_ALIGNED_HI_OP
2155*c87b03e5Sespie #define TARGET_ASM_ALIGNED_HI_OP "\t.hword\t"
2156*c87b03e5Sespie #undef TARGET_ASM_ALIGNED_SI_OP
2157*c87b03e5Sespie #define TARGET_ASM_ALIGNED_SI_OP "\t.word\t"
2158*c87b03e5Sespie #undef TARGET_ENCODE_SECTION_INFO
2159*c87b03e5Sespie #define TARGET_ENCODE_SECTION_INFO xstormy16_encode_section_info
2160*c87b03e5Sespie 
2161*c87b03e5Sespie #undef TARGET_ASM_OUTPUT_MI_THUNK
2162*c87b03e5Sespie #define TARGET_ASM_OUTPUT_MI_THUNK xstormy16_asm_output_mi_thunk
2163*c87b03e5Sespie #undef TARGET_ASM_CAN_OUTPUT_MI_THUNK
2164*c87b03e5Sespie #define TARGET_ASM_CAN_OUTPUT_MI_THUNK default_can_output_mi_thunk_no_vcall
2165*c87b03e5Sespie 
2166*c87b03e5Sespie struct gcc_target targetm = TARGET_INITIALIZER;
2167