1/* The Blackfin code generation auxiliary output file.
2   Copyright (C) 2005, 2006  Free Software Foundation, Inc.
3   Contributed by Analog Devices.
4
5   This file is part of GCC.
6
7   GCC is free software; you can redistribute it and/or modify it
8   under the terms of the GNU General Public License as published
9   by the Free Software Foundation; either version 2, or (at your
10   option) any later version.
11
12   GCC is distributed in the hope that it will be useful, but WITHOUT
13   ANY WARRANTY; without even the implied warranty of MERCHANTABILITY
14   or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public
15   License for more details.
16
17   You should have received a copy of the GNU General Public License
18   along with GCC; see the file COPYING.  If not, write to
19   the Free Software Foundation, 51 Franklin Street, Fifth Floor,
20   Boston, MA 02110-1301, USA.  */
21
22#include "config.h"
23#include "system.h"
24#include "coretypes.h"
25#include "tm.h"
26#include "rtl.h"
27#include "regs.h"
28#include "hard-reg-set.h"
29#include "real.h"
30#include "insn-config.h"
31#include "insn-codes.h"
32#include "conditions.h"
33#include "insn-flags.h"
34#include "output.h"
35#include "insn-attr.h"
36#include "tree.h"
37#include "flags.h"
38#include "except.h"
39#include "function.h"
40#include "input.h"
41#include "target.h"
42#include "target-def.h"
43#include "expr.h"
44#include "toplev.h"
45#include "recog.h"
46#include "optabs.h"
47#include "ggc.h"
48#include "integrate.h"
49#include "cgraph.h"
50#include "langhooks.h"
51#include "bfin-protos.h"
52#include "tm-preds.h"
53#include "gt-bfin.h"
54#include "basic-block.h"
55
56/* A C structure for machine-specific, per-function data.
57   This is added to the cfun structure.  */
58struct machine_function GTY(())
59{
60  int has_hardware_loops;
61};
62
63/* Test and compare insns in bfin.md store the information needed to
64   generate branch and scc insns here.  */
65rtx bfin_compare_op0, bfin_compare_op1;
66
67/* RTX for condition code flag register and RETS register */
68extern GTY(()) rtx bfin_cc_rtx;
69extern GTY(()) rtx bfin_rets_rtx;
70rtx bfin_cc_rtx, bfin_rets_rtx;
71
72int max_arg_registers = 0;
73
74/* Arrays used when emitting register names.  */
75const char *short_reg_names[]  =  SHORT_REGISTER_NAMES;
76const char *high_reg_names[]   =  HIGH_REGISTER_NAMES;
77const char *dregs_pair_names[] =  DREGS_PAIR_NAMES;
78const char *byte_reg_names[]   =  BYTE_REGISTER_NAMES;
79
80static int arg_regs[] = FUNCTION_ARG_REGISTERS;
81
82/* Nonzero if -mshared-library-id was given.  */
83static int bfin_lib_id_given;
84
85static void
86bfin_globalize_label (FILE *stream, const char *name)
87{
88  fputs (".global ", stream);
89  assemble_name (stream, name);
90  fputc (';',stream);
91  fputc ('\n',stream);
92}
93
94static void
95output_file_start (void)
96{
97  FILE *file = asm_out_file;
98  int i;
99
100  fprintf (file, ".file \"%s\";\n", input_filename);
101
102  for (i = 0; arg_regs[i] >= 0; i++)
103    ;
104  max_arg_registers = i;	/* how many arg reg used  */
105}
106
107/* Called early in the compilation to conditionally modify
108   fixed_regs/call_used_regs.  */
109
110void
111conditional_register_usage (void)
112{
113  /* initialize condition code flag register rtx */
114  bfin_cc_rtx = gen_rtx_REG (BImode, REG_CC);
115  bfin_rets_rtx = gen_rtx_REG (Pmode, REG_RETS);
116}
117
118/* Examine machine-dependent attributes of function type FUNTYPE and return its
119   type.  See the definition of E_FUNKIND.  */
120
121static e_funkind funkind (tree funtype)
122{
123  tree attrs = TYPE_ATTRIBUTES (funtype);
124  if (lookup_attribute ("interrupt_handler", attrs))
125    return INTERRUPT_HANDLER;
126  else if (lookup_attribute ("exception_handler", attrs))
127    return EXCPT_HANDLER;
128  else if (lookup_attribute ("nmi_handler", attrs))
129    return NMI_HANDLER;
130  else
131    return SUBROUTINE;
132}
133
134/* Legitimize PIC addresses.  If the address is already position-independent,
135   we return ORIG.  Newly generated position-independent addresses go into a
136   reg.  This is REG if nonzero, otherwise we allocate register(s) as
137   necessary.  PICREG is the register holding the pointer to the PIC offset
138   table.  */
139
140static rtx
141legitimize_pic_address (rtx orig, rtx reg, rtx picreg)
142{
143  rtx addr = orig;
144  rtx new = orig;
145
146  if (GET_CODE (addr) == SYMBOL_REF || GET_CODE (addr) == LABEL_REF)
147    {
148      if (GET_CODE (addr) == SYMBOL_REF && CONSTANT_POOL_ADDRESS_P (addr))
149	reg = new = orig;
150      else
151	{
152	  int unspec;
153	  rtx tmp;
154
155	  if (TARGET_ID_SHARED_LIBRARY)
156	    unspec = UNSPEC_MOVE_PIC;
157	  else if (GET_CODE (addr) == SYMBOL_REF
158		   && SYMBOL_REF_FUNCTION_P (addr))
159	    {
160	      unspec = UNSPEC_FUNCDESC_GOT17M4;
161	    }
162	  else
163	    {
164	      unspec = UNSPEC_MOVE_FDPIC;
165	    }
166
167	  if (reg == 0)
168	    {
169	      gcc_assert (!no_new_pseudos);
170	      reg = gen_reg_rtx (Pmode);
171	    }
172
173	  tmp = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, addr), unspec);
174	  new = gen_const_mem (Pmode, gen_rtx_PLUS (Pmode, picreg, tmp));
175
176	  emit_move_insn (reg, new);
177	}
178      if (picreg == pic_offset_table_rtx)
179	current_function_uses_pic_offset_table = 1;
180      return reg;
181    }
182
183  else if (GET_CODE (addr) == CONST || GET_CODE (addr) == PLUS)
184    {
185      rtx base;
186
187      if (GET_CODE (addr) == CONST)
188	{
189	  addr = XEXP (addr, 0);
190	  gcc_assert (GET_CODE (addr) == PLUS);
191	}
192
193      if (XEXP (addr, 0) == picreg)
194	return orig;
195
196      if (reg == 0)
197	{
198	  gcc_assert (!no_new_pseudos);
199	  reg = gen_reg_rtx (Pmode);
200	}
201
202      base = legitimize_pic_address (XEXP (addr, 0), reg, picreg);
203      addr = legitimize_pic_address (XEXP (addr, 1),
204				     base == reg ? NULL_RTX : reg,
205				     picreg);
206
207      if (GET_CODE (addr) == CONST_INT)
208	{
209	  gcc_assert (! reload_in_progress && ! reload_completed);
210	  addr = force_reg (Pmode, addr);
211	}
212
213      if (GET_CODE (addr) == PLUS && CONSTANT_P (XEXP (addr, 1)))
214	{
215	  base = gen_rtx_PLUS (Pmode, base, XEXP (addr, 0));
216	  addr = XEXP (addr, 1);
217	}
218
219      return gen_rtx_PLUS (Pmode, base, addr);
220    }
221
222  return new;
223}
224
225/* Stack frame layout. */
226
227/* Compute the number of DREGS to save with a push_multiple operation.
228   This could include registers that aren't modified in the function,
229   since push_multiple only takes a range of registers.
230   If IS_INTHANDLER, then everything that is live must be saved, even
231   if normally call-clobbered.  */
232
233static int
234n_dregs_to_save (bool is_inthandler)
235{
236  unsigned i;
237
238  for (i = REG_R0; i <= REG_R7; i++)
239    {
240      if (regs_ever_live[i] && (is_inthandler || ! call_used_regs[i]))
241	return REG_R7 - i + 1;
242
243      if (current_function_calls_eh_return)
244	{
245	  unsigned j;
246	  for (j = 0; ; j++)
247	    {
248	      unsigned test = EH_RETURN_DATA_REGNO (j);
249	      if (test == INVALID_REGNUM)
250		break;
251	      if (test == i)
252		return REG_R7 - i + 1;
253	    }
254	}
255
256    }
257  return 0;
258}
259
260/* Like n_dregs_to_save, but compute number of PREGS to save.  */
261
262static int
263n_pregs_to_save (bool is_inthandler)
264{
265  unsigned i;
266
267  for (i = REG_P0; i <= REG_P5; i++)
268    if ((regs_ever_live[i] && (is_inthandler || ! call_used_regs[i]))
269	|| (!TARGET_FDPIC
270	    && i == PIC_OFFSET_TABLE_REGNUM
271	    && (current_function_uses_pic_offset_table
272		|| (TARGET_ID_SHARED_LIBRARY && ! current_function_is_leaf))))
273      return REG_P5 - i + 1;
274  return 0;
275}
276
277/* Determine if we are going to save the frame pointer in the prologue.  */
278
279static bool
280must_save_fp_p (void)
281{
282  return frame_pointer_needed || regs_ever_live[REG_FP];
283}
284
285static bool
286stack_frame_needed_p (void)
287{
288  /* EH return puts a new return address into the frame using an
289     address relative to the frame pointer.  */
290  if (current_function_calls_eh_return)
291    return true;
292  return frame_pointer_needed;
293}
294
295/* Emit code to save registers in the prologue.  SAVEALL is nonzero if we
296   must save all registers; this is used for interrupt handlers.
297   SPREG contains (reg:SI REG_SP).  IS_INTHANDLER is true if we're doing
298   this for an interrupt (or exception) handler.  */
299
300static void
301expand_prologue_reg_save (rtx spreg, int saveall, bool is_inthandler)
302{
303  int ndregs = saveall ? 8 : n_dregs_to_save (is_inthandler);
304  int npregs = saveall ? 6 : n_pregs_to_save (is_inthandler);
305  int dregno = REG_R7 + 1 - ndregs;
306  int pregno = REG_P5 + 1 - npregs;
307  int total = ndregs + npregs;
308  int i;
309  rtx pat, insn, val;
310
311  if (total == 0)
312    return;
313
314  val = GEN_INT (-total * 4);
315  pat = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (total + 2));
316  XVECEXP (pat, 0, 0) = gen_rtx_UNSPEC (VOIDmode, gen_rtvec (1, val),
317					UNSPEC_PUSH_MULTIPLE);
318  XVECEXP (pat, 0, total + 1) = gen_rtx_SET (VOIDmode, spreg,
319					     gen_rtx_PLUS (Pmode, spreg,
320							   val));
321  RTX_FRAME_RELATED_P (XVECEXP (pat, 0, total + 1)) = 1;
322  for (i = 0; i < total; i++)
323    {
324      rtx memref = gen_rtx_MEM (word_mode,
325				gen_rtx_PLUS (Pmode, spreg,
326					      GEN_INT (- i * 4 - 4)));
327      rtx subpat;
328      if (ndregs > 0)
329	{
330	  subpat = gen_rtx_SET (VOIDmode, memref, gen_rtx_REG (word_mode,
331							       dregno++));
332	  ndregs--;
333	}
334      else
335	{
336	  subpat = gen_rtx_SET (VOIDmode, memref, gen_rtx_REG (word_mode,
337							       pregno++));
338	  npregs++;
339	}
340      XVECEXP (pat, 0, i + 1) = subpat;
341      RTX_FRAME_RELATED_P (subpat) = 1;
342    }
343  insn = emit_insn (pat);
344  RTX_FRAME_RELATED_P (insn) = 1;
345}
346
347/* Emit code to restore registers in the epilogue.  SAVEALL is nonzero if we
348   must save all registers; this is used for interrupt handlers.
349   SPREG contains (reg:SI REG_SP).  IS_INTHANDLER is true if we're doing
350   this for an interrupt (or exception) handler.  */
351
352static void
353expand_epilogue_reg_restore (rtx spreg, bool saveall, bool is_inthandler)
354{
355  int ndregs = saveall ? 8 : n_dregs_to_save (is_inthandler);
356  int npregs = saveall ? 6 : n_pregs_to_save (is_inthandler);
357  int total = ndregs + npregs;
358  int i, regno;
359  rtx pat, insn;
360
361  if (total == 0)
362    return;
363
364  pat = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (total + 1));
365  XVECEXP (pat, 0, 0) = gen_rtx_SET (VOIDmode, spreg,
366				     gen_rtx_PLUS (Pmode, spreg,
367						   GEN_INT (total * 4)));
368
369  if (npregs > 0)
370    regno = REG_P5 + 1;
371  else
372    regno = REG_R7 + 1;
373
374  for (i = 0; i < total; i++)
375    {
376      rtx addr = (i > 0
377		  ? gen_rtx_PLUS (Pmode, spreg, GEN_INT (i * 4))
378		  : spreg);
379      rtx memref = gen_rtx_MEM (word_mode, addr);
380
381      regno--;
382      XVECEXP (pat, 0, i + 1)
383	= gen_rtx_SET (VOIDmode, gen_rtx_REG (word_mode, regno), memref);
384
385      if (npregs > 0)
386	{
387	  if (--npregs == 0)
388	    regno = REG_R7 + 1;
389	}
390    }
391
392  insn = emit_insn (pat);
393  RTX_FRAME_RELATED_P (insn) = 1;
394}
395
396/* Perform any needed actions needed for a function that is receiving a
397   variable number of arguments.
398
399   CUM is as above.
400
401   MODE and TYPE are the mode and type of the current parameter.
402
403   PRETEND_SIZE is a variable that should be set to the amount of stack
404   that must be pushed by the prolog to pretend that our caller pushed
405   it.
406
407   Normally, this macro will push all remaining incoming registers on the
408   stack and set PRETEND_SIZE to the length of the registers pushed.
409
410   Blackfin specific :
411   - VDSP C compiler manual (our ABI) says that a variable args function
412     should save the R0, R1 and R2 registers in the stack.
413   - The caller will always leave space on the stack for the
414     arguments that are passed in registers, so we dont have
415     to leave any extra space.
416   - now, the vastart pointer can access all arguments from the stack.  */
417
418static void
419setup_incoming_varargs (CUMULATIVE_ARGS *cum,
420			enum machine_mode mode ATTRIBUTE_UNUSED,
421			tree type ATTRIBUTE_UNUSED, int *pretend_size,
422			int no_rtl)
423{
424  rtx mem;
425  int i;
426
427  if (no_rtl)
428    return;
429
430  /* The move for named arguments will be generated automatically by the
431     compiler.  We need to generate the move rtx for the unnamed arguments
432     if they are in the first 3 words.  We assume at least 1 named argument
433     exists, so we never generate [ARGP] = R0 here.  */
434
435  for (i = cum->words + 1; i < max_arg_registers; i++)
436    {
437      mem = gen_rtx_MEM (Pmode,
438			 plus_constant (arg_pointer_rtx, (i * UNITS_PER_WORD)));
439      emit_move_insn (mem, gen_rtx_REG (Pmode, i));
440    }
441
442  *pretend_size = 0;
443}
444
445/* Value should be nonzero if functions must have frame pointers.
446   Zero means the frame pointer need not be set up (and parms may
447   be accessed via the stack pointer) in functions that seem suitable.  */
448
449int
450bfin_frame_pointer_required (void)
451{
452  e_funkind fkind = funkind (TREE_TYPE (current_function_decl));
453
454  if (fkind != SUBROUTINE)
455    return 1;
456
457  /* We turn on -fomit-frame-pointer if -momit-leaf-frame-pointer is used,
458     so we have to override it for non-leaf functions.  */
459  if (TARGET_OMIT_LEAF_FRAME_POINTER && ! current_function_is_leaf)
460    return 1;
461
462  return 0;
463}
464
465/* Return the number of registers pushed during the prologue.  */
466
467static int
468n_regs_saved_by_prologue (void)
469{
470  e_funkind fkind = funkind (TREE_TYPE (current_function_decl));
471  bool is_inthandler = fkind != SUBROUTINE;
472  tree attrs = TYPE_ATTRIBUTES (TREE_TYPE (current_function_decl));
473  bool all = (lookup_attribute ("saveall", attrs) != NULL_TREE
474	      || (is_inthandler && !current_function_is_leaf));
475  int ndregs = all ? 8 : n_dregs_to_save (is_inthandler);
476  int npregs = all ? 6 : n_pregs_to_save (is_inthandler);
477  int n = ndregs + npregs;
478
479  if (all || stack_frame_needed_p ())
480    /* We use a LINK instruction in this case.  */
481    n += 2;
482  else
483    {
484      if (must_save_fp_p ())
485	n++;
486      if (! current_function_is_leaf)
487	n++;
488    }
489
490  if (fkind != SUBROUTINE)
491    {
492      int i;
493
494      /* Increment once for ASTAT.  */
495      n++;
496
497      /* RETE/X/N.  */
498      if (lookup_attribute ("nesting", attrs))
499	n++;
500
501      for (i = REG_P7 + 1; i < REG_CC; i++)
502	if (all
503	    || regs_ever_live[i]
504	    || (!leaf_function_p () && call_used_regs[i]))
505	  n += i == REG_A0 || i == REG_A1 ? 2 : 1;
506    }
507  return n;
508}
509
510/* Return the offset between two registers, one to be eliminated, and the other
511   its replacement, at the start of a routine.  */
512
513HOST_WIDE_INT
514bfin_initial_elimination_offset (int from, int to)
515{
516  HOST_WIDE_INT offset = 0;
517
518  if (from == ARG_POINTER_REGNUM)
519    offset = n_regs_saved_by_prologue () * 4;
520
521  if (to == STACK_POINTER_REGNUM)
522    {
523      if (current_function_outgoing_args_size >= FIXED_STACK_AREA)
524	offset += current_function_outgoing_args_size;
525      else if (current_function_outgoing_args_size)
526	offset += FIXED_STACK_AREA;
527
528      offset += get_frame_size ();
529    }
530
531  return offset;
532}
533
534/* Emit code to load a constant CONSTANT into register REG; setting
535   RTX_FRAME_RELATED_P on all insns we generate if RELATED is true.
536   Make sure that the insns we generate need not be split.  */
537
538static void
539frame_related_constant_load (rtx reg, HOST_WIDE_INT constant, bool related)
540{
541  rtx insn;
542  rtx cst = GEN_INT (constant);
543
544  if (constant >= -32768 && constant < 65536)
545    insn = emit_move_insn (reg, cst);
546  else
547    {
548      /* We don't call split_load_immediate here, since dwarf2out.c can get
549	 confused about some of the more clever sequences it can generate.  */
550      insn = emit_insn (gen_movsi_high (reg, cst));
551      if (related)
552	RTX_FRAME_RELATED_P (insn) = 1;
553      insn = emit_insn (gen_movsi_low (reg, reg, cst));
554    }
555  if (related)
556    RTX_FRAME_RELATED_P (insn) = 1;
557}
558
559/* Generate efficient code to add a value to the frame pointer.  We
560   can use P1 as a scratch register.  Set RTX_FRAME_RELATED_P on the
561   generated insns if FRAME is nonzero.  */
562
563static void
564add_to_sp (rtx spreg, HOST_WIDE_INT value, int frame)
565{
566  if (value == 0)
567    return;
568
569  /* Choose whether to use a sequence using a temporary register, or
570     a sequence with multiple adds.  We can add a signed 7 bit value
571     in one instruction.  */
572  if (value > 120 || value < -120)
573    {
574      rtx tmpreg = gen_rtx_REG (SImode, REG_P1);
575      rtx insn;
576
577      if (frame)
578	frame_related_constant_load (tmpreg, value, TRUE);
579      else
580	{
581	  insn = emit_move_insn (tmpreg, GEN_INT (value));
582	  if (frame)
583	    RTX_FRAME_RELATED_P (insn) = 1;
584	}
585
586      insn = emit_insn (gen_addsi3 (spreg, spreg, tmpreg));
587      if (frame)
588	RTX_FRAME_RELATED_P (insn) = 1;
589    }
590  else
591    do
592      {
593	int size = value;
594	rtx insn;
595
596	if (size > 60)
597	  size = 60;
598	else if (size < -60)
599	  /* We could use -62, but that would leave the stack unaligned, so
600	     it's no good.  */
601	  size = -60;
602
603	insn = emit_insn (gen_addsi3 (spreg, spreg, GEN_INT (size)));
604	if (frame)
605	  RTX_FRAME_RELATED_P (insn) = 1;
606	value -= size;
607      }
608    while (value != 0);
609}
610
611/* Generate a LINK insn for a frame sized FRAME_SIZE.  If this constant
612   is too large, generate a sequence of insns that has the same effect.
613   SPREG contains (reg:SI REG_SP).  */
614
615static void
616emit_link_insn (rtx spreg, HOST_WIDE_INT frame_size)
617{
618  HOST_WIDE_INT link_size = frame_size;
619  rtx insn;
620  int i;
621
622  if (link_size > 262140)
623    link_size = 262140;
624
625  /* Use a LINK insn with as big a constant as possible, then subtract
626     any remaining size from the SP.  */
627  insn = emit_insn (gen_link (GEN_INT (-8 - link_size)));
628  RTX_FRAME_RELATED_P (insn) = 1;
629
630  for (i = 0; i < XVECLEN (PATTERN (insn), 0); i++)
631    {
632      rtx set = XVECEXP (PATTERN (insn), 0, i);
633      gcc_assert (GET_CODE (set) == SET);
634      RTX_FRAME_RELATED_P (set) = 1;
635    }
636
637  frame_size -= link_size;
638
639  if (frame_size > 0)
640    {
641      /* Must use a call-clobbered PREG that isn't the static chain.  */
642      rtx tmpreg = gen_rtx_REG (Pmode, REG_P1);
643
644      frame_related_constant_load (tmpreg, -frame_size, TRUE);
645      insn = emit_insn (gen_addsi3 (spreg, spreg, tmpreg));
646      RTX_FRAME_RELATED_P (insn) = 1;
647    }
648}
649
650/* Return the number of bytes we must reserve for outgoing arguments
651   in the current function's stack frame.  */
652
653static HOST_WIDE_INT
654arg_area_size (void)
655{
656  if (current_function_outgoing_args_size)
657    {
658      if (current_function_outgoing_args_size >= FIXED_STACK_AREA)
659	return current_function_outgoing_args_size;
660      else
661	return FIXED_STACK_AREA;
662    }
663  return 0;
664}
665
666/* Save RETS and FP, and allocate a stack frame.  ALL is true if the
667   function must save all its registers (true only for certain interrupt
668   handlers).  */
669
670static void
671do_link (rtx spreg, HOST_WIDE_INT frame_size, bool all)
672{
673  frame_size += arg_area_size ();
674
675  if (all || stack_frame_needed_p ()
676      || (must_save_fp_p () && ! current_function_is_leaf))
677    emit_link_insn (spreg, frame_size);
678  else
679    {
680      if (! current_function_is_leaf)
681	{
682	  rtx pat = gen_movsi (gen_rtx_MEM (Pmode,
683					    gen_rtx_PRE_DEC (Pmode, spreg)),
684			       bfin_rets_rtx);
685	  rtx insn = emit_insn (pat);
686	  RTX_FRAME_RELATED_P (insn) = 1;
687	}
688      if (must_save_fp_p ())
689	{
690	  rtx pat = gen_movsi (gen_rtx_MEM (Pmode,
691					    gen_rtx_PRE_DEC (Pmode, spreg)),
692			       gen_rtx_REG (Pmode, REG_FP));
693	  rtx insn = emit_insn (pat);
694	  RTX_FRAME_RELATED_P (insn) = 1;
695	}
696      add_to_sp (spreg, -frame_size, 1);
697    }
698}
699
700/* Like do_link, but used for epilogues to deallocate the stack frame.  */
701
702static void
703do_unlink (rtx spreg, HOST_WIDE_INT frame_size, bool all)
704{
705  frame_size += arg_area_size ();
706
707  if (all || stack_frame_needed_p ())
708    emit_insn (gen_unlink ());
709  else
710    {
711      rtx postinc = gen_rtx_MEM (Pmode, gen_rtx_POST_INC (Pmode, spreg));
712
713      add_to_sp (spreg, frame_size, 0);
714      if (must_save_fp_p ())
715	{
716	  rtx fpreg = gen_rtx_REG (Pmode, REG_FP);
717	  emit_move_insn (fpreg, postinc);
718	  emit_insn (gen_rtx_USE (VOIDmode, fpreg));
719	}
720      if (! current_function_is_leaf)
721	{
722	  emit_move_insn (bfin_rets_rtx, postinc);
723	  emit_insn (gen_rtx_USE (VOIDmode, bfin_rets_rtx));
724	}
725    }
726}
727
728/* Generate a prologue suitable for a function of kind FKIND.  This is
729   called for interrupt and exception handler prologues.
730   SPREG contains (reg:SI REG_SP).  */
731
732static void
733expand_interrupt_handler_prologue (rtx spreg, e_funkind fkind)
734{
735  int i;
736  HOST_WIDE_INT frame_size = get_frame_size ();
737  rtx predec1 = gen_rtx_PRE_DEC (SImode, spreg);
738  rtx predec = gen_rtx_MEM (SImode, predec1);
739  rtx insn;
740  tree attrs = TYPE_ATTRIBUTES (TREE_TYPE (current_function_decl));
741  bool all = lookup_attribute ("saveall", attrs) != NULL_TREE;
742  tree kspisusp = lookup_attribute ("kspisusp", attrs);
743
744  if (kspisusp)
745    {
746      insn = emit_move_insn (spreg, gen_rtx_REG (Pmode, REG_USP));
747      RTX_FRAME_RELATED_P (insn) = 1;
748    }
749
750  /* We need space on the stack in case we need to save the argument
751     registers.  */
752  if (fkind == EXCPT_HANDLER)
753    {
754      insn = emit_insn (gen_addsi3 (spreg, spreg, GEN_INT (-12)));
755      RTX_FRAME_RELATED_P (insn) = 1;
756    }
757
758  insn = emit_move_insn (predec, gen_rtx_REG (SImode, REG_ASTAT));
759  RTX_FRAME_RELATED_P (insn) = 1;
760
761  /* If we're calling other functions, they won't save their call-clobbered
762     registers, so we must save everything here.  */
763  if (!current_function_is_leaf)
764    all = true;
765  expand_prologue_reg_save (spreg, all, true);
766
767  for (i = REG_P7 + 1; i < REG_CC; i++)
768    if (all
769	|| regs_ever_live[i]
770	|| (!leaf_function_p () && call_used_regs[i]))
771      {
772	if (i == REG_A0 || i == REG_A1)
773	  insn = emit_move_insn (gen_rtx_MEM (PDImode, predec1),
774				 gen_rtx_REG (PDImode, i));
775	else
776	  insn = emit_move_insn (predec, gen_rtx_REG (SImode, i));
777	RTX_FRAME_RELATED_P (insn) = 1;
778      }
779
780  if (lookup_attribute ("nesting", attrs))
781    {
782      rtx srcreg = gen_rtx_REG (Pmode, (fkind == EXCPT_HANDLER ? REG_RETX
783					: fkind == NMI_HANDLER ? REG_RETN
784					: REG_RETI));
785      insn = emit_move_insn (predec, srcreg);
786      RTX_FRAME_RELATED_P (insn) = 1;
787    }
788
789  do_link (spreg, frame_size, all);
790
791  if (fkind == EXCPT_HANDLER)
792    {
793      rtx r0reg = gen_rtx_REG (SImode, REG_R0);
794      rtx r1reg = gen_rtx_REG (SImode, REG_R1);
795      rtx r2reg = gen_rtx_REG (SImode, REG_R2);
796      rtx insn;
797
798      insn = emit_move_insn (r0reg, gen_rtx_REG (SImode, REG_SEQSTAT));
799      REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_MAYBE_DEAD, const0_rtx,
800					    NULL_RTX);
801      insn = emit_insn (gen_ashrsi3 (r0reg, r0reg, GEN_INT (26)));
802      REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_MAYBE_DEAD, const0_rtx,
803					    NULL_RTX);
804      insn = emit_insn (gen_ashlsi3 (r0reg, r0reg, GEN_INT (26)));
805      REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_MAYBE_DEAD, const0_rtx,
806					    NULL_RTX);
807      insn = emit_move_insn (r1reg, spreg);
808      REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_MAYBE_DEAD, const0_rtx,
809					    NULL_RTX);
810      insn = emit_move_insn (r2reg, gen_rtx_REG (Pmode, REG_FP));
811      REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_MAYBE_DEAD, const0_rtx,
812					    NULL_RTX);
813      insn = emit_insn (gen_addsi3 (r2reg, r2reg, GEN_INT (8)));
814      REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_MAYBE_DEAD, const0_rtx,
815					    NULL_RTX);
816    }
817}
818
819/* Generate an epilogue suitable for a function of kind FKIND.  This is
820   called for interrupt and exception handler epilogues.
821   SPREG contains (reg:SI REG_SP).  */
822
823static void
824expand_interrupt_handler_epilogue (rtx spreg, e_funkind fkind)
825{
826  int i;
827  rtx postinc1 = gen_rtx_POST_INC (SImode, spreg);
828  rtx postinc = gen_rtx_MEM (SImode, postinc1);
829  tree attrs = TYPE_ATTRIBUTES (TREE_TYPE (current_function_decl));
830  bool all = lookup_attribute ("saveall", attrs) != NULL_TREE;
831
832  /* A slightly crude technique to stop flow from trying to delete "dead"
833     insns.  */
834  MEM_VOLATILE_P (postinc) = 1;
835
836  do_unlink (spreg, get_frame_size (), all);
837
838  if (lookup_attribute ("nesting", attrs))
839    {
840      rtx srcreg = gen_rtx_REG (Pmode, (fkind == EXCPT_HANDLER ? REG_RETX
841					: fkind == NMI_HANDLER ? REG_RETN
842					: REG_RETI));
843      emit_move_insn (srcreg, postinc);
844    }
845
846  /* If we're calling other functions, they won't save their call-clobbered
847     registers, so we must save (and restore) everything here.  */
848  if (!current_function_is_leaf)
849    all = true;
850
851  for (i = REG_CC - 1; i > REG_P7; i--)
852    if (all
853	|| regs_ever_live[i]
854	|| (!leaf_function_p () && call_used_regs[i]))
855      {
856	if (i == REG_A0 || i == REG_A1)
857	  {
858	    rtx mem = gen_rtx_MEM (PDImode, postinc1);
859	    MEM_VOLATILE_P (mem) = 1;
860	    emit_move_insn (gen_rtx_REG (PDImode, i), mem);
861	  }
862	else
863	  emit_move_insn (gen_rtx_REG (SImode, i), postinc);
864      }
865
866  expand_epilogue_reg_restore (spreg, all, true);
867
868  emit_move_insn (gen_rtx_REG (SImode, REG_ASTAT), postinc);
869
870  /* Deallocate any space we left on the stack in case we needed to save the
871     argument registers.  */
872  if (fkind == EXCPT_HANDLER)
873    emit_insn (gen_addsi3 (spreg, spreg, GEN_INT (12)));
874
875  emit_jump_insn (gen_return_internal (GEN_INT (fkind)));
876}
877
878/* Used while emitting the prologue to generate code to load the correct value
879   into the PIC register, which is passed in DEST.  */
880
881static rtx
882bfin_load_pic_reg (rtx dest)
883{
884  struct cgraph_local_info *i = NULL;
885  rtx addr, insn;
886
887  if (flag_unit_at_a_time)
888    i = cgraph_local_info (current_function_decl);
889
890  /* Functions local to the translation unit don't need to reload the
891     pic reg, since the caller always passes a usable one.  */
892  if (i && i->local)
893    return pic_offset_table_rtx;
894
895  if (bfin_lib_id_given)
896    addr = plus_constant (pic_offset_table_rtx, -4 - bfin_library_id * 4);
897  else
898    addr = gen_rtx_PLUS (Pmode, pic_offset_table_rtx,
899			 gen_rtx_UNSPEC (Pmode, gen_rtvec (1, const0_rtx),
900					 UNSPEC_LIBRARY_OFFSET));
901  insn = emit_insn (gen_movsi (dest, gen_rtx_MEM (Pmode, addr)));
902  REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_MAYBE_DEAD, const0_rtx, NULL);
903  return dest;
904}
905
906/* Generate RTL for the prologue of the current function.  */
907
908void
909bfin_expand_prologue (void)
910{
911  rtx insn;
912  HOST_WIDE_INT frame_size = get_frame_size ();
913  rtx spreg = gen_rtx_REG (Pmode, REG_SP);
914  e_funkind fkind = funkind (TREE_TYPE (current_function_decl));
915  rtx pic_reg_loaded = NULL_RTX;
916
917  if (fkind != SUBROUTINE)
918    {
919      expand_interrupt_handler_prologue (spreg, fkind);
920      return;
921    }
922
923  if (current_function_limit_stack)
924    {
925      HOST_WIDE_INT offset
926	= bfin_initial_elimination_offset (ARG_POINTER_REGNUM,
927					   STACK_POINTER_REGNUM);
928      rtx lim = stack_limit_rtx;
929
930      if (GET_CODE (lim) == SYMBOL_REF)
931	{
932	  rtx p2reg = gen_rtx_REG (Pmode, REG_P2);
933	  if (TARGET_ID_SHARED_LIBRARY)
934	    {
935	      rtx p1reg = gen_rtx_REG (Pmode, REG_P1);
936	      rtx val;
937	      pic_reg_loaded = bfin_load_pic_reg (p2reg);
938	      val = legitimize_pic_address (stack_limit_rtx, p1reg,
939					    pic_reg_loaded);
940	      emit_move_insn (p1reg, val);
941	      frame_related_constant_load (p2reg, offset, FALSE);
942	      emit_insn (gen_addsi3 (p2reg, p2reg, p1reg));
943	      lim = p2reg;
944	    }
945	  else
946	    {
947	      rtx limit = plus_constant (stack_limit_rtx, offset);
948	      emit_move_insn (p2reg, limit);
949	      lim = p2reg;
950	    }
951	}
952      emit_insn (gen_compare_lt (bfin_cc_rtx, spreg, lim));
953      emit_insn (gen_trapifcc ());
954    }
955  expand_prologue_reg_save (spreg, 0, false);
956
957  do_link (spreg, frame_size, false);
958
959  if (TARGET_ID_SHARED_LIBRARY
960      && (current_function_uses_pic_offset_table
961	  || !current_function_is_leaf))
962    bfin_load_pic_reg (pic_offset_table_rtx);
963}
964
965/* Generate RTL for the epilogue of the current function.  NEED_RETURN is zero
966   if this is for a sibcall.  EH_RETURN is nonzero if we're expanding an
967   eh_return pattern.  */
968
969void
970bfin_expand_epilogue (int need_return, int eh_return)
971{
972  rtx spreg = gen_rtx_REG (Pmode, REG_SP);
973  e_funkind fkind = funkind (TREE_TYPE (current_function_decl));
974
975  if (fkind != SUBROUTINE)
976    {
977      expand_interrupt_handler_epilogue (spreg, fkind);
978      return;
979    }
980
981  do_unlink (spreg, get_frame_size (), false);
982
983  expand_epilogue_reg_restore (spreg, false, false);
984
985  /* Omit the return insn if this is for a sibcall.  */
986  if (! need_return)
987    return;
988
989  if (eh_return)
990    emit_insn (gen_addsi3 (spreg, spreg, gen_rtx_REG (Pmode, REG_P2)));
991
992  emit_jump_insn (gen_return_internal (GEN_INT (SUBROUTINE)));
993}
994
995/* Return nonzero if register OLD_REG can be renamed to register NEW_REG.  */
996
997int
998bfin_hard_regno_rename_ok (unsigned int old_reg ATTRIBUTE_UNUSED,
999			   unsigned int new_reg)
1000{
1001  /* Interrupt functions can only use registers that have already been
1002     saved by the prologue, even if they would normally be
1003     call-clobbered.  */
1004
1005  if (funkind (TREE_TYPE (current_function_decl)) != SUBROUTINE
1006      && !regs_ever_live[new_reg])
1007    return 0;
1008
1009  return 1;
1010}
1011
1012/* Return the value of the return address for the frame COUNT steps up
1013   from the current frame, after the prologue.
1014   We punt for everything but the current frame by returning const0_rtx.  */
1015
1016rtx
1017bfin_return_addr_rtx (int count)
1018{
1019  if (count != 0)
1020    return const0_rtx;
1021
1022  return get_hard_reg_initial_val (Pmode, REG_RETS);
1023}
1024
1025/* Try machine-dependent ways of modifying an illegitimate address X
1026   to be legitimate.  If we find one, return the new, valid address,
1027   otherwise return NULL_RTX.
1028
1029   OLDX is the address as it was before break_out_memory_refs was called.
1030   In some cases it is useful to look at this to decide what needs to be done.
1031
1032   MODE is the mode of the memory reference.  */
1033
1034rtx
1035legitimize_address (rtx x ATTRIBUTE_UNUSED, rtx oldx ATTRIBUTE_UNUSED,
1036		    enum machine_mode mode ATTRIBUTE_UNUSED)
1037{
1038  return NULL_RTX;
1039}
1040
1041static rtx
1042bfin_delegitimize_address (rtx orig_x)
1043{
1044  rtx x = orig_x, y;
1045
1046  if (GET_CODE (x) != MEM)
1047    return orig_x;
1048
1049  x = XEXP (x, 0);
1050  if (GET_CODE (x) == PLUS
1051      && GET_CODE (XEXP (x, 1)) == UNSPEC
1052      && XINT (XEXP (x, 1), 1) == UNSPEC_MOVE_PIC
1053      && GET_CODE (XEXP (x, 0)) == REG
1054      && REGNO (XEXP (x, 0)) == PIC_OFFSET_TABLE_REGNUM)
1055    return XVECEXP (XEXP (x, 1), 0, 0);
1056
1057  return orig_x;
1058}
1059
1060/* This predicate is used to compute the length of a load/store insn.
1061   OP is a MEM rtx, we return nonzero if its addressing mode requires a
1062   32 bit instruction.  */
1063
1064int
1065effective_address_32bit_p (rtx op, enum machine_mode mode)
1066{
1067  HOST_WIDE_INT offset;
1068
1069  mode = GET_MODE (op);
1070  op = XEXP (op, 0);
1071
1072  if (GET_CODE (op) != PLUS)
1073    {
1074      gcc_assert (REG_P (op) || GET_CODE (op) == POST_INC
1075		  || GET_CODE (op) == PRE_DEC || GET_CODE (op) == POST_DEC);
1076      return 0;
1077    }
1078
1079  offset = INTVAL (XEXP (op, 1));
1080
1081  /* All byte loads use a 16 bit offset.  */
1082  if (GET_MODE_SIZE (mode) == 1)
1083    return 1;
1084
1085  if (GET_MODE_SIZE (mode) == 4)
1086    {
1087      /* Frame pointer relative loads can use a negative offset, all others
1088	 are restricted to a small positive one.  */
1089      if (XEXP (op, 0) == frame_pointer_rtx)
1090	return offset < -128 || offset > 60;
1091      return offset < 0 || offset > 60;
1092    }
1093
1094  /* Must be HImode now.  */
1095  return offset < 0 || offset > 30;
1096}
1097
1098/* Returns true if X is a memory reference using an I register.  */
1099bool
1100bfin_dsp_memref_p (rtx x)
1101{
1102  if (! MEM_P (x))
1103    return false;
1104  x = XEXP (x, 0);
1105  if (GET_CODE (x) == POST_INC || GET_CODE (x) == PRE_INC
1106      || GET_CODE (x) == POST_DEC || GET_CODE (x) == PRE_DEC)
1107    x = XEXP (x, 0);
1108  return IREG_P (x);
1109}
1110
1111/* Return cost of the memory address ADDR.
1112   All addressing modes are equally cheap on the Blackfin.  */
1113
1114static int
1115bfin_address_cost (rtx addr ATTRIBUTE_UNUSED)
1116{
1117  return 1;
1118}
1119
1120/* Subroutine of print_operand; used to print a memory reference X to FILE.  */
1121
1122void
1123print_address_operand (FILE *file, rtx x)
1124{
1125  switch (GET_CODE (x))
1126    {
1127    case PLUS:
1128      output_address (XEXP (x, 0));
1129      fprintf (file, "+");
1130      output_address (XEXP (x, 1));
1131      break;
1132
1133    case PRE_DEC:
1134      fprintf (file, "--");
1135      output_address (XEXP (x, 0));
1136      break;
1137    case POST_INC:
1138      output_address (XEXP (x, 0));
1139      fprintf (file, "++");
1140      break;
1141    case POST_DEC:
1142      output_address (XEXP (x, 0));
1143      fprintf (file, "--");
1144      break;
1145
1146    default:
1147      gcc_assert (GET_CODE (x) != MEM);
1148      print_operand (file, x, 0);
1149      break;
1150    }
1151}
1152
1153/* Adding intp DImode support by Tony
1154 * -- Q: (low  word)
1155 * -- R: (high word)
1156 */
1157
1158void
1159print_operand (FILE *file, rtx x, char code)
1160{
1161  enum machine_mode mode = GET_MODE (x);
1162
1163  switch (code)
1164    {
1165    case 'j':
1166      switch (GET_CODE (x))
1167	{
1168	case EQ:
1169	  fprintf (file, "e");
1170	  break;
1171	case NE:
1172	  fprintf (file, "ne");
1173	  break;
1174	case GT:
1175	  fprintf (file, "g");
1176	  break;
1177	case LT:
1178	  fprintf (file, "l");
1179	  break;
1180	case GE:
1181	  fprintf (file, "ge");
1182	  break;
1183	case LE:
1184	  fprintf (file, "le");
1185	  break;
1186	case GTU:
1187	  fprintf (file, "g");
1188	  break;
1189	case LTU:
1190	  fprintf (file, "l");
1191	  break;
1192	case GEU:
1193	  fprintf (file, "ge");
1194	  break;
1195	case LEU:
1196	  fprintf (file, "le");
1197	  break;
1198	default:
1199	  output_operand_lossage ("invalid %%j value");
1200	}
1201      break;
1202
1203    case 'J':					 /* reverse logic */
1204      switch (GET_CODE(x))
1205	{
1206	case EQ:
1207	  fprintf (file, "ne");
1208	  break;
1209	case NE:
1210	  fprintf (file, "e");
1211	  break;
1212	case GT:
1213	  fprintf (file, "le");
1214	  break;
1215	case LT:
1216	  fprintf (file, "ge");
1217	  break;
1218	case GE:
1219	  fprintf (file, "l");
1220	  break;
1221	case LE:
1222	  fprintf (file, "g");
1223	  break;
1224	case GTU:
1225	  fprintf (file, "le");
1226	  break;
1227	case LTU:
1228	  fprintf (file, "ge");
1229	  break;
1230	case GEU:
1231	  fprintf (file, "l");
1232	  break;
1233	case LEU:
1234	  fprintf (file, "g");
1235	  break;
1236	default:
1237	  output_operand_lossage ("invalid %%J value");
1238	}
1239      break;
1240
1241    default:
1242      switch (GET_CODE (x))
1243	{
1244	case REG:
1245	  if (code == 'h')
1246	    {
1247	      gcc_assert (REGNO (x) < 32);
1248	      fprintf (file, "%s", short_reg_names[REGNO (x)]);
1249	      /*fprintf (file, "\n%d\n ", REGNO (x));*/
1250	      break;
1251	    }
1252	  else if (code == 'd')
1253	    {
1254	      gcc_assert (REGNO (x) < 32);
1255	      fprintf (file, "%s", high_reg_names[REGNO (x)]);
1256	      break;
1257	    }
1258	  else if (code == 'w')
1259	    {
1260	      gcc_assert (REGNO (x) == REG_A0 || REGNO (x) == REG_A1);
1261	      fprintf (file, "%s.w", reg_names[REGNO (x)]);
1262	    }
1263	  else if (code == 'x')
1264	    {
1265	      gcc_assert (REGNO (x) == REG_A0 || REGNO (x) == REG_A1);
1266	      fprintf (file, "%s.x", reg_names[REGNO (x)]);
1267	    }
1268	  else if (code == 'D')
1269	    {
1270	      fprintf (file, "%s", dregs_pair_names[REGNO (x)]);
1271	    }
1272	  else if (code == 'H')
1273	    {
1274	      gcc_assert (mode == DImode || mode == DFmode);
1275	      gcc_assert (REG_P (x));
1276	      fprintf (file, "%s", reg_names[REGNO (x) + 1]);
1277	    }
1278	  else if (code == 'T')
1279	    {
1280	      gcc_assert (D_REGNO_P (REGNO (x)));
1281	      fprintf (file, "%s", byte_reg_names[REGNO (x)]);
1282	    }
1283	  else
1284	    fprintf (file, "%s", reg_names[REGNO (x)]);
1285	  break;
1286
1287	case MEM:
1288	  fputc ('[', file);
1289	  x = XEXP (x,0);
1290	  print_address_operand (file, x);
1291	  fputc (']', file);
1292	  break;
1293
1294	case CONST_INT:
1295	  if (code == 'M')
1296	    {
1297	      switch (INTVAL (x))
1298		{
1299		case MACFLAG_NONE:
1300		  break;
1301		case MACFLAG_FU:
1302		  fputs ("(FU)", file);
1303		  break;
1304		case MACFLAG_T:
1305		  fputs ("(T)", file);
1306		  break;
1307		case MACFLAG_TFU:
1308		  fputs ("(TFU)", file);
1309		  break;
1310		case MACFLAG_W32:
1311		  fputs ("(W32)", file);
1312		  break;
1313		case MACFLAG_IS:
1314		  fputs ("(IS)", file);
1315		  break;
1316		case MACFLAG_IU:
1317		  fputs ("(IU)", file);
1318		  break;
1319		case MACFLAG_IH:
1320		  fputs ("(IH)", file);
1321		  break;
1322		case MACFLAG_M:
1323		  fputs ("(M)", file);
1324		  break;
1325		case MACFLAG_ISS2:
1326		  fputs ("(ISS2)", file);
1327		  break;
1328		case MACFLAG_S2RND:
1329		  fputs ("(S2RND)", file);
1330		  break;
1331		default:
1332		  gcc_unreachable ();
1333		}
1334	      break;
1335	    }
1336	  else if (code == 'b')
1337	    {
1338	      if (INTVAL (x) == 0)
1339		fputs ("+=", file);
1340	      else if (INTVAL (x) == 1)
1341		fputs ("-=", file);
1342	      else
1343		gcc_unreachable ();
1344	      break;
1345	    }
1346	  /* Moves to half registers with d or h modifiers always use unsigned
1347	     constants.  */
1348	  else if (code == 'd')
1349	    x = GEN_INT ((INTVAL (x) >> 16) & 0xffff);
1350	  else if (code == 'h')
1351	    x = GEN_INT (INTVAL (x) & 0xffff);
1352	  else if (code == 'X')
1353	    x = GEN_INT (exact_log2 (0xffffffff & INTVAL (x)));
1354	  else if (code == 'Y')
1355	    x = GEN_INT (exact_log2 (0xffffffff & ~INTVAL (x)));
1356	  else if (code == 'Z')
1357	    /* Used for LINK insns.  */
1358	    x = GEN_INT (-8 - INTVAL (x));
1359
1360	  /* fall through */
1361
1362	case SYMBOL_REF:
1363	  output_addr_const (file, x);
1364	  break;
1365
1366	case CONST_DOUBLE:
1367	  output_operand_lossage ("invalid const_double operand");
1368	  break;
1369
1370	case UNSPEC:
1371	  switch (XINT (x, 1))
1372	    {
1373	    case UNSPEC_MOVE_PIC:
1374	      output_addr_const (file, XVECEXP (x, 0, 0));
1375	      fprintf (file, "@GOT");
1376	      break;
1377
1378	    case UNSPEC_MOVE_FDPIC:
1379	      output_addr_const (file, XVECEXP (x, 0, 0));
1380	      fprintf (file, "@GOT17M4");
1381	      break;
1382
1383	    case UNSPEC_FUNCDESC_GOT17M4:
1384	      output_addr_const (file, XVECEXP (x, 0, 0));
1385	      fprintf (file, "@FUNCDESC_GOT17M4");
1386	      break;
1387
1388	    case UNSPEC_LIBRARY_OFFSET:
1389	      fprintf (file, "_current_shared_library_p5_offset_");
1390	      break;
1391
1392	    default:
1393	      gcc_unreachable ();
1394	    }
1395	  break;
1396
1397	default:
1398	  output_addr_const (file, x);
1399	}
1400    }
1401}
1402
1403/* Argument support functions.  */
1404
1405/* Initialize a variable CUM of type CUMULATIVE_ARGS
1406   for a call to a function whose data type is FNTYPE.
1407   For a library call, FNTYPE is 0.
1408   VDSP C Compiler manual, our ABI says that
1409   first 3 words of arguments will use R0, R1 and R2.
1410*/
1411
1412void
1413init_cumulative_args (CUMULATIVE_ARGS *cum, tree fntype,
1414		      rtx libname ATTRIBUTE_UNUSED)
1415{
1416  static CUMULATIVE_ARGS zero_cum;
1417
1418  *cum = zero_cum;
1419
1420  /* Set up the number of registers to use for passing arguments.  */
1421
1422  cum->nregs = max_arg_registers;
1423  cum->arg_regs = arg_regs;
1424
1425  cum->call_cookie = CALL_NORMAL;
1426  /* Check for a longcall attribute.  */
1427  if (fntype && lookup_attribute ("shortcall", TYPE_ATTRIBUTES (fntype)))
1428    cum->call_cookie |= CALL_SHORT;
1429  else if (fntype && lookup_attribute ("longcall", TYPE_ATTRIBUTES (fntype)))
1430    cum->call_cookie |= CALL_LONG;
1431
1432  return;
1433}
1434
1435/* Update the data in CUM to advance over an argument
1436   of mode MODE and data type TYPE.
1437   (TYPE is null for libcalls where that information may not be available.)  */
1438
1439void
1440function_arg_advance (CUMULATIVE_ARGS *cum, enum machine_mode mode, tree type,
1441		      int named ATTRIBUTE_UNUSED)
1442{
1443  int count, bytes, words;
1444
1445  bytes = (mode == BLKmode) ? int_size_in_bytes (type) : GET_MODE_SIZE (mode);
1446  words = (bytes + UNITS_PER_WORD - 1) / UNITS_PER_WORD;
1447
1448  cum->words += words;
1449  cum->nregs -= words;
1450
1451  if (cum->nregs <= 0)
1452    {
1453      cum->nregs = 0;
1454      cum->arg_regs = NULL;
1455    }
1456  else
1457    {
1458      for (count = 1; count <= words; count++)
1459        cum->arg_regs++;
1460    }
1461
1462  return;
1463}
1464
1465/* Define where to put the arguments to a function.
1466   Value is zero to push the argument on the stack,
1467   or a hard register in which to store the argument.
1468
1469   MODE is the argument's machine mode.
1470   TYPE is the data type of the argument (as a tree).
1471    This is null for libcalls where that information may
1472    not be available.
1473   CUM is a variable of type CUMULATIVE_ARGS which gives info about
1474    the preceding args and about the function being called.
1475   NAMED is nonzero if this argument is a named parameter
1476    (otherwise it is an extra parameter matching an ellipsis).  */
1477
1478struct rtx_def *
1479function_arg (CUMULATIVE_ARGS *cum, enum machine_mode mode, tree type,
1480	      int named ATTRIBUTE_UNUSED)
1481{
1482  int bytes
1483    = (mode == BLKmode) ? int_size_in_bytes (type) : GET_MODE_SIZE (mode);
1484
1485  if (mode == VOIDmode)
1486    /* Compute operand 2 of the call insn.  */
1487    return GEN_INT (cum->call_cookie);
1488
1489  if (bytes == -1)
1490    return NULL_RTX;
1491
1492  if (cum->nregs)
1493    return gen_rtx_REG (mode, *(cum->arg_regs));
1494
1495  return NULL_RTX;
1496}
1497
1498/* For an arg passed partly in registers and partly in memory,
1499   this is the number of bytes passed in registers.
1500   For args passed entirely in registers or entirely in memory, zero.
1501
1502   Refer VDSP C Compiler manual, our ABI.
1503   First 3 words are in registers. So, if a an argument is larger
1504   than the registers available, it will span the register and
1505   stack.   */
1506
1507static int
1508bfin_arg_partial_bytes (CUMULATIVE_ARGS *cum, enum machine_mode mode,
1509			tree type ATTRIBUTE_UNUSED,
1510			bool named ATTRIBUTE_UNUSED)
1511{
1512  int bytes
1513    = (mode == BLKmode) ? int_size_in_bytes (type) : GET_MODE_SIZE (mode);
1514  int bytes_left = cum->nregs * UNITS_PER_WORD;
1515
1516  if (bytes == -1)
1517    return 0;
1518
1519  if (bytes_left == 0)
1520    return 0;
1521  if (bytes > bytes_left)
1522    return bytes_left;
1523  return 0;
1524}
1525
1526/* Variable sized types are passed by reference.  */
1527
1528static bool
1529bfin_pass_by_reference (CUMULATIVE_ARGS *cum ATTRIBUTE_UNUSED,
1530			enum machine_mode mode ATTRIBUTE_UNUSED,
1531			tree type, bool named ATTRIBUTE_UNUSED)
1532{
1533  return type && TREE_CODE (TYPE_SIZE (type)) != INTEGER_CST;
1534}
1535
1536/* Decide whether a type should be returned in memory (true)
1537   or in a register (false).  This is called by the macro
1538   RETURN_IN_MEMORY.  */
1539
1540int
1541bfin_return_in_memory (tree type)
1542{
1543  int size = int_size_in_bytes (type);
1544  return size > 2 * UNITS_PER_WORD || size == -1;
1545}
1546
1547/* Register in which address to store a structure value
1548   is passed to a function.  */
1549static rtx
1550bfin_struct_value_rtx (tree fntype ATTRIBUTE_UNUSED,
1551		      int incoming ATTRIBUTE_UNUSED)
1552{
1553  return gen_rtx_REG (Pmode, REG_P0);
1554}
1555
1556/* Return true when register may be used to pass function parameters.  */
1557
1558bool
1559function_arg_regno_p (int n)
1560{
1561  int i;
1562  for (i = 0; arg_regs[i] != -1; i++)
1563    if (n == arg_regs[i])
1564      return true;
1565  return false;
1566}
1567
1568/* Returns 1 if OP contains a symbol reference */
1569
1570int
1571symbolic_reference_mentioned_p (rtx op)
1572{
1573  register const char *fmt;
1574  register int i;
1575
1576  if (GET_CODE (op) == SYMBOL_REF || GET_CODE (op) == LABEL_REF)
1577    return 1;
1578
1579  fmt = GET_RTX_FORMAT (GET_CODE (op));
1580  for (i = GET_RTX_LENGTH (GET_CODE (op)) - 1; i >= 0; i--)
1581    {
1582      if (fmt[i] == 'E')
1583	{
1584	  register int j;
1585
1586	  for (j = XVECLEN (op, i) - 1; j >= 0; j--)
1587	    if (symbolic_reference_mentioned_p (XVECEXP (op, i, j)))
1588	      return 1;
1589	}
1590
1591      else if (fmt[i] == 'e' && symbolic_reference_mentioned_p (XEXP (op, i)))
1592	return 1;
1593    }
1594
1595  return 0;
1596}
1597
1598/* Decide whether we can make a sibling call to a function.  DECL is the
1599   declaration of the function being targeted by the call and EXP is the
1600   CALL_EXPR representing the call.  */
1601
1602static bool
1603bfin_function_ok_for_sibcall (tree decl ATTRIBUTE_UNUSED,
1604			      tree exp ATTRIBUTE_UNUSED)
1605{
1606  e_funkind fkind = funkind (TREE_TYPE (current_function_decl));
1607  return fkind == SUBROUTINE;
1608}
1609
1610/* Emit RTL insns to initialize the variable parts of a trampoline at
1611   TRAMP. FNADDR is an RTX for the address of the function's pure
1612   code.  CXT is an RTX for the static chain value for the function.  */
1613
1614void
1615initialize_trampoline (tramp, fnaddr, cxt)
1616     rtx tramp, fnaddr, cxt;
1617{
1618  rtx t1 = copy_to_reg (fnaddr);
1619  rtx t2 = copy_to_reg (cxt);
1620  rtx addr;
1621  int i = 0;
1622
1623  if (TARGET_FDPIC)
1624    {
1625      rtx a = memory_address (Pmode, plus_constant (tramp, 8));
1626      addr = memory_address (Pmode, tramp);
1627      emit_move_insn (gen_rtx_MEM (SImode, addr), a);
1628      i = 8;
1629    }
1630
1631  addr = memory_address (Pmode, plus_constant (tramp, i + 2));
1632  emit_move_insn (gen_rtx_MEM (HImode, addr), gen_lowpart (HImode, t1));
1633  emit_insn (gen_ashrsi3 (t1, t1, GEN_INT (16)));
1634  addr = memory_address (Pmode, plus_constant (tramp, i + 6));
1635  emit_move_insn (gen_rtx_MEM (HImode, addr), gen_lowpart (HImode, t1));
1636
1637  addr = memory_address (Pmode, plus_constant (tramp, i + 10));
1638  emit_move_insn (gen_rtx_MEM (HImode, addr), gen_lowpart (HImode, t2));
1639  emit_insn (gen_ashrsi3 (t2, t2, GEN_INT (16)));
1640  addr = memory_address (Pmode, plus_constant (tramp, i + 14));
1641  emit_move_insn (gen_rtx_MEM (HImode, addr), gen_lowpart (HImode, t2));
1642}
1643
1644/* Emit insns to move operands[1] into operands[0].  */
1645
1646void
1647emit_pic_move (rtx *operands, enum machine_mode mode ATTRIBUTE_UNUSED)
1648{
1649  rtx temp = reload_in_progress ? operands[0] : gen_reg_rtx (Pmode);
1650
1651  gcc_assert (!TARGET_FDPIC || !(reload_in_progress || reload_completed));
1652  if (GET_CODE (operands[0]) == MEM && SYMBOLIC_CONST (operands[1]))
1653    operands[1] = force_reg (SImode, operands[1]);
1654  else
1655    operands[1] = legitimize_pic_address (operands[1], temp,
1656					  TARGET_FDPIC ? OUR_FDPIC_REG
1657					  : pic_offset_table_rtx);
1658}
1659
1660/* Expand a move operation in mode MODE.  The operands are in OPERANDS.  */
1661
1662void
1663expand_move (rtx *operands, enum machine_mode mode)
1664{
1665  rtx op = operands[1];
1666  if ((TARGET_ID_SHARED_LIBRARY || TARGET_FDPIC)
1667      && SYMBOLIC_CONST (op))
1668    emit_pic_move (operands, mode);
1669  /* Don't generate memory->memory or constant->memory moves, go through a
1670     register */
1671  else if ((reload_in_progress | reload_completed) == 0
1672	   && GET_CODE (operands[0]) == MEM
1673    	   && GET_CODE (operands[1]) != REG)
1674    operands[1] = force_reg (mode, operands[1]);
1675}
1676
1677/* Split one or more DImode RTL references into pairs of SImode
1678   references.  The RTL can be REG, offsettable MEM, integer constant, or
1679   CONST_DOUBLE.  "operands" is a pointer to an array of DImode RTL to
1680   split and "num" is its length.  lo_half and hi_half are output arrays
1681   that parallel "operands".  */
1682
1683void
1684split_di (rtx operands[], int num, rtx lo_half[], rtx hi_half[])
1685{
1686  while (num--)
1687    {
1688      rtx op = operands[num];
1689
1690      /* simplify_subreg refuse to split volatile memory addresses,
1691         but we still have to handle it.  */
1692      if (GET_CODE (op) == MEM)
1693	{
1694	  lo_half[num] = adjust_address (op, SImode, 0);
1695	  hi_half[num] = adjust_address (op, SImode, 4);
1696	}
1697      else
1698	{
1699	  lo_half[num] = simplify_gen_subreg (SImode, op,
1700					      GET_MODE (op) == VOIDmode
1701					      ? DImode : GET_MODE (op), 0);
1702	  hi_half[num] = simplify_gen_subreg (SImode, op,
1703					      GET_MODE (op) == VOIDmode
1704					      ? DImode : GET_MODE (op), 4);
1705	}
1706    }
1707}
1708
1709bool
1710bfin_longcall_p (rtx op, int call_cookie)
1711{
1712  gcc_assert (GET_CODE (op) == SYMBOL_REF);
1713  if (call_cookie & CALL_SHORT)
1714    return 0;
1715  if (call_cookie & CALL_LONG)
1716    return 1;
1717  if (TARGET_LONG_CALLS)
1718    return 1;
1719  return 0;
1720}
1721
1722/* Expand a call instruction.  FNADDR is the call target, RETVAL the return value.
1723   COOKIE is a CONST_INT holding the call_cookie prepared init_cumulative_args.
1724   SIBCALL is nonzero if this is a sibling call.  */
1725
1726void
1727bfin_expand_call (rtx retval, rtx fnaddr, rtx callarg1, rtx cookie, int sibcall)
1728{
1729  rtx use = NULL, call;
1730  rtx callee = XEXP (fnaddr, 0);
1731  int nelts = 2 + !!sibcall;
1732  rtx pat;
1733  rtx picreg = get_hard_reg_initial_val (SImode, FDPIC_REGNO);
1734  int n;
1735
1736  /* In an untyped call, we can get NULL for operand 2.  */
1737  if (cookie == NULL_RTX)
1738    cookie = const0_rtx;
1739
1740  /* Static functions and indirect calls don't need the pic register.  */
1741  if (!TARGET_FDPIC && flag_pic
1742      && GET_CODE (callee) == SYMBOL_REF
1743      && !SYMBOL_REF_LOCAL_P (callee))
1744    use_reg (&use, pic_offset_table_rtx);
1745
1746  if (TARGET_FDPIC)
1747    {
1748      if (GET_CODE (callee) != SYMBOL_REF
1749	  || bfin_longcall_p (callee, INTVAL (cookie)))
1750	{
1751	  rtx addr = callee;
1752	  if (! address_operand (addr, Pmode))
1753	    addr = force_reg (Pmode, addr);
1754
1755	  fnaddr = gen_reg_rtx (SImode);
1756	  emit_insn (gen_load_funcdescsi (fnaddr, addr));
1757	  fnaddr = gen_rtx_MEM (Pmode, fnaddr);
1758
1759	  picreg = gen_reg_rtx (SImode);
1760	  emit_insn (gen_load_funcdescsi (picreg,
1761					  plus_constant (addr, 4)));
1762	}
1763
1764      nelts++;
1765    }
1766  else if ((!register_no_elim_operand (callee, Pmode)
1767	    && GET_CODE (callee) != SYMBOL_REF)
1768	   || (GET_CODE (callee) == SYMBOL_REF
1769	       && (flag_pic
1770		   || bfin_longcall_p (callee, INTVAL (cookie)))))
1771    {
1772      callee = copy_to_mode_reg (Pmode, callee);
1773      fnaddr = gen_rtx_MEM (Pmode, callee);
1774    }
1775  call = gen_rtx_CALL (VOIDmode, fnaddr, callarg1);
1776
1777  if (retval)
1778    call = gen_rtx_SET (VOIDmode, retval, call);
1779
1780  pat = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (nelts));
1781  n = 0;
1782  XVECEXP (pat, 0, n++) = call;
1783  if (TARGET_FDPIC)
1784    XVECEXP (pat, 0, n++) = gen_rtx_USE (VOIDmode, picreg);
1785  XVECEXP (pat, 0, n++) = gen_rtx_USE (VOIDmode, cookie);
1786  if (sibcall)
1787    XVECEXP (pat, 0, n++) = gen_rtx_RETURN (VOIDmode);
1788  call = emit_call_insn (pat);
1789  if (use)
1790    CALL_INSN_FUNCTION_USAGE (call) = use;
1791}
1792
1793/* Return 1 if hard register REGNO can hold a value of machine-mode MODE.  */
1794
1795int
1796hard_regno_mode_ok (int regno, enum machine_mode mode)
1797{
1798  /* Allow only dregs to store value of mode HI or QI */
1799  enum reg_class class = REGNO_REG_CLASS (regno);
1800
1801  if (mode == CCmode)
1802    return 0;
1803
1804  if (mode == V2HImode)
1805    return D_REGNO_P (regno);
1806  if (class == CCREGS)
1807    return mode == BImode;
1808  if (mode == PDImode || mode == V2PDImode)
1809    return regno == REG_A0 || regno == REG_A1;
1810  if (mode == SImode
1811      && TEST_HARD_REG_BIT (reg_class_contents[PROLOGUE_REGS], regno))
1812    return 1;
1813
1814  return TEST_HARD_REG_BIT (reg_class_contents[MOST_REGS], regno);
1815}
1816
1817/* Implements target hook vector_mode_supported_p.  */
1818
1819static bool
1820bfin_vector_mode_supported_p (enum machine_mode mode)
1821{
1822  return mode == V2HImode;
1823}
1824
1825/* Return the cost of moving data from a register in class CLASS1 to
1826   one in class CLASS2.  A cost of 2 is the default.  */
1827
1828int
1829bfin_register_move_cost (enum machine_mode mode ATTRIBUTE_UNUSED,
1830			 enum reg_class class1, enum reg_class class2)
1831{
1832  /* These need secondary reloads, so they're more expensive.  */
1833  if ((class1 == CCREGS && class2 != DREGS)
1834      || (class1 != DREGS && class2 == CCREGS))
1835    return 4;
1836
1837  /* If optimizing for size, always prefer reg-reg over reg-memory moves.  */
1838  if (optimize_size)
1839    return 2;
1840
1841  /* There are some stalls involved when moving from a DREG to a different
1842     class reg, and using the value in one of the following instructions.
1843     Attempt to model this by slightly discouraging such moves.  */
1844  if (class1 == DREGS && class2 != DREGS)
1845    return 2 * 2;
1846
1847  return 2;
1848}
1849
1850/* Return the cost of moving data of mode M between a
1851   register and memory.  A value of 2 is the default; this cost is
1852   relative to those in `REGISTER_MOVE_COST'.
1853
1854   ??? In theory L1 memory has single-cycle latency.  We should add a switch
1855   that tells the compiler whether we expect to use only L1 memory for the
1856   program; it'll make the costs more accurate.  */
1857
1858int
1859bfin_memory_move_cost (enum machine_mode mode ATTRIBUTE_UNUSED,
1860		       enum reg_class class,
1861		       int in ATTRIBUTE_UNUSED)
1862{
1863  /* Make memory accesses slightly more expensive than any register-register
1864     move.  Also, penalize non-DP registers, since they need secondary
1865     reloads to load and store.  */
1866  if (! reg_class_subset_p (class, DPREGS))
1867    return 10;
1868
1869  return 8;
1870}
1871
1872/* Inform reload about cases where moving X with a mode MODE to a register in
1873   CLASS requires an extra scratch register.  Return the class needed for the
1874   scratch register.  */
1875
1876static enum reg_class
1877bfin_secondary_reload (bool in_p, rtx x, enum reg_class class,
1878		     enum machine_mode mode, secondary_reload_info *sri)
1879{
1880  /* If we have HImode or QImode, we can only use DREGS as secondary registers;
1881     in most other cases we can also use PREGS.  */
1882  enum reg_class default_class = GET_MODE_SIZE (mode) >= 4 ? DPREGS : DREGS;
1883  enum reg_class x_class = NO_REGS;
1884  enum rtx_code code = GET_CODE (x);
1885
1886  if (code == SUBREG)
1887    x = SUBREG_REG (x), code = GET_CODE (x);
1888  if (REG_P (x))
1889    {
1890      int regno = REGNO (x);
1891      if (regno >= FIRST_PSEUDO_REGISTER)
1892	regno = reg_renumber[regno];
1893
1894      if (regno == -1)
1895	code = MEM;
1896      else
1897	x_class = REGNO_REG_CLASS (regno);
1898    }
1899
1900  /* We can be asked to reload (plus (FP) (large_constant)) into a DREG.
1901     This happens as a side effect of register elimination, and we need
1902     a scratch register to do it.  */
1903  if (fp_plus_const_operand (x, mode))
1904    {
1905      rtx op2 = XEXP (x, 1);
1906      int large_constant_p = ! CONST_7BIT_IMM_P (INTVAL (op2));
1907
1908      if (class == PREGS || class == PREGS_CLOBBERED)
1909	return NO_REGS;
1910      /* If destination is a DREG, we can do this without a scratch register
1911	 if the constant is valid for an add instruction.  */
1912      if ((class == DREGS || class == DPREGS)
1913	  && ! large_constant_p)
1914	return NO_REGS;
1915      /* Reloading to anything other than a DREG?  Use a PREG scratch
1916	 register.  */
1917      sri->icode = CODE_FOR_reload_insi;
1918      return NO_REGS;
1919    }
1920
1921  /* Data can usually be moved freely between registers of most classes.
1922     AREGS are an exception; they can only move to or from another register
1923     in AREGS or one in DREGS.  They can also be assigned the constant 0.  */
1924  if (x_class == AREGS)
1925    return class == DREGS || class == AREGS ? NO_REGS : DREGS;
1926
1927  if (class == AREGS)
1928    {
1929      if (x != const0_rtx && x_class != DREGS)
1930	return DREGS;
1931      else
1932	return NO_REGS;
1933    }
1934
1935  /* CCREGS can only be moved from/to DREGS.  */
1936  if (class == CCREGS && x_class != DREGS)
1937    return DREGS;
1938  if (x_class == CCREGS && class != DREGS)
1939    return DREGS;
1940
1941  /* All registers other than AREGS can load arbitrary constants.  The only
1942     case that remains is MEM.  */
1943  if (code == MEM)
1944    if (! reg_class_subset_p (class, default_class))
1945      return default_class;
1946  return NO_REGS;
1947}
1948
1949/* Implement TARGET_HANDLE_OPTION.  */
1950
1951static bool
1952bfin_handle_option (size_t code, const char *arg, int value)
1953{
1954  switch (code)
1955    {
1956    case OPT_mshared_library_id_:
1957      if (value > MAX_LIBRARY_ID)
1958	error ("-mshared-library-id=%s is not between 0 and %d",
1959	       arg, MAX_LIBRARY_ID);
1960      bfin_lib_id_given = 1;
1961      return true;
1962
1963    default:
1964      return true;
1965    }
1966}
1967
1968static struct machine_function *
1969bfin_init_machine_status (void)
1970{
1971  struct machine_function *f;
1972
1973  f = ggc_alloc_cleared (sizeof (struct machine_function));
1974
1975  return f;
1976}
1977
1978/* Implement the macro OVERRIDE_OPTIONS.  */
1979
1980void
1981override_options (void)
1982{
1983  if (TARGET_OMIT_LEAF_FRAME_POINTER)
1984    flag_omit_frame_pointer = 1;
1985
1986  /* Library identification */
1987  if (bfin_lib_id_given && ! TARGET_ID_SHARED_LIBRARY)
1988    error ("-mshared-library-id= specified without -mid-shared-library");
1989
1990  if (TARGET_ID_SHARED_LIBRARY && flag_pic == 0)
1991    flag_pic = 1;
1992
1993  if (TARGET_ID_SHARED_LIBRARY && TARGET_FDPIC)
1994      error ("ID shared libraries and FD-PIC mode can't be used together.");
1995
1996  /* There is no single unaligned SI op for PIC code.  Sometimes we
1997     need to use ".4byte" and sometimes we need to use ".picptr".
1998     See bfin_assemble_integer for details.  */
1999  if (TARGET_FDPIC)
2000    targetm.asm_out.unaligned_op.si = 0;
2001
2002  /* Silently turn off flag_pic if not doing FDPIC or ID shared libraries,
2003     since we don't support it and it'll just break.  */
2004  if (flag_pic && !TARGET_FDPIC && !TARGET_ID_SHARED_LIBRARY)
2005    flag_pic = 0;
2006
2007  flag_schedule_insns = 0;
2008
2009  init_machine_status = bfin_init_machine_status;
2010}
2011
2012/* Return the destination address of BRANCH.
2013   We need to use this instead of get_attr_length, because the
2014   cbranch_with_nops pattern conservatively sets its length to 6, and
2015   we still prefer to use shorter sequences.  */
2016
2017static int
2018branch_dest (rtx branch)
2019{
2020  rtx dest;
2021  int dest_uid;
2022  rtx pat = PATTERN (branch);
2023  if (GET_CODE (pat) == PARALLEL)
2024    pat = XVECEXP (pat, 0, 0);
2025  dest = SET_SRC (pat);
2026  if (GET_CODE (dest) == IF_THEN_ELSE)
2027    dest = XEXP (dest, 1);
2028  dest = XEXP (dest, 0);
2029  dest_uid = INSN_UID (dest);
2030  return INSN_ADDRESSES (dest_uid);
2031}
2032
2033/* Return nonzero if INSN is annotated with a REG_BR_PROB note that indicates
2034   it's a branch that's predicted taken.  */
2035
2036static int
2037cbranch_predicted_taken_p (rtx insn)
2038{
2039  rtx x = find_reg_note (insn, REG_BR_PROB, 0);
2040
2041  if (x)
2042    {
2043      int pred_val = INTVAL (XEXP (x, 0));
2044
2045      return pred_val >= REG_BR_PROB_BASE / 2;
2046    }
2047
2048  return 0;
2049}
2050
2051/* Templates for use by asm_conditional_branch.  */
2052
2053static const char *ccbranch_templates[][3] = {
2054  { "if !cc jump %3;",  "if cc jump 4 (bp); jump.s %3;",  "if cc jump 6 (bp); jump.l %3;" },
2055  { "if cc jump %3;",   "if !cc jump 4 (bp); jump.s %3;", "if !cc jump 6 (bp); jump.l %3;" },
2056  { "if !cc jump %3 (bp);",  "if cc jump 4; jump.s %3;",  "if cc jump 6; jump.l %3;" },
2057  { "if cc jump %3 (bp);",  "if !cc jump 4; jump.s %3;",  "if !cc jump 6; jump.l %3;" },
2058};
2059
2060/* Output INSN, which is a conditional branch instruction with operands
2061   OPERANDS.
2062
2063   We deal with the various forms of conditional branches that can be generated
2064   by bfin_reorg to prevent the hardware from doing speculative loads, by
2065   - emitting a sufficient number of nops, if N_NOPS is nonzero, or
2066   - always emitting the branch as predicted taken, if PREDICT_TAKEN is true.
2067   Either of these is only necessary if the branch is short, otherwise the
2068   template we use ends in an unconditional jump which flushes the pipeline
2069   anyway.  */
2070
2071void
2072asm_conditional_branch (rtx insn, rtx *operands, int n_nops, int predict_taken)
2073{
2074  int offset = branch_dest (insn) - INSN_ADDRESSES (INSN_UID (insn));
2075  /* Note : offset for instructions like if cc jmp; jump.[sl] offset
2076            is to be taken from start of if cc rather than jump.
2077            Range for jump.s is (-4094, 4096) instead of (-4096, 4094)
2078  */
2079  int len = (offset >= -1024 && offset <= 1022 ? 0
2080	     : offset >= -4094 && offset <= 4096 ? 1
2081	     : 2);
2082  int bp = predict_taken && len == 0 ? 1 : cbranch_predicted_taken_p (insn);
2083  int idx = (bp << 1) | (GET_CODE (operands[0]) == EQ ? BRF : BRT);
2084  output_asm_insn (ccbranch_templates[idx][len], operands);
2085  gcc_assert (n_nops == 0 || !bp);
2086  if (len == 0)
2087    while (n_nops-- > 0)
2088      output_asm_insn ("nop;", NULL);
2089}
2090
2091/* Emit rtl for a comparison operation CMP in mode MODE.  Operands have been
2092   stored in bfin_compare_op0 and bfin_compare_op1 already.  */
2093
2094rtx
2095bfin_gen_compare (rtx cmp, enum machine_mode mode ATTRIBUTE_UNUSED)
2096{
2097  enum rtx_code code1, code2;
2098  rtx op0 = bfin_compare_op0, op1 = bfin_compare_op1;
2099  rtx tem = bfin_cc_rtx;
2100  enum rtx_code code = GET_CODE (cmp);
2101
2102  /* If we have a BImode input, then we already have a compare result, and
2103     do not need to emit another comparison.  */
2104  if (GET_MODE (op0) == BImode)
2105    {
2106      gcc_assert ((code == NE || code == EQ) && op1 == const0_rtx);
2107      tem = op0, code2 = code;
2108    }
2109  else
2110    {
2111      switch (code) {
2112	/* bfin has these conditions */
2113      case EQ:
2114      case LT:
2115      case LE:
2116      case LEU:
2117      case LTU:
2118	code1 = code;
2119	code2 = NE;
2120	break;
2121      default:
2122	code1 = reverse_condition (code);
2123	code2 = EQ;
2124	break;
2125      }
2126      emit_insn (gen_rtx_SET (BImode, tem,
2127			      gen_rtx_fmt_ee (code1, BImode, op0, op1)));
2128    }
2129
2130  return gen_rtx_fmt_ee (code2, BImode, tem, CONST0_RTX (BImode));
2131}
2132
2133/* Return nonzero iff C has exactly one bit set if it is interpreted
2134   as a 32 bit constant.  */
2135
2136int
2137log2constp (unsigned HOST_WIDE_INT c)
2138{
2139  c &= 0xFFFFFFFF;
2140  return c != 0 && (c & (c-1)) == 0;
2141}
2142
2143/* Returns the number of consecutive least significant zeros in the binary
2144   representation of *V.
2145   We modify *V to contain the original value arithmetically shifted right by
2146   the number of zeroes.  */
2147
2148static int
2149shiftr_zero (HOST_WIDE_INT *v)
2150{
2151  unsigned HOST_WIDE_INT tmp = *v;
2152  unsigned HOST_WIDE_INT sgn;
2153  int n = 0;
2154
2155  if (tmp == 0)
2156    return 0;
2157
2158  sgn = tmp & ((unsigned HOST_WIDE_INT) 1 << (HOST_BITS_PER_WIDE_INT - 1));
2159  while ((tmp & 0x1) == 0 && n <= 32)
2160    {
2161      tmp = (tmp >> 1) | sgn;
2162      n++;
2163    }
2164  *v = tmp;
2165  return n;
2166}
2167
2168/* After reload, split the load of an immediate constant.  OPERANDS are the
2169   operands of the movsi_insn pattern which we are splitting.  We return
2170   nonzero if we emitted a sequence to load the constant, zero if we emitted
2171   nothing because we want to use the splitter's default sequence.  */
2172
2173int
2174split_load_immediate (rtx operands[])
2175{
2176  HOST_WIDE_INT val = INTVAL (operands[1]);
2177  HOST_WIDE_INT tmp;
2178  HOST_WIDE_INT shifted = val;
2179  HOST_WIDE_INT shifted_compl = ~val;
2180  int num_zero = shiftr_zero (&shifted);
2181  int num_compl_zero = shiftr_zero (&shifted_compl);
2182  unsigned int regno = REGNO (operands[0]);
2183  enum reg_class class1 = REGNO_REG_CLASS (regno);
2184
2185  /* This case takes care of single-bit set/clear constants, which we could
2186     also implement with BITSET/BITCLR.  */
2187  if (num_zero
2188      && shifted >= -32768 && shifted < 65536
2189      && (D_REGNO_P (regno)
2190	  || (regno >= REG_P0 && regno <= REG_P7 && num_zero <= 2)))
2191    {
2192      emit_insn (gen_movsi (operands[0], GEN_INT (shifted)));
2193      emit_insn (gen_ashlsi3 (operands[0], operands[0], GEN_INT (num_zero)));
2194      return 1;
2195    }
2196
2197  tmp = val & 0xFFFF;
2198  tmp |= -(tmp & 0x8000);
2199
2200  /* If high word has one bit set or clear, try to use a bit operation.  */
2201  if (D_REGNO_P (regno))
2202    {
2203      if (log2constp (val & 0xFFFF0000))
2204	{
2205	  emit_insn (gen_movsi (operands[0], GEN_INT (val & 0xFFFF)));
2206	  emit_insn (gen_iorsi3 (operands[0], operands[0], GEN_INT (val & 0xFFFF0000)));
2207	  return 1;
2208	}
2209      else if (log2constp (val | 0xFFFF) && (val & 0x8000) != 0)
2210	{
2211	  emit_insn (gen_movsi (operands[0], GEN_INT (tmp)));
2212	  emit_insn (gen_andsi3 (operands[0], operands[0], GEN_INT (val | 0xFFFF)));
2213	}
2214    }
2215
2216  if (D_REGNO_P (regno))
2217    {
2218      if (CONST_7BIT_IMM_P (tmp))
2219	{
2220	  emit_insn (gen_movsi (operands[0], GEN_INT (tmp)));
2221	  emit_insn (gen_movstricthi_high (operands[0], GEN_INT (val & -65536)));
2222	  return 1;
2223	}
2224
2225      if ((val & 0xFFFF0000) == 0)
2226	{
2227	  emit_insn (gen_movsi (operands[0], const0_rtx));
2228	  emit_insn (gen_movsi_low (operands[0], operands[0], operands[1]));
2229	  return 1;
2230	}
2231
2232      if ((val & 0xFFFF0000) == 0xFFFF0000)
2233	{
2234	  emit_insn (gen_movsi (operands[0], constm1_rtx));
2235	  emit_insn (gen_movsi_low (operands[0], operands[0], operands[1]));
2236	  return 1;
2237	}
2238    }
2239
2240  /* Need DREGs for the remaining case.  */
2241  if (regno > REG_R7)
2242    return 0;
2243
2244  if (optimize_size
2245      && num_compl_zero && CONST_7BIT_IMM_P (shifted_compl))
2246    {
2247      /* If optimizing for size, generate a sequence that has more instructions
2248	 but is shorter.  */
2249      emit_insn (gen_movsi (operands[0], GEN_INT (shifted_compl)));
2250      emit_insn (gen_ashlsi3 (operands[0], operands[0],
2251			      GEN_INT (num_compl_zero)));
2252      emit_insn (gen_one_cmplsi2 (operands[0], operands[0]));
2253      return 1;
2254    }
2255  return 0;
2256}
2257
2258/* Return true if the legitimate memory address for a memory operand of mode
2259   MODE.  Return false if not.  */
2260
2261static bool
2262bfin_valid_add (enum machine_mode mode, HOST_WIDE_INT value)
2263{
2264  unsigned HOST_WIDE_INT v = value > 0 ? value : -value;
2265  int sz = GET_MODE_SIZE (mode);
2266  int shift = sz == 1 ? 0 : sz == 2 ? 1 : 2;
2267  /* The usual offsettable_memref machinery doesn't work so well for this
2268     port, so we deal with the problem here.  */
2269  unsigned HOST_WIDE_INT mask = sz == 8 ? 0x7ffe : 0x7fff;
2270  return (v & ~(mask << shift)) == 0;
2271}
2272
2273static bool
2274bfin_valid_reg_p (unsigned int regno, int strict, enum machine_mode mode,
2275		  enum rtx_code outer_code)
2276{
2277  if (strict)
2278    return REGNO_OK_FOR_BASE_STRICT_P (regno, mode, outer_code, SCRATCH);
2279  else
2280    return REGNO_OK_FOR_BASE_NONSTRICT_P (regno, mode, outer_code, SCRATCH);
2281}
2282
2283bool
2284bfin_legitimate_address_p (enum machine_mode mode, rtx x, int strict)
2285{
2286  switch (GET_CODE (x)) {
2287  case REG:
2288    if (bfin_valid_reg_p (REGNO (x), strict, mode, MEM))
2289      return true;
2290    break;
2291  case PLUS:
2292    if (REG_P (XEXP (x, 0))
2293	&& bfin_valid_reg_p (REGNO (XEXP (x, 0)), strict, mode, PLUS)
2294	&& ((GET_CODE (XEXP (x, 1)) == UNSPEC && mode == SImode)
2295	    || (GET_CODE (XEXP (x, 1)) == CONST_INT
2296		&& bfin_valid_add (mode, INTVAL (XEXP (x, 1))))))
2297      return true;
2298    break;
2299  case POST_INC:
2300  case POST_DEC:
2301    if (LEGITIMATE_MODE_FOR_AUTOINC_P (mode)
2302	&& REG_P (XEXP (x, 0))
2303	&& bfin_valid_reg_p (REGNO (XEXP (x, 0)), strict, mode, POST_INC))
2304      return true;
2305  case PRE_DEC:
2306    if (LEGITIMATE_MODE_FOR_AUTOINC_P (mode)
2307	&& XEXP (x, 0) == stack_pointer_rtx
2308	&& REG_P (XEXP (x, 0))
2309	&& bfin_valid_reg_p (REGNO (XEXP (x, 0)), strict, mode, PRE_DEC))
2310      return true;
2311    break;
2312  default:
2313    break;
2314  }
2315  return false;
2316}
2317
2318static bool
2319bfin_rtx_costs (rtx x, int code, int outer_code, int *total)
2320{
2321  int cost2 = COSTS_N_INSNS (1);
2322
2323  switch (code)
2324    {
2325    case CONST_INT:
2326      if (outer_code == SET || outer_code == PLUS)
2327        *total = CONST_7BIT_IMM_P (INTVAL (x)) ? 0 : cost2;
2328      else if (outer_code == AND)
2329        *total = log2constp (~INTVAL (x)) ? 0 : cost2;
2330      else if (outer_code == LE || outer_code == LT || outer_code == EQ)
2331        *total = (INTVAL (x) >= -4 && INTVAL (x) <= 3) ? 0 : cost2;
2332      else if (outer_code == LEU || outer_code == LTU)
2333        *total = (INTVAL (x) >= 0 && INTVAL (x) <= 7) ? 0 : cost2;
2334      else if (outer_code == MULT)
2335        *total = (INTVAL (x) == 2 || INTVAL (x) == 4) ? 0 : cost2;
2336      else if (outer_code == ASHIFT && (INTVAL (x) == 1 || INTVAL (x) == 2))
2337        *total = 0;
2338      else if (outer_code == ASHIFT || outer_code == ASHIFTRT
2339	       || outer_code == LSHIFTRT)
2340        *total = (INTVAL (x) >= 0 && INTVAL (x) <= 31) ? 0 : cost2;
2341      else if (outer_code == IOR || outer_code == XOR)
2342        *total = (INTVAL (x) & (INTVAL (x) - 1)) == 0 ? 0 : cost2;
2343      else
2344	*total = cost2;
2345      return true;
2346
2347    case CONST:
2348    case LABEL_REF:
2349    case SYMBOL_REF:
2350    case CONST_DOUBLE:
2351      *total = COSTS_N_INSNS (2);
2352      return true;
2353
2354    case PLUS:
2355      if (GET_MODE (x) == Pmode)
2356	{
2357	  if (GET_CODE (XEXP (x, 0)) == MULT
2358	      && GET_CODE (XEXP (XEXP (x, 0), 1)) == CONST_INT)
2359	    {
2360	      HOST_WIDE_INT val = INTVAL (XEXP (XEXP (x, 0), 1));
2361	      if (val == 2 || val == 4)
2362		{
2363		  *total = cost2;
2364		  *total += rtx_cost (XEXP (XEXP (x, 0), 0), outer_code);
2365		  *total += rtx_cost (XEXP (x, 1), outer_code);
2366		  return true;
2367		}
2368	    }
2369	}
2370
2371      /* fall through */
2372
2373    case MINUS:
2374    case ASHIFT:
2375    case ASHIFTRT:
2376    case LSHIFTRT:
2377      if (GET_MODE (x) == DImode)
2378	*total = 6 * cost2;
2379      return false;
2380
2381    case AND:
2382    case IOR:
2383    case XOR:
2384      if (GET_MODE (x) == DImode)
2385	*total = 2 * cost2;
2386      return false;
2387
2388    case MULT:
2389      if (GET_MODE_SIZE (GET_MODE (x)) <= UNITS_PER_WORD)
2390	*total = COSTS_N_INSNS (3);
2391      return false;
2392
2393    case UDIV:
2394    case UMOD:
2395      *total = COSTS_N_INSNS (32);
2396      return true;
2397
2398    case VEC_CONCAT:
2399    case VEC_SELECT:
2400      if (outer_code == SET)
2401	*total = cost2;
2402      return true;
2403
2404    default:
2405      return false;
2406    }
2407}
2408
2409static void
2410bfin_internal_label (FILE *stream, const char *prefix, unsigned long num)
2411{
2412  fprintf (stream, "%s%s$%ld:\n", LOCAL_LABEL_PREFIX, prefix, num);
2413}
2414
2415/* Used for communication between {push,pop}_multiple_operation (which
2416   we use not only as a predicate) and the corresponding output functions.  */
2417static int first_preg_to_save, first_dreg_to_save;
2418
2419int
2420push_multiple_operation (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2421{
2422  int lastdreg = 8, lastpreg = 6;
2423  int i, group;
2424
2425  first_preg_to_save = lastpreg;
2426  first_dreg_to_save = lastdreg;
2427  for (i = 1, group = 0; i < XVECLEN (op, 0) - 1; i++)
2428    {
2429      rtx t = XVECEXP (op, 0, i);
2430      rtx src, dest;
2431      int regno;
2432
2433      if (GET_CODE (t) != SET)
2434	return 0;
2435
2436      src = SET_SRC (t);
2437      dest = SET_DEST (t);
2438      if (GET_CODE (dest) != MEM || ! REG_P (src))
2439	return 0;
2440      dest = XEXP (dest, 0);
2441      if (GET_CODE (dest) != PLUS
2442	  || ! REG_P (XEXP (dest, 0))
2443	  || REGNO (XEXP (dest, 0)) != REG_SP
2444	  || GET_CODE (XEXP (dest, 1)) != CONST_INT
2445	  || INTVAL (XEXP (dest, 1)) != -i * 4)
2446	return 0;
2447
2448      regno = REGNO (src);
2449      if (group == 0)
2450	{
2451	  if (D_REGNO_P (regno))
2452	    {
2453	      group = 1;
2454	      first_dreg_to_save = lastdreg = regno - REG_R0;
2455	    }
2456	  else if (regno >= REG_P0 && regno <= REG_P7)
2457	    {
2458	      group = 2;
2459	      first_preg_to_save = lastpreg = regno - REG_P0;
2460	    }
2461	  else
2462	    return 0;
2463
2464	  continue;
2465	}
2466
2467      if (group == 1)
2468	{
2469	  if (regno >= REG_P0 && regno <= REG_P7)
2470	    {
2471	      group = 2;
2472	      first_preg_to_save = lastpreg = regno - REG_P0;
2473	    }
2474	  else if (regno != REG_R0 + lastdreg + 1)
2475	    return 0;
2476	  else
2477	    lastdreg++;
2478	}
2479      else if (group == 2)
2480	{
2481	  if (regno != REG_P0 + lastpreg + 1)
2482	    return 0;
2483	  lastpreg++;
2484	}
2485    }
2486  return 1;
2487}
2488
2489int
2490pop_multiple_operation (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2491{
2492  int lastdreg = 8, lastpreg = 6;
2493  int i, group;
2494
2495  for (i = 1, group = 0; i < XVECLEN (op, 0); i++)
2496    {
2497      rtx t = XVECEXP (op, 0, i);
2498      rtx src, dest;
2499      int regno;
2500
2501      if (GET_CODE (t) != SET)
2502	return 0;
2503
2504      src = SET_SRC (t);
2505      dest = SET_DEST (t);
2506      if (GET_CODE (src) != MEM || ! REG_P (dest))
2507	return 0;
2508      src = XEXP (src, 0);
2509
2510      if (i == 1)
2511	{
2512	  if (! REG_P (src) || REGNO (src) != REG_SP)
2513	    return 0;
2514	}
2515      else if (GET_CODE (src) != PLUS
2516	       || ! REG_P (XEXP (src, 0))
2517	       || REGNO (XEXP (src, 0)) != REG_SP
2518	       || GET_CODE (XEXP (src, 1)) != CONST_INT
2519	       || INTVAL (XEXP (src, 1)) != (i - 1) * 4)
2520	return 0;
2521
2522      regno = REGNO (dest);
2523      if (group == 0)
2524	{
2525	  if (regno == REG_R7)
2526	    {
2527	      group = 1;
2528	      lastdreg = 7;
2529	    }
2530	  else if (regno != REG_P0 + lastpreg - 1)
2531	    return 0;
2532	  else
2533	    lastpreg--;
2534	}
2535      else if (group == 1)
2536	{
2537	  if (regno != REG_R0 + lastdreg - 1)
2538	    return 0;
2539	  else
2540	    lastdreg--;
2541	}
2542    }
2543  first_dreg_to_save = lastdreg;
2544  first_preg_to_save = lastpreg;
2545  return 1;
2546}
2547
2548/* Emit assembly code for one multi-register push described by INSN, with
2549   operands in OPERANDS.  */
2550
2551void
2552output_push_multiple (rtx insn, rtx *operands)
2553{
2554  char buf[80];
2555  int ok;
2556
2557  /* Validate the insn again, and compute first_[dp]reg_to_save. */
2558  ok = push_multiple_operation (PATTERN (insn), VOIDmode);
2559  gcc_assert (ok);
2560
2561  if (first_dreg_to_save == 8)
2562    sprintf (buf, "[--sp] = ( p5:%d );\n", first_preg_to_save);
2563  else if (first_preg_to_save == 6)
2564    sprintf (buf, "[--sp] = ( r7:%d );\n", first_dreg_to_save);
2565  else
2566    sprintf (buf, "[--sp] = ( r7:%d, p5:%d );\n",
2567	     first_dreg_to_save, first_preg_to_save);
2568
2569  output_asm_insn (buf, operands);
2570}
2571
2572/* Emit assembly code for one multi-register pop described by INSN, with
2573   operands in OPERANDS.  */
2574
2575void
2576output_pop_multiple (rtx insn, rtx *operands)
2577{
2578  char buf[80];
2579  int ok;
2580
2581  /* Validate the insn again, and compute first_[dp]reg_to_save. */
2582  ok = pop_multiple_operation (PATTERN (insn), VOIDmode);
2583  gcc_assert (ok);
2584
2585  if (first_dreg_to_save == 8)
2586    sprintf (buf, "( p5:%d ) = [sp++];\n", first_preg_to_save);
2587  else if (first_preg_to_save == 6)
2588    sprintf (buf, "( r7:%d ) = [sp++];\n", first_dreg_to_save);
2589  else
2590    sprintf (buf, "( r7:%d, p5:%d ) = [sp++];\n",
2591	     first_dreg_to_save, first_preg_to_save);
2592
2593  output_asm_insn (buf, operands);
2594}
2595
2596/* Adjust DST and SRC by OFFSET bytes, and generate one move in mode MODE.  */
2597
2598static void
2599single_move_for_movmem (rtx dst, rtx src, enum machine_mode mode, HOST_WIDE_INT offset)
2600{
2601  rtx scratch = gen_reg_rtx (mode);
2602  rtx srcmem, dstmem;
2603
2604  srcmem = adjust_address_nv (src, mode, offset);
2605  dstmem = adjust_address_nv (dst, mode, offset);
2606  emit_move_insn (scratch, srcmem);
2607  emit_move_insn (dstmem, scratch);
2608}
2609
2610/* Expand a string move operation of COUNT_EXP bytes from SRC to DST, with
2611   alignment ALIGN_EXP.  Return true if successful, false if we should fall
2612   back on a different method.  */
2613
2614bool
2615bfin_expand_movmem (rtx dst, rtx src, rtx count_exp, rtx align_exp)
2616{
2617  rtx srcreg, destreg, countreg;
2618  HOST_WIDE_INT align = 0;
2619  unsigned HOST_WIDE_INT count = 0;
2620
2621  if (GET_CODE (align_exp) == CONST_INT)
2622    align = INTVAL (align_exp);
2623  if (GET_CODE (count_exp) == CONST_INT)
2624    {
2625      count = INTVAL (count_exp);
2626#if 0
2627      if (!TARGET_INLINE_ALL_STRINGOPS && count > 64)
2628	return false;
2629#endif
2630    }
2631
2632  /* If optimizing for size, only do single copies inline.  */
2633  if (optimize_size)
2634    {
2635      if (count == 2 && align < 2)
2636	return false;
2637      if (count == 4 && align < 4)
2638	return false;
2639      if (count != 1 && count != 2 && count != 4)
2640	return false;
2641    }
2642  if (align < 2 && count != 1)
2643    return false;
2644
2645  destreg = copy_to_mode_reg (Pmode, XEXP (dst, 0));
2646  if (destreg != XEXP (dst, 0))
2647    dst = replace_equiv_address_nv (dst, destreg);
2648  srcreg = copy_to_mode_reg (Pmode, XEXP (src, 0));
2649  if (srcreg != XEXP (src, 0))
2650    src = replace_equiv_address_nv (src, srcreg);
2651
2652  if (count != 0 && align >= 2)
2653    {
2654      unsigned HOST_WIDE_INT offset = 0;
2655
2656      if (align >= 4)
2657	{
2658	  if ((count & ~3) == 4)
2659	    {
2660	      single_move_for_movmem (dst, src, SImode, offset);
2661	      offset = 4;
2662	    }
2663	  else if (count & ~3)
2664	    {
2665	      HOST_WIDE_INT new_count = ((count >> 2) & 0x3fffffff) - 1;
2666	      countreg = copy_to_mode_reg (Pmode, GEN_INT (new_count));
2667
2668	      emit_insn (gen_rep_movsi (destreg, srcreg, countreg, destreg, srcreg));
2669	    }
2670	  if (count & 2)
2671	    {
2672	      single_move_for_movmem (dst, src, HImode, offset);
2673	      offset += 2;
2674	    }
2675	}
2676      else
2677	{
2678	  if ((count & ~1) == 2)
2679	    {
2680	      single_move_for_movmem (dst, src, HImode, offset);
2681	      offset = 2;
2682	    }
2683	  else if (count & ~1)
2684	    {
2685	      HOST_WIDE_INT new_count = ((count >> 1) & 0x7fffffff) - 1;
2686	      countreg = copy_to_mode_reg (Pmode, GEN_INT (new_count));
2687
2688	      emit_insn (gen_rep_movhi (destreg, srcreg, countreg, destreg, srcreg));
2689	    }
2690	}
2691      if (count & 1)
2692	{
2693	  single_move_for_movmem (dst, src, QImode, offset);
2694	}
2695      return true;
2696    }
2697  return false;
2698}
2699
2700
2701static int
2702bfin_adjust_cost (rtx insn, rtx link, rtx dep_insn, int cost)
2703{
2704  enum attr_type insn_type, dep_insn_type;
2705  int dep_insn_code_number;
2706
2707  /* Anti and output dependencies have zero cost.  */
2708  if (REG_NOTE_KIND (link) != 0)
2709    return 0;
2710
2711  dep_insn_code_number = recog_memoized (dep_insn);
2712
2713  /* If we can't recognize the insns, we can't really do anything.  */
2714  if (dep_insn_code_number < 0 || recog_memoized (insn) < 0)
2715    return cost;
2716
2717  insn_type = get_attr_type (insn);
2718  dep_insn_type = get_attr_type (dep_insn);
2719
2720  if (dep_insn_type == TYPE_MOVE || dep_insn_type == TYPE_MCLD)
2721    {
2722      rtx pat = PATTERN (dep_insn);
2723      rtx dest = SET_DEST (pat);
2724      rtx src = SET_SRC (pat);
2725      if (! ADDRESS_REGNO_P (REGNO (dest)) || ! D_REGNO_P (REGNO (src)))
2726	return cost;
2727      return cost + (dep_insn_type == TYPE_MOVE ? 4 : 3);
2728    }
2729
2730  return cost;
2731}
2732
2733
2734/* Increment the counter for the number of loop instructions in the
2735   current function.  */
2736
2737void
2738bfin_hardware_loop (void)
2739{
2740  cfun->machine->has_hardware_loops++;
2741}
2742
2743/* Maximum loop nesting depth.  */
2744#define MAX_LOOP_DEPTH 2
2745
2746/* Maximum size of a loop.  */
2747#define MAX_LOOP_LENGTH 2042
2748
2749/* We need to keep a vector of loops */
2750typedef struct loop_info *loop_info;
2751DEF_VEC_P (loop_info);
2752DEF_VEC_ALLOC_P (loop_info,heap);
2753
2754/* Information about a loop we have found (or are in the process of
2755   finding).  */
2756struct loop_info GTY (())
2757{
2758  /* loop number, for dumps */
2759  int loop_no;
2760
2761  /* Predecessor block of the loop.   This is the one that falls into
2762     the loop and contains the initialization instruction.  */
2763  basic_block predecessor;
2764
2765  /* First block in the loop.  This is the one branched to by the loop_end
2766     insn.  */
2767  basic_block head;
2768
2769  /* Last block in the loop (the one with the loop_end insn).  */
2770  basic_block tail;
2771
2772  /* The successor block of the loop.  This is the one the loop_end insn
2773     falls into.  */
2774  basic_block successor;
2775
2776  /* The last instruction in the tail.  */
2777  rtx last_insn;
2778
2779  /* The loop_end insn.  */
2780  rtx loop_end;
2781
2782  /* The iteration register.  */
2783  rtx iter_reg;
2784
2785  /* The new initialization insn.  */
2786  rtx init;
2787
2788  /* The new initialization instruction.  */
2789  rtx loop_init;
2790
2791  /* The new label placed at the beginning of the loop. */
2792  rtx start_label;
2793
2794  /* The new label placed at the end of the loop. */
2795  rtx end_label;
2796
2797  /* The length of the loop.  */
2798  int length;
2799
2800  /* The nesting depth of the loop.  */
2801  int depth;
2802
2803  /* Nonzero if we can't optimize this loop.  */
2804  int bad;
2805
2806  /* True if we have visited this loop.  */
2807  int visited;
2808
2809  /* True if this loop body clobbers any of LC0, LT0, or LB0.  */
2810  int clobber_loop0;
2811
2812  /* True if this loop body clobbers any of LC1, LT1, or LB1.  */
2813  int clobber_loop1;
2814
2815  /* Next loop in the graph. */
2816  struct loop_info *next;
2817
2818  /* Immediate outer loop of this loop.  */
2819  struct loop_info *outer;
2820
2821  /* Vector of blocks only within the loop, including those within
2822     inner loops.  */
2823  VEC (basic_block,heap) *blocks;
2824
2825  /* Same information in a bitmap.  */
2826  bitmap block_bitmap;
2827
2828  /* Vector of inner loops within this loop  */
2829  VEC (loop_info,heap) *loops;
2830};
2831
2832static void
2833bfin_dump_loops (loop_info loops)
2834{
2835  loop_info loop;
2836
2837  for (loop = loops; loop; loop = loop->next)
2838    {
2839      loop_info i;
2840      basic_block b;
2841      unsigned ix;
2842
2843      fprintf (dump_file, ";; loop %d: ", loop->loop_no);
2844      if (loop->bad)
2845	fprintf (dump_file, "(bad) ");
2846      fprintf (dump_file, "{head:%d, depth:%d}", loop->head->index, loop->depth);
2847
2848      fprintf (dump_file, " blocks: [ ");
2849      for (ix = 0; VEC_iterate (basic_block, loop->blocks, ix, b); ix++)
2850	fprintf (dump_file, "%d ", b->index);
2851      fprintf (dump_file, "] ");
2852
2853      fprintf (dump_file, " inner loops: [ ");
2854      for (ix = 0; VEC_iterate (loop_info, loop->loops, ix, i); ix++)
2855	fprintf (dump_file, "%d ", i->loop_no);
2856      fprintf (dump_file, "]\n");
2857    }
2858  fprintf (dump_file, "\n");
2859}
2860
2861/* Scan the blocks of LOOP (and its inferiors) looking for basic block
2862   BB. Return true, if we find it.  */
2863
2864static bool
2865bfin_bb_in_loop (loop_info loop, basic_block bb)
2866{
2867  return bitmap_bit_p (loop->block_bitmap, bb->index);
2868}
2869
2870/* Scan the blocks of LOOP (and its inferiors) looking for uses of
2871   REG.  Return true, if we find any.  Don't count the loop's loop_end
2872   insn if it matches LOOP_END.  */
2873
2874static bool
2875bfin_scan_loop (loop_info loop, rtx reg, rtx loop_end)
2876{
2877  unsigned ix;
2878  basic_block bb;
2879
2880  for (ix = 0; VEC_iterate (basic_block, loop->blocks, ix, bb); ix++)
2881    {
2882      rtx insn;
2883
2884      for (insn = BB_HEAD (bb);
2885	   insn != NEXT_INSN (BB_END (bb));
2886	   insn = NEXT_INSN (insn))
2887	{
2888	  if (!INSN_P (insn))
2889	    continue;
2890	  if (insn == loop_end)
2891	    continue;
2892	  if (reg_mentioned_p (reg, PATTERN (insn)))
2893	    return true;
2894	}
2895    }
2896  return false;
2897}
2898
2899/* Optimize LOOP.  */
2900
2901static void
2902bfin_optimize_loop (loop_info loop)
2903{
2904  basic_block bb;
2905  loop_info inner;
2906  rtx insn, init_insn, last_insn, nop_insn;
2907  rtx loop_init, start_label, end_label;
2908  rtx reg_lc0, reg_lc1, reg_lt0, reg_lt1, reg_lb0, reg_lb1;
2909  rtx iter_reg;
2910  rtx lc_reg, lt_reg, lb_reg;
2911  rtx seq;
2912  int length;
2913  unsigned ix;
2914  int inner_depth = 0;
2915
2916  if (loop->visited)
2917    return;
2918
2919  loop->visited = 1;
2920
2921  if (loop->bad)
2922    {
2923      if (dump_file)
2924	fprintf (dump_file, ";; loop %d bad when found\n", loop->loop_no);
2925      goto bad_loop;
2926    }
2927
2928  /* Every loop contains in its list of inner loops every loop nested inside
2929     it, even if there are intermediate loops.  This works because we're doing
2930     a depth-first search here and never visit a loop more than once.  */
2931  for (ix = 0; VEC_iterate (loop_info, loop->loops, ix, inner); ix++)
2932    {
2933      bfin_optimize_loop (inner);
2934
2935      if (!inner->bad && inner_depth < inner->depth)
2936	{
2937	  inner_depth = inner->depth;
2938
2939	  loop->clobber_loop0 |= inner->clobber_loop0;
2940	  loop->clobber_loop1 |= inner->clobber_loop1;
2941	}
2942    }
2943
2944  loop->depth = inner_depth + 1;
2945  if (loop->depth > MAX_LOOP_DEPTH)
2946    {
2947      if (dump_file)
2948	fprintf (dump_file, ";; loop %d too deep\n", loop->loop_no);
2949      goto bad_loop;
2950    }
2951
2952  /* Get the loop iteration register.  */
2953  iter_reg = loop->iter_reg;
2954
2955  if (!DPREG_P (iter_reg))
2956    {
2957      if (dump_file)
2958	fprintf (dump_file, ";; loop %d iteration count NOT in PREG or DREG\n",
2959		 loop->loop_no);
2960      goto bad_loop;
2961    }
2962
2963  /* Check if start_label appears before loop_end and calculate the
2964     offset between them.  We calculate the length of instructions
2965     conservatively.  */
2966  length = 0;
2967  for (insn = loop->start_label;
2968       insn && insn != loop->loop_end;
2969       insn = NEXT_INSN (insn))
2970    {
2971      if (JUMP_P (insn) && any_condjump_p (insn) && !optimize_size)
2972	{
2973	  if (TARGET_CSYNC_ANOMALY)
2974	    length += 8;
2975	  else if (TARGET_SPECLD_ANOMALY)
2976	    length += 6;
2977	}
2978      else if (LABEL_P (insn))
2979	{
2980	  if (TARGET_CSYNC_ANOMALY)
2981	    length += 4;
2982	}
2983
2984      if (INSN_P (insn))
2985	length += get_attr_length (insn);
2986    }
2987
2988  if (!insn)
2989    {
2990      if (dump_file)
2991	fprintf (dump_file, ";; loop %d start_label not before loop_end\n",
2992		 loop->loop_no);
2993      goto bad_loop;
2994    }
2995
2996  loop->length = length;
2997  if (loop->length > MAX_LOOP_LENGTH)
2998    {
2999      if (dump_file)
3000	fprintf (dump_file, ";; loop %d too long\n", loop->loop_no);
3001      goto bad_loop;
3002    }
3003
3004  /* Scan all the blocks to make sure they don't use iter_reg.  */
3005  if (bfin_scan_loop (loop, iter_reg, loop->loop_end))
3006    {
3007      if (dump_file)
3008	fprintf (dump_file, ";; loop %d uses iterator\n", loop->loop_no);
3009      goto bad_loop;
3010    }
3011
3012  /* Scan all the insns to see if the loop body clobber
3013     any hardware loop registers. */
3014
3015  reg_lc0 = gen_rtx_REG (SImode, REG_LC0);
3016  reg_lc1 = gen_rtx_REG (SImode, REG_LC1);
3017  reg_lt0 = gen_rtx_REG (SImode, REG_LT0);
3018  reg_lt1 = gen_rtx_REG (SImode, REG_LT1);
3019  reg_lb0 = gen_rtx_REG (SImode, REG_LB0);
3020  reg_lb1 = gen_rtx_REG (SImode, REG_LB1);
3021
3022  for (ix = 0; VEC_iterate (basic_block, loop->blocks, ix, bb); ix++)
3023    {
3024      rtx insn;
3025
3026      for (insn = BB_HEAD (bb);
3027	   insn != NEXT_INSN (BB_END (bb));
3028	   insn = NEXT_INSN (insn))
3029	{
3030	  if (!INSN_P (insn))
3031	    continue;
3032
3033	  if (reg_set_p (reg_lc0, insn)
3034	      || reg_set_p (reg_lt0, insn)
3035	      || reg_set_p (reg_lb0, insn))
3036	    loop->clobber_loop0 = 1;
3037
3038	  if (reg_set_p (reg_lc1, insn)
3039	      || reg_set_p (reg_lt1, insn)
3040	      || reg_set_p (reg_lb1, insn))
3041	    loop->clobber_loop1 |= 1;
3042	}
3043    }
3044
3045  if ((loop->clobber_loop0 && loop->clobber_loop1)
3046      || (loop->depth == MAX_LOOP_DEPTH && loop->clobber_loop0))
3047    {
3048      loop->depth = MAX_LOOP_DEPTH + 1;
3049      if (dump_file)
3050	fprintf (dump_file, ";; loop %d no loop reg available\n",
3051		 loop->loop_no);
3052      goto bad_loop;
3053    }
3054
3055  /* There should be an instruction before the loop_end instruction
3056     in the same basic block. And the instruction must not be
3057     - JUMP
3058     - CONDITIONAL BRANCH
3059     - CALL
3060     - CSYNC
3061     - SSYNC
3062     - Returns (RTS, RTN, etc.)  */
3063
3064  bb = loop->tail;
3065  last_insn = PREV_INSN (loop->loop_end);
3066
3067  while (1)
3068    {
3069      for (; last_insn != PREV_INSN (BB_HEAD (bb));
3070	   last_insn = PREV_INSN (last_insn))
3071	if (INSN_P (last_insn))
3072	  break;
3073
3074      if (last_insn != PREV_INSN (BB_HEAD (bb)))
3075	break;
3076
3077      if (single_pred_p (bb)
3078	  && single_pred (bb) != ENTRY_BLOCK_PTR)
3079	{
3080	  bb = single_pred (bb);
3081	  last_insn = BB_END (bb);
3082	  continue;
3083	}
3084      else
3085	{
3086	  last_insn = NULL_RTX;
3087	  break;
3088	}
3089    }
3090
3091  if (!last_insn)
3092    {
3093      if (dump_file)
3094	fprintf (dump_file, ";; loop %d has no last instruction\n",
3095		 loop->loop_no);
3096      goto bad_loop;
3097    }
3098
3099  if (JUMP_P (last_insn))
3100    {
3101      loop_info inner = bb->aux;
3102      if (inner
3103	  && inner->outer == loop
3104	  && inner->loop_end == last_insn
3105	  && inner->depth == 1)
3106	/* This jump_insn is the exact loop_end of an inner loop
3107	   and to be optimized away. So use the inner's last_insn.  */
3108	last_insn = inner->last_insn;
3109      else
3110	{
3111	  if (dump_file)
3112	    fprintf (dump_file, ";; loop %d has bad last instruction\n",
3113		     loop->loop_no);
3114	  goto bad_loop;
3115	}
3116    }
3117  else if (CALL_P (last_insn)
3118	   || get_attr_type (last_insn) == TYPE_SYNC
3119	   || recog_memoized (last_insn) == CODE_FOR_return_internal)
3120    {
3121      if (dump_file)
3122	fprintf (dump_file, ";; loop %d has bad last instruction\n",
3123		 loop->loop_no);
3124      goto bad_loop;
3125    }
3126
3127  if (GET_CODE (PATTERN (last_insn)) == ASM_INPUT
3128      || asm_noperands (PATTERN (last_insn)) >= 0
3129      || get_attr_seq_insns (last_insn) == SEQ_INSNS_MULTI)
3130    {
3131      nop_insn = emit_insn_after (gen_nop (), last_insn);
3132      last_insn = nop_insn;
3133    }
3134
3135  loop->last_insn = last_insn;
3136
3137  /* The loop is good for replacement.  */
3138  start_label = loop->start_label;
3139  end_label = gen_label_rtx ();
3140  iter_reg = loop->iter_reg;
3141
3142  if (loop->depth == 1 && !loop->clobber_loop1)
3143    {
3144      lc_reg = reg_lc1;
3145      lt_reg = reg_lt1;
3146      lb_reg = reg_lb1;
3147      loop->clobber_loop1 = 1;
3148    }
3149  else
3150    {
3151      lc_reg = reg_lc0;
3152      lt_reg = reg_lt0;
3153      lb_reg = reg_lb0;
3154      loop->clobber_loop0 = 1;
3155    }
3156
3157  /* If iter_reg is a DREG, we need generate an instruction to load
3158     the loop count into LC register. */
3159  if (D_REGNO_P (REGNO (iter_reg)))
3160    {
3161      init_insn = gen_movsi (lc_reg, iter_reg);
3162      loop_init = gen_lsetup_without_autoinit (lt_reg, start_label,
3163					       lb_reg, end_label,
3164					       lc_reg);
3165    }
3166  else if (P_REGNO_P (REGNO (iter_reg)))
3167    {
3168      init_insn = NULL_RTX;
3169      loop_init = gen_lsetup_with_autoinit (lt_reg, start_label,
3170					    lb_reg, end_label,
3171					    lc_reg, iter_reg);
3172    }
3173  else
3174    gcc_unreachable ();
3175
3176  loop->init = init_insn;
3177  loop->end_label = end_label;
3178  loop->loop_init = loop_init;
3179
3180  if (dump_file)
3181    {
3182      fprintf (dump_file, ";; replacing loop %d initializer with\n",
3183	       loop->loop_no);
3184      print_rtl_single (dump_file, loop->loop_init);
3185      fprintf (dump_file, ";; replacing loop %d terminator with\n",
3186	       loop->loop_no);
3187      print_rtl_single (dump_file, loop->loop_end);
3188    }
3189
3190  start_sequence ();
3191
3192  if (loop->init != NULL_RTX)
3193    emit_insn (loop->init);
3194  emit_insn(loop->loop_init);
3195  emit_label (loop->start_label);
3196
3197  seq = get_insns ();
3198  end_sequence ();
3199
3200  emit_insn_after (seq, BB_END (loop->predecessor));
3201  delete_insn (loop->loop_end);
3202
3203  /* Insert the loop end label before the last instruction of the loop.  */
3204  emit_label_before (loop->end_label, loop->last_insn);
3205
3206  return;
3207
3208bad_loop:
3209
3210  if (dump_file)
3211    fprintf (dump_file, ";; loop %d is bad\n", loop->loop_no);
3212
3213  loop->bad = 1;
3214
3215  if (DPREG_P (loop->iter_reg))
3216    {
3217      /* If loop->iter_reg is a DREG or PREG, we can split it here
3218	 without scratch register.  */
3219      rtx insn;
3220
3221      emit_insn_before (gen_addsi3 (loop->iter_reg,
3222				    loop->iter_reg,
3223				    constm1_rtx),
3224			loop->loop_end);
3225
3226      emit_insn_before (gen_cmpsi (loop->iter_reg, const0_rtx),
3227			loop->loop_end);
3228
3229      insn = emit_jump_insn_before (gen_bne (loop->start_label),
3230				    loop->loop_end);
3231
3232      JUMP_LABEL (insn) = loop->start_label;
3233      LABEL_NUSES (loop->start_label)++;
3234      delete_insn (loop->loop_end);
3235    }
3236}
3237
3238/* Called from bfin_reorg_loops when a potential loop end is found.  LOOP is
3239   a newly set up structure describing the loop, it is this function's
3240   responsibility to fill most of it.  TAIL_BB and TAIL_INSN point to the
3241   loop_end insn and its enclosing basic block.  */
3242
3243static void
3244bfin_discover_loop (loop_info loop, basic_block tail_bb, rtx tail_insn)
3245{
3246  unsigned dwork = 0;
3247  basic_block bb;
3248  VEC (basic_block,heap) *works = VEC_alloc (basic_block,heap,20);
3249
3250  loop->tail = tail_bb;
3251  loop->head = BRANCH_EDGE (tail_bb)->dest;
3252  loop->successor = FALLTHRU_EDGE (tail_bb)->dest;
3253  loop->predecessor = NULL;
3254  loop->loop_end = tail_insn;
3255  loop->last_insn = NULL_RTX;
3256  loop->iter_reg = SET_DEST (XVECEXP (PATTERN (tail_insn), 0, 1));
3257  loop->depth = loop->length = 0;
3258  loop->visited = 0;
3259  loop->clobber_loop0 = loop->clobber_loop1 = 0;
3260  loop->outer = NULL;
3261  loop->loops = NULL;
3262
3263  loop->init = loop->loop_init = NULL_RTX;
3264  loop->start_label = XEXP (XEXP (SET_SRC (XVECEXP (PATTERN (tail_insn), 0, 0)), 1), 0);
3265  loop->end_label = NULL_RTX;
3266  loop->bad = 0;
3267
3268  VEC_safe_push (basic_block, heap, works, loop->head);
3269
3270  while (VEC_iterate (basic_block, works, dwork++, bb))
3271    {
3272      edge e;
3273      edge_iterator ei;
3274      if (bb == EXIT_BLOCK_PTR)
3275	{
3276	  /* We've reached the exit block.  The loop must be bad. */
3277	  if (dump_file)
3278	    fprintf (dump_file,
3279		     ";; Loop is bad - reached exit block while scanning\n");
3280	  loop->bad = 1;
3281	  break;
3282	}
3283
3284      if (bitmap_bit_p (loop->block_bitmap, bb->index))
3285	continue;
3286
3287      /* We've not seen this block before.  Add it to the loop's
3288	 list and then add each successor to the work list.  */
3289
3290      VEC_safe_push (basic_block, heap, loop->blocks, bb);
3291      bitmap_set_bit (loop->block_bitmap, bb->index);
3292
3293      if (bb != tail_bb)
3294	{
3295	  FOR_EACH_EDGE (e, ei, bb->succs)
3296	    {
3297	      basic_block succ = EDGE_SUCC (bb, ei.index)->dest;
3298	      if (!REGNO_REG_SET_P (succ->il.rtl->global_live_at_start,
3299				    REGNO (loop->iter_reg)))
3300		continue;
3301	      if (!VEC_space (basic_block, works, 1))
3302		{
3303		  if (dwork)
3304		    {
3305		      VEC_block_remove (basic_block, works, 0, dwork);
3306		      dwork = 0;
3307		    }
3308		  else
3309		    VEC_reserve (basic_block, heap, works, 1);
3310		}
3311	      VEC_quick_push (basic_block, works, succ);
3312	    }
3313	}
3314    }
3315
3316  if (!loop->bad)
3317    {
3318      /* Make sure we only have one entry point.  */
3319      if (EDGE_COUNT (loop->head->preds) == 2)
3320	{
3321	  loop->predecessor = EDGE_PRED (loop->head, 0)->src;
3322	  if (loop->predecessor == loop->tail)
3323	    /* We wanted the other predecessor.  */
3324	    loop->predecessor = EDGE_PRED (loop->head, 1)->src;
3325
3326	  /* We can only place a loop insn on a fall through edge of a
3327	     single exit block.  */
3328	  if (EDGE_COUNT (loop->predecessor->succs) != 1
3329	      || !(EDGE_SUCC (loop->predecessor, 0)->flags & EDGE_FALLTHRU)
3330	      /* If loop->predecessor is in loop, loop->head is not really
3331		 the head of the loop.  */
3332	      || bfin_bb_in_loop (loop, loop->predecessor))
3333	    loop->predecessor = NULL;
3334	}
3335
3336      if (loop->predecessor == NULL)
3337	{
3338	  if (dump_file)
3339	    fprintf (dump_file, ";; loop has bad predecessor\n");
3340	  loop->bad = 1;
3341	}
3342    }
3343
3344#ifdef ENABLE_CHECKING
3345  /* Make sure nothing jumps into this loop.  This shouldn't happen as we
3346     wouldn't have generated the counted loop patterns in such a case.
3347     However, this test must be done after the test above to detect loops
3348     with invalid headers.  */
3349  if (!loop->bad)
3350    for (dwork = 0; VEC_iterate (basic_block, loop->blocks, dwork, bb); dwork++)
3351      {
3352	edge e;
3353	edge_iterator ei;
3354	if (bb == loop->head)
3355	  continue;
3356	FOR_EACH_EDGE (e, ei, bb->preds)
3357	  {
3358	    basic_block pred = EDGE_PRED (bb, ei.index)->src;
3359	    if (!bfin_bb_in_loop (loop, pred))
3360	      abort ();
3361	  }
3362      }
3363#endif
3364  VEC_free (basic_block, heap, works);
3365}
3366
3367static void
3368bfin_reorg_loops (FILE *dump_file)
3369{
3370  bitmap_obstack stack;
3371  bitmap tmp_bitmap;
3372  basic_block bb;
3373  loop_info loops = NULL;
3374  loop_info loop;
3375  int nloops = 0;
3376
3377  bitmap_obstack_initialize (&stack);
3378
3379  /* Find all the possible loop tails.  This means searching for every
3380     loop_end instruction.  For each one found, create a loop_info
3381     structure and add the head block to the work list. */
3382  FOR_EACH_BB (bb)
3383    {
3384      rtx tail = BB_END (bb);
3385
3386      while (GET_CODE (tail) == NOTE)
3387	tail = PREV_INSN (tail);
3388
3389      bb->aux = NULL;
3390
3391      if (INSN_P (tail) && recog_memoized (tail) == CODE_FOR_loop_end)
3392	{
3393	  /* A possible loop end */
3394
3395	  loop = XNEW (struct loop_info);
3396	  loop->next = loops;
3397	  loops = loop;
3398	  loop->loop_no = nloops++;
3399	  loop->blocks = VEC_alloc (basic_block, heap, 20);
3400	  loop->block_bitmap = BITMAP_ALLOC (&stack);
3401	  bb->aux = loop;
3402
3403	  if (dump_file)
3404	    {
3405	      fprintf (dump_file, ";; potential loop %d ending at\n",
3406		       loop->loop_no);
3407	      print_rtl_single (dump_file, tail);
3408	    }
3409
3410	  bfin_discover_loop (loop, bb, tail);
3411	}
3412    }
3413
3414  tmp_bitmap = BITMAP_ALLOC (&stack);
3415  /* Compute loop nestings.  */
3416  for (loop = loops; loop; loop = loop->next)
3417    {
3418      loop_info other;
3419      if (loop->bad)
3420	continue;
3421
3422      for (other = loop->next; other; other = other->next)
3423	{
3424	  if (other->bad)
3425	    continue;
3426
3427	  bitmap_and (tmp_bitmap, other->block_bitmap, loop->block_bitmap);
3428	  if (bitmap_empty_p (tmp_bitmap))
3429	    continue;
3430	  if (bitmap_equal_p (tmp_bitmap, other->block_bitmap))
3431	    {
3432	      other->outer = loop;
3433	      VEC_safe_push (loop_info, heap, loop->loops, other);
3434	    }
3435	  else if (bitmap_equal_p (tmp_bitmap, loop->block_bitmap))
3436	    {
3437	      loop->outer = other;
3438	      VEC_safe_push (loop_info, heap, other->loops, loop);
3439	    }
3440	  else
3441	    {
3442	      loop->bad = other->bad = 1;
3443	    }
3444	}
3445    }
3446  BITMAP_FREE (tmp_bitmap);
3447
3448  if (dump_file)
3449    {
3450      fprintf (dump_file, ";; All loops found:\n\n");
3451      bfin_dump_loops (loops);
3452    }
3453
3454  /* Now apply the optimizations.  */
3455  for (loop = loops; loop; loop = loop->next)
3456    bfin_optimize_loop (loop);
3457
3458  if (dump_file)
3459    {
3460      fprintf (dump_file, ";; After hardware loops optimization:\n\n");
3461      bfin_dump_loops (loops);
3462    }
3463
3464  /* Free up the loop structures */
3465  while (loops)
3466    {
3467      loop = loops;
3468      loops = loop->next;
3469      VEC_free (loop_info, heap, loop->loops);
3470      VEC_free (basic_block, heap, loop->blocks);
3471      BITMAP_FREE (loop->block_bitmap);
3472      XDELETE (loop);
3473    }
3474
3475  if (dump_file)
3476    print_rtl (dump_file, get_insns ());
3477}
3478
3479
3480/* We use the machine specific reorg pass for emitting CSYNC instructions
3481   after conditional branches as needed.
3482
3483   The Blackfin is unusual in that a code sequence like
3484     if cc jump label
3485     r0 = (p0)
3486   may speculatively perform the load even if the condition isn't true.  This
3487   happens for a branch that is predicted not taken, because the pipeline
3488   isn't flushed or stalled, so the early stages of the following instructions,
3489   which perform the memory reference, are allowed to execute before the
3490   jump condition is evaluated.
3491   Therefore, we must insert additional instructions in all places where this
3492   could lead to incorrect behavior.  The manual recommends CSYNC, while
3493   VDSP seems to use NOPs (even though its corresponding compiler option is
3494   named CSYNC).
3495
3496   When optimizing for speed, we emit NOPs, which seems faster than a CSYNC.
3497   When optimizing for size, we turn the branch into a predicted taken one.
3498   This may be slower due to mispredicts, but saves code size.  */
3499
3500static void
3501bfin_reorg (void)
3502{
3503  rtx insn, last_condjump = NULL_RTX;
3504  int cycles_since_jump = INT_MAX;
3505
3506  /* Doloop optimization */
3507  if (cfun->machine->has_hardware_loops)
3508    bfin_reorg_loops (dump_file);
3509
3510  if (! TARGET_SPECLD_ANOMALY && ! TARGET_CSYNC_ANOMALY)
3511    return;
3512
3513  /* First pass: find predicted-false branches; if something after them
3514     needs nops, insert them or change the branch to predict true.  */
3515  for (insn = get_insns (); insn; insn = NEXT_INSN (insn))
3516    {
3517      rtx pat;
3518
3519      if (NOTE_P (insn) || BARRIER_P (insn) || LABEL_P (insn))
3520	continue;
3521
3522      pat = PATTERN (insn);
3523      if (GET_CODE (pat) == USE || GET_CODE (pat) == CLOBBER
3524	  || GET_CODE (pat) == ASM_INPUT || GET_CODE (pat) == ADDR_VEC
3525	  || GET_CODE (pat) == ADDR_DIFF_VEC || asm_noperands (pat) >= 0)
3526	continue;
3527
3528      if (JUMP_P (insn))
3529	{
3530	  if (any_condjump_p (insn)
3531	      && ! cbranch_predicted_taken_p (insn))
3532	    {
3533	      last_condjump = insn;
3534	      cycles_since_jump = 0;
3535	    }
3536	  else
3537	    cycles_since_jump = INT_MAX;
3538	}
3539      else if (INSN_P (insn))
3540	{
3541	  enum attr_type type = get_attr_type (insn);
3542	  int delay_needed = 0;
3543	  if (cycles_since_jump < INT_MAX)
3544	    cycles_since_jump++;
3545
3546	  if (type == TYPE_MCLD && TARGET_SPECLD_ANOMALY)
3547	    {
3548	      rtx pat = single_set (insn);
3549	      if (may_trap_p (SET_SRC (pat)))
3550		delay_needed = 3;
3551	    }
3552	  else if (type == TYPE_SYNC && TARGET_CSYNC_ANOMALY)
3553	    delay_needed = 4;
3554
3555	  if (delay_needed > cycles_since_jump)
3556	    {
3557	      rtx pat;
3558	      int num_clobbers;
3559	      rtx *op = recog_data.operand;
3560
3561	      delay_needed -= cycles_since_jump;
3562
3563	      extract_insn (last_condjump);
3564	      if (optimize_size)
3565		{
3566		  pat = gen_cbranch_predicted_taken (op[0], op[1], op[2],
3567						     op[3]);
3568		  cycles_since_jump = INT_MAX;
3569		}
3570	      else
3571		/* Do not adjust cycles_since_jump in this case, so that
3572		   we'll increase the number of NOPs for a subsequent insn
3573		   if necessary.  */
3574		pat = gen_cbranch_with_nops (op[0], op[1], op[2], op[3],
3575					     GEN_INT (delay_needed));
3576	      PATTERN (last_condjump) = pat;
3577	      INSN_CODE (last_condjump) = recog (pat, insn, &num_clobbers);
3578	    }
3579	}
3580    }
3581  /* Second pass: for predicted-true branches, see if anything at the
3582     branch destination needs extra nops.  */
3583  if (! TARGET_CSYNC_ANOMALY)
3584    return;
3585
3586  for (insn = get_insns (); insn; insn = NEXT_INSN (insn))
3587    {
3588      if (JUMP_P (insn)
3589	  && any_condjump_p (insn)
3590	  && (INSN_CODE (insn) == CODE_FOR_cbranch_predicted_taken
3591	      || cbranch_predicted_taken_p (insn)))
3592	{
3593	  rtx target = JUMP_LABEL (insn);
3594	  rtx label = target;
3595	  cycles_since_jump = 0;
3596	  for (; target && cycles_since_jump < 3; target = NEXT_INSN (target))
3597	    {
3598	      rtx pat;
3599
3600	      if (NOTE_P (target) || BARRIER_P (target) || LABEL_P (target))
3601		continue;
3602
3603	      pat = PATTERN (target);
3604	      if (GET_CODE (pat) == USE || GET_CODE (pat) == CLOBBER
3605		  || GET_CODE (pat) == ASM_INPUT || GET_CODE (pat) == ADDR_VEC
3606		  || GET_CODE (pat) == ADDR_DIFF_VEC || asm_noperands (pat) >= 0)
3607		continue;
3608
3609	      if (INSN_P (target))
3610		{
3611		  enum attr_type type = get_attr_type (target);
3612		  int delay_needed = 0;
3613		  if (cycles_since_jump < INT_MAX)
3614		    cycles_since_jump++;
3615
3616		  if (type == TYPE_SYNC && TARGET_CSYNC_ANOMALY)
3617		    delay_needed = 2;
3618
3619		  if (delay_needed > cycles_since_jump)
3620		    {
3621		      rtx prev = prev_real_insn (label);
3622		      delay_needed -= cycles_since_jump;
3623		      if (dump_file)
3624			fprintf (dump_file, "Adding %d nops after %d\n",
3625				 delay_needed, INSN_UID (label));
3626		      if (JUMP_P (prev)
3627			  && INSN_CODE (prev) == CODE_FOR_cbranch_with_nops)
3628			{
3629			  rtx x;
3630			  HOST_WIDE_INT v;
3631
3632			  if (dump_file)
3633			    fprintf (dump_file,
3634				     "Reducing nops on insn %d.\n",
3635				     INSN_UID (prev));
3636			  x = PATTERN (prev);
3637			  x = XVECEXP (x, 0, 1);
3638			  v = INTVAL (XVECEXP (x, 0, 0)) - delay_needed;
3639			  XVECEXP (x, 0, 0) = GEN_INT (v);
3640			}
3641		      while (delay_needed-- > 0)
3642			emit_insn_after (gen_nop (), label);
3643		      break;
3644		    }
3645		}
3646	    }
3647	}
3648    }
3649}
3650
3651/* Handle interrupt_handler, exception_handler and nmi_handler function
3652   attributes; arguments as in struct attribute_spec.handler.  */
3653
3654static tree
3655handle_int_attribute (tree *node, tree name,
3656		      tree args ATTRIBUTE_UNUSED,
3657		      int flags ATTRIBUTE_UNUSED,
3658		      bool *no_add_attrs)
3659{
3660  tree x = *node;
3661  if (TREE_CODE (x) == FUNCTION_DECL)
3662    x = TREE_TYPE (x);
3663
3664  if (TREE_CODE (x) != FUNCTION_TYPE)
3665    {
3666      warning (OPT_Wattributes, "%qs attribute only applies to functions",
3667	       IDENTIFIER_POINTER (name));
3668      *no_add_attrs = true;
3669    }
3670  else if (funkind (x) != SUBROUTINE)
3671    error ("multiple function type attributes specified");
3672
3673  return NULL_TREE;
3674}
3675
3676/* Return 0 if the attributes for two types are incompatible, 1 if they
3677   are compatible, and 2 if they are nearly compatible (which causes a
3678   warning to be generated).  */
3679
3680static int
3681bfin_comp_type_attributes (tree type1, tree type2)
3682{
3683  e_funkind kind1, kind2;
3684
3685  if (TREE_CODE (type1) != FUNCTION_TYPE)
3686    return 1;
3687
3688  kind1 = funkind (type1);
3689  kind2 = funkind (type2);
3690
3691  if (kind1 != kind2)
3692    return 0;
3693
3694  /*  Check for mismatched modifiers */
3695  if (!lookup_attribute ("nesting", TYPE_ATTRIBUTES (type1))
3696      != !lookup_attribute ("nesting", TYPE_ATTRIBUTES (type2)))
3697    return 0;
3698
3699  if (!lookup_attribute ("saveall", TYPE_ATTRIBUTES (type1))
3700      != !lookup_attribute ("saveall", TYPE_ATTRIBUTES (type2)))
3701    return 0;
3702
3703  if (!lookup_attribute ("kspisusp", TYPE_ATTRIBUTES (type1))
3704      != !lookup_attribute ("kspisusp", TYPE_ATTRIBUTES (type2)))
3705    return 0;
3706
3707  if (!lookup_attribute ("longcall", TYPE_ATTRIBUTES (type1))
3708      != !lookup_attribute ("longcall", TYPE_ATTRIBUTES (type2)))
3709    return 0;
3710
3711  return 1;
3712}
3713
3714/* Handle a "longcall" or "shortcall" attribute; arguments as in
3715   struct attribute_spec.handler.  */
3716
3717static tree
3718bfin_handle_longcall_attribute (tree *node, tree name,
3719				tree args ATTRIBUTE_UNUSED,
3720				int flags ATTRIBUTE_UNUSED,
3721				bool *no_add_attrs)
3722{
3723  if (TREE_CODE (*node) != FUNCTION_TYPE
3724      && TREE_CODE (*node) != FIELD_DECL
3725      && TREE_CODE (*node) != TYPE_DECL)
3726    {
3727      warning (OPT_Wattributes, "`%s' attribute only applies to functions",
3728	       IDENTIFIER_POINTER (name));
3729      *no_add_attrs = true;
3730    }
3731
3732  if ((strcmp (IDENTIFIER_POINTER (name), "longcall") == 0
3733       && lookup_attribute ("shortcall", TYPE_ATTRIBUTES (*node)))
3734      || (strcmp (IDENTIFIER_POINTER (name), "shortcall") == 0
3735	  && lookup_attribute ("longcall", TYPE_ATTRIBUTES (*node))))
3736    {
3737      warning (OPT_Wattributes,
3738	       "can't apply both longcall and shortcall attributes to the same function");
3739      *no_add_attrs = true;
3740    }
3741
3742  return NULL_TREE;
3743}
3744
3745/* Table of valid machine attributes.  */
3746const struct attribute_spec bfin_attribute_table[] =
3747{
3748  /* { name, min_len, max_len, decl_req, type_req, fn_type_req, handler } */
3749  { "interrupt_handler", 0, 0, false, true,  true, handle_int_attribute },
3750  { "exception_handler", 0, 0, false, true,  true, handle_int_attribute },
3751  { "nmi_handler", 0, 0, false, true,  true, handle_int_attribute },
3752  { "nesting", 0, 0, false, true,  true, NULL },
3753  { "kspisusp", 0, 0, false, true,  true, NULL },
3754  { "saveall", 0, 0, false, true,  true, NULL },
3755  { "longcall",  0, 0, false, true,  true,  bfin_handle_longcall_attribute },
3756  { "shortcall", 0, 0, false, true,  true,  bfin_handle_longcall_attribute },
3757  { NULL, 0, 0, false, false, false, NULL }
3758};
3759
3760/* Implementation of TARGET_ASM_INTEGER.  When using FD-PIC, we need to
3761   tell the assembler to generate pointers to function descriptors in
3762   some cases.  */
3763
3764static bool
3765bfin_assemble_integer (rtx value, unsigned int size, int aligned_p)
3766{
3767  if (TARGET_FDPIC && size == UNITS_PER_WORD)
3768    {
3769      if (GET_CODE (value) == SYMBOL_REF
3770	  && SYMBOL_REF_FUNCTION_P (value))
3771	{
3772	  fputs ("\t.picptr\tfuncdesc(", asm_out_file);
3773	  output_addr_const (asm_out_file, value);
3774	  fputs (")\n", asm_out_file);
3775	  return true;
3776	}
3777      if (!aligned_p)
3778	{
3779	  /* We've set the unaligned SI op to NULL, so we always have to
3780	     handle the unaligned case here.  */
3781	  assemble_integer_with_op ("\t.4byte\t", value);
3782	  return true;
3783	}
3784    }
3785  return default_assemble_integer (value, size, aligned_p);
3786}
3787
3788/* Output the assembler code for a thunk function.  THUNK_DECL is the
3789   declaration for the thunk function itself, FUNCTION is the decl for
3790   the target function.  DELTA is an immediate constant offset to be
3791   added to THIS.  If VCALL_OFFSET is nonzero, the word at
3792   *(*this + vcall_offset) should be added to THIS.  */
3793
3794static void
3795bfin_output_mi_thunk (FILE *file ATTRIBUTE_UNUSED,
3796		      tree thunk ATTRIBUTE_UNUSED, HOST_WIDE_INT delta,
3797		      HOST_WIDE_INT vcall_offset, tree function)
3798{
3799  rtx xops[3];
3800  /* The this parameter is passed as the first argument.  */
3801  rtx this = gen_rtx_REG (Pmode, REG_R0);
3802
3803  /* Adjust the this parameter by a fixed constant.  */
3804  if (delta)
3805    {
3806      xops[1] = this;
3807      if (delta >= -64 && delta <= 63)
3808	{
3809	  xops[0] = GEN_INT (delta);
3810	  output_asm_insn ("%1 += %0;", xops);
3811	}
3812      else if (delta >= -128 && delta < -64)
3813	{
3814	  xops[0] = GEN_INT (delta + 64);
3815	  output_asm_insn ("%1 += -64; %1 += %0;", xops);
3816	}
3817      else if (delta > 63 && delta <= 126)
3818	{
3819	  xops[0] = GEN_INT (delta - 63);
3820	  output_asm_insn ("%1 += 63; %1 += %0;", xops);
3821	}
3822      else
3823	{
3824	  xops[0] = GEN_INT (delta);
3825	  output_asm_insn ("r3.l = %h0; r3.h = %d0; %1 = %1 + r3;", xops);
3826	}
3827    }
3828
3829  /* Adjust the this parameter by a value stored in the vtable.  */
3830  if (vcall_offset)
3831    {
3832      rtx p2tmp = gen_rtx_REG (Pmode, REG_P2);
3833      rtx tmp = gen_rtx_REG (Pmode, REG_R2);
3834
3835      xops[1] = tmp;
3836      xops[2] = p2tmp;
3837      output_asm_insn ("%2 = r0; %2 = [%2];", xops);
3838
3839      /* Adjust the this parameter.  */
3840      xops[0] = gen_rtx_MEM (Pmode, plus_constant (p2tmp, vcall_offset));
3841      if (!memory_operand (xops[0], Pmode))
3842	{
3843	  rtx tmp2 = gen_rtx_REG (Pmode, REG_P1);
3844	  xops[0] = GEN_INT (vcall_offset);
3845	  xops[1] = tmp2;
3846	  output_asm_insn ("%h1 = %h0; %d1 = %d0; %2 = %2 + %1", xops);
3847	  xops[0] = gen_rtx_MEM (Pmode, p2tmp);
3848	}
3849      xops[2] = this;
3850      output_asm_insn ("%1 = %0; %2 = %2 + %1;", xops);
3851    }
3852
3853  xops[0] = XEXP (DECL_RTL (function), 0);
3854  if (1 || !flag_pic || (*targetm.binds_local_p) (function))
3855    output_asm_insn ("jump.l\t%P0", xops);
3856}
3857
3858/* Codes for all the Blackfin builtins.  */
3859enum bfin_builtins
3860{
3861  BFIN_BUILTIN_CSYNC,
3862  BFIN_BUILTIN_SSYNC,
3863  BFIN_BUILTIN_COMPOSE_2X16,
3864  BFIN_BUILTIN_EXTRACTLO,
3865  BFIN_BUILTIN_EXTRACTHI,
3866
3867  BFIN_BUILTIN_SSADD_2X16,
3868  BFIN_BUILTIN_SSSUB_2X16,
3869  BFIN_BUILTIN_SSADDSUB_2X16,
3870  BFIN_BUILTIN_SSSUBADD_2X16,
3871  BFIN_BUILTIN_MULT_2X16,
3872  BFIN_BUILTIN_MULTR_2X16,
3873  BFIN_BUILTIN_NEG_2X16,
3874  BFIN_BUILTIN_ABS_2X16,
3875  BFIN_BUILTIN_MIN_2X16,
3876  BFIN_BUILTIN_MAX_2X16,
3877
3878  BFIN_BUILTIN_SSADD_1X16,
3879  BFIN_BUILTIN_SSSUB_1X16,
3880  BFIN_BUILTIN_MULT_1X16,
3881  BFIN_BUILTIN_MULTR_1X16,
3882  BFIN_BUILTIN_NORM_1X16,
3883  BFIN_BUILTIN_NEG_1X16,
3884  BFIN_BUILTIN_ABS_1X16,
3885  BFIN_BUILTIN_MIN_1X16,
3886  BFIN_BUILTIN_MAX_1X16,
3887
3888  BFIN_BUILTIN_DIFFHL_2X16,
3889  BFIN_BUILTIN_DIFFLH_2X16,
3890
3891  BFIN_BUILTIN_SSADD_1X32,
3892  BFIN_BUILTIN_SSSUB_1X32,
3893  BFIN_BUILTIN_NORM_1X32,
3894  BFIN_BUILTIN_NEG_1X32,
3895  BFIN_BUILTIN_MIN_1X32,
3896  BFIN_BUILTIN_MAX_1X32,
3897  BFIN_BUILTIN_MULT_1X32,
3898
3899  BFIN_BUILTIN_MULHISILL,
3900  BFIN_BUILTIN_MULHISILH,
3901  BFIN_BUILTIN_MULHISIHL,
3902  BFIN_BUILTIN_MULHISIHH,
3903
3904  BFIN_BUILTIN_LSHIFT_1X16,
3905  BFIN_BUILTIN_LSHIFT_2X16,
3906  BFIN_BUILTIN_SSASHIFT_1X16,
3907  BFIN_BUILTIN_SSASHIFT_2X16,
3908
3909  BFIN_BUILTIN_CPLX_MUL_16,
3910  BFIN_BUILTIN_CPLX_MAC_16,
3911  BFIN_BUILTIN_CPLX_MSU_16,
3912
3913  BFIN_BUILTIN_MAX
3914};
3915
3916#define def_builtin(NAME, TYPE, CODE)					\
3917do {									\
3918  lang_hooks.builtin_function ((NAME), (TYPE), (CODE), BUILT_IN_MD,	\
3919			       NULL, NULL_TREE);			\
3920} while (0)
3921
3922/* Set up all builtin functions for this target.  */
3923static void
3924bfin_init_builtins (void)
3925{
3926  tree V2HI_type_node = build_vector_type_for_mode (intHI_type_node, V2HImode);
3927  tree void_ftype_void
3928    = build_function_type (void_type_node, void_list_node);
3929  tree short_ftype_short
3930    = build_function_type_list (short_integer_type_node, short_integer_type_node,
3931				NULL_TREE);
3932  tree short_ftype_int_int
3933    = build_function_type_list (short_integer_type_node, integer_type_node,
3934				integer_type_node, NULL_TREE);
3935  tree int_ftype_int_int
3936    = build_function_type_list (integer_type_node, integer_type_node,
3937				integer_type_node, NULL_TREE);
3938  tree int_ftype_int
3939    = build_function_type_list (integer_type_node, integer_type_node,
3940				NULL_TREE);
3941  tree short_ftype_int
3942    = build_function_type_list (short_integer_type_node, integer_type_node,
3943				NULL_TREE);
3944  tree int_ftype_v2hi_v2hi
3945    = build_function_type_list (integer_type_node, V2HI_type_node,
3946				V2HI_type_node, NULL_TREE);
3947  tree v2hi_ftype_v2hi_v2hi
3948    = build_function_type_list (V2HI_type_node, V2HI_type_node,
3949				V2HI_type_node, NULL_TREE);
3950  tree v2hi_ftype_v2hi_v2hi_v2hi
3951    = build_function_type_list (V2HI_type_node, V2HI_type_node,
3952				V2HI_type_node, V2HI_type_node, NULL_TREE);
3953  tree v2hi_ftype_int_int
3954    = build_function_type_list (V2HI_type_node, integer_type_node,
3955				integer_type_node, NULL_TREE);
3956  tree v2hi_ftype_v2hi_int
3957    = build_function_type_list (V2HI_type_node, V2HI_type_node,
3958				integer_type_node, NULL_TREE);
3959  tree int_ftype_short_short
3960    = build_function_type_list (integer_type_node, short_integer_type_node,
3961				short_integer_type_node, NULL_TREE);
3962  tree v2hi_ftype_v2hi
3963    = build_function_type_list (V2HI_type_node, V2HI_type_node, NULL_TREE);
3964  tree short_ftype_v2hi
3965    = build_function_type_list (short_integer_type_node, V2HI_type_node,
3966				NULL_TREE);
3967
3968  /* Add the remaining MMX insns with somewhat more complicated types.  */
3969  def_builtin ("__builtin_bfin_csync", void_ftype_void, BFIN_BUILTIN_CSYNC);
3970  def_builtin ("__builtin_bfin_ssync", void_ftype_void, BFIN_BUILTIN_SSYNC);
3971
3972  def_builtin ("__builtin_bfin_compose_2x16", v2hi_ftype_int_int,
3973	       BFIN_BUILTIN_COMPOSE_2X16);
3974  def_builtin ("__builtin_bfin_extract_hi", short_ftype_v2hi,
3975	       BFIN_BUILTIN_EXTRACTHI);
3976  def_builtin ("__builtin_bfin_extract_lo", short_ftype_v2hi,
3977	       BFIN_BUILTIN_EXTRACTLO);
3978
3979  def_builtin ("__builtin_bfin_min_fr2x16", v2hi_ftype_v2hi_v2hi,
3980	       BFIN_BUILTIN_MIN_2X16);
3981  def_builtin ("__builtin_bfin_max_fr2x16", v2hi_ftype_v2hi_v2hi,
3982	       BFIN_BUILTIN_MAX_2X16);
3983
3984  def_builtin ("__builtin_bfin_add_fr2x16", v2hi_ftype_v2hi_v2hi,
3985	       BFIN_BUILTIN_SSADD_2X16);
3986  def_builtin ("__builtin_bfin_sub_fr2x16", v2hi_ftype_v2hi_v2hi,
3987	       BFIN_BUILTIN_SSSUB_2X16);
3988  def_builtin ("__builtin_bfin_dspaddsubsat", v2hi_ftype_v2hi_v2hi,
3989	       BFIN_BUILTIN_SSADDSUB_2X16);
3990  def_builtin ("__builtin_bfin_dspsubaddsat", v2hi_ftype_v2hi_v2hi,
3991	       BFIN_BUILTIN_SSSUBADD_2X16);
3992  def_builtin ("__builtin_bfin_mult_fr2x16", v2hi_ftype_v2hi_v2hi,
3993	       BFIN_BUILTIN_MULT_2X16);
3994  def_builtin ("__builtin_bfin_multr_fr2x16", v2hi_ftype_v2hi_v2hi,
3995	       BFIN_BUILTIN_MULTR_2X16);
3996  def_builtin ("__builtin_bfin_negate_fr2x16", v2hi_ftype_v2hi,
3997	       BFIN_BUILTIN_NEG_2X16);
3998  def_builtin ("__builtin_bfin_abs_fr2x16", v2hi_ftype_v2hi,
3999	       BFIN_BUILTIN_ABS_2X16);
4000
4001  def_builtin ("__builtin_bfin_add_fr1x16", short_ftype_int_int,
4002	       BFIN_BUILTIN_SSADD_1X16);
4003  def_builtin ("__builtin_bfin_sub_fr1x16", short_ftype_int_int,
4004	       BFIN_BUILTIN_SSSUB_1X16);
4005  def_builtin ("__builtin_bfin_mult_fr1x16", short_ftype_int_int,
4006	       BFIN_BUILTIN_MULT_1X16);
4007  def_builtin ("__builtin_bfin_multr_fr1x16", short_ftype_int_int,
4008	       BFIN_BUILTIN_MULTR_1X16);
4009  def_builtin ("__builtin_bfin_negate_fr1x16", short_ftype_short,
4010	       BFIN_BUILTIN_NEG_1X16);
4011  def_builtin ("__builtin_bfin_abs_fr1x16", short_ftype_short,
4012	       BFIN_BUILTIN_ABS_1X16);
4013  def_builtin ("__builtin_bfin_norm_fr1x16", short_ftype_int,
4014	       BFIN_BUILTIN_NORM_1X16);
4015
4016  def_builtin ("__builtin_bfin_diff_hl_fr2x16", short_ftype_v2hi,
4017	       BFIN_BUILTIN_DIFFHL_2X16);
4018  def_builtin ("__builtin_bfin_diff_lh_fr2x16", short_ftype_v2hi,
4019	       BFIN_BUILTIN_DIFFLH_2X16);
4020
4021  def_builtin ("__builtin_bfin_mulhisill", int_ftype_v2hi_v2hi,
4022	       BFIN_BUILTIN_MULHISILL);
4023  def_builtin ("__builtin_bfin_mulhisihl", int_ftype_v2hi_v2hi,
4024	       BFIN_BUILTIN_MULHISIHL);
4025  def_builtin ("__builtin_bfin_mulhisilh", int_ftype_v2hi_v2hi,
4026	       BFIN_BUILTIN_MULHISILH);
4027  def_builtin ("__builtin_bfin_mulhisihh", int_ftype_v2hi_v2hi,
4028	       BFIN_BUILTIN_MULHISIHH);
4029
4030  def_builtin ("__builtin_bfin_add_fr1x32", int_ftype_int_int,
4031	       BFIN_BUILTIN_SSADD_1X32);
4032  def_builtin ("__builtin_bfin_sub_fr1x32", int_ftype_int_int,
4033	       BFIN_BUILTIN_SSSUB_1X32);
4034  def_builtin ("__builtin_bfin_negate_fr1x32", int_ftype_int,
4035	       BFIN_BUILTIN_NEG_1X32);
4036  def_builtin ("__builtin_bfin_norm_fr1x32", short_ftype_int,
4037	       BFIN_BUILTIN_NORM_1X32);
4038  def_builtin ("__builtin_bfin_mult_fr1x32", int_ftype_short_short,
4039	       BFIN_BUILTIN_MULT_1X32);
4040
4041  /* Shifts.  */
4042  def_builtin ("__builtin_bfin_shl_fr1x16", short_ftype_int_int,
4043	       BFIN_BUILTIN_SSASHIFT_1X16);
4044  def_builtin ("__builtin_bfin_shl_fr2x16", v2hi_ftype_v2hi_int,
4045	       BFIN_BUILTIN_SSASHIFT_2X16);
4046  def_builtin ("__builtin_bfin_lshl_fr1x16", short_ftype_int_int,
4047	       BFIN_BUILTIN_LSHIFT_1X16);
4048  def_builtin ("__builtin_bfin_lshl_fr2x16", v2hi_ftype_v2hi_int,
4049	       BFIN_BUILTIN_LSHIFT_2X16);
4050
4051  /* Complex numbers.  */
4052  def_builtin ("__builtin_bfin_cmplx_mul", v2hi_ftype_v2hi_v2hi,
4053	       BFIN_BUILTIN_CPLX_MUL_16);
4054  def_builtin ("__builtin_bfin_cmplx_mac", v2hi_ftype_v2hi_v2hi_v2hi,
4055	       BFIN_BUILTIN_CPLX_MAC_16);
4056  def_builtin ("__builtin_bfin_cmplx_msu", v2hi_ftype_v2hi_v2hi_v2hi,
4057	       BFIN_BUILTIN_CPLX_MSU_16);
4058}
4059
4060
4061struct builtin_description
4062{
4063  const enum insn_code icode;
4064  const char *const name;
4065  const enum bfin_builtins code;
4066  int macflag;
4067};
4068
4069static const struct builtin_description bdesc_2arg[] =
4070{
4071  { CODE_FOR_composev2hi, "__builtin_bfin_compose_2x16", BFIN_BUILTIN_COMPOSE_2X16, -1 },
4072
4073  { CODE_FOR_ssashiftv2hi3, "__builtin_bfin_shl_fr2x16", BFIN_BUILTIN_SSASHIFT_2X16, -1 },
4074  { CODE_FOR_ssashifthi3, "__builtin_bfin_shl_fr1x16", BFIN_BUILTIN_SSASHIFT_1X16, -1 },
4075  { CODE_FOR_lshiftv2hi3, "__builtin_bfin_lshl_fr2x16", BFIN_BUILTIN_LSHIFT_2X16, -1 },
4076  { CODE_FOR_lshifthi3, "__builtin_bfin_lshl_fr1x16", BFIN_BUILTIN_LSHIFT_1X16, -1 },
4077
4078  { CODE_FOR_sminhi3, "__builtin_bfin_min_fr1x16", BFIN_BUILTIN_MIN_1X16, -1 },
4079  { CODE_FOR_smaxhi3, "__builtin_bfin_max_fr1x16", BFIN_BUILTIN_MAX_1X16, -1 },
4080  { CODE_FOR_ssaddhi3, "__builtin_bfin_add_fr1x16", BFIN_BUILTIN_SSADD_1X16, -1 },
4081  { CODE_FOR_sssubhi3, "__builtin_bfin_sub_fr1x16", BFIN_BUILTIN_SSSUB_1X16, -1 },
4082
4083  { CODE_FOR_sminsi3, "__builtin_bfin_min_fr1x32", BFIN_BUILTIN_MIN_1X32, -1 },
4084  { CODE_FOR_smaxsi3, "__builtin_bfin_max_fr1x32", BFIN_BUILTIN_MAX_1X32, -1 },
4085  { CODE_FOR_ssaddsi3, "__builtin_bfin_add_fr1x32", BFIN_BUILTIN_SSADD_1X32, -1 },
4086  { CODE_FOR_sssubsi3, "__builtin_bfin_sub_fr1x32", BFIN_BUILTIN_SSSUB_1X32, -1 },
4087
4088  { CODE_FOR_sminv2hi3, "__builtin_bfin_min_fr2x16", BFIN_BUILTIN_MIN_2X16, -1 },
4089  { CODE_FOR_smaxv2hi3, "__builtin_bfin_max_fr2x16", BFIN_BUILTIN_MAX_2X16, -1 },
4090  { CODE_FOR_ssaddv2hi3, "__builtin_bfin_add_fr2x16", BFIN_BUILTIN_SSADD_2X16, -1 },
4091  { CODE_FOR_sssubv2hi3, "__builtin_bfin_sub_fr2x16", BFIN_BUILTIN_SSSUB_2X16, -1 },
4092  { CODE_FOR_ssaddsubv2hi3, "__builtin_bfin_dspaddsubsat", BFIN_BUILTIN_SSADDSUB_2X16, -1 },
4093  { CODE_FOR_sssubaddv2hi3, "__builtin_bfin_dspsubaddsat", BFIN_BUILTIN_SSSUBADD_2X16, -1 },
4094
4095  { CODE_FOR_flag_mulhisi, "__builtin_bfin_mult_fr1x32", BFIN_BUILTIN_MULT_1X32, MACFLAG_NONE },
4096  { CODE_FOR_flag_mulhi, "__builtin_bfin_mult_fr1x16", BFIN_BUILTIN_MULT_1X16, MACFLAG_T },
4097  { CODE_FOR_flag_mulhi, "__builtin_bfin_multr_fr1x16", BFIN_BUILTIN_MULTR_1X16, MACFLAG_NONE },
4098  { CODE_FOR_flag_mulv2hi, "__builtin_bfin_mult_fr2x16", BFIN_BUILTIN_MULT_2X16, MACFLAG_T },
4099  { CODE_FOR_flag_mulv2hi, "__builtin_bfin_multr_fr2x16", BFIN_BUILTIN_MULTR_2X16, MACFLAG_NONE }
4100};
4101
4102static const struct builtin_description bdesc_1arg[] =
4103{
4104  { CODE_FOR_signbitshi2, "__builtin_bfin_norm_fr1x16", BFIN_BUILTIN_NORM_1X16, 0 },
4105  { CODE_FOR_ssneghi2, "__builtin_bfin_negate_fr1x16", BFIN_BUILTIN_NEG_1X16, 0 },
4106  { CODE_FOR_abshi2, "__builtin_bfin_abs_fr1x16", BFIN_BUILTIN_ABS_1X16, 0 },
4107
4108  { CODE_FOR_signbitssi2, "__builtin_bfin_norm_fr1x32", BFIN_BUILTIN_NORM_1X32, 0 },
4109  { CODE_FOR_ssnegsi2, "__builtin_bfin_negate_fr1x32", BFIN_BUILTIN_NEG_1X32, 0 },
4110
4111  { CODE_FOR_movv2hi_hi_low, "__builtin_bfin_extract_lo", BFIN_BUILTIN_EXTRACTLO, 0 },
4112  { CODE_FOR_movv2hi_hi_high, "__builtin_bfin_extract_hi", BFIN_BUILTIN_EXTRACTHI, 0 },
4113  { CODE_FOR_ssnegv2hi2, "__builtin_bfin_negate_fr2x16", BFIN_BUILTIN_NEG_2X16, 0 },
4114  { CODE_FOR_absv2hi2, "__builtin_bfin_abs_fr2x16", BFIN_BUILTIN_ABS_2X16, 0 }
4115};
4116
4117/* Errors in the source file can cause expand_expr to return const0_rtx
4118   where we expect a vector.  To avoid crashing, use one of the vector
4119   clear instructions.  */
4120static rtx
4121safe_vector_operand (rtx x, enum machine_mode mode)
4122{
4123  if (x != const0_rtx)
4124    return x;
4125  x = gen_reg_rtx (SImode);
4126
4127  emit_insn (gen_movsi (x, CONST0_RTX (SImode)));
4128  return gen_lowpart (mode, x);
4129}
4130
4131/* Subroutine of bfin_expand_builtin to take care of binop insns.  MACFLAG is -1
4132   if this is a normal binary op, or one of the MACFLAG_xxx constants.  */
4133
4134static rtx
4135bfin_expand_binop_builtin (enum insn_code icode, tree arglist, rtx target,
4136			   int macflag)
4137{
4138  rtx pat;
4139  tree arg0 = TREE_VALUE (arglist);
4140  tree arg1 = TREE_VALUE (TREE_CHAIN (arglist));
4141  rtx op0 = expand_expr (arg0, NULL_RTX, VOIDmode, 0);
4142  rtx op1 = expand_expr (arg1, NULL_RTX, VOIDmode, 0);
4143  enum machine_mode op0mode = GET_MODE (op0);
4144  enum machine_mode op1mode = GET_MODE (op1);
4145  enum machine_mode tmode = insn_data[icode].operand[0].mode;
4146  enum machine_mode mode0 = insn_data[icode].operand[1].mode;
4147  enum machine_mode mode1 = insn_data[icode].operand[2].mode;
4148
4149  if (VECTOR_MODE_P (mode0))
4150    op0 = safe_vector_operand (op0, mode0);
4151  if (VECTOR_MODE_P (mode1))
4152    op1 = safe_vector_operand (op1, mode1);
4153
4154  if (! target
4155      || GET_MODE (target) != tmode
4156      || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
4157    target = gen_reg_rtx (tmode);
4158
4159  if ((op0mode == SImode || op0mode == VOIDmode) && mode0 == HImode)
4160    {
4161      op0mode = HImode;
4162      op0 = gen_lowpart (HImode, op0);
4163    }
4164  if ((op1mode == SImode || op1mode == VOIDmode) && mode1 == HImode)
4165    {
4166      op1mode = HImode;
4167      op1 = gen_lowpart (HImode, op1);
4168    }
4169  /* In case the insn wants input operands in modes different from
4170     the result, abort.  */
4171  gcc_assert ((op0mode == mode0 || op0mode == VOIDmode)
4172	      && (op1mode == mode1 || op1mode == VOIDmode));
4173
4174  if (! (*insn_data[icode].operand[1].predicate) (op0, mode0))
4175    op0 = copy_to_mode_reg (mode0, op0);
4176  if (! (*insn_data[icode].operand[2].predicate) (op1, mode1))
4177    op1 = copy_to_mode_reg (mode1, op1);
4178
4179  if (macflag == -1)
4180    pat = GEN_FCN (icode) (target, op0, op1);
4181  else
4182    pat = GEN_FCN (icode) (target, op0, op1, GEN_INT (macflag));
4183  if (! pat)
4184    return 0;
4185
4186  emit_insn (pat);
4187  return target;
4188}
4189
4190/* Subroutine of bfin_expand_builtin to take care of unop insns.  */
4191
4192static rtx
4193bfin_expand_unop_builtin (enum insn_code icode, tree arglist,
4194			  rtx target)
4195{
4196  rtx pat;
4197  tree arg0 = TREE_VALUE (arglist);
4198  rtx op0 = expand_expr (arg0, NULL_RTX, VOIDmode, 0);
4199  enum machine_mode op0mode = GET_MODE (op0);
4200  enum machine_mode tmode = insn_data[icode].operand[0].mode;
4201  enum machine_mode mode0 = insn_data[icode].operand[1].mode;
4202
4203  if (! target
4204      || GET_MODE (target) != tmode
4205      || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
4206    target = gen_reg_rtx (tmode);
4207
4208  if (VECTOR_MODE_P (mode0))
4209    op0 = safe_vector_operand (op0, mode0);
4210
4211  if (op0mode == SImode && mode0 == HImode)
4212    {
4213      op0mode = HImode;
4214      op0 = gen_lowpart (HImode, op0);
4215    }
4216  gcc_assert (op0mode == mode0 || op0mode == VOIDmode);
4217
4218  if (! (*insn_data[icode].operand[1].predicate) (op0, mode0))
4219    op0 = copy_to_mode_reg (mode0, op0);
4220
4221  pat = GEN_FCN (icode) (target, op0);
4222  if (! pat)
4223    return 0;
4224  emit_insn (pat);
4225  return target;
4226}
4227
4228/* Expand an expression EXP that calls a built-in function,
4229   with result going to TARGET if that's convenient
4230   (and in mode MODE if that's convenient).
4231   SUBTARGET may be used as the target for computing one of EXP's operands.
4232   IGNORE is nonzero if the value is to be ignored.  */
4233
4234static rtx
4235bfin_expand_builtin (tree exp, rtx target ATTRIBUTE_UNUSED,
4236		     rtx subtarget ATTRIBUTE_UNUSED,
4237		     enum machine_mode mode ATTRIBUTE_UNUSED,
4238		     int ignore ATTRIBUTE_UNUSED)
4239{
4240  size_t i;
4241  enum insn_code icode;
4242  const struct builtin_description *d;
4243  tree fndecl = TREE_OPERAND (TREE_OPERAND (exp, 0), 0);
4244  tree arglist = TREE_OPERAND (exp, 1);
4245  unsigned int fcode = DECL_FUNCTION_CODE (fndecl);
4246  tree arg0, arg1, arg2;
4247  rtx op0, op1, op2, accvec, pat, tmp1, tmp2;
4248  enum machine_mode tmode, mode0;
4249
4250  switch (fcode)
4251    {
4252    case BFIN_BUILTIN_CSYNC:
4253      emit_insn (gen_csync ());
4254      return 0;
4255    case BFIN_BUILTIN_SSYNC:
4256      emit_insn (gen_ssync ());
4257      return 0;
4258
4259    case BFIN_BUILTIN_DIFFHL_2X16:
4260    case BFIN_BUILTIN_DIFFLH_2X16:
4261      arg0 = TREE_VALUE (arglist);
4262      op0 = expand_expr (arg0, NULL_RTX, VOIDmode, 0);
4263      icode = (fcode == BFIN_BUILTIN_DIFFHL_2X16
4264	       ? CODE_FOR_subhilov2hi3 : CODE_FOR_sublohiv2hi3);
4265      tmode = insn_data[icode].operand[0].mode;
4266      mode0 = insn_data[icode].operand[1].mode;
4267
4268      if (! target
4269	  || GET_MODE (target) != tmode
4270	  || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
4271	target = gen_reg_rtx (tmode);
4272
4273      if (VECTOR_MODE_P (mode0))
4274	op0 = safe_vector_operand (op0, mode0);
4275
4276      if (! (*insn_data[icode].operand[1].predicate) (op0, mode0))
4277	op0 = copy_to_mode_reg (mode0, op0);
4278
4279      pat = GEN_FCN (icode) (target, op0, op0);
4280      if (! pat)
4281	return 0;
4282      emit_insn (pat);
4283      return target;
4284
4285    case BFIN_BUILTIN_CPLX_MUL_16:
4286      arg0 = TREE_VALUE (arglist);
4287      arg1 = TREE_VALUE (TREE_CHAIN (arglist));
4288      op0 = expand_expr (arg0, NULL_RTX, VOIDmode, 0);
4289      op1 = expand_expr (arg1, NULL_RTX, VOIDmode, 0);
4290      accvec = gen_reg_rtx (V2PDImode);
4291
4292      if (! target
4293	  || GET_MODE (target) != V2HImode
4294	  || ! (*insn_data[icode].operand[0].predicate) (target, V2HImode))
4295	target = gen_reg_rtx (tmode);
4296      if (! register_operand (op0, GET_MODE (op0)))
4297	op0 = copy_to_mode_reg (GET_MODE (op0), op0);
4298      if (! register_operand (op1, GET_MODE (op1)))
4299	op1 = copy_to_mode_reg (GET_MODE (op1), op1);
4300
4301      emit_insn (gen_flag_macinit1v2hi_parts (accvec, op0, op1, const0_rtx,
4302					      const0_rtx, const0_rtx,
4303					      const1_rtx, GEN_INT (MACFLAG_NONE)));
4304      emit_insn (gen_flag_macv2hi_parts (target, op0, op1, const1_rtx,
4305					 const1_rtx, const1_rtx,
4306					 const0_rtx, accvec, const1_rtx, const0_rtx,
4307					 GEN_INT (MACFLAG_NONE), accvec));
4308
4309      return target;
4310
4311    case BFIN_BUILTIN_CPLX_MAC_16:
4312    case BFIN_BUILTIN_CPLX_MSU_16:
4313      arg0 = TREE_VALUE (arglist);
4314      arg1 = TREE_VALUE (TREE_CHAIN (arglist));
4315      arg2 = TREE_VALUE (TREE_CHAIN (TREE_CHAIN (arglist)));
4316      op0 = expand_expr (arg0, NULL_RTX, VOIDmode, 0);
4317      op1 = expand_expr (arg1, NULL_RTX, VOIDmode, 0);
4318      op2 = expand_expr (arg2, NULL_RTX, VOIDmode, 0);
4319      accvec = gen_reg_rtx (V2PDImode);
4320
4321      if (! target
4322	  || GET_MODE (target) != V2HImode
4323	  || ! (*insn_data[icode].operand[0].predicate) (target, V2HImode))
4324	target = gen_reg_rtx (tmode);
4325      if (! register_operand (op0, GET_MODE (op0)))
4326	op0 = copy_to_mode_reg (GET_MODE (op0), op0);
4327      if (! register_operand (op1, GET_MODE (op1)))
4328	op1 = copy_to_mode_reg (GET_MODE (op1), op1);
4329
4330      tmp1 = gen_reg_rtx (SImode);
4331      tmp2 = gen_reg_rtx (SImode);
4332      emit_insn (gen_ashlsi3 (tmp1, gen_lowpart (SImode, op2), GEN_INT (16)));
4333      emit_move_insn (tmp2, gen_lowpart (SImode, op2));
4334      emit_insn (gen_movstricthi_1 (gen_lowpart (HImode, tmp2), const0_rtx));
4335      emit_insn (gen_load_accumulator_pair (accvec, tmp1, tmp2));
4336      emit_insn (gen_flag_macv2hi_parts_acconly (accvec, op0, op1, const0_rtx,
4337						 const0_rtx, const0_rtx,
4338						 const1_rtx, accvec, const0_rtx,
4339						 const0_rtx,
4340						 GEN_INT (MACFLAG_W32)));
4341      tmp1 = (fcode == BFIN_BUILTIN_CPLX_MAC_16 ? const1_rtx : const0_rtx);
4342      tmp2 = (fcode == BFIN_BUILTIN_CPLX_MAC_16 ? const0_rtx : const1_rtx);
4343      emit_insn (gen_flag_macv2hi_parts (target, op0, op1, const1_rtx,
4344					 const1_rtx, const1_rtx,
4345					 const0_rtx, accvec, tmp1, tmp2,
4346					 GEN_INT (MACFLAG_NONE), accvec));
4347
4348      return target;
4349
4350    default:
4351      break;
4352    }
4353
4354  for (i = 0, d = bdesc_2arg; i < ARRAY_SIZE (bdesc_2arg); i++, d++)
4355    if (d->code == fcode)
4356      return bfin_expand_binop_builtin (d->icode, arglist, target,
4357					d->macflag);
4358
4359  for (i = 0, d = bdesc_1arg; i < ARRAY_SIZE (bdesc_1arg); i++, d++)
4360    if (d->code == fcode)
4361      return bfin_expand_unop_builtin (d->icode, arglist, target);
4362
4363  gcc_unreachable ();
4364}
4365
4366#undef TARGET_INIT_BUILTINS
4367#define TARGET_INIT_BUILTINS bfin_init_builtins
4368
4369#undef TARGET_EXPAND_BUILTIN
4370#define TARGET_EXPAND_BUILTIN bfin_expand_builtin
4371
4372#undef TARGET_ASM_GLOBALIZE_LABEL
4373#define TARGET_ASM_GLOBALIZE_LABEL bfin_globalize_label
4374
4375#undef TARGET_ASM_FILE_START
4376#define TARGET_ASM_FILE_START output_file_start
4377
4378#undef TARGET_ATTRIBUTE_TABLE
4379#define TARGET_ATTRIBUTE_TABLE bfin_attribute_table
4380
4381#undef TARGET_COMP_TYPE_ATTRIBUTES
4382#define TARGET_COMP_TYPE_ATTRIBUTES bfin_comp_type_attributes
4383
4384#undef TARGET_RTX_COSTS
4385#define TARGET_RTX_COSTS bfin_rtx_costs
4386
4387#undef  TARGET_ADDRESS_COST
4388#define TARGET_ADDRESS_COST bfin_address_cost
4389
4390#undef TARGET_ASM_INTERNAL_LABEL
4391#define TARGET_ASM_INTERNAL_LABEL bfin_internal_label
4392
4393#undef  TARGET_ASM_INTEGER
4394#define TARGET_ASM_INTEGER bfin_assemble_integer
4395
4396#undef TARGET_MACHINE_DEPENDENT_REORG
4397#define TARGET_MACHINE_DEPENDENT_REORG bfin_reorg
4398
4399#undef TARGET_FUNCTION_OK_FOR_SIBCALL
4400#define TARGET_FUNCTION_OK_FOR_SIBCALL bfin_function_ok_for_sibcall
4401
4402#undef TARGET_ASM_OUTPUT_MI_THUNK
4403#define TARGET_ASM_OUTPUT_MI_THUNK bfin_output_mi_thunk
4404#undef TARGET_ASM_CAN_OUTPUT_MI_THUNK
4405#define TARGET_ASM_CAN_OUTPUT_MI_THUNK hook_bool_tree_hwi_hwi_tree_true
4406
4407#undef TARGET_SCHED_ADJUST_COST
4408#define TARGET_SCHED_ADJUST_COST bfin_adjust_cost
4409
4410#undef TARGET_PROMOTE_PROTOTYPES
4411#define TARGET_PROMOTE_PROTOTYPES hook_bool_tree_true
4412#undef TARGET_PROMOTE_FUNCTION_ARGS
4413#define TARGET_PROMOTE_FUNCTION_ARGS hook_bool_tree_true
4414#undef TARGET_PROMOTE_FUNCTION_RETURN
4415#define TARGET_PROMOTE_FUNCTION_RETURN hook_bool_tree_true
4416
4417#undef TARGET_ARG_PARTIAL_BYTES
4418#define TARGET_ARG_PARTIAL_BYTES bfin_arg_partial_bytes
4419
4420#undef TARGET_PASS_BY_REFERENCE
4421#define TARGET_PASS_BY_REFERENCE bfin_pass_by_reference
4422
4423#undef TARGET_SETUP_INCOMING_VARARGS
4424#define TARGET_SETUP_INCOMING_VARARGS setup_incoming_varargs
4425
4426#undef TARGET_STRUCT_VALUE_RTX
4427#define TARGET_STRUCT_VALUE_RTX bfin_struct_value_rtx
4428
4429#undef TARGET_VECTOR_MODE_SUPPORTED_P
4430#define TARGET_VECTOR_MODE_SUPPORTED_P bfin_vector_mode_supported_p
4431
4432#undef TARGET_HANDLE_OPTION
4433#define TARGET_HANDLE_OPTION bfin_handle_option
4434
4435#undef TARGET_DEFAULT_TARGET_FLAGS
4436#define TARGET_DEFAULT_TARGET_FLAGS TARGET_DEFAULT
4437
4438#undef TARGET_SECONDARY_RELOAD
4439#define TARGET_SECONDARY_RELOAD bfin_secondary_reload
4440
4441#undef TARGET_DELEGITIMIZE_ADDRESS
4442#define TARGET_DELEGITIMIZE_ADDRESS bfin_delegitimize_address
4443
4444struct gcc_target targetm = TARGET_INITIALIZER;
4445