1*59692Selan /* Subroutines for insn-output.c for Motorola 68000 family.
2*59692Selan    Copyright (C) 1987 Free Software Foundation, Inc.
3*59692Selan 
4*59692Selan This file is part of GNU CC.
5*59692Selan 
6*59692Selan GNU CC is free software; you can redistribute it and/or modify
7*59692Selan it under the terms of the GNU General Public License as published by
8*59692Selan the Free Software Foundation; either version 2, or (at your option)
9*59692Selan any later version.
10*59692Selan 
11*59692Selan GNU CC is distributed in the hope that it will be useful,
12*59692Selan but WITHOUT ANY WARRANTY; without even the implied warranty of
13*59692Selan MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14*59692Selan GNU General Public License for more details.
15*59692Selan 
16*59692Selan You should have received a copy of the GNU General Public License
17*59692Selan along with GNU CC; see the file COPYING.  If not, write to
18*59692Selan the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  */
19*59692Selan 
20*59692Selan 
21*59692Selan /* Some output-actions in m68k.md need these.  */
22*59692Selan #include <stdio.h>
23*59692Selan #include "config.h"
24*59692Selan #include "rtl.h"
25*59692Selan #include "regs.h"
26*59692Selan #include "hard-reg-set.h"
27*59692Selan #include "real.h"
28*59692Selan #include "insn-config.h"
29*59692Selan #include "conditions.h"
30*59692Selan #include "insn-flags.h"
31*59692Selan #include "output.h"
32*59692Selan #include "insn-attr.h"
33*59692Selan 
34*59692Selan /* Needed for use_return_insn.  */
35*59692Selan #include "flags.h"
36*59692Selan 
37*59692Selan #ifdef SUPPORT_SUN_FPA
38*59692Selan 
39*59692Selan /* Index into this array by (register number >> 3) to find the
40*59692Selan    smallest class which contains that register.  */
41*59692Selan enum reg_class regno_reg_class[]
42*59692Selan   = { DATA_REGS, ADDR_REGS, FP_REGS,
43*59692Selan       LO_FPA_REGS, LO_FPA_REGS, FPA_REGS, FPA_REGS };
44*59692Selan 
45*59692Selan #endif /* defined SUPPORT_SUN_FPA */
46*59692Selan 
47*59692Selan /* This flag is used to communicate between movhi and ASM_OUTPUT_CASE_END,
48*59692Selan    if SGS_SWITCH_TABLE.  */
49*59692Selan int switch_table_difference_label_flag;
50*59692Selan 
51*59692Selan static rtx find_addr_reg ();
52*59692Selan rtx legitimize_pic_address ();
53*59692Selan 
54*59692Selan 
55*59692Selan /* Emit a (use pic_offset_table_rtx) if we used PIC relocation in the
56*59692Selan    function at any time during the compilation process.  In the future
57*59692Selan    we should try and eliminate the USE if we can easily determine that
58*59692Selan    all PIC references were deleted from the current function.  That would
59*59692Selan    save an address register */
60*59692Selan 
61*59692Selan finalize_pic ()
62*59692Selan {
63*59692Selan   if (flag_pic && current_function_uses_pic_offset_table)
64*59692Selan     emit_insn (gen_rtx (USE, VOIDmode, pic_offset_table_rtx));
65*59692Selan }
66*59692Selan 
67*59692Selan 
68*59692Selan /* This function generates the assembly code for function entry.
69*59692Selan    STREAM is a stdio stream to output the code to.
70*59692Selan    SIZE is an int: how many units of temporary storage to allocate.
71*59692Selan    Refer to the array `regs_ever_live' to determine which registers
72*59692Selan    to save; `regs_ever_live[I]' is nonzero if register number I
73*59692Selan    is ever used in the function.  This function is responsible for
74*59692Selan    knowing which registers should not be saved even if used.  */
75*59692Selan 
76*59692Selan 
77*59692Selan /* Note that the order of the bit mask for fmovem is the opposite
78*59692Selan    of the order for movem!  */
79*59692Selan 
80*59692Selan 
81*59692Selan void
82*59692Selan output_function_prologue (stream, size)
83*59692Selan      FILE *stream;
84*59692Selan      int size;
85*59692Selan {
86*59692Selan   register int regno;
87*59692Selan   register int mask = 0;
88*59692Selan   int num_saved_regs = 0;
89*59692Selan   extern char call_used_regs[];
90*59692Selan   int fsize = (size + 3) & -4;
91*59692Selan 
92*59692Selan 
93*59692Selan   if (frame_pointer_needed)
94*59692Selan     {
95*59692Selan       /* Adding negative number is faster on the 68040.  */
96*59692Selan       if (fsize < 0x8000 && !TARGET_68040)
97*59692Selan 	{
98*59692Selan #ifdef MOTOROLA
99*59692Selan 	  asm_fprintf (stream, "\tlink.w %s,%0I%d\n",
100*59692Selan 		       reg_names[FRAME_POINTER_REGNUM], -fsize);
101*59692Selan #else
102*59692Selan 	  asm_fprintf (stream, "\tlink %s,%0I%d\n",
103*59692Selan 		       reg_names[FRAME_POINTER_REGNUM], -fsize);
104*59692Selan #endif
105*59692Selan 	}
106*59692Selan       else if (TARGET_68020)
107*59692Selan 	{
108*59692Selan #ifdef MOTOROLA
109*59692Selan 	  asm_fprintf (stream, "\tlink.l %s,%0I%d\n",
110*59692Selan 		       reg_names[FRAME_POINTER_REGNUM], -fsize);
111*59692Selan #else
112*59692Selan 	  asm_fprintf (stream, "\tlink %s,%0I%d\n",
113*59692Selan 		       reg_names[FRAME_POINTER_REGNUM], -fsize);
114*59692Selan #endif
115*59692Selan 	}
116*59692Selan       else
117*59692Selan 	{
118*59692Selan #ifdef MOTOROLA
119*59692Selan 	  asm_fprintf (stream, "\tlink.w %s,%0I0\n\tadd.l %0I%d,%Rsp\n",
120*59692Selan 		       reg_names[FRAME_POINTER_REGNUM], -fsize);
121*59692Selan #else
122*59692Selan 	  asm_fprintf (stream, "\tlink %s,%0I0\n\taddl %0I%d,%Rsp\n",
123*59692Selan 		       reg_names[FRAME_POINTER_REGNUM], -fsize);
124*59692Selan #endif
125*59692Selan 	}
126*59692Selan     }
127*59692Selan   else if (fsize)
128*59692Selan     {
129*59692Selan       /* Adding negative number is faster on the 68040.  */
130*59692Selan       if (fsize + 4 < 0x8000)
131*59692Selan 	{
132*59692Selan #ifdef MOTOROLA
133*59692Selan 	  asm_fprintf (stream, "\tadd.w %0I%d,%Rsp\n", - (fsize + 4));
134*59692Selan #else
135*59692Selan 	  asm_fprintf (stream, "\taddw %0I%d,%Rsp\n", - (fsize + 4));
136*59692Selan #endif
137*59692Selan 	}
138*59692Selan       else
139*59692Selan 	{
140*59692Selan #ifdef MOTOROLA
141*59692Selan 	  asm_fprintf (stream, "\tadd.l %0I%d,%Rsp\n", - (fsize + 4));
142*59692Selan #else
143*59692Selan 	  asm_fprintf (stream, "\taddl %0I%d,%Rsp\n", - (fsize + 4));
144*59692Selan #endif
145*59692Selan 	}
146*59692Selan     }
147*59692Selan #ifdef SUPPORT_SUN_FPA
148*59692Selan   for (regno = 24; regno < 56; regno++)
149*59692Selan     if (regs_ever_live[regno] && ! call_used_regs[regno])
150*59692Selan       {
151*59692Selan #ifdef MOTOROLA
152*59692Selan 	asm_fprintf (stream, "\tfpmovd %s,-(%Rsp)\n",
153*59692Selan 		     reg_names[regno]);
154*59692Selan #else
155*59692Selan 	asm_fprintf (stream, "\tfpmoved %s,%Rsp@-\n",
156*59692Selan 		     reg_names[regno]);
157*59692Selan #endif
158*59692Selan       }
159*59692Selan #endif
160*59692Selan   for (regno = 16; regno < 24; regno++)
161*59692Selan     if (regs_ever_live[regno] && ! call_used_regs[regno])
162*59692Selan        mask |= 1 << (regno - 16);
163*59692Selan   if ((mask & 0xff) != 0)
164*59692Selan     {
165*59692Selan #ifdef MOTOROLA
166*59692Selan       asm_fprintf (stream, "\tfmovm %0I0x%x,-(%Rsp)\n", mask & 0xff);
167*59692Selan #else
168*59692Selan       asm_fprintf (stream, "\tfmovem %0I0x%x,%Rsp@-\n", mask & 0xff);
169*59692Selan #endif
170*59692Selan     }
171*59692Selan   mask = 0;
172*59692Selan   for (regno = 0; regno < 16; regno++)
173*59692Selan     if (regs_ever_live[regno] && ! call_used_regs[regno])
174*59692Selan       {
175*59692Selan         mask |= 1 << (15 - regno);
176*59692Selan         num_saved_regs++;
177*59692Selan       }
178*59692Selan   if (frame_pointer_needed)
179*59692Selan     {
180*59692Selan       mask &= ~ (1 << (15 - FRAME_POINTER_REGNUM));
181*59692Selan       num_saved_regs--;
182*59692Selan     }
183*59692Selan 
184*59692Selan #if NEED_PROBE
185*59692Selan   fprintf (stream, "\ttstl sp@(%d)\n", NEED_PROBE - num_saved_regs * 4);
186*59692Selan #endif
187*59692Selan 
188*59692Selan   if (num_saved_regs <= 2)
189*59692Selan     {
190*59692Selan       /* Store each separately in the same order moveml uses.
191*59692Selan          Using two movel instructions instead of a single moveml
192*59692Selan          is about 15% faster for the 68020 and 68030 at no expense
193*59692Selan          in code size */
194*59692Selan 
195*59692Selan       int i;
196*59692Selan 
197*59692Selan       /* Undo the work from above. */
198*59692Selan       for (i = 0; i< 16; i++)
199*59692Selan         if (mask & (1 << i))
200*59692Selan           asm_fprintf (stream,
201*59692Selan #ifdef MOTOROLA
202*59692Selan 		       "\t%Omove.l %s,-(%Rsp)\n",
203*59692Selan #else
204*59692Selan 		       "\tmovel %s,%Rsp@-\n",
205*59692Selan #endif
206*59692Selan 		       reg_names[15 - i]);
207*59692Selan     }
208*59692Selan   else if (mask)
209*59692Selan     {
210*59692Selan #ifdef MOTOROLA
211*59692Selan       asm_fprintf (stream, "\tmovm.l %0I0x%x,-(%Rsp)\n", mask);
212*59692Selan #else
213*59692Selan       asm_fprintf (stream, "\tmoveml %0I0x%x,%Rsp@-\n", mask);
214*59692Selan #endif
215*59692Selan     }
216*59692Selan   if (flag_pic && current_function_uses_pic_offset_table)
217*59692Selan     {
218*59692Selan #ifdef MOTOROLA
219*59692Selan       asm_fprintf (stream, "\t%Omove.l %0I__GLOBAL_OFFSET_TABLE_, %s\n",
220*59692Selan 		   reg_names[PIC_OFFSET_TABLE_REGNUM]);
221*59692Selan       asm_fprintf (stream, "\tlea.l (%Rpc,%s.l),%s\n",
222*59692Selan 		   reg_names[PIC_OFFSET_TABLE_REGNUM],
223*59692Selan 		   reg_names[PIC_OFFSET_TABLE_REGNUM]);
224*59692Selan #else
225*59692Selan       asm_fprintf (stream, "\tmovel %0I__GLOBAL_OFFSET_TABLE_, %s\n",
226*59692Selan 		   reg_names[PIC_OFFSET_TABLE_REGNUM]);
227*59692Selan       asm_fprintf (stream, "\tlea %Rpc@(0,%s:l),%s\n",
228*59692Selan 		   reg_names[PIC_OFFSET_TABLE_REGNUM],
229*59692Selan 		   reg_names[PIC_OFFSET_TABLE_REGNUM]);
230*59692Selan #endif
231*59692Selan     }
232*59692Selan }
233*59692Selan 
234*59692Selan /* Return true if this function's epilogue can be output as RTL.  */
235*59692Selan 
236*59692Selan int
237*59692Selan use_return_insn ()
238*59692Selan {
239*59692Selan   int regno;
240*59692Selan 
241*59692Selan   if (!reload_completed || frame_pointer_needed || get_frame_size () != 0)
242*59692Selan     return 0;
243*59692Selan 
244*59692Selan   /* Copied from output_function_epilogue ().  We should probably create a
245*59692Selan      separate layout routine to perform the common work.  */
246*59692Selan 
247*59692Selan   for (regno = 0 ; regno < FIRST_PSEUDO_REGISTER ; regno++)
248*59692Selan     if (regs_ever_live[regno] && ! call_used_regs[regno])
249*59692Selan       return 0;
250*59692Selan 
251*59692Selan   return 1;
252*59692Selan }
253*59692Selan 
254*59692Selan /* This function generates the assembly code for function exit,
255*59692Selan    on machines that need it.  Args are same as for FUNCTION_PROLOGUE.
256*59692Selan 
257*59692Selan    The function epilogue should not depend on the current stack pointer!
258*59692Selan    It should use the frame pointer only, if there is a frame pointer.
259*59692Selan    This is mandatory because of alloca; we also take advantage of it to
260*59692Selan    omit stack adjustments before returning.  */
261*59692Selan 
262*59692Selan void
263*59692Selan output_function_epilogue (stream, size)
264*59692Selan      FILE *stream;
265*59692Selan      int size;
266*59692Selan {
267*59692Selan   register int regno;
268*59692Selan   register int mask, fmask;
269*59692Selan   register int nregs;
270*59692Selan   int offset, foffset, fpoffset;
271*59692Selan   extern char call_used_regs[];
272*59692Selan   int fsize = (size + 3) & -4;
273*59692Selan   int big = 0;
274*59692Selan   rtx insn = get_last_insn ();
275*59692Selan 
276*59692Selan   /* If the last insn was a BARRIER, we don't have to write any code.  */
277*59692Selan   if (GET_CODE (insn) == NOTE)
278*59692Selan     insn = prev_nonnote_insn (insn);
279*59692Selan   if (insn && GET_CODE (insn) == BARRIER)
280*59692Selan     {
281*59692Selan       /* Output just a no-op so that debuggers don't get confused
282*59692Selan 	 about which function the pc is in at this address.  */
283*59692Selan       asm_fprintf (stream, "\tnop\n");
284*59692Selan       return;
285*59692Selan     }
286*59692Selan 
287*59692Selan #ifdef FUNCTION_EXTRA_EPILOGUE
288*59692Selan   FUNCTION_EXTRA_EPILOGUE (stream, size);
289*59692Selan #endif
290*59692Selan   nregs = 0;  fmask = 0; fpoffset = 0;
291*59692Selan #ifdef SUPPORT_SUN_FPA
292*59692Selan   for (regno = 24 ; regno < 56 ; regno++)
293*59692Selan     if (regs_ever_live[regno] && ! call_used_regs[regno])
294*59692Selan       nregs++;
295*59692Selan   fpoffset = nregs * 8;
296*59692Selan #endif
297*59692Selan   nregs = 0;
298*59692Selan   for (regno = 16; regno < 24; regno++)
299*59692Selan     if (regs_ever_live[regno] && ! call_used_regs[regno])
300*59692Selan       {
301*59692Selan         nregs++;
302*59692Selan 	fmask |= 1 << (23 - regno);
303*59692Selan       }
304*59692Selan   foffset = fpoffset + nregs * 12;
305*59692Selan   nregs = 0;  mask = 0;
306*59692Selan   if (frame_pointer_needed)
307*59692Selan     regs_ever_live[FRAME_POINTER_REGNUM] = 0;
308*59692Selan   for (regno = 0; regno < 16; regno++)
309*59692Selan     if (regs_ever_live[regno] && ! call_used_regs[regno])
310*59692Selan       {
311*59692Selan         nregs++;
312*59692Selan 	mask |= 1 << regno;
313*59692Selan       }
314*59692Selan   offset = foffset + nregs * 4;
315*59692Selan   if (offset + fsize >= 0x8000
316*59692Selan       && frame_pointer_needed
317*59692Selan       && (mask || fmask || fpoffset))
318*59692Selan     {
319*59692Selan #ifdef MOTOROLA
320*59692Selan       asm_fprintf (stream, "\t%Omove.l %0I%d,%Ra0\n", -fsize);
321*59692Selan #else
322*59692Selan       asm_fprintf (stream, "\tmovel %0I%d,%Ra0\n", -fsize);
323*59692Selan #endif
324*59692Selan       fsize = 0, big = 1;
325*59692Selan     }
326*59692Selan   if (nregs <= 2)
327*59692Selan     {
328*59692Selan       /* Restore each separately in the same order moveml does.
329*59692Selan          Using two movel instructions instead of a single moveml
330*59692Selan          is about 15% faster for the 68020 and 68030 at no expense
331*59692Selan          in code size. */
332*59692Selan 
333*59692Selan       int i;
334*59692Selan 
335*59692Selan       /* Undo the work from above. */
336*59692Selan       for (i = 0; i< 16; i++)
337*59692Selan         if (mask & (1 << i))
338*59692Selan           {
339*59692Selan             if (big)
340*59692Selan 	      {
341*59692Selan #ifdef MOTOROLA
342*59692Selan 		asm_fprintf (stream, "\t%Omove.l -%d(%s,%Ra0.l),%s\n",
343*59692Selan 			     offset + fsize,
344*59692Selan 			     reg_names[FRAME_POINTER_REGNUM],
345*59692Selan 			     reg_names[i]);
346*59692Selan #else
347*59692Selan 		asm_fprintf (stream, "\tmovel %s@(-%d,%Ra0:l),%s\n",
348*59692Selan 			     reg_names[FRAME_POINTER_REGNUM],
349*59692Selan 			     offset + fsize, reg_names[i]);
350*59692Selan #endif
351*59692Selan 	      }
352*59692Selan             else if (! frame_pointer_needed)
353*59692Selan 	      {
354*59692Selan #ifdef MOTOROLA
355*59692Selan 		asm_fprintf (stream, "\t%Omove.l (%Rsp)+,%s\n",
356*59692Selan 			     reg_names[i]);
357*59692Selan #else
358*59692Selan 		asm_fprintf (stream, "\tmovel %Rsp@+,%s\n",
359*59692Selan 			     reg_names[i]);
360*59692Selan #endif
361*59692Selan 	      }
362*59692Selan             else
363*59692Selan 	      {
364*59692Selan #ifdef MOTOROLA
365*59692Selan 		asm_fprintf (stream, "\t%Omove.l -%d(%s),%s\n",
366*59692Selan 			     offset + fsize,
367*59692Selan 			     reg_names[FRAME_POINTER_REGNUM],
368*59692Selan 			     reg_names[i]);
369*59692Selan #else
370*59692Selan 		asm_fprintf (stream, "\tmovel %s@(-%d),%s\n",
371*59692Selan 			     reg_names[FRAME_POINTER_REGNUM],
372*59692Selan 			     offset + fsize, reg_names[i]);
373*59692Selan #endif
374*59692Selan 	      }
375*59692Selan             offset = offset - 4;
376*59692Selan           }
377*59692Selan     }
378*59692Selan   else if (mask)
379*59692Selan     {
380*59692Selan       if (big)
381*59692Selan 	{
382*59692Selan #ifdef MOTOROLA
383*59692Selan 	  asm_fprintf (stream, "\tmovm.l -%d(%s,%Ra0.l),%0I0x%x\n",
384*59692Selan 		       offset + fsize,
385*59692Selan 		       reg_names[FRAME_POINTER_REGNUM],
386*59692Selan 		       mask);
387*59692Selan #else
388*59692Selan 	  asm_fprintf (stream, "\tmoveml %s@(-%d,%Ra0:l),%0I0x%x\n",
389*59692Selan 		       reg_names[FRAME_POINTER_REGNUM],
390*59692Selan 		       offset + fsize, mask);
391*59692Selan #endif
392*59692Selan 	}
393*59692Selan       else if (! frame_pointer_needed)
394*59692Selan 	{
395*59692Selan #ifdef MOTOROLA
396*59692Selan 	  asm_fprintf (stream, "\tmovm.l (%Rsp)+,%0I0x%x\n", mask);
397*59692Selan #else
398*59692Selan 	  asm_fprintf (stream, "\tmoveml %Rsp@+,%0I0x%x\n", mask);
399*59692Selan #endif
400*59692Selan 	}
401*59692Selan       else
402*59692Selan 	{
403*59692Selan #ifdef MOTOROLA
404*59692Selan 	  asm_fprintf (stream, "\tmovm.l -%d(%s),%0I0x%x\n",
405*59692Selan 		       offset + fsize,
406*59692Selan 		       reg_names[FRAME_POINTER_REGNUM],
407*59692Selan 		       mask);
408*59692Selan #else
409*59692Selan 	  asm_fprintf (stream, "\tmoveml %s@(-%d),%0I0x%x\n",
410*59692Selan 		       reg_names[FRAME_POINTER_REGNUM],
411*59692Selan 		       offset + fsize, mask);
412*59692Selan #endif
413*59692Selan 	}
414*59692Selan     }
415*59692Selan   if (fmask)
416*59692Selan     {
417*59692Selan       if (big)
418*59692Selan 	{
419*59692Selan #ifdef MOTOROLA
420*59692Selan 	  asm_fprintf (stream, "\tfmovm -%d(%s,%Ra0.l),%0I0x%x\n",
421*59692Selan 		       foffset + fsize,
422*59692Selan 		       reg_names[FRAME_POINTER_REGNUM],
423*59692Selan 		       fmask);
424*59692Selan #else
425*59692Selan 	  asm_fprintf (stream, "\tfmovem %s@(-%d,%Ra0:l),%0I0x%x\n",
426*59692Selan 		       reg_names[FRAME_POINTER_REGNUM],
427*59692Selan 		       foffset + fsize, fmask);
428*59692Selan #endif
429*59692Selan 	}
430*59692Selan       else if (! frame_pointer_needed)
431*59692Selan 	{
432*59692Selan #ifdef MOTOROLA
433*59692Selan 	  asm_fprintf (stream, "\tfmovm (%Rsp)+,%0I0x%x\n", fmask);
434*59692Selan #else
435*59692Selan 	  asm_fprintf (stream, "\tfmovem %Rsp@+,%0I0x%x\n", fmask);
436*59692Selan #endif
437*59692Selan 	}
438*59692Selan       else
439*59692Selan 	{
440*59692Selan #ifdef MOTOROLA
441*59692Selan 	  asm_fprintf (stream, "\tfmovm -%d(%s),%0I0x%x\n",
442*59692Selan 		       foffset + fsize,
443*59692Selan 		       reg_names[FRAME_POINTER_REGNUM],
444*59692Selan 		       fmask);
445*59692Selan #else
446*59692Selan 	  asm_fprintf (stream, "\tfmovem %s@(-%d),%0I0x%x\n",
447*59692Selan 		       reg_names[FRAME_POINTER_REGNUM],
448*59692Selan 		       foffset + fsize, fmask);
449*59692Selan #endif
450*59692Selan 	}
451*59692Selan     }
452*59692Selan   if (fpoffset != 0)
453*59692Selan     for (regno = 55; regno >= 24; regno--)
454*59692Selan       if (regs_ever_live[regno] && ! call_used_regs[regno])
455*59692Selan         {
456*59692Selan 	  if (big)
457*59692Selan 	    {
458*59692Selan #ifdef MOTOROLA
459*59692Selan 	      asm_fprintf (stream, "\tfpmovd -%d(%s,%Ra0.l), %s\n",
460*59692Selan 			   fpoffset + fsize,
461*59692Selan 			   reg_names[FRAME_POINTER_REGNUM],
462*59692Selan 			   reg_names[regno]);
463*59692Selan #else
464*59692Selan 	      asm_fprintf (stream, "\tfpmoved %s@(-%d,%Ra0:l), %s\n",
465*59692Selan 			   reg_names[FRAME_POINTER_REGNUM],
466*59692Selan 			   fpoffset + fsize, reg_names[regno]);
467*59692Selan #endif
468*59692Selan 	    }
469*59692Selan 	  else if (! frame_pointer_needed)
470*59692Selan 	    {
471*59692Selan #ifdef MOTOROLA
472*59692Selan 	      asm_fprintf (stream, "\tfpmovd (%Rsp)+,%s\n",
473*59692Selan 			   reg_names[regno]);
474*59692Selan #else
475*59692Selan 	      asm_fprintf (stream, "\tfpmoved %Rsp@+, %s\n",
476*59692Selan 			   reg_names[regno]);
477*59692Selan #endif
478*59692Selan 	    }
479*59692Selan 	  else
480*59692Selan 	    {
481*59692Selan #ifdef MOTOROLA
482*59692Selan 	      asm_fprintf (stream, "\tfpmovd -%d(%s), %s\n",
483*59692Selan 			   fpoffset + fsize,
484*59692Selan 			   reg_names[FRAME_POINTER_REGNUM],
485*59692Selan 			   reg_names[regno]);
486*59692Selan #else
487*59692Selan 	      asm_fprintf (stream, "\tfpmoved %s@(-%d), %s\n",
488*59692Selan 			   reg_names[FRAME_POINTER_REGNUM],
489*59692Selan 			   fpoffset + fsize, reg_names[regno]);
490*59692Selan #endif
491*59692Selan 	    }
492*59692Selan 	  fpoffset -= 8;
493*59692Selan 	}
494*59692Selan   if (frame_pointer_needed)
495*59692Selan     fprintf (stream, "\tunlk %s\n",
496*59692Selan 	     reg_names[FRAME_POINTER_REGNUM]);
497*59692Selan   else if (fsize)
498*59692Selan     {
499*59692Selan       if (fsize + 4 < 0x8000)
500*59692Selan 	{
501*59692Selan #ifdef MOTOROLA
502*59692Selan 	  asm_fprintf (stream, "\tadd.w %0I%d,%Rsp\n", fsize + 4);
503*59692Selan #else
504*59692Selan 	  asm_fprintf (stream, "\taddw %0I%d,%Rsp\n", fsize + 4);
505*59692Selan #endif
506*59692Selan 	}
507*59692Selan       else
508*59692Selan 	{
509*59692Selan #ifdef MOTOROLA
510*59692Selan 	  asm_fprintf (stream, "\tadd.l %0I%d,%Rsp\n", fsize + 4);
511*59692Selan #else
512*59692Selan 	  asm_fprintf (stream, "\taddl %0I%d,%Rsp\n", fsize + 4);
513*59692Selan #endif
514*59692Selan 	}
515*59692Selan     }
516*59692Selan   if (current_function_pops_args)
517*59692Selan     asm_fprintf (stream, "\trtd %0I%d\n", current_function_pops_args);
518*59692Selan   else
519*59692Selan     fprintf (stream, "\trts\n");
520*59692Selan }
521*59692Selan 
522*59692Selan /* Similar to general_operand, but exclude stack_pointer_rtx.  */
523*59692Selan 
524*59692Selan int
525*59692Selan not_sp_operand (op, mode)
526*59692Selan      register rtx op;
527*59692Selan      enum machine_mode mode;
528*59692Selan {
529*59692Selan   return op != stack_pointer_rtx && general_operand (op, mode);
530*59692Selan }
531*59692Selan 
532*59692Selan /* Return TRUE if X is a valid comparison operator for the dbcc
533*59692Selan    instruction.
534*59692Selan 
535*59692Selan    Note it rejects floating point comparison operators.
536*59692Selan    (In the future we could use Fdbcc).
537*59692Selan 
538*59692Selan    It also rejects some comparisons when CC_NO_OVERFLOW is set.  */
539*59692Selan 
540*59692Selan int
541*59692Selan valid_dbcc_comparison_p (x, mode)
542*59692Selan      rtx x;
543*59692Selan      enum machine_mode mode;
544*59692Selan {
545*59692Selan   /* We could add support for these in the future */
546*59692Selan   if (cc_prev_status.flags & CC_IN_68881)
547*59692Selan     return 0;
548*59692Selan 
549*59692Selan   switch (GET_CODE (x))
550*59692Selan     {
551*59692Selan 
552*59692Selan       case EQ: case NE: case GTU: case LTU:
553*59692Selan       case GEU: case LEU:
554*59692Selan         return 1;
555*59692Selan 
556*59692Selan       /* Reject some when CC_NO_OVERFLOW is set.  This may be over
557*59692Selan          conservative */
558*59692Selan       case GT: case LT: case GE: case LE:
559*59692Selan         return ! (cc_prev_status.flags & CC_NO_OVERFLOW);
560*59692Selan       default:
561*59692Selan         return 0;
562*59692Selan     }
563*59692Selan }
564*59692Selan 
565*59692Selan /* Output a dbCC; jCC sequence.  Note we do not handle the
566*59692Selan    floating point version of this sequence (Fdbcc).  We also
567*59692Selan    do not handle alternative conditions when CC_NO_OVERFLOW is
568*59692Selan    set.  It is assumed that valid_dbcc_comparison_p will kick
569*59692Selan    those out before we get here.  */
570*59692Selan 
571*59692Selan output_dbcc_and_branch (operands)
572*59692Selan      rtx *operands;
573*59692Selan {
574*59692Selan 
575*59692Selan   switch (GET_CODE (operands[3]))
576*59692Selan     {
577*59692Selan       case EQ:
578*59692Selan #ifdef MOTOROLA
579*59692Selan         output_asm_insn ("dbeq %0,%l1\n\tjbeq %l2", operands);
580*59692Selan #else
581*59692Selan         output_asm_insn ("dbeq %0,%l1\n\tjeq %l2", operands);
582*59692Selan #endif
583*59692Selan         break;
584*59692Selan 
585*59692Selan       case NE:
586*59692Selan #ifdef MOTOROLA
587*59692Selan         output_asm_insn ("dbne %0,%l1\n\tjbne %l2", operands);
588*59692Selan #else
589*59692Selan         output_asm_insn ("dbne %0,%l1\n\tjne %l2", operands);
590*59692Selan #endif
591*59692Selan         break;
592*59692Selan 
593*59692Selan       case GT:
594*59692Selan #ifdef MOTOROLA
595*59692Selan         output_asm_insn ("dbgt %0,%l1\n\tjbgt %l2", operands);
596*59692Selan #else
597*59692Selan         output_asm_insn ("dbgt %0,%l1\n\tjgt %l2", operands);
598*59692Selan #endif
599*59692Selan         break;
600*59692Selan 
601*59692Selan       case GTU:
602*59692Selan #ifdef MOTOROLA
603*59692Selan         output_asm_insn ("dbhi %0,%l1\n\tjbhi %l2", operands);
604*59692Selan #else
605*59692Selan         output_asm_insn ("dbhi %0,%l1\n\tjhi %l2", operands);
606*59692Selan #endif
607*59692Selan         break;
608*59692Selan 
609*59692Selan       case LT:
610*59692Selan #ifdef MOTOROLA
611*59692Selan         output_asm_insn ("dblt %0,%l1\n\tjblt %l2", operands);
612*59692Selan #else
613*59692Selan         output_asm_insn ("dblt %0,%l1\n\tjlt %l2", operands);
614*59692Selan #endif
615*59692Selan         break;
616*59692Selan 
617*59692Selan       case LTU:
618*59692Selan #ifdef MOTOROLA
619*59692Selan         output_asm_insn ("dbcs %0,%l1\n\tjbcs %l2", operands);
620*59692Selan #else
621*59692Selan         output_asm_insn ("dbcs %0,%l1\n\tjcs %l2", operands);
622*59692Selan #endif
623*59692Selan         break;
624*59692Selan 
625*59692Selan       case GE:
626*59692Selan #ifdef MOTOROLA
627*59692Selan         output_asm_insn ("dbge %0,%l1\n\tjbge %l2", operands);
628*59692Selan #else
629*59692Selan         output_asm_insn ("dbge %0,%l1\n\tjge %l2", operands);
630*59692Selan #endif
631*59692Selan         break;
632*59692Selan 
633*59692Selan       case GEU:
634*59692Selan #ifdef MOTOROLA
635*59692Selan         output_asm_insn ("dbcc %0,%l1\n\tjbcc %l2", operands);
636*59692Selan #else
637*59692Selan         output_asm_insn ("dbcc %0,%l1\n\tjcc %l2", operands);
638*59692Selan #endif
639*59692Selan         break;
640*59692Selan 
641*59692Selan       case LE:
642*59692Selan #ifdef MOTOROLA
643*59692Selan         output_asm_insn ("dble %0,%l1\n\tjble %l2", operands);
644*59692Selan #else
645*59692Selan         output_asm_insn ("dble %0,%l1\n\tjle %l2", operands);
646*59692Selan #endif
647*59692Selan         break;
648*59692Selan 
649*59692Selan       case LEU:
650*59692Selan #ifdef MOTOROLA
651*59692Selan         output_asm_insn ("dbls %0,%l1\n\tjbls %l2", operands);
652*59692Selan #else
653*59692Selan         output_asm_insn ("dbls %0,%l1\n\tjls %l2", operands);
654*59692Selan #endif
655*59692Selan         break;
656*59692Selan 
657*59692Selan       default:
658*59692Selan 	abort ();
659*59692Selan     }
660*59692Selan 
661*59692Selan   /* If the decrement is to be done in SImode, then we have
662*59692Selan      to compensate for the fact that dbcc decrements in HImode. */
663*59692Selan   switch (GET_MODE (operands[0]))
664*59692Selan     {
665*59692Selan       case SImode:
666*59692Selan #ifdef MOTOROLA
667*59692Selan         output_asm_insn ("clr%.w %0\n\tsubq%.l %#1,%0\n\tjbpl %l1", operands);
668*59692Selan #else
669*59692Selan         output_asm_insn ("clr%.w %0\n\tsubq%.l %#1,%0\n\tjpl %l1", operands);
670*59692Selan #endif
671*59692Selan         break;
672*59692Selan 
673*59692Selan       case HImode:
674*59692Selan         break;
675*59692Selan 
676*59692Selan       default:
677*59692Selan         abort ();
678*59692Selan     }
679*59692Selan }
680*59692Selan 
681*59692Selan char *
682*59692Selan output_btst (operands, countop, dataop, insn, signpos)
683*59692Selan      rtx *operands;
684*59692Selan      rtx countop, dataop;
685*59692Selan      rtx insn;
686*59692Selan      int signpos;
687*59692Selan {
688*59692Selan   operands[0] = countop;
689*59692Selan   operands[1] = dataop;
690*59692Selan 
691*59692Selan   if (GET_CODE (countop) == CONST_INT)
692*59692Selan     {
693*59692Selan       register int count = INTVAL (countop);
694*59692Selan       /* If COUNT is bigger than size of storage unit in use,
695*59692Selan 	 advance to the containing unit of same size.  */
696*59692Selan       if (count > signpos)
697*59692Selan 	{
698*59692Selan 	  int offset = (count & ~signpos) / 8;
699*59692Selan 	  count = count & signpos;
700*59692Selan 	  operands[1] = dataop = adj_offsettable_operand (dataop, offset);
701*59692Selan 	}
702*59692Selan       if (count == signpos)
703*59692Selan 	cc_status.flags = CC_NOT_POSITIVE | CC_Z_IN_NOT_N;
704*59692Selan       else
705*59692Selan 	cc_status.flags = CC_NOT_NEGATIVE | CC_Z_IN_NOT_N;
706*59692Selan 
707*59692Selan       /* These three statements used to use next_insns_test_no...
708*59692Selan 	 but it appears that this should do the same job.  */
709*59692Selan       if (count == 31
710*59692Selan 	  && next_insn_tests_no_inequality (insn))
711*59692Selan 	return "tst%.l %1";
712*59692Selan       if (count == 15
713*59692Selan 	  && next_insn_tests_no_inequality (insn))
714*59692Selan 	return "tst%.w %1";
715*59692Selan       if (count == 7
716*59692Selan 	  && next_insn_tests_no_inequality (insn))
717*59692Selan 	return "tst%.b %1";
718*59692Selan 
719*59692Selan       cc_status.flags = CC_NOT_NEGATIVE;
720*59692Selan     }
721*59692Selan   return "btst %0,%1";
722*59692Selan }
723*59692Selan 
724*59692Selan /* Returns 1 if OP is either a symbol reference or a sum of a symbol
725*59692Selan    reference and a constant.  */
726*59692Selan 
727*59692Selan int
728*59692Selan symbolic_operand (op, mode)
729*59692Selan      register rtx op;
730*59692Selan      enum machine_mode mode;
731*59692Selan {
732*59692Selan   switch (GET_CODE (op))
733*59692Selan     {
734*59692Selan     case SYMBOL_REF:
735*59692Selan     case LABEL_REF:
736*59692Selan       return 1;
737*59692Selan 
738*59692Selan     case CONST:
739*59692Selan       op = XEXP (op, 0);
740*59692Selan       return ((GET_CODE (XEXP (op, 0)) == SYMBOL_REF
741*59692Selan 	       || GET_CODE (XEXP (op, 0)) == LABEL_REF)
742*59692Selan 	      && GET_CODE (XEXP (op, 1)) == CONST_INT);
743*59692Selan 
744*59692Selan #if 0 /* Deleted, with corresponding change in m68k.h,
745*59692Selan 	 so as to fit the specs.  No CONST_DOUBLE is ever symbolic.  */
746*59692Selan     case CONST_DOUBLE:
747*59692Selan       return GET_MODE (op) == mode;
748*59692Selan #endif
749*59692Selan 
750*59692Selan     default:
751*59692Selan       return 0;
752*59692Selan     }
753*59692Selan }
754*59692Selan 
755*59692Selan 
756*59692Selan /* Legitimize PIC addresses.  If the address is already
757*59692Selan    position-independent, we return ORIG.  Newly generated
758*59692Selan    position-independent addresses go to REG.  If we need more
759*59692Selan    than one register, we lose.
760*59692Selan 
761*59692Selan    An address is legitimized by making an indirect reference
762*59692Selan    through the Global Offset Table with the name of the symbol
763*59692Selan    used as an offset.
764*59692Selan 
765*59692Selan    The assembler and linker are responsible for placing the
766*59692Selan    address of the symbol in the GOT.  The function prologue
767*59692Selan    is responsible for initializing a5 to the starting address
768*59692Selan    of the GOT.
769*59692Selan 
770*59692Selan    The assembler is also responsible for translating a symbol name
771*59692Selan    into a constant displacement from the start of the GOT.
772*59692Selan 
773*59692Selan    A quick example may make things a little clearer:
774*59692Selan 
775*59692Selan    When not generating PIC code to store the value 12345 into _foo
776*59692Selan    we would generate the following code:
777*59692Selan 
778*59692Selan 	movel #12345, _foo
779*59692Selan 
780*59692Selan    When generating PIC two transformations are made.  First, the compiler
781*59692Selan    loads the address of foo into a register.  So the first transformation makes:
782*59692Selan 
783*59692Selan 	lea	_foo, a0
784*59692Selan 	movel   #12345, a0@
785*59692Selan 
786*59692Selan    The code in movsi will intercept the lea instruction and call this
787*59692Selan    routine which will transform the instructions into:
788*59692Selan 
789*59692Selan 	movel   a5@(_foo:w), a0
790*59692Selan 	movel   #12345, a0@
791*59692Selan 
792*59692Selan 
793*59692Selan    That (in a nutshell) is how *all* symbol and label references are
794*59692Selan    handled.  */
795*59692Selan 
796*59692Selan rtx
797*59692Selan legitimize_pic_address (orig, mode, reg)
798*59692Selan      rtx orig, reg;
799*59692Selan      enum machine_mode mode;
800*59692Selan {
801*59692Selan   rtx pic_ref = orig;
802*59692Selan 
803*59692Selan   /* First handle a simple SYMBOL_REF or LABEL_REF */
804*59692Selan   if (GET_CODE (orig) == SYMBOL_REF || GET_CODE (orig) == LABEL_REF)
805*59692Selan     {
806*59692Selan       if (reg == 0)
807*59692Selan 	abort ();
808*59692Selan 
809*59692Selan       pic_ref = gen_rtx (MEM, Pmode,
810*59692Selan 			 gen_rtx (PLUS, Pmode,
811*59692Selan 				  pic_offset_table_rtx, orig));
812*59692Selan       current_function_uses_pic_offset_table = 1;
813*59692Selan       RTX_UNCHANGING_P (pic_ref) = 1;
814*59692Selan       emit_move_insn (reg, pic_ref);
815*59692Selan       return reg;
816*59692Selan     }
817*59692Selan   else if (GET_CODE (orig) == CONST)
818*59692Selan     {
819*59692Selan       rtx base, offset;
820*59692Selan 
821*59692Selan       /* Make sure this is CONST has not already been legitimized */
822*59692Selan       if (GET_CODE (XEXP (orig, 0)) == PLUS
823*59692Selan 	  && XEXP (XEXP (orig, 0), 0) == pic_offset_table_rtx)
824*59692Selan 	return orig;
825*59692Selan 
826*59692Selan       if (reg == 0)
827*59692Selan 	abort ();
828*59692Selan 
829*59692Selan       /* legitimize both operands of the PLUS */
830*59692Selan       if (GET_CODE (XEXP (orig, 0)) == PLUS)
831*59692Selan 	{
832*59692Selan 	  base = legitimize_pic_address (XEXP (XEXP (orig, 0), 0), Pmode, reg);
833*59692Selan 	  orig = legitimize_pic_address (XEXP (XEXP (orig, 0), 1), Pmode,
834*59692Selan 					 base == reg ? 0 : reg);
835*59692Selan 	}
836*59692Selan       else abort ();
837*59692Selan 
838*59692Selan       if (GET_CODE (orig) == CONST_INT)
839*59692Selan 	return plus_constant_for_output (base, INTVAL (orig));
840*59692Selan       pic_ref = gen_rtx (PLUS, Pmode, base, orig);
841*59692Selan       /* Likewise, should we set special REG_NOTEs here?  */
842*59692Selan     }
843*59692Selan   return pic_ref;
844*59692Selan }
845*59692Selan 
846*59692Selan 
847*59692Selan /* Return the best assembler insn template
848*59692Selan    for moving operands[1] into operands[0] as a fullword.  */
849*59692Selan 
850*59692Selan static char *
851*59692Selan singlemove_string (operands)
852*59692Selan      rtx *operands;
853*59692Selan {
854*59692Selan #ifdef SUPPORT_SUN_FPA
855*59692Selan   if (FPA_REG_P (operands[0]) || FPA_REG_P (operands[1]))
856*59692Selan     return "fpmoves %1,%0";
857*59692Selan #endif
858*59692Selan   if (DATA_REG_P (operands[0])
859*59692Selan       && GET_CODE (operands[1]) == CONST_INT
860*59692Selan       && INTVAL (operands[1]) < 128
861*59692Selan       && INTVAL (operands[1]) >= -128)
862*59692Selan     {
863*59692Selan #if defined (MOTOROLA) && !defined (CRDS)
864*59692Selan       return "moveq%.l %1,%0";
865*59692Selan #else
866*59692Selan       return "moveq %1,%0";
867*59692Selan #endif
868*59692Selan     }
869*59692Selan   if (operands[1] != const0_rtx)
870*59692Selan     return "move%.l %1,%0";
871*59692Selan   if (! ADDRESS_REG_P (operands[0]))
872*59692Selan     return "clr%.l %0";
873*59692Selan   return "sub%.l %0,%0";
874*59692Selan }
875*59692Selan 
876*59692Selan /* Output assembler code to perform a doubleword move insn
877*59692Selan    with operands OPERANDS.  */
878*59692Selan 
879*59692Selan char *
880*59692Selan output_move_double (operands)
881*59692Selan      rtx *operands;
882*59692Selan {
883*59692Selan   enum { REGOP, OFFSOP, MEMOP, PUSHOP, POPOP, CNSTOP, RNDOP } optype0, optype1;
884*59692Selan   rtx latehalf[2];
885*59692Selan   rtx addreg0 = 0, addreg1 = 0;
886*59692Selan 
887*59692Selan   /* First classify both operands.  */
888*59692Selan 
889*59692Selan   if (REG_P (operands[0]))
890*59692Selan     optype0 = REGOP;
891*59692Selan   else if (offsettable_memref_p (operands[0]))
892*59692Selan     optype0 = OFFSOP;
893*59692Selan   else if (GET_CODE (XEXP (operands[0], 0)) == POST_INC)
894*59692Selan     optype0 = POPOP;
895*59692Selan   else if (GET_CODE (XEXP (operands[0], 0)) == PRE_DEC)
896*59692Selan     optype0 = PUSHOP;
897*59692Selan   else if (GET_CODE (operands[0]) == MEM)
898*59692Selan     optype0 = MEMOP;
899*59692Selan   else
900*59692Selan     optype0 = RNDOP;
901*59692Selan 
902*59692Selan   if (REG_P (operands[1]))
903*59692Selan     optype1 = REGOP;
904*59692Selan   else if (CONSTANT_P (operands[1]))
905*59692Selan     optype1 = CNSTOP;
906*59692Selan   else if (offsettable_memref_p (operands[1]))
907*59692Selan     optype1 = OFFSOP;
908*59692Selan   else if (GET_CODE (XEXP (operands[1], 0)) == POST_INC)
909*59692Selan     optype1 = POPOP;
910*59692Selan   else if (GET_CODE (XEXP (operands[1], 0)) == PRE_DEC)
911*59692Selan     optype1 = PUSHOP;
912*59692Selan   else if (GET_CODE (operands[1]) == MEM)
913*59692Selan     optype1 = MEMOP;
914*59692Selan   else
915*59692Selan     optype1 = RNDOP;
916*59692Selan 
917*59692Selan   /* Check for the cases that the operand constraints are not
918*59692Selan      supposed to allow to happen.  Abort if we get one,
919*59692Selan      because generating code for these cases is painful.  */
920*59692Selan 
921*59692Selan   if (optype0 == RNDOP || optype1 == RNDOP)
922*59692Selan     abort ();
923*59692Selan 
924*59692Selan   /* If one operand is decrementing and one is incrementing
925*59692Selan      decrement the former register explicitly
926*59692Selan      and change that operand into ordinary indexing.  */
927*59692Selan 
928*59692Selan   if (optype0 == PUSHOP && optype1 == POPOP)
929*59692Selan     {
930*59692Selan       operands[0] = XEXP (XEXP (operands[0], 0), 0);
931*59692Selan       output_asm_insn ("subq%.l %#8,%0", operands);
932*59692Selan       operands[0] = gen_rtx (MEM, DImode, operands[0]);
933*59692Selan       optype0 = OFFSOP;
934*59692Selan     }
935*59692Selan   if (optype0 == POPOP && optype1 == PUSHOP)
936*59692Selan     {
937*59692Selan       operands[1] = XEXP (XEXP (operands[1], 0), 0);
938*59692Selan       output_asm_insn ("subq%.l %#8,%1", operands);
939*59692Selan       operands[1] = gen_rtx (MEM, DImode, operands[1]);
940*59692Selan       optype1 = OFFSOP;
941*59692Selan     }
942*59692Selan 
943*59692Selan   /* If an operand is an unoffsettable memory ref, find a register
944*59692Selan      we can increment temporarily to make it refer to the second word.  */
945*59692Selan 
946*59692Selan   if (optype0 == MEMOP)
947*59692Selan     addreg0 = find_addr_reg (XEXP (operands[0], 0));
948*59692Selan 
949*59692Selan   if (optype1 == MEMOP)
950*59692Selan     addreg1 = find_addr_reg (XEXP (operands[1], 0));
951*59692Selan 
952*59692Selan   /* Ok, we can do one word at a time.
953*59692Selan      Normally we do the low-numbered word first,
954*59692Selan      but if either operand is autodecrementing then we
955*59692Selan      do the high-numbered word first.
956*59692Selan 
957*59692Selan      In either case, set up in LATEHALF the operands to use
958*59692Selan      for the high-numbered word and in some cases alter the
959*59692Selan      operands in OPERANDS to be suitable for the low-numbered word.  */
960*59692Selan 
961*59692Selan   if (optype0 == REGOP)
962*59692Selan     latehalf[0] = gen_rtx (REG, SImode, REGNO (operands[0]) + 1);
963*59692Selan   else if (optype0 == OFFSOP)
964*59692Selan     latehalf[0] = adj_offsettable_operand (operands[0], 4);
965*59692Selan   else
966*59692Selan     latehalf[0] = operands[0];
967*59692Selan 
968*59692Selan   if (optype1 == REGOP)
969*59692Selan     latehalf[1] = gen_rtx (REG, SImode, REGNO (operands[1]) + 1);
970*59692Selan   else if (optype1 == OFFSOP)
971*59692Selan     latehalf[1] = adj_offsettable_operand (operands[1], 4);
972*59692Selan   else if (optype1 == CNSTOP)
973*59692Selan     split_double (operands[1], &operands[1], &latehalf[1]);
974*59692Selan   else
975*59692Selan     latehalf[1] = operands[1];
976*59692Selan 
977*59692Selan   /* If insn is effectively movd N(sp),-(sp) then we will do the
978*59692Selan      high word first.  We should use the adjusted operand 1 (which is N+4(sp))
979*59692Selan      for the low word as well, to compensate for the first decrement of sp.  */
980*59692Selan   if (optype0 == PUSHOP
981*59692Selan       && REGNO (XEXP (XEXP (operands[0], 0), 0)) == STACK_POINTER_REGNUM
982*59692Selan       && reg_overlap_mentioned_p (stack_pointer_rtx, operands[1]))
983*59692Selan     operands[1] = latehalf[1];
984*59692Selan 
985*59692Selan   /* If one or both operands autodecrementing,
986*59692Selan      do the two words, high-numbered first.  */
987*59692Selan 
988*59692Selan   /* Likewise,  the first move would clobber the source of the second one,
989*59692Selan      do them in the other order.  This happens only for registers;
990*59692Selan      such overlap can't happen in memory unless the user explicitly
991*59692Selan      sets it up, and that is an undefined circumstance.  */
992*59692Selan 
993*59692Selan   if (optype0 == PUSHOP || optype1 == PUSHOP
994*59692Selan       || (optype0 == REGOP && optype1 == REGOP
995*59692Selan 	  && REGNO (operands[0]) == REGNO (latehalf[1])))
996*59692Selan     {
997*59692Selan       /* Make any unoffsettable addresses point at high-numbered word.  */
998*59692Selan       if (addreg0)
999*59692Selan 	output_asm_insn ("addql %#4,%0", &addreg0);
1000*59692Selan       if (addreg1)
1001*59692Selan 	output_asm_insn ("addql %#4,%0", &addreg1);
1002*59692Selan 
1003*59692Selan       /* Do that word.  */
1004*59692Selan       output_asm_insn (singlemove_string (latehalf), latehalf);
1005*59692Selan 
1006*59692Selan       /* Undo the adds we just did.  */
1007*59692Selan       if (addreg0)
1008*59692Selan 	output_asm_insn ("subql %#4,%0", &addreg0);
1009*59692Selan       if (addreg1)
1010*59692Selan 	output_asm_insn ("subql %#4,%0", &addreg1);
1011*59692Selan 
1012*59692Selan       /* Do low-numbered word.  */
1013*59692Selan       return singlemove_string (operands);
1014*59692Selan     }
1015*59692Selan 
1016*59692Selan   /* Normal case: do the two words, low-numbered first.  */
1017*59692Selan 
1018*59692Selan   output_asm_insn (singlemove_string (operands), operands);
1019*59692Selan 
1020*59692Selan   /* Make any unoffsettable addresses point at high-numbered word.  */
1021*59692Selan   if (addreg0)
1022*59692Selan     output_asm_insn ("addql %#4,%0", &addreg0);
1023*59692Selan   if (addreg1)
1024*59692Selan     output_asm_insn ("addql %#4,%0", &addreg1);
1025*59692Selan 
1026*59692Selan   /* Do that word.  */
1027*59692Selan   output_asm_insn (singlemove_string (latehalf), latehalf);
1028*59692Selan 
1029*59692Selan   /* Undo the adds we just did.  */
1030*59692Selan   if (addreg0)
1031*59692Selan     output_asm_insn ("subql %#4,%0", &addreg0);
1032*59692Selan   if (addreg1)
1033*59692Selan     output_asm_insn ("subql %#4,%0", &addreg1);
1034*59692Selan 
1035*59692Selan   return "";
1036*59692Selan }
1037*59692Selan 
1038*59692Selan /* Return a REG that occurs in ADDR with coefficient 1.
1039*59692Selan    ADDR can be effectively incremented by incrementing REG.  */
1040*59692Selan 
1041*59692Selan static rtx
1042*59692Selan find_addr_reg (addr)
1043*59692Selan      rtx addr;
1044*59692Selan {
1045*59692Selan   while (GET_CODE (addr) == PLUS)
1046*59692Selan     {
1047*59692Selan       if (GET_CODE (XEXP (addr, 0)) == REG)
1048*59692Selan 	addr = XEXP (addr, 0);
1049*59692Selan       else if (GET_CODE (XEXP (addr, 1)) == REG)
1050*59692Selan 	addr = XEXP (addr, 1);
1051*59692Selan       else if (CONSTANT_P (XEXP (addr, 0)))
1052*59692Selan 	addr = XEXP (addr, 1);
1053*59692Selan       else if (CONSTANT_P (XEXP (addr, 1)))
1054*59692Selan 	addr = XEXP (addr, 0);
1055*59692Selan       else
1056*59692Selan 	abort ();
1057*59692Selan     }
1058*59692Selan   if (GET_CODE (addr) == REG)
1059*59692Selan     return addr;
1060*59692Selan   abort ();
1061*59692Selan }
1062*59692Selan 
1063*59692Selan /* Store in cc_status the expressions that the condition codes will
1064*59692Selan    describe after execution of an instruction whose pattern is EXP.
1065*59692Selan    Do not alter them if the instruction would not alter the cc's.  */
1066*59692Selan 
1067*59692Selan /* On the 68000, all the insns to store in an address register fail to
1068*59692Selan    set the cc's.  However, in some cases these instructions can make it
1069*59692Selan    possibly invalid to use the saved cc's.  In those cases we clear out
1070*59692Selan    some or all of the saved cc's so they won't be used.  */
1071*59692Selan 
1072*59692Selan notice_update_cc (exp, insn)
1073*59692Selan      rtx exp;
1074*59692Selan      rtx insn;
1075*59692Selan {
1076*59692Selan   /* If the cc is being set from the fpa and the expression is not an
1077*59692Selan      explicit floating point test instruction (which has code to deal with
1078*59692Selan      this), reinit the CC.  */
1079*59692Selan   if (((cc_status.value1 && FPA_REG_P (cc_status.value1))
1080*59692Selan        || (cc_status.value2 && FPA_REG_P (cc_status.value2)))
1081*59692Selan       && !(GET_CODE (exp) == PARALLEL
1082*59692Selan 	   && GET_CODE (XVECEXP (exp, 0, 0)) == SET
1083*59692Selan 	   && XEXP (XVECEXP (exp, 0, 0), 0) == cc0_rtx))
1084*59692Selan     {
1085*59692Selan       CC_STATUS_INIT;
1086*59692Selan     }
1087*59692Selan   else if (GET_CODE (exp) == SET)
1088*59692Selan     {
1089*59692Selan       if (GET_CODE (SET_SRC (exp)) == CALL)
1090*59692Selan 	{
1091*59692Selan 	  CC_STATUS_INIT;
1092*59692Selan 	}
1093*59692Selan       else if (ADDRESS_REG_P (SET_DEST (exp)))
1094*59692Selan 	{
1095*59692Selan 	  if (cc_status.value1
1096*59692Selan 	      && reg_overlap_mentioned_p (SET_DEST (exp), cc_status.value1))
1097*59692Selan 	    cc_status.value1 = 0;
1098*59692Selan 	  if (cc_status.value2
1099*59692Selan 	      && reg_overlap_mentioned_p (SET_DEST (exp), cc_status.value2))
1100*59692Selan 	    cc_status.value2 = 0;
1101*59692Selan 	}
1102*59692Selan       else if (!FP_REG_P (SET_DEST (exp))
1103*59692Selan 	       && SET_DEST (exp) != cc0_rtx
1104*59692Selan 	       && (FP_REG_P (SET_SRC (exp))
1105*59692Selan 		   || GET_CODE (SET_SRC (exp)) == FIX
1106*59692Selan 		   || GET_CODE (SET_SRC (exp)) == FLOAT_TRUNCATE
1107*59692Selan 		   || GET_CODE (SET_SRC (exp)) == FLOAT_EXTEND))
1108*59692Selan 	{
1109*59692Selan 	  CC_STATUS_INIT;
1110*59692Selan 	}
1111*59692Selan       /* A pair of move insns doesn't produce a useful overall cc.  */
1112*59692Selan       else if (!FP_REG_P (SET_DEST (exp))
1113*59692Selan 	       && !FP_REG_P (SET_SRC (exp))
1114*59692Selan 	       && GET_MODE_SIZE (GET_MODE (SET_SRC (exp))) > 4
1115*59692Selan 	       && (GET_CODE (SET_SRC (exp)) == REG
1116*59692Selan 		   || GET_CODE (SET_SRC (exp)) == MEM
1117*59692Selan 		   || GET_CODE (SET_SRC (exp)) == CONST_DOUBLE))
1118*59692Selan 	{
1119*59692Selan 	  CC_STATUS_INIT;
1120*59692Selan 	}
1121*59692Selan       else if (GET_CODE (SET_SRC (exp)) == CALL)
1122*59692Selan 	{
1123*59692Selan 	  CC_STATUS_INIT;
1124*59692Selan 	}
1125*59692Selan       else if (XEXP (exp, 0) != pc_rtx)
1126*59692Selan 	{
1127*59692Selan 	  cc_status.flags = 0;
1128*59692Selan 	  cc_status.value1 = XEXP (exp, 0);
1129*59692Selan 	  cc_status.value2 = XEXP (exp, 1);
1130*59692Selan 	}
1131*59692Selan     }
1132*59692Selan   else if (GET_CODE (exp) == PARALLEL
1133*59692Selan 	   && GET_CODE (XVECEXP (exp, 0, 0)) == SET)
1134*59692Selan     {
1135*59692Selan       if (ADDRESS_REG_P (XEXP (XVECEXP (exp, 0, 0), 0)))
1136*59692Selan 	CC_STATUS_INIT;
1137*59692Selan       else if (XEXP (XVECEXP (exp, 0, 0), 0) != pc_rtx)
1138*59692Selan 	{
1139*59692Selan 	  cc_status.flags = 0;
1140*59692Selan 	  cc_status.value1 = XEXP (XVECEXP (exp, 0, 0), 0);
1141*59692Selan 	  cc_status.value2 = XEXP (XVECEXP (exp, 0, 0), 1);
1142*59692Selan 	}
1143*59692Selan     }
1144*59692Selan   else
1145*59692Selan     CC_STATUS_INIT;
1146*59692Selan   if (cc_status.value2 != 0
1147*59692Selan       && ADDRESS_REG_P (cc_status.value2)
1148*59692Selan       && GET_MODE (cc_status.value2) == QImode)
1149*59692Selan     CC_STATUS_INIT;
1150*59692Selan   if (cc_status.value2 != 0
1151*59692Selan       && !(cc_status.value1 && FPA_REG_P (cc_status.value1)))
1152*59692Selan     switch (GET_CODE (cc_status.value2))
1153*59692Selan       {
1154*59692Selan       case PLUS: case MINUS: case MULT:
1155*59692Selan       case DIV: case UDIV: case MOD: case UMOD: case NEG:
1156*59692Selan       case ASHIFT: case LSHIFT: case ASHIFTRT: case LSHIFTRT:
1157*59692Selan       case ROTATE: case ROTATERT:
1158*59692Selan 	if (GET_MODE (cc_status.value2) != VOIDmode)
1159*59692Selan 	  cc_status.flags |= CC_NO_OVERFLOW;
1160*59692Selan 	break;
1161*59692Selan       case ZERO_EXTEND:
1162*59692Selan 	/* (SET r1 (ZERO_EXTEND r2)) on this machine
1163*59692Selan 	   ends with a move insn moving r2 in r2's mode.
1164*59692Selan 	   Thus, the cc's are set for r2.
1165*59692Selan 	   This can set N bit spuriously. */
1166*59692Selan 	cc_status.flags |= CC_NOT_NEGATIVE;
1167*59692Selan       }
1168*59692Selan   if (cc_status.value1 && GET_CODE (cc_status.value1) == REG
1169*59692Selan       && cc_status.value2
1170*59692Selan       && reg_overlap_mentioned_p (cc_status.value1, cc_status.value2))
1171*59692Selan     cc_status.value2 = 0;
1172*59692Selan   if (((cc_status.value1 && FP_REG_P (cc_status.value1))
1173*59692Selan        || (cc_status.value2 && FP_REG_P (cc_status.value2)))
1174*59692Selan       && !((cc_status.value1 && FPA_REG_P (cc_status.value1))
1175*59692Selan 	   || (cc_status.value2 && FPA_REG_P (cc_status.value2))))
1176*59692Selan     cc_status.flags = CC_IN_68881;
1177*59692Selan }
1178*59692Selan 
1179*59692Selan char *
1180*59692Selan output_move_const_double (operands)
1181*59692Selan      rtx *operands;
1182*59692Selan {
1183*59692Selan #ifdef SUPPORT_SUN_FPA
1184*59692Selan   if (TARGET_FPA && FPA_REG_P (operands[0]))
1185*59692Selan     {
1186*59692Selan       int code = standard_sun_fpa_constant_p (operands[1]);
1187*59692Selan 
1188*59692Selan       if (code != 0)
1189*59692Selan 	{
1190*59692Selan 	  static char buf[40];
1191*59692Selan 
1192*59692Selan 	  sprintf (buf, "fpmove%%.d %%%%%d,%%0", code & 0x1ff);
1193*59692Selan 	  return buf;
1194*59692Selan 	}
1195*59692Selan       return "fpmove%.d %1,%0";
1196*59692Selan     }
1197*59692Selan   else
1198*59692Selan #endif
1199*59692Selan     {
1200*59692Selan       int code = standard_68881_constant_p (operands[1]);
1201*59692Selan 
1202*59692Selan       if (code != 0)
1203*59692Selan 	{
1204*59692Selan 	  static char buf[40];
1205*59692Selan 
1206*59692Selan 	  sprintf (buf, "fmovecr %%#0x%x,%%0", code & 0xff);
1207*59692Selan 	  return buf;
1208*59692Selan 	}
1209*59692Selan       return "fmove%.d %1,%0";
1210*59692Selan     }
1211*59692Selan }
1212*59692Selan 
1213*59692Selan char *
1214*59692Selan output_move_const_single (operands)
1215*59692Selan      rtx *operands;
1216*59692Selan {
1217*59692Selan #ifdef SUPPORT_SUN_FPA
1218*59692Selan   if (TARGET_FPA)
1219*59692Selan     {
1220*59692Selan       int code = standard_sun_fpa_constant_p (operands[1]);
1221*59692Selan 
1222*59692Selan       if (code != 0)
1223*59692Selan 	{
1224*59692Selan 	  static char buf[40];
1225*59692Selan 
1226*59692Selan 	  sprintf (buf, "fpmove%%.s %%%%%d,%%0", code & 0x1ff);
1227*59692Selan 	  return buf;
1228*59692Selan 	}
1229*59692Selan       return "fpmove%.s %1,%0";
1230*59692Selan     }
1231*59692Selan   else
1232*59692Selan #endif /* defined SUPPORT_SUN_FPA */
1233*59692Selan     {
1234*59692Selan       int code = standard_68881_constant_p (operands[1]);
1235*59692Selan 
1236*59692Selan       if (code != 0)
1237*59692Selan 	{
1238*59692Selan 	  static char buf[40];
1239*59692Selan 
1240*59692Selan 	  sprintf (buf, "fmovecr %%#0x%x,%%0", code & 0xff);
1241*59692Selan 	  return buf;
1242*59692Selan 	}
1243*59692Selan       return "fmove%.s %f1,%0";
1244*59692Selan     }
1245*59692Selan }
1246*59692Selan 
1247*59692Selan /* Return nonzero if X, a CONST_DOUBLE, has a value that we can get
1248*59692Selan    from the "fmovecr" instruction.
1249*59692Selan    The value, anded with 0xff, gives the code to use in fmovecr
1250*59692Selan    to get the desired constant.  */
1251*59692Selan 
1252*59692Selan /* ??? This code should be fixed for cross-compilation. */
1253*59692Selan 
1254*59692Selan int
1255*59692Selan standard_68881_constant_p (x)
1256*59692Selan      rtx x;
1257*59692Selan {
1258*59692Selan   register double d;
1259*59692Selan 
1260*59692Selan   /* fmovecr must be emulated on the 68040, so it shouldn't be used at all. */
1261*59692Selan   if (TARGET_68040)
1262*59692Selan     return 0;
1263*59692Selan 
1264*59692Selan #if HOST_FLOAT_FORMAT != TARGET_FLOAT_FORMAT
1265*59692Selan   if (! flag_pretend_float)
1266*59692Selan     return 0;
1267*59692Selan #endif
1268*59692Selan 
1269*59692Selan   REAL_VALUE_FROM_CONST_DOUBLE (d, x);
1270*59692Selan 
1271*59692Selan   if (d == 0)
1272*59692Selan     return 0x0f;
1273*59692Selan   /* Note: there are various other constants available
1274*59692Selan      but it is a nuisance to put in their values here.  */
1275*59692Selan   if (d == 1)
1276*59692Selan     return 0x32;
1277*59692Selan   if (d == 10)
1278*59692Selan     return 0x33;
1279*59692Selan   if (d == 100)
1280*59692Selan     return 0x34;
1281*59692Selan   if (d == 10000)
1282*59692Selan     return 0x35;
1283*59692Selan   if (d == 1e8)
1284*59692Selan     return 0x36;
1285*59692Selan   if (GET_MODE (x) == SFmode)
1286*59692Selan     return 0;
1287*59692Selan   if (d == 1e16)
1288*59692Selan     return 0x37;
1289*59692Selan   /* larger powers of ten in the constants ram are not used
1290*59692Selan      because they are not equal to a `double' C constant.  */
1291*59692Selan   return 0;
1292*59692Selan }
1293*59692Selan 
1294*59692Selan /* If X is a floating-point constant, return the logarithm of X base 2,
1295*59692Selan    or 0 if X is not a power of 2.  */
1296*59692Selan 
1297*59692Selan int
1298*59692Selan floating_exact_log2 (x)
1299*59692Selan      rtx x;
1300*59692Selan {
1301*59692Selan   register double d, d1;
1302*59692Selan   int i;
1303*59692Selan 
1304*59692Selan #if HOST_FLOAT_FORMAT != TARGET_FLOAT_FORMAT
1305*59692Selan   if (! flag_pretend_float)
1306*59692Selan     return 0;
1307*59692Selan #endif
1308*59692Selan 
1309*59692Selan   REAL_VALUE_FROM_CONST_DOUBLE (d, x);
1310*59692Selan 
1311*59692Selan   if (! (d > 0))
1312*59692Selan     return 0;
1313*59692Selan 
1314*59692Selan   for (d1 = 1.0, i = 0; d1 < d; d1 *= 2.0, i++)
1315*59692Selan     ;
1316*59692Selan 
1317*59692Selan   if (d == d1)
1318*59692Selan     return i;
1319*59692Selan 
1320*59692Selan   return 0;
1321*59692Selan }
1322*59692Selan 
1323*59692Selan #ifdef SUPPORT_SUN_FPA
1324*59692Selan /* Return nonzero if X, a CONST_DOUBLE, has a value that we can get
1325*59692Selan    from the Sun FPA's constant RAM.
1326*59692Selan    The value returned, anded with 0x1ff, gives the code to use in fpmove
1327*59692Selan    to get the desired constant. */
1328*59692Selan #define S_E (2.718281745910644531)
1329*59692Selan #define D_E (2.718281828459045091)
1330*59692Selan #define S_PI (3.141592741012573242)
1331*59692Selan #define D_PI (3.141592653589793116)
1332*59692Selan #define S_SQRT2 (1.414213538169860840)
1333*59692Selan #define D_SQRT2 (1.414213562373095145)
1334*59692Selan #define S_LOG2ofE (1.442695021629333496)
1335*59692Selan #define D_LOG2ofE (1.442695040888963387)
1336*59692Selan #define S_LOG2of10 (3.321928024291992188)
1337*59692Selan #define D_LOG2of10 (3.321928024887362182)
1338*59692Selan #define S_LOGEof2 (0.6931471824645996094)
1339*59692Selan #define D_LOGEof2 (0.6931471805599452862)
1340*59692Selan #define S_LOGEof10 (2.302585124969482442)
1341*59692Selan #define D_LOGEof10 (2.302585092994045901)
1342*59692Selan #define S_LOG10of2 (0.3010300099849700928)
1343*59692Selan #define D_LOG10of2 (0.3010299956639811980)
1344*59692Selan #define S_LOG10ofE (0.4342944920063018799)
1345*59692Selan #define D_LOG10ofE (0.4342944819032518167)
1346*59692Selan 
1347*59692Selan /* This code should be fixed for cross-compilation. */
1348*59692Selan 
1349*59692Selan int
1350*59692Selan standard_sun_fpa_constant_p (x)
1351*59692Selan      rtx x;
1352*59692Selan {
1353*59692Selan   register double d;
1354*59692Selan 
1355*59692Selan #if HOST_FLOAT_FORMAT != TARGET_FLOAT_FORMAT
1356*59692Selan   if (! flag_pretend_float)
1357*59692Selan     return 0;
1358*59692Selan #endif
1359*59692Selan 
1360*59692Selan   REAL_VALUE_FROM_CONST_DOUBLE (d, x);
1361*59692Selan 
1362*59692Selan   if (d == 0.0)
1363*59692Selan     return 0x200;		/* 0 once 0x1ff is anded with it */
1364*59692Selan   if (d == 1.0)
1365*59692Selan     return 0xe;
1366*59692Selan   if (d == 0.5)
1367*59692Selan     return 0xf;
1368*59692Selan   if (d == -1.0)
1369*59692Selan     return 0x10;
1370*59692Selan   if (d == 2.0)
1371*59692Selan     return 0x11;
1372*59692Selan   if (d == 3.0)
1373*59692Selan     return 0xB1;
1374*59692Selan   if (d == 4.0)
1375*59692Selan     return 0x12;
1376*59692Selan   if (d == 8.0)
1377*59692Selan     return 0x13;
1378*59692Selan   if (d == 0.25)
1379*59692Selan     return 0x15;
1380*59692Selan   if (d == 0.125)
1381*59692Selan     return 0x16;
1382*59692Selan   if (d == 10.0)
1383*59692Selan     return 0x17;
1384*59692Selan   if (d == -(1.0/2.0))
1385*59692Selan     return 0x2E;
1386*59692Selan 
1387*59692Selan /*
1388*59692Selan  * Stuff that looks different if it's single or double
1389*59692Selan  */
1390*59692Selan   if (GET_MODE (x) == SFmode)
1391*59692Selan     {
1392*59692Selan       if (d == S_E)
1393*59692Selan 	return 0x8;
1394*59692Selan       if (d == (2*S_PI))
1395*59692Selan 	return 0x9;
1396*59692Selan       if (d == S_PI)
1397*59692Selan 	return 0xA;
1398*59692Selan       if (d == (S_PI / 2.0))
1399*59692Selan 	return 0xB;
1400*59692Selan       if (d == S_SQRT2)
1401*59692Selan 	return 0xC;
1402*59692Selan       if (d == (1.0 / S_SQRT2))
1403*59692Selan 	return 0xD;
1404*59692Selan       /* Large powers of 10 in the constant
1405*59692Selan 	 ram are not used because they are
1406*59692Selan 	 not equal to a C double constant  */
1407*59692Selan       if (d == -(S_PI / 2.0))
1408*59692Selan 	return 0x27;
1409*59692Selan       if (d == S_LOG2ofE)
1410*59692Selan 	return 0x28;
1411*59692Selan       if (d == S_LOG2of10)
1412*59692Selan 	return 0x29;
1413*59692Selan       if (d == S_LOGEof2)
1414*59692Selan 	return 0x2A;
1415*59692Selan       if (d == S_LOGEof10)
1416*59692Selan 	return 0x2B;
1417*59692Selan       if (d == S_LOG10of2)
1418*59692Selan 	return 0x2C;
1419*59692Selan       if (d == S_LOG10ofE)
1420*59692Selan 	return 0x2D;
1421*59692Selan     }
1422*59692Selan   else
1423*59692Selan     {
1424*59692Selan       if (d == D_E)
1425*59692Selan 	return 0x8;
1426*59692Selan       if (d == (2*D_PI))
1427*59692Selan 	return 0x9;
1428*59692Selan       if (d == D_PI)
1429*59692Selan 	return 0xA;
1430*59692Selan       if (d == (D_PI / 2.0))
1431*59692Selan 	return 0xB;
1432*59692Selan       if (d == D_SQRT2)
1433*59692Selan 	return 0xC;
1434*59692Selan       if (d == (1.0 / D_SQRT2))
1435*59692Selan 	return 0xD;
1436*59692Selan       /* Large powers of 10 in the constant
1437*59692Selan 	 ram are not used because they are
1438*59692Selan 	 not equal to a C double constant  */
1439*59692Selan       if (d == -(D_PI / 2.0))
1440*59692Selan 	return 0x27;
1441*59692Selan       if (d == D_LOG2ofE)
1442*59692Selan 	return 0x28;
1443*59692Selan       if (d == D_LOG2of10)
1444*59692Selan 	return 0x29;
1445*59692Selan       if (d == D_LOGEof2)
1446*59692Selan 	return 0x2A;
1447*59692Selan       if (d == D_LOGEof10)
1448*59692Selan 	return 0x2B;
1449*59692Selan       if (d == D_LOG10of2)
1450*59692Selan 	return 0x2C;
1451*59692Selan       if (d == D_LOG10ofE)
1452*59692Selan 	return 0x2D;
1453*59692Selan     }
1454*59692Selan   return 0x0;
1455*59692Selan }
1456*59692Selan #endif /* define SUPPORT_SUN_FPA */
1457*59692Selan 
1458*59692Selan /* A C compound statement to output to stdio stream STREAM the
1459*59692Selan    assembler syntax for an instruction operand X.  X is an RTL
1460*59692Selan    expression.
1461*59692Selan 
1462*59692Selan    CODE is a value that can be used to specify one of several ways
1463*59692Selan    of printing the operand.  It is used when identical operands
1464*59692Selan    must be printed differently depending on the context.  CODE
1465*59692Selan    comes from the `%' specification that was used to request
1466*59692Selan    printing of the operand.  If the specification was just `%DIGIT'
1467*59692Selan    then CODE is 0; if the specification was `%LTR DIGIT' then CODE
1468*59692Selan    is the ASCII code for LTR.
1469*59692Selan 
1470*59692Selan    If X is a register, this macro should print the register's name.
1471*59692Selan    The names can be found in an array `reg_names' whose type is
1472*59692Selan    `char *[]'.  `reg_names' is initialized from `REGISTER_NAMES'.
1473*59692Selan 
1474*59692Selan    When the machine description has a specification `%PUNCT' (a `%'
1475*59692Selan    followed by a punctuation character), this macro is called with
1476*59692Selan    a null pointer for X and the punctuation character for CODE.
1477*59692Selan 
1478*59692Selan    The m68k specific codes are:
1479*59692Selan 
1480*59692Selan    '.' for dot needed in Motorola-style opcode names.
1481*59692Selan    '-' for an operand pushing on the stack:
1482*59692Selan        sp@-, -(sp) or -(%sp) depending on the style of syntax.
1483*59692Selan    '+' for an operand pushing on the stack:
1484*59692Selan        sp@+, (sp)+ or (%sp)+ depending on the style of syntax.
1485*59692Selan    '@' for a reference to the top word on the stack:
1486*59692Selan        sp@, (sp) or (%sp) depending on the style of syntax.
1487*59692Selan    '#' for an immediate operand prefix (# in MIT and Motorola syntax
1488*59692Selan        but & in SGS syntax).
1489*59692Selan    '!' for the cc register (used in an `and to cc' insn).
1490*59692Selan    '$' for the letter `s' in an op code, but only on the 68040.
1491*59692Selan    '&' for the letter `d' in an op code, but only on the 68040.
1492*59692Selan 
1493*59692Selan    'b' for byte insn (no effect, on the Sun; this is for the ISI).
1494*59692Selan    'd' to force memory addressing to be absolute, not relative.
1495*59692Selan    'f' for float insn (print a CONST_DOUBLE as a float rather than in hex)
1496*59692Selan    'w' for FPA insn (print a CONST_DOUBLE as a SunFPA constant rather
1497*59692Selan        than directly).  Second part of 'y' below.
1498*59692Selan    'x' for float insn (print a CONST_DOUBLE as a float rather than in hex),
1499*59692Selan        or print pair of registers as rx:ry.
1500*59692Selan    'y' for a FPA insn (print pair of registers as rx:ry).  This also outputs
1501*59692Selan        CONST_DOUBLE's as SunFPA constant RAM registers if
1502*59692Selan        possible, so it should not be used except for the SunFPA.
1503*59692Selan 
1504*59692Selan    */
1505*59692Selan 
1506*59692Selan void
1507*59692Selan print_operand (file, op, letter)
1508*59692Selan      FILE *file;		/* file to write to */
1509*59692Selan      rtx op;			/* operand to print */
1510*59692Selan      int letter;		/* %<letter> or 0 */
1511*59692Selan {
1512*59692Selan   int i;
1513*59692Selan 
1514*59692Selan   if (letter == '.')
1515*59692Selan     {
1516*59692Selan #ifdef MOTOROLA
1517*59692Selan       asm_fprintf (file, ".");
1518*59692Selan #endif
1519*59692Selan     }
1520*59692Selan   else if (letter == '#')
1521*59692Selan     {
1522*59692Selan       asm_fprintf (file, "%0I");
1523*59692Selan     }
1524*59692Selan   else if (letter == '-')
1525*59692Selan     {
1526*59692Selan #ifdef MOTOROLA
1527*59692Selan       asm_fprintf (file, "-(%Rsp)");
1528*59692Selan #else
1529*59692Selan       asm_fprintf (file, "%Rsp@-");
1530*59692Selan #endif
1531*59692Selan     }
1532*59692Selan   else if (letter == '+')
1533*59692Selan     {
1534*59692Selan #ifdef MOTOROLA
1535*59692Selan       asm_fprintf (file, "(%Rsp)+");
1536*59692Selan #else
1537*59692Selan       asm_fprintf (file, "%Rsp@+");
1538*59692Selan #endif
1539*59692Selan     }
1540*59692Selan   else if (letter == '@')
1541*59692Selan     {
1542*59692Selan #ifdef MOTOROLA
1543*59692Selan       asm_fprintf (file, "(%Rsp)");
1544*59692Selan #else
1545*59692Selan       asm_fprintf (file, "%Rsp@");
1546*59692Selan #endif
1547*59692Selan     }
1548*59692Selan   else if (letter == '!')
1549*59692Selan     {
1550*59692Selan       asm_fprintf (file, "%Rfpcr");
1551*59692Selan     }
1552*59692Selan   else if (letter == '$')
1553*59692Selan     {
1554*59692Selan       if (TARGET_68040_ONLY)
1555*59692Selan 	{
1556*59692Selan 	  fprintf (file, "s");
1557*59692Selan 	}
1558*59692Selan     }
1559*59692Selan   else if (letter == '&')
1560*59692Selan     {
1561*59692Selan       if (TARGET_68040_ONLY)
1562*59692Selan 	{
1563*59692Selan 	  fprintf (file, "d");
1564*59692Selan 	}
1565*59692Selan     }
1566*59692Selan   else if (GET_CODE (op) == REG)
1567*59692Selan     {
1568*59692Selan       if (REGNO (op) < 16
1569*59692Selan 	  && (letter == 'y' || letter == 'x')
1570*59692Selan 	  && GET_MODE (op) == DFmode)
1571*59692Selan 	{
1572*59692Selan 	  fprintf (file, "%s:%s", reg_names[REGNO (op)],
1573*59692Selan 		   reg_names[REGNO (op)+1]);
1574*59692Selan 	}
1575*59692Selan       else
1576*59692Selan 	{
1577*59692Selan 	  fprintf (file, "%s", reg_names[REGNO (op)]);
1578*59692Selan 	}
1579*59692Selan     }
1580*59692Selan   else if (GET_CODE (op) == MEM)
1581*59692Selan     {
1582*59692Selan       output_address (XEXP (op, 0));
1583*59692Selan       if (letter == 'd' && ! TARGET_68020
1584*59692Selan 	  && CONSTANT_ADDRESS_P (XEXP (op, 0))
1585*59692Selan 	  && !(GET_CODE (XEXP (op, 0)) == CONST_INT
1586*59692Selan 	       && INTVAL (XEXP (op, 0)) < 0x8000
1587*59692Selan 	       && INTVAL (XEXP (op, 0)) >= -0x8000))
1588*59692Selan 	{
1589*59692Selan 	  fprintf (file, ":l");
1590*59692Selan 	}
1591*59692Selan     }
1592*59692Selan #ifdef SUPPORT_SUN_FPA
1593*59692Selan   else if ((letter == 'y' || letter == 'w')
1594*59692Selan 	   && GET_CODE (op) == CONST_DOUBLE
1595*59692Selan 	   && (i = standard_sun_fpa_constant_p (op)))
1596*59692Selan     {
1597*59692Selan       fprintf (file, "%%%d", i & 0x1ff);
1598*59692Selan     }
1599*59692Selan #endif
1600*59692Selan   else if (GET_CODE (op) == CONST_DOUBLE && GET_MODE (op) == SFmode)
1601*59692Selan     {
1602*59692Selan       double d;
1603*59692Selan       union { float f; int i; } u1;
1604*59692Selan       REAL_VALUE_FROM_CONST_DOUBLE (d, op);
1605*59692Selan       u1.f = d;
1606*59692Selan       PRINT_OPERAND_PRINT_FLOAT (letter, file);
1607*59692Selan     }
1608*59692Selan   else if (GET_CODE (op) == CONST_DOUBLE && GET_MODE (op) != DImode)
1609*59692Selan     {
1610*59692Selan       double d;
1611*59692Selan       REAL_VALUE_FROM_CONST_DOUBLE (d, op);
1612*59692Selan       ASM_OUTPUT_DOUBLE_OPERAND (file, d);
1613*59692Selan     }
1614*59692Selan   else
1615*59692Selan     {
1616*59692Selan       asm_fprintf (file, "%0I"); output_addr_const (file, op);
1617*59692Selan     }
1618*59692Selan }
1619*59692Selan 
1620*59692Selan 
1621*59692Selan /* A C compound statement to output to stdio stream STREAM the
1622*59692Selan    assembler syntax for an instruction operand that is a memory
1623*59692Selan    reference whose address is ADDR.  ADDR is an RTL expression.
1624*59692Selan 
1625*59692Selan    Note that this contains a kludge that knows that the only reason
1626*59692Selan    we have an address (plus (label_ref...) (reg...)) when not generating
1627*59692Selan    PIC code is in the insn before a tablejump, and we know that m68k.md
1628*59692Selan    generates a label LInnn: on such an insn.
1629*59692Selan 
1630*59692Selan    It is possible for PIC to generate a (plus (label_ref...) (reg...))
1631*59692Selan    and we handle that just like we would a (plus (symbol_ref...) (reg...)).
1632*59692Selan 
1633*59692Selan    Some SGS assemblers have a bug such that "Lnnn-LInnn-2.b(pc,d0.l*2)"
1634*59692Selan    fails to assemble.  Luckily "Lnnn(pc,d0.l*2)" produces the results
1635*59692Selan    we want.  This difference can be accommodated by using an assembler
1636*59692Selan    define such "LDnnn" to be either "Lnnn-LInnn-2.b", "Lnnn", or any other
1637*59692Selan    string, as necessary.  This is accomplished via the ASM_OUTPUT_CASE_END
1638*59692Selan    macro.  See m68ksgs.h for an example; for versions without the bug.
1639*59692Selan 
1640*59692Selan    They also do not like things like "pea 1.w", so we simple leave off
1641*59692Selan    the .w on small constants.
1642*59692Selan 
1643*59692Selan    This routine is responsible for distinguishing between -fpic and -fPIC
1644*59692Selan    style relocations in an address.  When generating -fpic code the
1645*59692Selan    offset is output in word mode (eg movel a5@(_foo:w), a0).  When generating
1646*59692Selan    -fPIC code the offset is output in long mode (eg movel a5@(_foo:l), a0) */
1647*59692Selan 
1648*59692Selan void
1649*59692Selan print_operand_address (file, addr)
1650*59692Selan      FILE *file;
1651*59692Selan      rtx addr;
1652*59692Selan {
1653*59692Selan   register rtx reg1, reg2, breg, ireg;
1654*59692Selan   rtx offset;
1655*59692Selan 
1656*59692Selan   switch (GET_CODE (addr))
1657*59692Selan     {
1658*59692Selan       case REG:
1659*59692Selan #ifdef MOTOROLA
1660*59692Selan 	fprintf (file, "(%s)", reg_names[REGNO (addr)]);
1661*59692Selan #else
1662*59692Selan 	fprintf (file, "%s@", reg_names[REGNO (addr)]);
1663*59692Selan #endif
1664*59692Selan 	break;
1665*59692Selan       case PRE_DEC:
1666*59692Selan #ifdef MOTOROLA
1667*59692Selan 	fprintf (file, "-(%s)", reg_names[REGNO (XEXP (addr, 0))]);
1668*59692Selan #else
1669*59692Selan 	fprintf (file, "%s@-", reg_names[REGNO (XEXP (addr, 0))]);
1670*59692Selan #endif
1671*59692Selan 	break;
1672*59692Selan       case POST_INC:
1673*59692Selan #ifdef MOTOROLA
1674*59692Selan 	fprintf (file, "(%s)+", reg_names[REGNO (XEXP (addr, 0))]);
1675*59692Selan #else
1676*59692Selan 	fprintf (file, "%s@+", reg_names[REGNO (XEXP (addr, 0))]);
1677*59692Selan #endif
1678*59692Selan 	break;
1679*59692Selan       case PLUS:
1680*59692Selan 	reg1 = reg2 = ireg = breg = offset = 0;
1681*59692Selan 	if (CONSTANT_ADDRESS_P (XEXP (addr, 0)))
1682*59692Selan 	  {
1683*59692Selan 	    offset = XEXP (addr, 0);
1684*59692Selan 	    addr = XEXP (addr, 1);
1685*59692Selan 	  }
1686*59692Selan 	else if (CONSTANT_ADDRESS_P (XEXP (addr, 1)))
1687*59692Selan 	  {
1688*59692Selan 	    offset = XEXP (addr, 1);
1689*59692Selan 	    addr = XEXP (addr, 0);
1690*59692Selan 	  }
1691*59692Selan 	if (GET_CODE (addr) != PLUS)
1692*59692Selan 	  {
1693*59692Selan 	    ;
1694*59692Selan 	  }
1695*59692Selan 	else if (GET_CODE (XEXP (addr, 0)) == SIGN_EXTEND)
1696*59692Selan 	  {
1697*59692Selan 	    reg1 = XEXP (addr, 0);
1698*59692Selan 	    addr = XEXP (addr, 1);
1699*59692Selan 	  }
1700*59692Selan 	else if (GET_CODE (XEXP (addr, 1)) == SIGN_EXTEND)
1701*59692Selan 	  {
1702*59692Selan 	    reg1 = XEXP (addr, 1);
1703*59692Selan 	    addr = XEXP (addr, 0);
1704*59692Selan 	  }
1705*59692Selan 	else if (GET_CODE (XEXP (addr, 0)) == MULT)
1706*59692Selan 	  {
1707*59692Selan 	    reg1 = XEXP (addr, 0);
1708*59692Selan 	    addr = XEXP (addr, 1);
1709*59692Selan 	  }
1710*59692Selan 	else if (GET_CODE (XEXP (addr, 1)) == MULT)
1711*59692Selan 	  {
1712*59692Selan 	    reg1 = XEXP (addr, 1);
1713*59692Selan 	    addr = XEXP (addr, 0);
1714*59692Selan 	  }
1715*59692Selan 	else if (GET_CODE (XEXP (addr, 0)) == REG)
1716*59692Selan 	  {
1717*59692Selan 	    reg1 = XEXP (addr, 0);
1718*59692Selan 	    addr = XEXP (addr, 1);
1719*59692Selan 	  }
1720*59692Selan 	else if (GET_CODE (XEXP (addr, 1)) == REG)
1721*59692Selan 	  {
1722*59692Selan 	    reg1 = XEXP (addr, 1);
1723*59692Selan 	    addr = XEXP (addr, 0);
1724*59692Selan 	  }
1725*59692Selan 	if (GET_CODE (addr) == REG || GET_CODE (addr) == MULT
1726*59692Selan 	    || GET_CODE (addr) == SIGN_EXTEND)
1727*59692Selan 	  {
1728*59692Selan 	    if (reg1 == 0)
1729*59692Selan 	      {
1730*59692Selan 		reg1 = addr;
1731*59692Selan 	      }
1732*59692Selan 	    else
1733*59692Selan 	      {
1734*59692Selan 		reg2 = addr;
1735*59692Selan 	      }
1736*59692Selan 	    addr = 0;
1737*59692Selan 	  }
1738*59692Selan #if 0	/* for OLD_INDEXING */
1739*59692Selan 	else if (GET_CODE (addr) == PLUS)
1740*59692Selan 	  {
1741*59692Selan 	    if (GET_CODE (XEXP (addr, 0)) == REG)
1742*59692Selan 	      {
1743*59692Selan 		reg2 = XEXP (addr, 0);
1744*59692Selan 		addr = XEXP (addr, 1);
1745*59692Selan 	      }
1746*59692Selan 	    else if (GET_CODE (XEXP (addr, 1)) == REG)
1747*59692Selan 	      {
1748*59692Selan 		reg2 = XEXP (addr, 1);
1749*59692Selan 		addr = XEXP (addr, 0);
1750*59692Selan 	      }
1751*59692Selan 	  }
1752*59692Selan #endif
1753*59692Selan 	if (offset != 0)
1754*59692Selan 	  {
1755*59692Selan 	    if (addr != 0)
1756*59692Selan 	      {
1757*59692Selan 		abort ();
1758*59692Selan 	      }
1759*59692Selan 	    addr = offset;
1760*59692Selan 	  }
1761*59692Selan 	if ((reg1 && (GET_CODE (reg1) == SIGN_EXTEND
1762*59692Selan 		      || GET_CODE (reg1) == MULT))
1763*59692Selan 	    || (reg2 != 0 && REGNO_OK_FOR_BASE_P (REGNO (reg2))))
1764*59692Selan 	  {
1765*59692Selan 	    breg = reg2;
1766*59692Selan 	    ireg = reg1;
1767*59692Selan 	  }
1768*59692Selan 	else if (reg1 != 0 && REGNO_OK_FOR_BASE_P (REGNO (reg1)))
1769*59692Selan 	  {
1770*59692Selan 	    breg = reg1;
1771*59692Selan 	    ireg = reg2;
1772*59692Selan 	  }
1773*59692Selan 	if (ireg != 0 && breg == 0 && GET_CODE (addr) == LABEL_REF
1774*59692Selan 	    && ! (flag_pic && ireg == pic_offset_table_rtx))
1775*59692Selan 	  {
1776*59692Selan 	    int scale = 1;
1777*59692Selan 	    if (GET_CODE (ireg) == MULT)
1778*59692Selan 	      {
1779*59692Selan 		scale = INTVAL (XEXP (ireg, 1));
1780*59692Selan 		ireg = XEXP (ireg, 0);
1781*59692Selan 	      }
1782*59692Selan 	    if (GET_CODE (ireg) == SIGN_EXTEND)
1783*59692Selan 	      {
1784*59692Selan #ifdef MOTOROLA
1785*59692Selan #ifdef SGS
1786*59692Selan 		asm_fprintf (file, "%LLD%d(%Rpc,%s.w",
1787*59692Selan 			     CODE_LABEL_NUMBER (XEXP (addr, 0)),
1788*59692Selan 			     reg_names[REGNO (XEXP (ireg, 0))]);
1789*59692Selan #else
1790*59692Selan 		asm_fprintf (file, "%LL%d-%LLI%d.b(%Rpc,%s.w",
1791*59692Selan 			     CODE_LABEL_NUMBER (XEXP (addr, 0)),
1792*59692Selan 			     CODE_LABEL_NUMBER (XEXP (addr, 0)),
1793*59692Selan 			     reg_names[REGNO (XEXP (ireg, 0))]);
1794*59692Selan #endif
1795*59692Selan #else
1796*59692Selan 		asm_fprintf (file, "%Rpc@(%LL%d-%LLI%d-2:b,%s:w",
1797*59692Selan 			     CODE_LABEL_NUMBER (XEXP (addr, 0)),
1798*59692Selan 			     CODE_LABEL_NUMBER (XEXP (addr, 0)),
1799*59692Selan 			     reg_names[REGNO (XEXP (ireg, 0))]);
1800*59692Selan #endif
1801*59692Selan 	      }
1802*59692Selan 	    else
1803*59692Selan 	      {
1804*59692Selan #ifdef MOTOROLA
1805*59692Selan #ifdef SGS
1806*59692Selan 		asm_fprintf (file, "%LLD%d(%Rpc,%s.l",
1807*59692Selan 			     CODE_LABEL_NUMBER (XEXP (addr, 0)),
1808*59692Selan 			     reg_names[REGNO (ireg)]);
1809*59692Selan #else
1810*59692Selan 		asm_fprintf (file, "%LL%d-%LLI%d.b(%Rpc,%s.l",
1811*59692Selan 			     CODE_LABEL_NUMBER (XEXP (addr, 0)),
1812*59692Selan 			     CODE_LABEL_NUMBER (XEXP (addr, 0)),
1813*59692Selan 			     reg_names[REGNO (ireg)]);
1814*59692Selan #endif
1815*59692Selan #else
1816*59692Selan 		asm_fprintf (file, "%Rpc@(%LL%d-%LLI%d-2:b,%s:l",
1817*59692Selan 			     CODE_LABEL_NUMBER (XEXP (addr, 0)),
1818*59692Selan 			     CODE_LABEL_NUMBER (XEXP (addr, 0)),
1819*59692Selan 			     reg_names[REGNO (ireg)]);
1820*59692Selan #endif
1821*59692Selan 	      }
1822*59692Selan 	    if (scale != 1)
1823*59692Selan 	      {
1824*59692Selan #ifdef MOTOROLA
1825*59692Selan 		fprintf (file, "*%d", scale);
1826*59692Selan #else
1827*59692Selan 		fprintf (file, ":%d", scale);
1828*59692Selan #endif
1829*59692Selan 	      }
1830*59692Selan 	    putc (')', file);
1831*59692Selan 	    break;
1832*59692Selan 	  }
1833*59692Selan 	if (breg != 0 && ireg == 0 && GET_CODE (addr) == LABEL_REF
1834*59692Selan 	    && ! (flag_pic && breg == pic_offset_table_rtx))
1835*59692Selan 	  {
1836*59692Selan #ifdef MOTOROLA
1837*59692Selan #ifdef SGS
1838*59692Selan 	    asm_fprintf (file, "%LLD%d(%Rpc,%s.l",
1839*59692Selan 			 CODE_LABEL_NUMBER (XEXP (addr, 0)),
1840*59692Selan 			 reg_names[REGNO (breg)]);
1841*59692Selan #else
1842*59692Selan 	    asm_fprintf (file, "%LL%d-%LLI%d.b(%Rpc,%s.l",
1843*59692Selan 			 CODE_LABEL_NUMBER (XEXP (addr, 0)),
1844*59692Selan 			 CODE_LABEL_NUMBER (XEXP (addr, 0)),
1845*59692Selan 			 reg_names[REGNO (breg)]);
1846*59692Selan #endif
1847*59692Selan #else
1848*59692Selan 	    asm_fprintf (file, "%Rpc@(%LL%d-%LLI%d-2:b,%s:l",
1849*59692Selan 			 CODE_LABEL_NUMBER (XEXP (addr, 0)),
1850*59692Selan 			 CODE_LABEL_NUMBER (XEXP (addr, 0)),
1851*59692Selan 			 reg_names[REGNO (breg)]);
1852*59692Selan #endif
1853*59692Selan 	    putc (')', file);
1854*59692Selan 	    break;
1855*59692Selan 	  }
1856*59692Selan 	if (ireg != 0 || breg != 0)
1857*59692Selan 	  {
1858*59692Selan 	    int scale = 1;
1859*59692Selan 	    if (breg == 0)
1860*59692Selan 	      {
1861*59692Selan 		abort ();
1862*59692Selan 	      }
1863*59692Selan 	    if (! flag_pic && addr && GET_CODE (addr) == LABEL_REF)
1864*59692Selan 	      {
1865*59692Selan 		abort ();
1866*59692Selan 	      }
1867*59692Selan #ifdef MOTOROLA
1868*59692Selan 	    if (addr != 0)
1869*59692Selan 	      {
1870*59692Selan 		output_addr_const (file, addr);
1871*59692Selan 	        if ((flag_pic == 1) && (breg == pic_offset_table_rtx))
1872*59692Selan 	          fprintf (file, ".w");
1873*59692Selan 	        if ((flag_pic == 2) && (breg == pic_offset_table_rtx))
1874*59692Selan 	          fprintf (file, ".l");
1875*59692Selan 	      }
1876*59692Selan 	    fprintf (file, "(%s", reg_names[REGNO (breg)]);
1877*59692Selan 	    if (ireg != 0)
1878*59692Selan 	      {
1879*59692Selan 		putc (',', file);
1880*59692Selan 	      }
1881*59692Selan #else
1882*59692Selan 	    fprintf (file, "%s@(", reg_names[REGNO (breg)]);
1883*59692Selan 	    if (addr != 0)
1884*59692Selan 	      {
1885*59692Selan 		output_addr_const (file, addr);
1886*59692Selan 	        if ((flag_pic == 1) && (breg == pic_offset_table_rtx))
1887*59692Selan 	          fprintf (file, ":w");
1888*59692Selan 	        if ((flag_pic == 2) && (breg == pic_offset_table_rtx))
1889*59692Selan 	          fprintf (file, ":l");
1890*59692Selan 	      }
1891*59692Selan 	    if (addr != 0 && ireg != 0)
1892*59692Selan 	      {
1893*59692Selan 		putc (',', file);
1894*59692Selan 	      }
1895*59692Selan #endif
1896*59692Selan 	    if (ireg != 0 && GET_CODE (ireg) == MULT)
1897*59692Selan 	      {
1898*59692Selan 		scale = INTVAL (XEXP (ireg, 1));
1899*59692Selan 		ireg = XEXP (ireg, 0);
1900*59692Selan 	      }
1901*59692Selan 	    if (ireg != 0 && GET_CODE (ireg) == SIGN_EXTEND)
1902*59692Selan 	      {
1903*59692Selan #ifdef MOTOROLA
1904*59692Selan 		fprintf (file, "%s.w", reg_names[REGNO (XEXP (ireg, 0))]);
1905*59692Selan #else
1906*59692Selan 		fprintf (file, "%s:w", reg_names[REGNO (XEXP (ireg, 0))]);
1907*59692Selan #endif
1908*59692Selan 	      }
1909*59692Selan 	    else if (ireg != 0)
1910*59692Selan 	      {
1911*59692Selan #ifdef MOTOROLA
1912*59692Selan 		fprintf (file, "%s.l", reg_names[REGNO (ireg)]);
1913*59692Selan #else
1914*59692Selan 		fprintf (file, "%s:l", reg_names[REGNO (ireg)]);
1915*59692Selan #endif
1916*59692Selan 	      }
1917*59692Selan 	    if (scale != 1)
1918*59692Selan 	      {
1919*59692Selan #ifdef MOTOROLA
1920*59692Selan 		fprintf (file, "*%d", scale);
1921*59692Selan #else
1922*59692Selan 		fprintf (file, ":%d", scale);
1923*59692Selan #endif
1924*59692Selan 	      }
1925*59692Selan 	    putc (')', file);
1926*59692Selan 	    break;
1927*59692Selan 	  }
1928*59692Selan 	else if (reg1 != 0 && GET_CODE (addr) == LABEL_REF
1929*59692Selan 		 && ! (flag_pic && reg1 == pic_offset_table_rtx))
1930*59692Selan 	  {
1931*59692Selan #ifdef MOTOROLA
1932*59692Selan #ifdef SGS
1933*59692Selan 	    asm_fprintf (file, "%LLD%d(%Rpc,%s.l)",
1934*59692Selan 			 CODE_LABEL_NUMBER (XEXP (addr, 0)),
1935*59692Selan 			 reg_names[REGNO (reg1)]);
1936*59692Selan #else
1937*59692Selan 	    asm_fprintf (file, "%LL%d-%LLI%d.b(%Rpc,%s.l)",
1938*59692Selan 			 CODE_LABEL_NUMBER (XEXP (addr, 0)),
1939*59692Selan 			 CODE_LABEL_NUMBER (XEXP (addr, 0)),
1940*59692Selan 			 reg_names[REGNO (reg1)]);
1941*59692Selan #endif
1942*59692Selan #else
1943*59692Selan 	    asm_fprintf (file, "%Rpc@(%LL%d-%LLI%d-2:b,%s:l)",
1944*59692Selan 			 CODE_LABEL_NUMBER (XEXP (addr, 0)),
1945*59692Selan 			 CODE_LABEL_NUMBER (XEXP (addr, 0)),
1946*59692Selan 			 reg_names[REGNO (reg1)]);
1947*59692Selan #endif
1948*59692Selan 	    break;
1949*59692Selan 	  }
1950*59692Selan 	/* FALL-THROUGH (is this really what we want? */
1951*59692Selan       default:
1952*59692Selan         if (GET_CODE (addr) == CONST_INT
1953*59692Selan 	    && INTVAL (addr) < 0x8000
1954*59692Selan 	    && INTVAL (addr) >= -0x8000)
1955*59692Selan 	  {
1956*59692Selan #ifdef MOTOROLA
1957*59692Selan #ifdef SGS
1958*59692Selan 	    /* Many SGS assemblers croak on size specifiers for constants. */
1959*59692Selan 	    fprintf (file, "%d", INTVAL (addr));
1960*59692Selan #else
1961*59692Selan 	    fprintf (file, "%d.w", INTVAL (addr));
1962*59692Selan #endif
1963*59692Selan #else
1964*59692Selan 	    fprintf (file, "%d:w", INTVAL (addr));
1965*59692Selan #endif
1966*59692Selan 	  }
1967*59692Selan 	else
1968*59692Selan 	  {
1969*59692Selan 	    output_addr_const (file, addr);
1970*59692Selan 	  }
1971*59692Selan 	break;
1972*59692Selan     }
1973*59692Selan }
1974