1/* Subroutines used for code generation on IBM RS/6000.
2   Copyright (C) 1991-2015 Free Software Foundation, Inc.
3   Contributed by Richard Kenner (kenner@vlsi1.ultra.nyu.edu)
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 3, 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 COPYING3.  If not see
19   <http://www.gnu.org/licenses/>.  */
20
21#include "config.h"
22#include "system.h"
23#include "coretypes.h"
24#include "tm.h"
25#include "rtl.h"
26#include "regs.h"
27#include "hard-reg-set.h"
28#include "insn-config.h"
29#include "conditions.h"
30#include "insn-attr.h"
31#include "flags.h"
32#include "recog.h"
33#include "obstack.h"
34#include "hash-set.h"
35#include "machmode.h"
36#include "vec.h"
37#include "double-int.h"
38#include "input.h"
39#include "alias.h"
40#include "symtab.h"
41#include "wide-int.h"
42#include "inchash.h"
43#include "tree.h"
44#include "fold-const.h"
45#include "stringpool.h"
46#include "stor-layout.h"
47#include "calls.h"
48#include "print-tree.h"
49#include "varasm.h"
50#include "hashtab.h"
51#include "function.h"
52#include "statistics.h"
53#include "real.h"
54#include "fixed-value.h"
55#include "expmed.h"
56#include "dojump.h"
57#include "explow.h"
58#include "emit-rtl.h"
59#include "stmt.h"
60#include "expr.h"
61#include "insn-codes.h"
62#include "optabs.h"
63#include "except.h"
64#include "output.h"
65#include "dbxout.h"
66#include "predict.h"
67#include "dominance.h"
68#include "cfg.h"
69#include "cfgrtl.h"
70#include "cfganal.h"
71#include "lcm.h"
72#include "cfgbuild.h"
73#include "cfgcleanup.h"
74#include "basic-block.h"
75#include "diagnostic-core.h"
76#include "toplev.h"
77#include "ggc.h"
78#include "tm_p.h"
79#include "target.h"
80#include "target-def.h"
81#include "common/common-target.h"
82#include "langhooks.h"
83#include "reload.h"
84#include "cfgloop.h"
85#include "sched-int.h"
86#include "hash-table.h"
87#include "tree-ssa-alias.h"
88#include "internal-fn.h"
89#include "gimple-fold.h"
90#include "tree-eh.h"
91#include "gimple-expr.h"
92#include "is-a.h"
93#include "gimple.h"
94#include "gimplify.h"
95#include "gimple-iterator.h"
96#include "gimple-walk.h"
97#include "intl.h"
98#include "params.h"
99#include "tm-constrs.h"
100#include "ira.h"
101#include "opts.h"
102#include "tree-vectorizer.h"
103#include "dumpfile.h"
104#include "hash-map.h"
105#include "plugin-api.h"
106#include "ipa-ref.h"
107#include "cgraph.h"
108#include "target-globals.h"
109#include "builtins.h"
110#include "context.h"
111#include "tree-pass.h"
112#if TARGET_XCOFF
113#include "xcoffout.h"  /* get declarations of xcoff_*_section_name */
114#endif
115#if TARGET_MACHO
116#include "gstab.h"  /* for N_SLINE */
117#endif
118
119#ifndef TARGET_NO_PROTOTYPE
120#define TARGET_NO_PROTOTYPE 0
121#endif
122
123#define min(A,B)	((A) < (B) ? (A) : (B))
124#define max(A,B)	((A) > (B) ? (A) : (B))
125
126/* Structure used to define the rs6000 stack */
127typedef struct rs6000_stack {
128  int reload_completed;		/* stack info won't change from here on */
129  int first_gp_reg_save;	/* first callee saved GP register used */
130  int first_fp_reg_save;	/* first callee saved FP register used */
131  int first_altivec_reg_save;	/* first callee saved AltiVec register used */
132  int lr_save_p;		/* true if the link reg needs to be saved */
133  int cr_save_p;		/* true if the CR reg needs to be saved */
134  unsigned int vrsave_mask;	/* mask of vec registers to save */
135  int push_p;			/* true if we need to allocate stack space */
136  int calls_p;			/* true if the function makes any calls */
137  int world_save_p;		/* true if we're saving *everything*:
138				   r13-r31, cr, f14-f31, vrsave, v20-v31  */
139  enum rs6000_abi abi;		/* which ABI to use */
140  int gp_save_offset;		/* offset to save GP regs from initial SP */
141  int fp_save_offset;		/* offset to save FP regs from initial SP */
142  int altivec_save_offset;	/* offset to save AltiVec regs from initial SP */
143  int lr_save_offset;		/* offset to save LR from initial SP */
144  int cr_save_offset;		/* offset to save CR from initial SP */
145  int vrsave_save_offset;	/* offset to save VRSAVE from initial SP */
146  int spe_gp_save_offset;	/* offset to save spe 64-bit gprs  */
147  int varargs_save_offset;	/* offset to save the varargs registers */
148  int ehrd_offset;		/* offset to EH return data */
149  int ehcr_offset;		/* offset to EH CR field data */
150  int reg_size;			/* register size (4 or 8) */
151  HOST_WIDE_INT vars_size;	/* variable save area size */
152  int parm_size;		/* outgoing parameter size */
153  int save_size;		/* save area size */
154  int fixed_size;		/* fixed size of stack frame */
155  int gp_size;			/* size of saved GP registers */
156  int fp_size;			/* size of saved FP registers */
157  int altivec_size;		/* size of saved AltiVec registers */
158  int cr_size;			/* size to hold CR if not in save_size */
159  int vrsave_size;		/* size to hold VRSAVE if not in save_size */
160  int altivec_padding_size;	/* size of altivec alignment padding if
161				   not in save_size */
162  int spe_gp_size;		/* size of 64-bit GPR save size for SPE */
163  int spe_padding_size;
164  HOST_WIDE_INT total_size;	/* total bytes allocated for stack */
165  int spe_64bit_regs_used;
166  int savres_strategy;
167} rs6000_stack_t;
168
169/* A C structure for machine-specific, per-function data.
170   This is added to the cfun structure.  */
171typedef struct GTY(()) machine_function
172{
173  /* Whether the instruction chain has been scanned already.  */
174  int insn_chain_scanned_p;
175  /* Flags if __builtin_return_address (n) with n >= 1 was used.  */
176  int ra_needs_full_frame;
177  /* Flags if __builtin_return_address (0) was used.  */
178  int ra_need_lr;
179  /* Cache lr_save_p after expansion of builtin_eh_return.  */
180  int lr_save_state;
181  /* Whether we need to save the TOC to the reserved stack location in the
182     function prologue.  */
183  bool save_toc_in_prologue;
184  /* Offset from virtual_stack_vars_rtx to the start of the ABI_V4
185     varargs save area.  */
186  HOST_WIDE_INT varargs_save_offset;
187  /* Temporary stack slot to use for SDmode copies.  This slot is
188     64-bits wide and is allocated early enough so that the offset
189     does not overflow the 16-bit load/store offset field.  */
190  rtx sdmode_stack_slot;
191  /* Flag if r2 setup is needed with ELFv2 ABI.  */
192  bool r2_setup_needed;
193} machine_function;
194
195/* Support targetm.vectorize.builtin_mask_for_load.  */
196static GTY(()) tree altivec_builtin_mask_for_load;
197
198/* Set to nonzero once AIX common-mode calls have been defined.  */
199static GTY(()) int common_mode_defined;
200
201/* Label number of label created for -mrelocatable, to call to so we can
202   get the address of the GOT section */
203static int rs6000_pic_labelno;
204
205#ifdef USING_ELFOS_H
206/* Counter for labels which are to be placed in .fixup.  */
207int fixuplabelno = 0;
208#endif
209
210/* Whether to use variant of AIX ABI for PowerPC64 Linux.  */
211int dot_symbols;
212
213/* Specify the machine mode that pointers have.  After generation of rtl, the
214   compiler makes no further distinction between pointers and any other objects
215   of this machine mode.  The type is unsigned since not all things that
216   include rs6000.h also include machmode.h.  */
217unsigned rs6000_pmode;
218
219/* Width in bits of a pointer.  */
220unsigned rs6000_pointer_size;
221
222#ifdef HAVE_AS_GNU_ATTRIBUTE
223/* Flag whether floating point values have been passed/returned.  */
224static bool rs6000_passes_float;
225/* Flag whether vector values have been passed/returned.  */
226static bool rs6000_passes_vector;
227/* Flag whether small (<= 8 byte) structures have been returned.  */
228static bool rs6000_returns_struct;
229#endif
230
231/* Value is TRUE if register/mode pair is acceptable.  */
232bool rs6000_hard_regno_mode_ok_p[NUM_MACHINE_MODES][FIRST_PSEUDO_REGISTER];
233
234/* Maximum number of registers needed for a given register class and mode.  */
235unsigned char rs6000_class_max_nregs[NUM_MACHINE_MODES][LIM_REG_CLASSES];
236
237/* How many registers are needed for a given register and mode.  */
238unsigned char rs6000_hard_regno_nregs[NUM_MACHINE_MODES][FIRST_PSEUDO_REGISTER];
239
240/* Map register number to register class.  */
241enum reg_class rs6000_regno_regclass[FIRST_PSEUDO_REGISTER];
242
243static int dbg_cost_ctrl;
244
245/* Built in types.  */
246tree rs6000_builtin_types[RS6000_BTI_MAX];
247tree rs6000_builtin_decls[RS6000_BUILTIN_COUNT];
248
249/* Flag to say the TOC is initialized */
250int toc_initialized;
251char toc_label_name[10];
252
253/* Cached value of rs6000_variable_issue. This is cached in
254   rs6000_variable_issue hook and returned from rs6000_sched_reorder2.  */
255static short cached_can_issue_more;
256
257static GTY(()) section *read_only_data_section;
258static GTY(()) section *private_data_section;
259static GTY(()) section *tls_data_section;
260static GTY(()) section *tls_private_data_section;
261static GTY(()) section *read_only_private_data_section;
262static GTY(()) section *sdata2_section;
263static GTY(()) section *toc_section;
264
265struct builtin_description
266{
267  const HOST_WIDE_INT mask;
268  const enum insn_code icode;
269  const char *const name;
270  const enum rs6000_builtins code;
271};
272
273/* Describe the vector unit used for modes.  */
274enum rs6000_vector rs6000_vector_unit[NUM_MACHINE_MODES];
275enum rs6000_vector rs6000_vector_mem[NUM_MACHINE_MODES];
276
277/* Register classes for various constraints that are based on the target
278   switches.  */
279enum reg_class rs6000_constraints[RS6000_CONSTRAINT_MAX];
280
281/* Describe the alignment of a vector.  */
282int rs6000_vector_align[NUM_MACHINE_MODES];
283
284/* Map selected modes to types for builtins.  */
285static GTY(()) tree builtin_mode_to_type[MAX_MACHINE_MODE][2];
286
287/* What modes to automatically generate reciprocal divide estimate (fre) and
288   reciprocal sqrt (frsqrte) for.  */
289unsigned char rs6000_recip_bits[MAX_MACHINE_MODE];
290
291/* Masks to determine which reciprocal esitmate instructions to generate
292   automatically.  */
293enum rs6000_recip_mask {
294  RECIP_SF_DIV		= 0x001,	/* Use divide estimate */
295  RECIP_DF_DIV		= 0x002,
296  RECIP_V4SF_DIV	= 0x004,
297  RECIP_V2DF_DIV	= 0x008,
298
299  RECIP_SF_RSQRT	= 0x010,	/* Use reciprocal sqrt estimate.  */
300  RECIP_DF_RSQRT	= 0x020,
301  RECIP_V4SF_RSQRT	= 0x040,
302  RECIP_V2DF_RSQRT	= 0x080,
303
304  /* Various combination of flags for -mrecip=xxx.  */
305  RECIP_NONE		= 0,
306  RECIP_ALL		= (RECIP_SF_DIV | RECIP_DF_DIV | RECIP_V4SF_DIV
307			   | RECIP_V2DF_DIV | RECIP_SF_RSQRT | RECIP_DF_RSQRT
308			   | RECIP_V4SF_RSQRT | RECIP_V2DF_RSQRT),
309
310  RECIP_HIGH_PRECISION	= RECIP_ALL,
311
312  /* On low precision machines like the power5, don't enable double precision
313     reciprocal square root estimate, since it isn't accurate enough.  */
314  RECIP_LOW_PRECISION	= (RECIP_ALL & ~(RECIP_DF_RSQRT | RECIP_V2DF_RSQRT))
315};
316
317/* -mrecip options.  */
318static struct
319{
320  const char *string;		/* option name */
321  unsigned int mask;		/* mask bits to set */
322} recip_options[] = {
323  { "all",	 RECIP_ALL },
324  { "none",	 RECIP_NONE },
325  { "div",	 (RECIP_SF_DIV | RECIP_DF_DIV | RECIP_V4SF_DIV
326		  | RECIP_V2DF_DIV) },
327  { "divf",	 (RECIP_SF_DIV | RECIP_V4SF_DIV) },
328  { "divd",	 (RECIP_DF_DIV | RECIP_V2DF_DIV) },
329  { "rsqrt",	 (RECIP_SF_RSQRT | RECIP_DF_RSQRT | RECIP_V4SF_RSQRT
330		  | RECIP_V2DF_RSQRT) },
331  { "rsqrtf",	 (RECIP_SF_RSQRT | RECIP_V4SF_RSQRT) },
332  { "rsqrtd",	 (RECIP_DF_RSQRT | RECIP_V2DF_RSQRT) },
333};
334
335/* Pointer to function (in rs6000-c.c) that can define or undefine target
336   macros that have changed.  Languages that don't support the preprocessor
337   don't link in rs6000-c.c, so we can't call it directly.  */
338void (*rs6000_target_modify_macros_ptr) (bool, HOST_WIDE_INT, HOST_WIDE_INT);
339
340/* Simplfy register classes into simpler classifications.  We assume
341   GPR_REG_TYPE - FPR_REG_TYPE are ordered so that we can use a simple range
342   check for standard register classes (gpr/floating/altivec/vsx) and
343   floating/vector classes (float/altivec/vsx).  */
344
345enum rs6000_reg_type {
346  NO_REG_TYPE,
347  PSEUDO_REG_TYPE,
348  GPR_REG_TYPE,
349  VSX_REG_TYPE,
350  ALTIVEC_REG_TYPE,
351  FPR_REG_TYPE,
352  SPR_REG_TYPE,
353  CR_REG_TYPE,
354  SPE_ACC_TYPE,
355  SPEFSCR_REG_TYPE
356};
357
358/* Map register class to register type.  */
359static enum rs6000_reg_type reg_class_to_reg_type[N_REG_CLASSES];
360
361/* First/last register type for the 'normal' register types (i.e. general
362   purpose, floating point, altivec, and VSX registers).  */
363#define IS_STD_REG_TYPE(RTYPE) IN_RANGE(RTYPE, GPR_REG_TYPE, FPR_REG_TYPE)
364
365#define IS_FP_VECT_REG_TYPE(RTYPE) IN_RANGE(RTYPE, VSX_REG_TYPE, FPR_REG_TYPE)
366
367
368/* Register classes we care about in secondary reload or go if legitimate
369   address.  We only need to worry about GPR, FPR, and Altivec registers here,
370   along an ANY field that is the OR of the 3 register classes.  */
371
372enum rs6000_reload_reg_type {
373  RELOAD_REG_GPR,			/* General purpose registers.  */
374  RELOAD_REG_FPR,			/* Traditional floating point regs.  */
375  RELOAD_REG_VMX,			/* Altivec (VMX) registers.  */
376  RELOAD_REG_ANY,			/* OR of GPR, FPR, Altivec masks.  */
377  N_RELOAD_REG
378};
379
380/* For setting up register classes, loop through the 3 register classes mapping
381   into real registers, and skip the ANY class, which is just an OR of the
382   bits.  */
383#define FIRST_RELOAD_REG_CLASS	RELOAD_REG_GPR
384#define LAST_RELOAD_REG_CLASS	RELOAD_REG_VMX
385
386/* Map reload register type to a register in the register class.  */
387struct reload_reg_map_type {
388  const char *name;			/* Register class name.  */
389  int reg;				/* Register in the register class.  */
390};
391
392static const struct reload_reg_map_type reload_reg_map[N_RELOAD_REG] = {
393  { "Gpr",	FIRST_GPR_REGNO },	/* RELOAD_REG_GPR.  */
394  { "Fpr",	FIRST_FPR_REGNO },	/* RELOAD_REG_FPR.  */
395  { "VMX",	FIRST_ALTIVEC_REGNO },	/* RELOAD_REG_VMX.  */
396  { "Any",	-1 },			/* RELOAD_REG_ANY.  */
397};
398
399/* Mask bits for each register class, indexed per mode.  Historically the
400   compiler has been more restrictive which types can do PRE_MODIFY instead of
401   PRE_INC and PRE_DEC, so keep track of sepaate bits for these two.  */
402typedef unsigned char addr_mask_type;
403
404#define RELOAD_REG_VALID	0x01	/* Mode valid in register..  */
405#define RELOAD_REG_MULTIPLE	0x02	/* Mode takes multiple registers.  */
406#define RELOAD_REG_INDEXED	0x04	/* Reg+reg addressing.  */
407#define RELOAD_REG_OFFSET	0x08	/* Reg+offset addressing. */
408#define RELOAD_REG_PRE_INCDEC	0x10	/* PRE_INC/PRE_DEC valid.  */
409#define RELOAD_REG_PRE_MODIFY	0x20	/* PRE_MODIFY valid.  */
410#define RELOAD_REG_AND_M16	0x40	/* AND -16 addressing.  */
411
412/* Register type masks based on the type, of valid addressing modes.  */
413struct rs6000_reg_addr {
414  enum insn_code reload_load;		/* INSN to reload for loading. */
415  enum insn_code reload_store;		/* INSN to reload for storing.  */
416  enum insn_code reload_fpr_gpr;	/* INSN to move from FPR to GPR.  */
417  enum insn_code reload_gpr_vsx;	/* INSN to move from GPR to VSX.  */
418  enum insn_code reload_vsx_gpr;	/* INSN to move from VSX to GPR.  */
419  addr_mask_type addr_mask[(int)N_RELOAD_REG]; /* Valid address masks.  */
420  bool scalar_in_vmx_p;			/* Scalar value can go in VMX.  */
421};
422
423static struct rs6000_reg_addr reg_addr[NUM_MACHINE_MODES];
424
425/* Helper function to say whether a mode supports PRE_INC or PRE_DEC.  */
426static inline bool
427mode_supports_pre_incdec_p (machine_mode mode)
428{
429  return ((reg_addr[mode].addr_mask[RELOAD_REG_ANY] & RELOAD_REG_PRE_INCDEC)
430	  != 0);
431}
432
433/* Helper function to say whether a mode supports PRE_MODIFY.  */
434static inline bool
435mode_supports_pre_modify_p (machine_mode mode)
436{
437  return ((reg_addr[mode].addr_mask[RELOAD_REG_ANY] & RELOAD_REG_PRE_MODIFY)
438	  != 0);
439}
440
441
442/* Target cpu costs.  */
443
444struct processor_costs {
445  const int mulsi;	  /* cost of SImode multiplication.  */
446  const int mulsi_const;  /* cost of SImode multiplication by constant.  */
447  const int mulsi_const9; /* cost of SImode mult by short constant.  */
448  const int muldi;	  /* cost of DImode multiplication.  */
449  const int divsi;	  /* cost of SImode division.  */
450  const int divdi;	  /* cost of DImode division.  */
451  const int fp;		  /* cost of simple SFmode and DFmode insns.  */
452  const int dmul;	  /* cost of DFmode multiplication (and fmadd).  */
453  const int sdiv;	  /* cost of SFmode division (fdivs).  */
454  const int ddiv;	  /* cost of DFmode division (fdiv).  */
455  const int cache_line_size;    /* cache line size in bytes. */
456  const int l1_cache_size;	/* size of l1 cache, in kilobytes.  */
457  const int l2_cache_size;	/* size of l2 cache, in kilobytes.  */
458  const int simultaneous_prefetches; /* number of parallel prefetch
459					operations.  */
460  const int sfdf_convert;	/* cost of SF->DF conversion.  */
461};
462
463const struct processor_costs *rs6000_cost;
464
465/* Processor costs (relative to an add) */
466
467/* Instruction size costs on 32bit processors.  */
468static const
469struct processor_costs size32_cost = {
470  COSTS_N_INSNS (1),    /* mulsi */
471  COSTS_N_INSNS (1),    /* mulsi_const */
472  COSTS_N_INSNS (1),    /* mulsi_const9 */
473  COSTS_N_INSNS (1),    /* muldi */
474  COSTS_N_INSNS (1),    /* divsi */
475  COSTS_N_INSNS (1),    /* divdi */
476  COSTS_N_INSNS (1),    /* fp */
477  COSTS_N_INSNS (1),    /* dmul */
478  COSTS_N_INSNS (1),    /* sdiv */
479  COSTS_N_INSNS (1),    /* ddiv */
480  32,			/* cache line size */
481  0,			/* l1 cache */
482  0,			/* l2 cache */
483  0,			/* streams */
484  0,			/* SF->DF convert */
485};
486
487/* Instruction size costs on 64bit processors.  */
488static const
489struct processor_costs size64_cost = {
490  COSTS_N_INSNS (1),    /* mulsi */
491  COSTS_N_INSNS (1),    /* mulsi_const */
492  COSTS_N_INSNS (1),    /* mulsi_const9 */
493  COSTS_N_INSNS (1),    /* muldi */
494  COSTS_N_INSNS (1),    /* divsi */
495  COSTS_N_INSNS (1),    /* divdi */
496  COSTS_N_INSNS (1),    /* fp */
497  COSTS_N_INSNS (1),    /* dmul */
498  COSTS_N_INSNS (1),    /* sdiv */
499  COSTS_N_INSNS (1),    /* ddiv */
500  128,			/* cache line size */
501  0,			/* l1 cache */
502  0,			/* l2 cache */
503  0,			/* streams */
504  0,			/* SF->DF convert */
505};
506
507/* Instruction costs on RS64A processors.  */
508static const
509struct processor_costs rs64a_cost = {
510  COSTS_N_INSNS (20),   /* mulsi */
511  COSTS_N_INSNS (12),   /* mulsi_const */
512  COSTS_N_INSNS (8),    /* mulsi_const9 */
513  COSTS_N_INSNS (34),   /* muldi */
514  COSTS_N_INSNS (65),   /* divsi */
515  COSTS_N_INSNS (67),   /* divdi */
516  COSTS_N_INSNS (4),    /* fp */
517  COSTS_N_INSNS (4),    /* dmul */
518  COSTS_N_INSNS (31),   /* sdiv */
519  COSTS_N_INSNS (31),   /* ddiv */
520  128,			/* cache line size */
521  128,			/* l1 cache */
522  2048,			/* l2 cache */
523  1,			/* streams */
524  0,			/* SF->DF convert */
525};
526
527/* Instruction costs on MPCCORE processors.  */
528static const
529struct processor_costs mpccore_cost = {
530  COSTS_N_INSNS (2),    /* mulsi */
531  COSTS_N_INSNS (2),    /* mulsi_const */
532  COSTS_N_INSNS (2),    /* mulsi_const9 */
533  COSTS_N_INSNS (2),    /* muldi */
534  COSTS_N_INSNS (6),    /* divsi */
535  COSTS_N_INSNS (6),    /* divdi */
536  COSTS_N_INSNS (4),    /* fp */
537  COSTS_N_INSNS (5),    /* dmul */
538  COSTS_N_INSNS (10),   /* sdiv */
539  COSTS_N_INSNS (17),   /* ddiv */
540  32,			/* cache line size */
541  4,			/* l1 cache */
542  16,			/* l2 cache */
543  1,			/* streams */
544  0,			/* SF->DF convert */
545};
546
547/* Instruction costs on PPC403 processors.  */
548static const
549struct processor_costs ppc403_cost = {
550  COSTS_N_INSNS (4),    /* mulsi */
551  COSTS_N_INSNS (4),    /* mulsi_const */
552  COSTS_N_INSNS (4),    /* mulsi_const9 */
553  COSTS_N_INSNS (4),    /* muldi */
554  COSTS_N_INSNS (33),   /* divsi */
555  COSTS_N_INSNS (33),   /* divdi */
556  COSTS_N_INSNS (11),   /* fp */
557  COSTS_N_INSNS (11),   /* dmul */
558  COSTS_N_INSNS (11),   /* sdiv */
559  COSTS_N_INSNS (11),   /* ddiv */
560  32,			/* cache line size */
561  4,			/* l1 cache */
562  16,			/* l2 cache */
563  1,			/* streams */
564  0,			/* SF->DF convert */
565};
566
567/* Instruction costs on PPC405 processors.  */
568static const
569struct processor_costs ppc405_cost = {
570  COSTS_N_INSNS (5),    /* mulsi */
571  COSTS_N_INSNS (4),    /* mulsi_const */
572  COSTS_N_INSNS (3),    /* mulsi_const9 */
573  COSTS_N_INSNS (5),    /* muldi */
574  COSTS_N_INSNS (35),   /* divsi */
575  COSTS_N_INSNS (35),   /* divdi */
576  COSTS_N_INSNS (11),   /* fp */
577  COSTS_N_INSNS (11),   /* dmul */
578  COSTS_N_INSNS (11),   /* sdiv */
579  COSTS_N_INSNS (11),   /* ddiv */
580  32,			/* cache line size */
581  16,			/* l1 cache */
582  128,			/* l2 cache */
583  1,			/* streams */
584  0,			/* SF->DF convert */
585};
586
587/* Instruction costs on PPC440 processors.  */
588static const
589struct processor_costs ppc440_cost = {
590  COSTS_N_INSNS (3),    /* mulsi */
591  COSTS_N_INSNS (2),    /* mulsi_const */
592  COSTS_N_INSNS (2),    /* mulsi_const9 */
593  COSTS_N_INSNS (3),    /* muldi */
594  COSTS_N_INSNS (34),   /* divsi */
595  COSTS_N_INSNS (34),   /* divdi */
596  COSTS_N_INSNS (5),    /* fp */
597  COSTS_N_INSNS (5),    /* dmul */
598  COSTS_N_INSNS (19),   /* sdiv */
599  COSTS_N_INSNS (33),   /* ddiv */
600  32,			/* cache line size */
601  32,			/* l1 cache */
602  256,			/* l2 cache */
603  1,			/* streams */
604  0,			/* SF->DF convert */
605};
606
607/* Instruction costs on PPC476 processors.  */
608static const
609struct processor_costs ppc476_cost = {
610  COSTS_N_INSNS (4),    /* mulsi */
611  COSTS_N_INSNS (4),    /* mulsi_const */
612  COSTS_N_INSNS (4),    /* mulsi_const9 */
613  COSTS_N_INSNS (4),    /* muldi */
614  COSTS_N_INSNS (11),   /* divsi */
615  COSTS_N_INSNS (11),   /* divdi */
616  COSTS_N_INSNS (6),    /* fp */
617  COSTS_N_INSNS (6),    /* dmul */
618  COSTS_N_INSNS (19),   /* sdiv */
619  COSTS_N_INSNS (33),   /* ddiv */
620  32,			/* l1 cache line size */
621  32,			/* l1 cache */
622  512,			/* l2 cache */
623  1,			/* streams */
624  0,			/* SF->DF convert */
625};
626
627/* Instruction costs on PPC601 processors.  */
628static const
629struct processor_costs ppc601_cost = {
630  COSTS_N_INSNS (5),    /* mulsi */
631  COSTS_N_INSNS (5),    /* mulsi_const */
632  COSTS_N_INSNS (5),    /* mulsi_const9 */
633  COSTS_N_INSNS (5),    /* muldi */
634  COSTS_N_INSNS (36),   /* divsi */
635  COSTS_N_INSNS (36),   /* divdi */
636  COSTS_N_INSNS (4),    /* fp */
637  COSTS_N_INSNS (5),    /* dmul */
638  COSTS_N_INSNS (17),   /* sdiv */
639  COSTS_N_INSNS (31),   /* ddiv */
640  32,			/* cache line size */
641  32,			/* l1 cache */
642  256,			/* l2 cache */
643  1,			/* streams */
644  0,			/* SF->DF convert */
645};
646
647/* Instruction costs on PPC603 processors.  */
648static const
649struct processor_costs ppc603_cost = {
650  COSTS_N_INSNS (5),    /* mulsi */
651  COSTS_N_INSNS (3),    /* mulsi_const */
652  COSTS_N_INSNS (2),    /* mulsi_const9 */
653  COSTS_N_INSNS (5),    /* muldi */
654  COSTS_N_INSNS (37),   /* divsi */
655  COSTS_N_INSNS (37),   /* divdi */
656  COSTS_N_INSNS (3),    /* fp */
657  COSTS_N_INSNS (4),    /* dmul */
658  COSTS_N_INSNS (18),   /* sdiv */
659  COSTS_N_INSNS (33),   /* ddiv */
660  32,			/* cache line size */
661  8,			/* l1 cache */
662  64,			/* l2 cache */
663  1,			/* streams */
664  0,			/* SF->DF convert */
665};
666
667/* Instruction costs on PPC604 processors.  */
668static const
669struct processor_costs ppc604_cost = {
670  COSTS_N_INSNS (4),    /* mulsi */
671  COSTS_N_INSNS (4),    /* mulsi_const */
672  COSTS_N_INSNS (4),    /* mulsi_const9 */
673  COSTS_N_INSNS (4),    /* muldi */
674  COSTS_N_INSNS (20),   /* divsi */
675  COSTS_N_INSNS (20),   /* divdi */
676  COSTS_N_INSNS (3),    /* fp */
677  COSTS_N_INSNS (3),    /* dmul */
678  COSTS_N_INSNS (18),   /* sdiv */
679  COSTS_N_INSNS (32),   /* ddiv */
680  32,			/* cache line size */
681  16,			/* l1 cache */
682  512,			/* l2 cache */
683  1,			/* streams */
684  0,			/* SF->DF convert */
685};
686
687/* Instruction costs on PPC604e processors.  */
688static const
689struct processor_costs ppc604e_cost = {
690  COSTS_N_INSNS (2),    /* mulsi */
691  COSTS_N_INSNS (2),    /* mulsi_const */
692  COSTS_N_INSNS (2),    /* mulsi_const9 */
693  COSTS_N_INSNS (2),    /* muldi */
694  COSTS_N_INSNS (20),   /* divsi */
695  COSTS_N_INSNS (20),   /* divdi */
696  COSTS_N_INSNS (3),    /* fp */
697  COSTS_N_INSNS (3),    /* dmul */
698  COSTS_N_INSNS (18),   /* sdiv */
699  COSTS_N_INSNS (32),   /* ddiv */
700  32,			/* cache line size */
701  32,			/* l1 cache */
702  1024,			/* l2 cache */
703  1,			/* streams */
704  0,			/* SF->DF convert */
705};
706
707/* Instruction costs on PPC620 processors.  */
708static const
709struct processor_costs ppc620_cost = {
710  COSTS_N_INSNS (5),    /* mulsi */
711  COSTS_N_INSNS (4),    /* mulsi_const */
712  COSTS_N_INSNS (3),    /* mulsi_const9 */
713  COSTS_N_INSNS (7),    /* muldi */
714  COSTS_N_INSNS (21),   /* divsi */
715  COSTS_N_INSNS (37),   /* divdi */
716  COSTS_N_INSNS (3),    /* fp */
717  COSTS_N_INSNS (3),    /* dmul */
718  COSTS_N_INSNS (18),   /* sdiv */
719  COSTS_N_INSNS (32),   /* ddiv */
720  128,			/* cache line size */
721  32,			/* l1 cache */
722  1024,			/* l2 cache */
723  1,			/* streams */
724  0,			/* SF->DF convert */
725};
726
727/* Instruction costs on PPC630 processors.  */
728static const
729struct processor_costs ppc630_cost = {
730  COSTS_N_INSNS (5),    /* mulsi */
731  COSTS_N_INSNS (4),    /* mulsi_const */
732  COSTS_N_INSNS (3),    /* mulsi_const9 */
733  COSTS_N_INSNS (7),    /* muldi */
734  COSTS_N_INSNS (21),   /* divsi */
735  COSTS_N_INSNS (37),   /* divdi */
736  COSTS_N_INSNS (3),    /* fp */
737  COSTS_N_INSNS (3),    /* dmul */
738  COSTS_N_INSNS (17),   /* sdiv */
739  COSTS_N_INSNS (21),   /* ddiv */
740  128,			/* cache line size */
741  64,			/* l1 cache */
742  1024,			/* l2 cache */
743  1,			/* streams */
744  0,			/* SF->DF convert */
745};
746
747/* Instruction costs on Cell processor.  */
748/* COSTS_N_INSNS (1) ~ one add.  */
749static const
750struct processor_costs ppccell_cost = {
751  COSTS_N_INSNS (9/2)+2,    /* mulsi */
752  COSTS_N_INSNS (6/2),    /* mulsi_const */
753  COSTS_N_INSNS (6/2),    /* mulsi_const9 */
754  COSTS_N_INSNS (15/2)+2,   /* muldi */
755  COSTS_N_INSNS (38/2),   /* divsi */
756  COSTS_N_INSNS (70/2),   /* divdi */
757  COSTS_N_INSNS (10/2),   /* fp */
758  COSTS_N_INSNS (10/2),   /* dmul */
759  COSTS_N_INSNS (74/2),   /* sdiv */
760  COSTS_N_INSNS (74/2),   /* ddiv */
761  128,			/* cache line size */
762  32,			/* l1 cache */
763  512,			/* l2 cache */
764  6,			/* streams */
765  0,			/* SF->DF convert */
766};
767
768/* Instruction costs on PPC750 and PPC7400 processors.  */
769static const
770struct processor_costs ppc750_cost = {
771  COSTS_N_INSNS (5),    /* mulsi */
772  COSTS_N_INSNS (3),    /* mulsi_const */
773  COSTS_N_INSNS (2),    /* mulsi_const9 */
774  COSTS_N_INSNS (5),    /* muldi */
775  COSTS_N_INSNS (17),   /* divsi */
776  COSTS_N_INSNS (17),   /* divdi */
777  COSTS_N_INSNS (3),    /* fp */
778  COSTS_N_INSNS (3),    /* dmul */
779  COSTS_N_INSNS (17),   /* sdiv */
780  COSTS_N_INSNS (31),   /* ddiv */
781  32,			/* cache line size */
782  32,			/* l1 cache */
783  512,			/* l2 cache */
784  1,			/* streams */
785  0,			/* SF->DF convert */
786};
787
788/* Instruction costs on PPC7450 processors.  */
789static const
790struct processor_costs ppc7450_cost = {
791  COSTS_N_INSNS (4),    /* mulsi */
792  COSTS_N_INSNS (3),    /* mulsi_const */
793  COSTS_N_INSNS (3),    /* mulsi_const9 */
794  COSTS_N_INSNS (4),    /* muldi */
795  COSTS_N_INSNS (23),   /* divsi */
796  COSTS_N_INSNS (23),   /* divdi */
797  COSTS_N_INSNS (5),    /* fp */
798  COSTS_N_INSNS (5),    /* dmul */
799  COSTS_N_INSNS (21),   /* sdiv */
800  COSTS_N_INSNS (35),   /* ddiv */
801  32,			/* cache line size */
802  32,			/* l1 cache */
803  1024,			/* l2 cache */
804  1,			/* streams */
805  0,			/* SF->DF convert */
806};
807
808/* Instruction costs on PPC8540 processors.  */
809static const
810struct processor_costs ppc8540_cost = {
811  COSTS_N_INSNS (4),    /* mulsi */
812  COSTS_N_INSNS (4),    /* mulsi_const */
813  COSTS_N_INSNS (4),    /* mulsi_const9 */
814  COSTS_N_INSNS (4),    /* muldi */
815  COSTS_N_INSNS (19),   /* divsi */
816  COSTS_N_INSNS (19),   /* divdi */
817  COSTS_N_INSNS (4),    /* fp */
818  COSTS_N_INSNS (4),    /* dmul */
819  COSTS_N_INSNS (29),   /* sdiv */
820  COSTS_N_INSNS (29),   /* ddiv */
821  32,			/* cache line size */
822  32,			/* l1 cache */
823  256,			/* l2 cache */
824  1,			/* prefetch streams /*/
825  0,			/* SF->DF convert */
826};
827
828/* Instruction costs on E300C2 and E300C3 cores.  */
829static const
830struct processor_costs ppce300c2c3_cost = {
831  COSTS_N_INSNS (4),    /* mulsi */
832  COSTS_N_INSNS (4),    /* mulsi_const */
833  COSTS_N_INSNS (4),    /* mulsi_const9 */
834  COSTS_N_INSNS (4),    /* muldi */
835  COSTS_N_INSNS (19),   /* divsi */
836  COSTS_N_INSNS (19),   /* divdi */
837  COSTS_N_INSNS (3),    /* fp */
838  COSTS_N_INSNS (4),    /* dmul */
839  COSTS_N_INSNS (18),   /* sdiv */
840  COSTS_N_INSNS (33),   /* ddiv */
841  32,
842  16,			/* l1 cache */
843  16,			/* l2 cache */
844  1,			/* prefetch streams /*/
845  0,			/* SF->DF convert */
846};
847
848/* Instruction costs on PPCE500MC processors.  */
849static const
850struct processor_costs ppce500mc_cost = {
851  COSTS_N_INSNS (4),    /* mulsi */
852  COSTS_N_INSNS (4),    /* mulsi_const */
853  COSTS_N_INSNS (4),    /* mulsi_const9 */
854  COSTS_N_INSNS (4),    /* muldi */
855  COSTS_N_INSNS (14),   /* divsi */
856  COSTS_N_INSNS (14),   /* divdi */
857  COSTS_N_INSNS (8),    /* fp */
858  COSTS_N_INSNS (10),   /* dmul */
859  COSTS_N_INSNS (36),   /* sdiv */
860  COSTS_N_INSNS (66),   /* ddiv */
861  64,			/* cache line size */
862  32,			/* l1 cache */
863  128,			/* l2 cache */
864  1,			/* prefetch streams /*/
865  0,			/* SF->DF convert */
866};
867
868/* Instruction costs on PPCE500MC64 processors.  */
869static const
870struct processor_costs ppce500mc64_cost = {
871  COSTS_N_INSNS (4),    /* mulsi */
872  COSTS_N_INSNS (4),    /* mulsi_const */
873  COSTS_N_INSNS (4),    /* mulsi_const9 */
874  COSTS_N_INSNS (4),    /* muldi */
875  COSTS_N_INSNS (14),   /* divsi */
876  COSTS_N_INSNS (14),   /* divdi */
877  COSTS_N_INSNS (4),    /* fp */
878  COSTS_N_INSNS (10),   /* dmul */
879  COSTS_N_INSNS (36),   /* sdiv */
880  COSTS_N_INSNS (66),   /* ddiv */
881  64,			/* cache line size */
882  32,			/* l1 cache */
883  128,			/* l2 cache */
884  1,			/* prefetch streams /*/
885  0,			/* SF->DF convert */
886};
887
888/* Instruction costs on PPCE5500 processors.  */
889static const
890struct processor_costs ppce5500_cost = {
891  COSTS_N_INSNS (5),    /* mulsi */
892  COSTS_N_INSNS (5),    /* mulsi_const */
893  COSTS_N_INSNS (4),    /* mulsi_const9 */
894  COSTS_N_INSNS (5),    /* muldi */
895  COSTS_N_INSNS (14),   /* divsi */
896  COSTS_N_INSNS (14),   /* divdi */
897  COSTS_N_INSNS (7),    /* fp */
898  COSTS_N_INSNS (10),   /* dmul */
899  COSTS_N_INSNS (36),   /* sdiv */
900  COSTS_N_INSNS (66),   /* ddiv */
901  64,			/* cache line size */
902  32,			/* l1 cache */
903  128,			/* l2 cache */
904  1,			/* prefetch streams /*/
905  0,			/* SF->DF convert */
906};
907
908/* Instruction costs on PPCE6500 processors.  */
909static const
910struct processor_costs ppce6500_cost = {
911  COSTS_N_INSNS (5),    /* mulsi */
912  COSTS_N_INSNS (5),    /* mulsi_const */
913  COSTS_N_INSNS (4),    /* mulsi_const9 */
914  COSTS_N_INSNS (5),    /* muldi */
915  COSTS_N_INSNS (14),   /* divsi */
916  COSTS_N_INSNS (14),   /* divdi */
917  COSTS_N_INSNS (7),    /* fp */
918  COSTS_N_INSNS (10),   /* dmul */
919  COSTS_N_INSNS (36),   /* sdiv */
920  COSTS_N_INSNS (66),   /* ddiv */
921  64,			/* cache line size */
922  32,			/* l1 cache */
923  128,			/* l2 cache */
924  1,			/* prefetch streams /*/
925  0,			/* SF->DF convert */
926};
927
928/* Instruction costs on AppliedMicro Titan processors.  */
929static const
930struct processor_costs titan_cost = {
931  COSTS_N_INSNS (5),    /* mulsi */
932  COSTS_N_INSNS (5),    /* mulsi_const */
933  COSTS_N_INSNS (5),    /* mulsi_const9 */
934  COSTS_N_INSNS (5),    /* muldi */
935  COSTS_N_INSNS (18),   /* divsi */
936  COSTS_N_INSNS (18),   /* divdi */
937  COSTS_N_INSNS (10),   /* fp */
938  COSTS_N_INSNS (10),   /* dmul */
939  COSTS_N_INSNS (46),   /* sdiv */
940  COSTS_N_INSNS (72),   /* ddiv */
941  32,			/* cache line size */
942  32,			/* l1 cache */
943  512,			/* l2 cache */
944  1,			/* prefetch streams /*/
945  0,			/* SF->DF convert */
946};
947
948/* Instruction costs on POWER4 and POWER5 processors.  */
949static const
950struct processor_costs power4_cost = {
951  COSTS_N_INSNS (3),    /* mulsi */
952  COSTS_N_INSNS (2),    /* mulsi_const */
953  COSTS_N_INSNS (2),    /* mulsi_const9 */
954  COSTS_N_INSNS (4),    /* muldi */
955  COSTS_N_INSNS (18),   /* divsi */
956  COSTS_N_INSNS (34),   /* divdi */
957  COSTS_N_INSNS (3),    /* fp */
958  COSTS_N_INSNS (3),    /* dmul */
959  COSTS_N_INSNS (17),   /* sdiv */
960  COSTS_N_INSNS (17),   /* ddiv */
961  128,			/* cache line size */
962  32,			/* l1 cache */
963  1024,			/* l2 cache */
964  8,			/* prefetch streams /*/
965  0,			/* SF->DF convert */
966};
967
968/* Instruction costs on POWER6 processors.  */
969static const
970struct processor_costs power6_cost = {
971  COSTS_N_INSNS (8),    /* mulsi */
972  COSTS_N_INSNS (8),    /* mulsi_const */
973  COSTS_N_INSNS (8),    /* mulsi_const9 */
974  COSTS_N_INSNS (8),    /* muldi */
975  COSTS_N_INSNS (22),   /* divsi */
976  COSTS_N_INSNS (28),   /* divdi */
977  COSTS_N_INSNS (3),    /* fp */
978  COSTS_N_INSNS (3),    /* dmul */
979  COSTS_N_INSNS (13),   /* sdiv */
980  COSTS_N_INSNS (16),   /* ddiv */
981  128,			/* cache line size */
982  64,			/* l1 cache */
983  2048,			/* l2 cache */
984  16,			/* prefetch streams */
985  0,			/* SF->DF convert */
986};
987
988/* Instruction costs on POWER7 processors.  */
989static const
990struct processor_costs power7_cost = {
991  COSTS_N_INSNS (2),	/* mulsi */
992  COSTS_N_INSNS (2),	/* mulsi_const */
993  COSTS_N_INSNS (2),	/* mulsi_const9 */
994  COSTS_N_INSNS (2),	/* muldi */
995  COSTS_N_INSNS (18),	/* divsi */
996  COSTS_N_INSNS (34),	/* divdi */
997  COSTS_N_INSNS (3),	/* fp */
998  COSTS_N_INSNS (3),	/* dmul */
999  COSTS_N_INSNS (13),	/* sdiv */
1000  COSTS_N_INSNS (16),	/* ddiv */
1001  128,			/* cache line size */
1002  32,			/* l1 cache */
1003  256,			/* l2 cache */
1004  12,			/* prefetch streams */
1005  COSTS_N_INSNS (3),	/* SF->DF convert */
1006};
1007
1008/* Instruction costs on POWER8 processors.  */
1009static const
1010struct processor_costs power8_cost = {
1011  COSTS_N_INSNS (3),	/* mulsi */
1012  COSTS_N_INSNS (3),	/* mulsi_const */
1013  COSTS_N_INSNS (3),	/* mulsi_const9 */
1014  COSTS_N_INSNS (3),	/* muldi */
1015  COSTS_N_INSNS (19),	/* divsi */
1016  COSTS_N_INSNS (35),	/* divdi */
1017  COSTS_N_INSNS (3),	/* fp */
1018  COSTS_N_INSNS (3),	/* dmul */
1019  COSTS_N_INSNS (14),	/* sdiv */
1020  COSTS_N_INSNS (17),	/* ddiv */
1021  128,			/* cache line size */
1022  32,			/* l1 cache */
1023  256,			/* l2 cache */
1024  12,			/* prefetch streams */
1025  COSTS_N_INSNS (3),	/* SF->DF convert */
1026};
1027
1028/* Instruction costs on POWER A2 processors.  */
1029static const
1030struct processor_costs ppca2_cost = {
1031  COSTS_N_INSNS (16),    /* mulsi */
1032  COSTS_N_INSNS (16),    /* mulsi_const */
1033  COSTS_N_INSNS (16),    /* mulsi_const9 */
1034  COSTS_N_INSNS (16),   /* muldi */
1035  COSTS_N_INSNS (22),   /* divsi */
1036  COSTS_N_INSNS (28),   /* divdi */
1037  COSTS_N_INSNS (3),    /* fp */
1038  COSTS_N_INSNS (3),    /* dmul */
1039  COSTS_N_INSNS (59),   /* sdiv */
1040  COSTS_N_INSNS (72),   /* ddiv */
1041  64,
1042  16,			/* l1 cache */
1043  2048,			/* l2 cache */
1044  16,			/* prefetch streams */
1045  0,			/* SF->DF convert */
1046};
1047
1048
1049/* Table that classifies rs6000 builtin functions (pure, const, etc.).  */
1050#undef RS6000_BUILTIN_1
1051#undef RS6000_BUILTIN_2
1052#undef RS6000_BUILTIN_3
1053#undef RS6000_BUILTIN_A
1054#undef RS6000_BUILTIN_D
1055#undef RS6000_BUILTIN_E
1056#undef RS6000_BUILTIN_H
1057#undef RS6000_BUILTIN_P
1058#undef RS6000_BUILTIN_Q
1059#undef RS6000_BUILTIN_S
1060#undef RS6000_BUILTIN_X
1061
1062#define RS6000_BUILTIN_1(ENUM, NAME, MASK, ATTR, ICODE) \
1063  { NAME, ICODE, MASK, ATTR },
1064
1065#define RS6000_BUILTIN_2(ENUM, NAME, MASK, ATTR, ICODE)  \
1066  { NAME, ICODE, MASK, ATTR },
1067
1068#define RS6000_BUILTIN_3(ENUM, NAME, MASK, ATTR, ICODE)  \
1069  { NAME, ICODE, MASK, ATTR },
1070
1071#define RS6000_BUILTIN_A(ENUM, NAME, MASK, ATTR, ICODE)  \
1072  { NAME, ICODE, MASK, ATTR },
1073
1074#define RS6000_BUILTIN_D(ENUM, NAME, MASK, ATTR, ICODE)  \
1075  { NAME, ICODE, MASK, ATTR },
1076
1077#define RS6000_BUILTIN_E(ENUM, NAME, MASK, ATTR, ICODE)  \
1078  { NAME, ICODE, MASK, ATTR },
1079
1080#define RS6000_BUILTIN_H(ENUM, NAME, MASK, ATTR, ICODE)  \
1081  { NAME, ICODE, MASK, ATTR },
1082
1083#define RS6000_BUILTIN_P(ENUM, NAME, MASK, ATTR, ICODE)  \
1084  { NAME, ICODE, MASK, ATTR },
1085
1086#define RS6000_BUILTIN_Q(ENUM, NAME, MASK, ATTR, ICODE)  \
1087  { NAME, ICODE, MASK, ATTR },
1088
1089#define RS6000_BUILTIN_S(ENUM, NAME, MASK, ATTR, ICODE)  \
1090  { NAME, ICODE, MASK, ATTR },
1091
1092#define RS6000_BUILTIN_X(ENUM, NAME, MASK, ATTR, ICODE)  \
1093  { NAME, ICODE, MASK, ATTR },
1094
1095struct rs6000_builtin_info_type {
1096  const char *name;
1097  const enum insn_code icode;
1098  const HOST_WIDE_INT mask;
1099  const unsigned attr;
1100};
1101
1102static const struct rs6000_builtin_info_type rs6000_builtin_info[] =
1103{
1104#include "rs6000-builtin.def"
1105};
1106
1107#undef RS6000_BUILTIN_1
1108#undef RS6000_BUILTIN_2
1109#undef RS6000_BUILTIN_3
1110#undef RS6000_BUILTIN_A
1111#undef RS6000_BUILTIN_D
1112#undef RS6000_BUILTIN_E
1113#undef RS6000_BUILTIN_H
1114#undef RS6000_BUILTIN_P
1115#undef RS6000_BUILTIN_Q
1116#undef RS6000_BUILTIN_S
1117#undef RS6000_BUILTIN_X
1118
1119/* Support for -mveclibabi=<xxx> to control which vector library to use.  */
1120static tree (*rs6000_veclib_handler) (tree, tree, tree);
1121
1122
1123static bool rs6000_debug_legitimate_address_p (machine_mode, rtx, bool);
1124static bool spe_func_has_64bit_regs_p (void);
1125static struct machine_function * rs6000_init_machine_status (void);
1126static int rs6000_ra_ever_killed (void);
1127static tree rs6000_handle_longcall_attribute (tree *, tree, tree, int, bool *);
1128static tree rs6000_handle_altivec_attribute (tree *, tree, tree, int, bool *);
1129static tree rs6000_handle_struct_attribute (tree *, tree, tree, int, bool *);
1130static tree rs6000_builtin_vectorized_libmass (tree, tree, tree);
1131static void rs6000_emit_set_long_const (rtx, HOST_WIDE_INT);
1132static int rs6000_memory_move_cost (machine_mode, reg_class_t, bool);
1133static bool rs6000_debug_rtx_costs (rtx, int, int, int, int *, bool);
1134static int rs6000_debug_address_cost (rtx, machine_mode, addr_space_t,
1135				      bool);
1136static int rs6000_debug_adjust_cost (rtx_insn *, rtx, rtx_insn *, int);
1137static bool is_microcoded_insn (rtx_insn *);
1138static bool is_nonpipeline_insn (rtx_insn *);
1139static bool is_cracked_insn (rtx_insn *);
1140static bool is_load_insn (rtx, rtx *);
1141static bool is_store_insn (rtx, rtx *);
1142static bool set_to_load_agen (rtx_insn *,rtx_insn *);
1143static bool insn_terminates_group_p (rtx_insn *, enum group_termination);
1144static bool insn_must_be_first_in_group (rtx_insn *);
1145static bool insn_must_be_last_in_group (rtx_insn *);
1146static void altivec_init_builtins (void);
1147static tree builtin_function_type (machine_mode, machine_mode,
1148				   machine_mode, machine_mode,
1149				   enum rs6000_builtins, const char *name);
1150static void rs6000_common_init_builtins (void);
1151static void paired_init_builtins (void);
1152static rtx paired_expand_predicate_builtin (enum insn_code, tree, rtx);
1153static void spe_init_builtins (void);
1154static void htm_init_builtins (void);
1155static rtx spe_expand_predicate_builtin (enum insn_code, tree, rtx);
1156static rtx spe_expand_evsel_builtin (enum insn_code, tree, rtx);
1157static int rs6000_emit_int_cmove (rtx, rtx, rtx, rtx);
1158static rs6000_stack_t *rs6000_stack_info (void);
1159static void is_altivec_return_reg (rtx, void *);
1160int easy_vector_constant (rtx, machine_mode);
1161static rtx rs6000_debug_legitimize_address (rtx, rtx, machine_mode);
1162static rtx rs6000_legitimize_tls_address (rtx, enum tls_model);
1163static rtx rs6000_darwin64_record_arg (CUMULATIVE_ARGS *, const_tree,
1164				       bool, bool);
1165#if TARGET_MACHO
1166static void macho_branch_islands (void);
1167#endif
1168static rtx rs6000_legitimize_reload_address (rtx, machine_mode, int, int,
1169					     int, int *);
1170static rtx rs6000_debug_legitimize_reload_address (rtx, machine_mode, int,
1171						   int, int, int *);
1172static bool rs6000_mode_dependent_address (const_rtx);
1173static bool rs6000_debug_mode_dependent_address (const_rtx);
1174static enum reg_class rs6000_secondary_reload_class (enum reg_class,
1175						     machine_mode, rtx);
1176static enum reg_class rs6000_debug_secondary_reload_class (enum reg_class,
1177							   machine_mode,
1178							   rtx);
1179static enum reg_class rs6000_preferred_reload_class (rtx, enum reg_class);
1180static enum reg_class rs6000_debug_preferred_reload_class (rtx,
1181							   enum reg_class);
1182static bool rs6000_secondary_memory_needed (enum reg_class, enum reg_class,
1183					    machine_mode);
1184static bool rs6000_debug_secondary_memory_needed (enum reg_class,
1185						  enum reg_class,
1186						  machine_mode);
1187static bool rs6000_cannot_change_mode_class (machine_mode,
1188					     machine_mode,
1189					     enum reg_class);
1190static bool rs6000_debug_cannot_change_mode_class (machine_mode,
1191						   machine_mode,
1192						   enum reg_class);
1193static bool rs6000_save_toc_in_prologue_p (void);
1194
1195rtx (*rs6000_legitimize_reload_address_ptr) (rtx, machine_mode, int, int,
1196					     int, int *)
1197  = rs6000_legitimize_reload_address;
1198
1199static bool (*rs6000_mode_dependent_address_ptr) (const_rtx)
1200  = rs6000_mode_dependent_address;
1201
1202enum reg_class (*rs6000_secondary_reload_class_ptr) (enum reg_class,
1203						     machine_mode, rtx)
1204  = rs6000_secondary_reload_class;
1205
1206enum reg_class (*rs6000_preferred_reload_class_ptr) (rtx, enum reg_class)
1207  = rs6000_preferred_reload_class;
1208
1209bool (*rs6000_secondary_memory_needed_ptr) (enum reg_class, enum reg_class,
1210					    machine_mode)
1211  = rs6000_secondary_memory_needed;
1212
1213bool (*rs6000_cannot_change_mode_class_ptr) (machine_mode,
1214					     machine_mode,
1215					     enum reg_class)
1216  = rs6000_cannot_change_mode_class;
1217
1218const int INSN_NOT_AVAILABLE = -1;
1219
1220static void rs6000_print_isa_options (FILE *, int, const char *,
1221				      HOST_WIDE_INT);
1222static void rs6000_print_builtin_options (FILE *, int, const char *,
1223					  HOST_WIDE_INT);
1224
1225static enum rs6000_reg_type register_to_reg_type (rtx, bool *);
1226static bool rs6000_secondary_reload_move (enum rs6000_reg_type,
1227					  enum rs6000_reg_type,
1228					  machine_mode,
1229					  secondary_reload_info *,
1230					  bool);
1231rtl_opt_pass *make_pass_analyze_swaps (gcc::context*);
1232
1233/* Hash table stuff for keeping track of TOC entries.  */
1234
1235struct GTY((for_user)) toc_hash_struct
1236{
1237  /* `key' will satisfy CONSTANT_P; in fact, it will satisfy
1238     ASM_OUTPUT_SPECIAL_POOL_ENTRY_P.  */
1239  rtx key;
1240  machine_mode key_mode;
1241  int labelno;
1242};
1243
1244struct toc_hasher : ggc_hasher<toc_hash_struct *>
1245{
1246  static hashval_t hash (toc_hash_struct *);
1247  static bool equal (toc_hash_struct *, toc_hash_struct *);
1248};
1249
1250static GTY (()) hash_table<toc_hasher> *toc_hash_table;
1251
1252/* Hash table to keep track of the argument types for builtin functions.  */
1253
1254struct GTY((for_user)) builtin_hash_struct
1255{
1256  tree type;
1257  machine_mode mode[4];	/* return value + 3 arguments.  */
1258  unsigned char uns_p[4];	/* and whether the types are unsigned.  */
1259};
1260
1261struct builtin_hasher : ggc_hasher<builtin_hash_struct *>
1262{
1263  static hashval_t hash (builtin_hash_struct *);
1264  static bool equal (builtin_hash_struct *, builtin_hash_struct *);
1265};
1266
1267static GTY (()) hash_table<builtin_hasher> *builtin_hash_table;
1268
1269
1270/* Default register names.  */
1271char rs6000_reg_names[][8] =
1272{
1273      "0",  "1",  "2",  "3",  "4",  "5",  "6",  "7",
1274      "8",  "9", "10", "11", "12", "13", "14", "15",
1275     "16", "17", "18", "19", "20", "21", "22", "23",
1276     "24", "25", "26", "27", "28", "29", "30", "31",
1277      "0",  "1",  "2",  "3",  "4",  "5",  "6",  "7",
1278      "8",  "9", "10", "11", "12", "13", "14", "15",
1279     "16", "17", "18", "19", "20", "21", "22", "23",
1280     "24", "25", "26", "27", "28", "29", "30", "31",
1281     "mq", "lr", "ctr","ap",
1282      "0",  "1",  "2",  "3",  "4",  "5",  "6",  "7",
1283      "ca",
1284      /* AltiVec registers.  */
1285      "0",  "1",  "2",  "3",  "4",  "5",  "6", "7",
1286      "8",  "9",  "10", "11", "12", "13", "14", "15",
1287      "16", "17", "18", "19", "20", "21", "22", "23",
1288      "24", "25", "26", "27", "28", "29", "30", "31",
1289      "vrsave", "vscr",
1290      /* SPE registers.  */
1291      "spe_acc", "spefscr",
1292      /* Soft frame pointer.  */
1293      "sfp",
1294      /* HTM SPR registers.  */
1295      "tfhar", "tfiar", "texasr",
1296      /* SPE High registers.  */
1297      "0",  "1",  "2",  "3",  "4",  "5",  "6",  "7",
1298      "8",  "9", "10", "11", "12", "13", "14", "15",
1299     "16", "17", "18", "19", "20", "21", "22", "23",
1300     "24", "25", "26", "27", "28", "29", "30", "31"
1301};
1302
1303#ifdef TARGET_REGNAMES
1304static const char alt_reg_names[][8] =
1305{
1306   "%r0",   "%r1",  "%r2",  "%r3",  "%r4",  "%r5",  "%r6",  "%r7",
1307   "%r8",   "%r9", "%r10", "%r11", "%r12", "%r13", "%r14", "%r15",
1308  "%r16",  "%r17", "%r18", "%r19", "%r20", "%r21", "%r22", "%r23",
1309  "%r24",  "%r25", "%r26", "%r27", "%r28", "%r29", "%r30", "%r31",
1310   "%f0",   "%f1",  "%f2",  "%f3",  "%f4",  "%f5",  "%f6",  "%f7",
1311   "%f8",   "%f9", "%f10", "%f11", "%f12", "%f13", "%f14", "%f15",
1312  "%f16",  "%f17", "%f18", "%f19", "%f20", "%f21", "%f22", "%f23",
1313  "%f24",  "%f25", "%f26", "%f27", "%f28", "%f29", "%f30", "%f31",
1314    "mq",    "lr",  "ctr",   "ap",
1315  "%cr0",  "%cr1", "%cr2", "%cr3", "%cr4", "%cr5", "%cr6", "%cr7",
1316   "ca",
1317  /* AltiVec registers.  */
1318   "%v0",  "%v1",  "%v2",  "%v3",  "%v4",  "%v5",  "%v6", "%v7",
1319   "%v8",  "%v9", "%v10", "%v11", "%v12", "%v13", "%v14", "%v15",
1320  "%v16", "%v17", "%v18", "%v19", "%v20", "%v21", "%v22", "%v23",
1321  "%v24", "%v25", "%v26", "%v27", "%v28", "%v29", "%v30", "%v31",
1322  "vrsave", "vscr",
1323  /* SPE registers.  */
1324  "spe_acc", "spefscr",
1325  /* Soft frame pointer.  */
1326  "sfp",
1327  /* HTM SPR registers.  */
1328  "tfhar", "tfiar", "texasr",
1329  /* SPE High registers.  */
1330  "%rh0",  "%rh1",  "%rh2",  "%rh3",  "%rh4",  "%rh5",  "%rh6",   "%rh7",
1331  "%rh8",  "%rh9",  "%rh10", "%r11",  "%rh12", "%rh13", "%rh14", "%rh15",
1332  "%rh16", "%rh17", "%rh18", "%rh19", "%rh20", "%rh21", "%rh22", "%rh23",
1333  "%rh24", "%rh25", "%rh26", "%rh27", "%rh28", "%rh29", "%rh30", "%rh31"
1334};
1335#endif
1336
1337/* Table of valid machine attributes.  */
1338
1339static const struct attribute_spec rs6000_attribute_table[] =
1340{
1341  /* { name, min_len, max_len, decl_req, type_req, fn_type_req, handler,
1342       affects_type_identity } */
1343  { "altivec",   1, 1, false, true,  false, rs6000_handle_altivec_attribute,
1344    false },
1345  { "longcall",  0, 0, false, true,  true,  rs6000_handle_longcall_attribute,
1346    false },
1347  { "shortcall", 0, 0, false, true,  true,  rs6000_handle_longcall_attribute,
1348    false },
1349  { "ms_struct", 0, 0, false, false, false, rs6000_handle_struct_attribute,
1350    false },
1351  { "gcc_struct", 0, 0, false, false, false, rs6000_handle_struct_attribute,
1352    false },
1353#ifdef SUBTARGET_ATTRIBUTE_TABLE
1354  SUBTARGET_ATTRIBUTE_TABLE,
1355#endif
1356  { NULL,        0, 0, false, false, false, NULL, false }
1357};
1358
1359#ifndef TARGET_PROFILE_KERNEL
1360#define TARGET_PROFILE_KERNEL 0
1361#endif
1362
1363/* The VRSAVE bitmask puts bit %v0 as the most significant bit.  */
1364#define ALTIVEC_REG_BIT(REGNO) (0x80000000 >> ((REGNO) - FIRST_ALTIVEC_REGNO))
1365
1366/* Initialize the GCC target structure.  */
1367#undef TARGET_ATTRIBUTE_TABLE
1368#define TARGET_ATTRIBUTE_TABLE rs6000_attribute_table
1369#undef TARGET_SET_DEFAULT_TYPE_ATTRIBUTES
1370#define TARGET_SET_DEFAULT_TYPE_ATTRIBUTES rs6000_set_default_type_attributes
1371#undef TARGET_ATTRIBUTE_TAKES_IDENTIFIER_P
1372#define TARGET_ATTRIBUTE_TAKES_IDENTIFIER_P rs6000_attribute_takes_identifier_p
1373
1374#undef TARGET_ASM_ALIGNED_DI_OP
1375#define TARGET_ASM_ALIGNED_DI_OP DOUBLE_INT_ASM_OP
1376
1377/* Default unaligned ops are only provided for ELF.  Find the ops needed
1378   for non-ELF systems.  */
1379#ifndef OBJECT_FORMAT_ELF
1380#if TARGET_XCOFF
1381/* For XCOFF.  rs6000_assemble_integer will handle unaligned DIs on
1382   64-bit targets.  */
1383#undef TARGET_ASM_UNALIGNED_HI_OP
1384#define TARGET_ASM_UNALIGNED_HI_OP "\t.vbyte\t2,"
1385#undef TARGET_ASM_UNALIGNED_SI_OP
1386#define TARGET_ASM_UNALIGNED_SI_OP "\t.vbyte\t4,"
1387#undef TARGET_ASM_UNALIGNED_DI_OP
1388#define TARGET_ASM_UNALIGNED_DI_OP "\t.vbyte\t8,"
1389#else
1390/* For Darwin.  */
1391#undef TARGET_ASM_UNALIGNED_HI_OP
1392#define TARGET_ASM_UNALIGNED_HI_OP "\t.short\t"
1393#undef TARGET_ASM_UNALIGNED_SI_OP
1394#define TARGET_ASM_UNALIGNED_SI_OP "\t.long\t"
1395#undef TARGET_ASM_UNALIGNED_DI_OP
1396#define TARGET_ASM_UNALIGNED_DI_OP "\t.quad\t"
1397#undef TARGET_ASM_ALIGNED_DI_OP
1398#define TARGET_ASM_ALIGNED_DI_OP "\t.quad\t"
1399#endif
1400#endif
1401
1402/* This hook deals with fixups for relocatable code and DI-mode objects
1403   in 64-bit code.  */
1404#undef TARGET_ASM_INTEGER
1405#define TARGET_ASM_INTEGER rs6000_assemble_integer
1406
1407#if defined (HAVE_GAS_HIDDEN) && !TARGET_MACHO
1408#undef TARGET_ASM_ASSEMBLE_VISIBILITY
1409#define TARGET_ASM_ASSEMBLE_VISIBILITY rs6000_assemble_visibility
1410#endif
1411
1412#undef TARGET_SET_UP_BY_PROLOGUE
1413#define TARGET_SET_UP_BY_PROLOGUE rs6000_set_up_by_prologue
1414
1415#undef TARGET_HAVE_TLS
1416#define TARGET_HAVE_TLS HAVE_AS_TLS
1417
1418#undef TARGET_CANNOT_FORCE_CONST_MEM
1419#define TARGET_CANNOT_FORCE_CONST_MEM rs6000_cannot_force_const_mem
1420
1421#undef TARGET_DELEGITIMIZE_ADDRESS
1422#define TARGET_DELEGITIMIZE_ADDRESS rs6000_delegitimize_address
1423
1424#undef TARGET_CONST_NOT_OK_FOR_DEBUG_P
1425#define TARGET_CONST_NOT_OK_FOR_DEBUG_P rs6000_const_not_ok_for_debug_p
1426
1427#undef TARGET_ASM_FUNCTION_PROLOGUE
1428#define TARGET_ASM_FUNCTION_PROLOGUE rs6000_output_function_prologue
1429#undef TARGET_ASM_FUNCTION_EPILOGUE
1430#define TARGET_ASM_FUNCTION_EPILOGUE rs6000_output_function_epilogue
1431
1432#undef TARGET_ASM_OUTPUT_ADDR_CONST_EXTRA
1433#define TARGET_ASM_OUTPUT_ADDR_CONST_EXTRA rs6000_output_addr_const_extra
1434
1435#undef TARGET_LEGITIMIZE_ADDRESS
1436#define TARGET_LEGITIMIZE_ADDRESS rs6000_legitimize_address
1437
1438#undef  TARGET_SCHED_VARIABLE_ISSUE
1439#define TARGET_SCHED_VARIABLE_ISSUE rs6000_variable_issue
1440
1441#undef TARGET_SCHED_ISSUE_RATE
1442#define TARGET_SCHED_ISSUE_RATE rs6000_issue_rate
1443#undef TARGET_SCHED_ADJUST_COST
1444#define TARGET_SCHED_ADJUST_COST rs6000_adjust_cost
1445#undef TARGET_SCHED_ADJUST_PRIORITY
1446#define TARGET_SCHED_ADJUST_PRIORITY rs6000_adjust_priority
1447#undef TARGET_SCHED_IS_COSTLY_DEPENDENCE
1448#define TARGET_SCHED_IS_COSTLY_DEPENDENCE rs6000_is_costly_dependence
1449#undef TARGET_SCHED_INIT
1450#define TARGET_SCHED_INIT rs6000_sched_init
1451#undef TARGET_SCHED_FINISH
1452#define TARGET_SCHED_FINISH rs6000_sched_finish
1453#undef TARGET_SCHED_REORDER
1454#define TARGET_SCHED_REORDER rs6000_sched_reorder
1455#undef TARGET_SCHED_REORDER2
1456#define TARGET_SCHED_REORDER2 rs6000_sched_reorder2
1457
1458#undef TARGET_SCHED_FIRST_CYCLE_MULTIPASS_DFA_LOOKAHEAD
1459#define TARGET_SCHED_FIRST_CYCLE_MULTIPASS_DFA_LOOKAHEAD rs6000_use_sched_lookahead
1460
1461#undef TARGET_SCHED_FIRST_CYCLE_MULTIPASS_DFA_LOOKAHEAD_GUARD
1462#define TARGET_SCHED_FIRST_CYCLE_MULTIPASS_DFA_LOOKAHEAD_GUARD rs6000_use_sched_lookahead_guard
1463
1464#undef TARGET_SCHED_ALLOC_SCHED_CONTEXT
1465#define TARGET_SCHED_ALLOC_SCHED_CONTEXT rs6000_alloc_sched_context
1466#undef TARGET_SCHED_INIT_SCHED_CONTEXT
1467#define TARGET_SCHED_INIT_SCHED_CONTEXT rs6000_init_sched_context
1468#undef TARGET_SCHED_SET_SCHED_CONTEXT
1469#define TARGET_SCHED_SET_SCHED_CONTEXT rs6000_set_sched_context
1470#undef TARGET_SCHED_FREE_SCHED_CONTEXT
1471#define TARGET_SCHED_FREE_SCHED_CONTEXT rs6000_free_sched_context
1472
1473#undef TARGET_VECTORIZE_BUILTIN_MASK_FOR_LOAD
1474#define TARGET_VECTORIZE_BUILTIN_MASK_FOR_LOAD rs6000_builtin_mask_for_load
1475#undef TARGET_VECTORIZE_SUPPORT_VECTOR_MISALIGNMENT
1476#define TARGET_VECTORIZE_SUPPORT_VECTOR_MISALIGNMENT		\
1477  rs6000_builtin_support_vector_misalignment
1478#undef TARGET_VECTORIZE_VECTOR_ALIGNMENT_REACHABLE
1479#define TARGET_VECTORIZE_VECTOR_ALIGNMENT_REACHABLE rs6000_vector_alignment_reachable
1480#undef TARGET_VECTORIZE_BUILTIN_VECTORIZATION_COST
1481#define TARGET_VECTORIZE_BUILTIN_VECTORIZATION_COST \
1482  rs6000_builtin_vectorization_cost
1483#undef TARGET_VECTORIZE_PREFERRED_SIMD_MODE
1484#define TARGET_VECTORIZE_PREFERRED_SIMD_MODE \
1485  rs6000_preferred_simd_mode
1486#undef TARGET_VECTORIZE_INIT_COST
1487#define TARGET_VECTORIZE_INIT_COST rs6000_init_cost
1488#undef TARGET_VECTORIZE_ADD_STMT_COST
1489#define TARGET_VECTORIZE_ADD_STMT_COST rs6000_add_stmt_cost
1490#undef TARGET_VECTORIZE_FINISH_COST
1491#define TARGET_VECTORIZE_FINISH_COST rs6000_finish_cost
1492#undef TARGET_VECTORIZE_DESTROY_COST_DATA
1493#define TARGET_VECTORIZE_DESTROY_COST_DATA rs6000_destroy_cost_data
1494
1495#undef TARGET_INIT_BUILTINS
1496#define TARGET_INIT_BUILTINS rs6000_init_builtins
1497#undef TARGET_BUILTIN_DECL
1498#define TARGET_BUILTIN_DECL rs6000_builtin_decl
1499
1500#undef TARGET_EXPAND_BUILTIN
1501#define TARGET_EXPAND_BUILTIN rs6000_expand_builtin
1502
1503#undef TARGET_MANGLE_TYPE
1504#define TARGET_MANGLE_TYPE rs6000_mangle_type
1505
1506#undef TARGET_INIT_LIBFUNCS
1507#define TARGET_INIT_LIBFUNCS rs6000_init_libfuncs
1508
1509#if TARGET_MACHO
1510#undef TARGET_BINDS_LOCAL_P
1511#define TARGET_BINDS_LOCAL_P darwin_binds_local_p
1512#endif
1513
1514#undef TARGET_MS_BITFIELD_LAYOUT_P
1515#define TARGET_MS_BITFIELD_LAYOUT_P rs6000_ms_bitfield_layout_p
1516
1517#undef TARGET_ASM_OUTPUT_MI_THUNK
1518#define TARGET_ASM_OUTPUT_MI_THUNK rs6000_output_mi_thunk
1519
1520#undef TARGET_ASM_CAN_OUTPUT_MI_THUNK
1521#define TARGET_ASM_CAN_OUTPUT_MI_THUNK hook_bool_const_tree_hwi_hwi_const_tree_true
1522
1523#undef TARGET_FUNCTION_OK_FOR_SIBCALL
1524#define TARGET_FUNCTION_OK_FOR_SIBCALL rs6000_function_ok_for_sibcall
1525
1526#undef TARGET_REGISTER_MOVE_COST
1527#define TARGET_REGISTER_MOVE_COST rs6000_register_move_cost
1528#undef TARGET_MEMORY_MOVE_COST
1529#define TARGET_MEMORY_MOVE_COST rs6000_memory_move_cost
1530#undef TARGET_RTX_COSTS
1531#define TARGET_RTX_COSTS rs6000_rtx_costs
1532#undef TARGET_ADDRESS_COST
1533#define TARGET_ADDRESS_COST hook_int_rtx_mode_as_bool_0
1534
1535#undef TARGET_DWARF_REGISTER_SPAN
1536#define TARGET_DWARF_REGISTER_SPAN rs6000_dwarf_register_span
1537
1538#undef TARGET_INIT_DWARF_REG_SIZES_EXTRA
1539#define TARGET_INIT_DWARF_REG_SIZES_EXTRA rs6000_init_dwarf_reg_sizes_extra
1540
1541#undef TARGET_MEMBER_TYPE_FORCES_BLK
1542#define TARGET_MEMBER_TYPE_FORCES_BLK rs6000_member_type_forces_blk
1543
1544#undef TARGET_PROMOTE_FUNCTION_MODE
1545#define TARGET_PROMOTE_FUNCTION_MODE rs6000_promote_function_mode
1546
1547#undef TARGET_RETURN_IN_MEMORY
1548#define TARGET_RETURN_IN_MEMORY rs6000_return_in_memory
1549
1550#undef TARGET_RETURN_IN_MSB
1551#define TARGET_RETURN_IN_MSB rs6000_return_in_msb
1552
1553#undef TARGET_SETUP_INCOMING_VARARGS
1554#define TARGET_SETUP_INCOMING_VARARGS setup_incoming_varargs
1555
1556/* Always strict argument naming on rs6000.  */
1557#undef TARGET_STRICT_ARGUMENT_NAMING
1558#define TARGET_STRICT_ARGUMENT_NAMING hook_bool_CUMULATIVE_ARGS_true
1559#undef TARGET_PRETEND_OUTGOING_VARARGS_NAMED
1560#define TARGET_PRETEND_OUTGOING_VARARGS_NAMED hook_bool_CUMULATIVE_ARGS_true
1561#undef TARGET_SPLIT_COMPLEX_ARG
1562#define TARGET_SPLIT_COMPLEX_ARG hook_bool_const_tree_true
1563#undef TARGET_MUST_PASS_IN_STACK
1564#define TARGET_MUST_PASS_IN_STACK rs6000_must_pass_in_stack
1565#undef TARGET_PASS_BY_REFERENCE
1566#define TARGET_PASS_BY_REFERENCE rs6000_pass_by_reference
1567#undef TARGET_ARG_PARTIAL_BYTES
1568#define TARGET_ARG_PARTIAL_BYTES rs6000_arg_partial_bytes
1569#undef TARGET_FUNCTION_ARG_ADVANCE
1570#define TARGET_FUNCTION_ARG_ADVANCE rs6000_function_arg_advance
1571#undef TARGET_FUNCTION_ARG
1572#define TARGET_FUNCTION_ARG rs6000_function_arg
1573#undef TARGET_FUNCTION_ARG_BOUNDARY
1574#define TARGET_FUNCTION_ARG_BOUNDARY rs6000_function_arg_boundary
1575
1576#undef TARGET_BUILD_BUILTIN_VA_LIST
1577#define TARGET_BUILD_BUILTIN_VA_LIST rs6000_build_builtin_va_list
1578
1579#undef TARGET_EXPAND_BUILTIN_VA_START
1580#define TARGET_EXPAND_BUILTIN_VA_START rs6000_va_start
1581
1582#undef TARGET_GIMPLIFY_VA_ARG_EXPR
1583#define TARGET_GIMPLIFY_VA_ARG_EXPR rs6000_gimplify_va_arg
1584
1585#undef TARGET_EH_RETURN_FILTER_MODE
1586#define TARGET_EH_RETURN_FILTER_MODE rs6000_eh_return_filter_mode
1587
1588#undef TARGET_SCALAR_MODE_SUPPORTED_P
1589#define TARGET_SCALAR_MODE_SUPPORTED_P rs6000_scalar_mode_supported_p
1590
1591#undef TARGET_VECTOR_MODE_SUPPORTED_P
1592#define TARGET_VECTOR_MODE_SUPPORTED_P rs6000_vector_mode_supported_p
1593
1594#undef TARGET_INVALID_ARG_FOR_UNPROTOTYPED_FN
1595#define TARGET_INVALID_ARG_FOR_UNPROTOTYPED_FN invalid_arg_for_unprototyped_fn
1596
1597#undef TARGET_ASM_LOOP_ALIGN_MAX_SKIP
1598#define TARGET_ASM_LOOP_ALIGN_MAX_SKIP rs6000_loop_align_max_skip
1599
1600#undef TARGET_MD_ASM_CLOBBERS
1601#define TARGET_MD_ASM_CLOBBERS rs6000_md_asm_clobbers
1602
1603#undef TARGET_OPTION_OVERRIDE
1604#define TARGET_OPTION_OVERRIDE rs6000_option_override
1605
1606#undef TARGET_VECTORIZE_BUILTIN_VECTORIZED_FUNCTION
1607#define TARGET_VECTORIZE_BUILTIN_VECTORIZED_FUNCTION \
1608  rs6000_builtin_vectorized_function
1609
1610#if !TARGET_MACHO
1611#undef TARGET_STACK_PROTECT_FAIL
1612#define TARGET_STACK_PROTECT_FAIL rs6000_stack_protect_fail
1613#endif
1614
1615/* MPC604EUM 3.5.2 Weak Consistency between Multiple Processors
1616   The PowerPC architecture requires only weak consistency among
1617   processors--that is, memory accesses between processors need not be
1618   sequentially consistent and memory accesses among processors can occur
1619   in any order. The ability to order memory accesses weakly provides
1620   opportunities for more efficient use of the system bus. Unless a
1621   dependency exists, the 604e allows read operations to precede store
1622   operations.  */
1623#undef TARGET_RELAXED_ORDERING
1624#define TARGET_RELAXED_ORDERING true
1625
1626#ifdef HAVE_AS_TLS
1627#undef TARGET_ASM_OUTPUT_DWARF_DTPREL
1628#define TARGET_ASM_OUTPUT_DWARF_DTPREL rs6000_output_dwarf_dtprel
1629#endif
1630
1631/* Use a 32-bit anchor range.  This leads to sequences like:
1632
1633	addis	tmp,anchor,high
1634	add	dest,tmp,low
1635
1636   where tmp itself acts as an anchor, and can be shared between
1637   accesses to the same 64k page.  */
1638#undef TARGET_MIN_ANCHOR_OFFSET
1639#define TARGET_MIN_ANCHOR_OFFSET -0x7fffffff - 1
1640#undef TARGET_MAX_ANCHOR_OFFSET
1641#define TARGET_MAX_ANCHOR_OFFSET 0x7fffffff
1642#undef TARGET_USE_BLOCKS_FOR_CONSTANT_P
1643#define TARGET_USE_BLOCKS_FOR_CONSTANT_P rs6000_use_blocks_for_constant_p
1644#undef TARGET_USE_BLOCKS_FOR_DECL_P
1645#define TARGET_USE_BLOCKS_FOR_DECL_P rs6000_use_blocks_for_decl_p
1646
1647#undef TARGET_BUILTIN_RECIPROCAL
1648#define TARGET_BUILTIN_RECIPROCAL rs6000_builtin_reciprocal
1649
1650#undef TARGET_EXPAND_TO_RTL_HOOK
1651#define TARGET_EXPAND_TO_RTL_HOOK rs6000_alloc_sdmode_stack_slot
1652
1653#undef TARGET_INSTANTIATE_DECLS
1654#define TARGET_INSTANTIATE_DECLS rs6000_instantiate_decls
1655
1656#undef TARGET_SECONDARY_RELOAD
1657#define TARGET_SECONDARY_RELOAD rs6000_secondary_reload
1658
1659#undef TARGET_LEGITIMATE_ADDRESS_P
1660#define TARGET_LEGITIMATE_ADDRESS_P rs6000_legitimate_address_p
1661
1662#undef TARGET_MODE_DEPENDENT_ADDRESS_P
1663#define TARGET_MODE_DEPENDENT_ADDRESS_P rs6000_mode_dependent_address_p
1664
1665#undef TARGET_LRA_P
1666#define TARGET_LRA_P rs6000_lra_p
1667
1668#undef TARGET_CAN_ELIMINATE
1669#define TARGET_CAN_ELIMINATE rs6000_can_eliminate
1670
1671#undef TARGET_CONDITIONAL_REGISTER_USAGE
1672#define TARGET_CONDITIONAL_REGISTER_USAGE rs6000_conditional_register_usage
1673
1674#undef TARGET_TRAMPOLINE_INIT
1675#define TARGET_TRAMPOLINE_INIT rs6000_trampoline_init
1676
1677#undef TARGET_FUNCTION_VALUE
1678#define TARGET_FUNCTION_VALUE rs6000_function_value
1679
1680#undef TARGET_OPTION_VALID_ATTRIBUTE_P
1681#define TARGET_OPTION_VALID_ATTRIBUTE_P rs6000_valid_attribute_p
1682
1683#undef TARGET_OPTION_SAVE
1684#define TARGET_OPTION_SAVE rs6000_function_specific_save
1685
1686#undef TARGET_OPTION_RESTORE
1687#define TARGET_OPTION_RESTORE rs6000_function_specific_restore
1688
1689#undef TARGET_OPTION_PRINT
1690#define TARGET_OPTION_PRINT rs6000_function_specific_print
1691
1692#undef TARGET_CAN_INLINE_P
1693#define TARGET_CAN_INLINE_P rs6000_can_inline_p
1694
1695#undef TARGET_SET_CURRENT_FUNCTION
1696#define TARGET_SET_CURRENT_FUNCTION rs6000_set_current_function
1697
1698#undef TARGET_LEGITIMATE_CONSTANT_P
1699#define TARGET_LEGITIMATE_CONSTANT_P rs6000_legitimate_constant_p
1700
1701#undef TARGET_VECTORIZE_VEC_PERM_CONST_OK
1702#define TARGET_VECTORIZE_VEC_PERM_CONST_OK rs6000_vectorize_vec_perm_const_ok
1703
1704#undef TARGET_CAN_USE_DOLOOP_P
1705#define TARGET_CAN_USE_DOLOOP_P can_use_doloop_if_innermost
1706
1707#undef TARGET_ATOMIC_ASSIGN_EXPAND_FENV
1708#define TARGET_ATOMIC_ASSIGN_EXPAND_FENV rs6000_atomic_assign_expand_fenv
1709
1710#undef TARGET_LIBGCC_CMP_RETURN_MODE
1711#define TARGET_LIBGCC_CMP_RETURN_MODE rs6000_abi_word_mode
1712#undef TARGET_LIBGCC_SHIFT_COUNT_MODE
1713#define TARGET_LIBGCC_SHIFT_COUNT_MODE rs6000_abi_word_mode
1714#undef TARGET_UNWIND_WORD_MODE
1715#define TARGET_UNWIND_WORD_MODE rs6000_abi_word_mode
1716
1717
1718/* Processor table.  */
1719struct rs6000_ptt
1720{
1721  const char *const name;		/* Canonical processor name.  */
1722  const enum processor_type processor;	/* Processor type enum value.  */
1723  const HOST_WIDE_INT target_enable;	/* Target flags to enable.  */
1724};
1725
1726static struct rs6000_ptt const processor_target_table[] =
1727{
1728#define RS6000_CPU(NAME, CPU, FLAGS) { NAME, CPU, FLAGS },
1729#include "rs6000-cpus.def"
1730#undef RS6000_CPU
1731};
1732
1733/* Look up a processor name for -mcpu=xxx and -mtune=xxx.  Return -1 if the
1734   name is invalid.  */
1735
1736static int
1737rs6000_cpu_name_lookup (const char *name)
1738{
1739  size_t i;
1740
1741  if (name != NULL)
1742    {
1743      for (i = 0; i < ARRAY_SIZE (processor_target_table); i++)
1744	if (! strcmp (name, processor_target_table[i].name))
1745	  return (int)i;
1746    }
1747
1748  return -1;
1749}
1750
1751
1752/* Return number of consecutive hard regs needed starting at reg REGNO
1753   to hold something of mode MODE.
1754   This is ordinarily the length in words of a value of mode MODE
1755   but can be less for certain modes in special long registers.
1756
1757   For the SPE, GPRs are 64 bits but only 32 bits are visible in
1758   scalar instructions.  The upper 32 bits are only available to the
1759   SIMD instructions.
1760
1761   POWER and PowerPC GPRs hold 32 bits worth;
1762   PowerPC64 GPRs and FPRs point register holds 64 bits worth.  */
1763
1764static int
1765rs6000_hard_regno_nregs_internal (int regno, machine_mode mode)
1766{
1767  unsigned HOST_WIDE_INT reg_size;
1768
1769  /* TF/TD modes are special in that they always take 2 registers.  */
1770  if (FP_REGNO_P (regno))
1771    reg_size = ((VECTOR_MEM_VSX_P (mode) && mode != TDmode && mode != TFmode)
1772		? UNITS_PER_VSX_WORD
1773		: UNITS_PER_FP_WORD);
1774
1775  else if (SPE_SIMD_REGNO_P (regno) && TARGET_SPE && SPE_VECTOR_MODE (mode))
1776    reg_size = UNITS_PER_SPE_WORD;
1777
1778  else if (ALTIVEC_REGNO_P (regno))
1779    reg_size = UNITS_PER_ALTIVEC_WORD;
1780
1781  /* The value returned for SCmode in the E500 double case is 2 for
1782     ABI compatibility; storing an SCmode value in a single register
1783     would require function_arg and rs6000_spe_function_arg to handle
1784     SCmode so as to pass the value correctly in a pair of
1785     registers.  */
1786  else if (TARGET_E500_DOUBLE && FLOAT_MODE_P (mode) && mode != SCmode
1787	   && !DECIMAL_FLOAT_MODE_P (mode) && SPE_SIMD_REGNO_P (regno))
1788    reg_size = UNITS_PER_FP_WORD;
1789
1790  else
1791    reg_size = UNITS_PER_WORD;
1792
1793  return (GET_MODE_SIZE (mode) + reg_size - 1) / reg_size;
1794}
1795
1796/* Value is 1 if hard register REGNO can hold a value of machine-mode
1797   MODE.  */
1798static int
1799rs6000_hard_regno_mode_ok (int regno, machine_mode mode)
1800{
1801  int last_regno = regno + rs6000_hard_regno_nregs[mode][regno] - 1;
1802
1803  /* PTImode can only go in GPRs.  Quad word memory operations require even/odd
1804     register combinations, and use PTImode where we need to deal with quad
1805     word memory operations.  Don't allow quad words in the argument or frame
1806     pointer registers, just registers 0..31.  */
1807  if (mode == PTImode)
1808    return (IN_RANGE (regno, FIRST_GPR_REGNO, LAST_GPR_REGNO)
1809	    && IN_RANGE (last_regno, FIRST_GPR_REGNO, LAST_GPR_REGNO)
1810	    && ((regno & 1) == 0));
1811
1812  /* VSX registers that overlap the FPR registers are larger than for non-VSX
1813     implementations.  Don't allow an item to be split between a FP register
1814     and an Altivec register.  Allow TImode in all VSX registers if the user
1815     asked for it.  */
1816  if (TARGET_VSX && VSX_REGNO_P (regno)
1817      && (VECTOR_MEM_VSX_P (mode)
1818	  || reg_addr[mode].scalar_in_vmx_p
1819	  || (TARGET_VSX_TIMODE && mode == TImode)
1820	  || (TARGET_VADDUQM && mode == V1TImode)))
1821    {
1822      if (FP_REGNO_P (regno))
1823	return FP_REGNO_P (last_regno);
1824
1825      if (ALTIVEC_REGNO_P (regno))
1826	{
1827	  if (GET_MODE_SIZE (mode) != 16 && !reg_addr[mode].scalar_in_vmx_p)
1828	    return 0;
1829
1830	  return ALTIVEC_REGNO_P (last_regno);
1831	}
1832    }
1833
1834  /* The GPRs can hold any mode, but values bigger than one register
1835     cannot go past R31.  */
1836  if (INT_REGNO_P (regno))
1837    return INT_REGNO_P (last_regno);
1838
1839  /* The float registers (except for VSX vector modes) can only hold floating
1840     modes and DImode.  */
1841  if (FP_REGNO_P (regno))
1842    {
1843      if (SCALAR_FLOAT_MODE_P (mode)
1844	  && (mode != TDmode || (regno % 2) == 0)
1845	  && FP_REGNO_P (last_regno))
1846	return 1;
1847
1848      if (GET_MODE_CLASS (mode) == MODE_INT
1849	  && GET_MODE_SIZE (mode) == UNITS_PER_FP_WORD)
1850	return 1;
1851
1852      if (PAIRED_SIMD_REGNO_P (regno) && TARGET_PAIRED_FLOAT
1853	  && PAIRED_VECTOR_MODE (mode))
1854	return 1;
1855
1856      return 0;
1857    }
1858
1859  /* The CR register can only hold CC modes.  */
1860  if (CR_REGNO_P (regno))
1861    return GET_MODE_CLASS (mode) == MODE_CC;
1862
1863  if (CA_REGNO_P (regno))
1864    return mode == Pmode || mode == SImode;
1865
1866  /* AltiVec only in AldyVec registers.  */
1867  if (ALTIVEC_REGNO_P (regno))
1868    return (VECTOR_MEM_ALTIVEC_OR_VSX_P (mode)
1869	    || mode == V1TImode);
1870
1871  /* ...but GPRs can hold SIMD data on the SPE in one register.  */
1872  if (SPE_SIMD_REGNO_P (regno) && TARGET_SPE && SPE_VECTOR_MODE (mode))
1873    return 1;
1874
1875  /* We cannot put non-VSX TImode or PTImode anywhere except general register
1876     and it must be able to fit within the register set.  */
1877
1878  return GET_MODE_SIZE (mode) <= UNITS_PER_WORD;
1879}
1880
1881/* Print interesting facts about registers.  */
1882static void
1883rs6000_debug_reg_print (int first_regno, int last_regno, const char *reg_name)
1884{
1885  int r, m;
1886
1887  for (r = first_regno; r <= last_regno; ++r)
1888    {
1889      const char *comma = "";
1890      int len;
1891
1892      if (first_regno == last_regno)
1893	fprintf (stderr, "%s:\t", reg_name);
1894      else
1895	fprintf (stderr, "%s%d:\t", reg_name, r - first_regno);
1896
1897      len = 8;
1898      for (m = 0; m < NUM_MACHINE_MODES; ++m)
1899	if (rs6000_hard_regno_mode_ok_p[m][r] && rs6000_hard_regno_nregs[m][r])
1900	  {
1901	    if (len > 70)
1902	      {
1903		fprintf (stderr, ",\n\t");
1904		len = 8;
1905		comma = "";
1906	      }
1907
1908	    if (rs6000_hard_regno_nregs[m][r] > 1)
1909	      len += fprintf (stderr, "%s%s/%d", comma, GET_MODE_NAME (m),
1910			     rs6000_hard_regno_nregs[m][r]);
1911	    else
1912	      len += fprintf (stderr, "%s%s", comma, GET_MODE_NAME (m));
1913
1914	    comma = ", ";
1915	  }
1916
1917      if (call_used_regs[r])
1918	{
1919	  if (len > 70)
1920	    {
1921	      fprintf (stderr, ",\n\t");
1922	      len = 8;
1923	      comma = "";
1924	    }
1925
1926	  len += fprintf (stderr, "%s%s", comma, "call-used");
1927	  comma = ", ";
1928	}
1929
1930      if (fixed_regs[r])
1931	{
1932	  if (len > 70)
1933	    {
1934	      fprintf (stderr, ",\n\t");
1935	      len = 8;
1936	      comma = "";
1937	    }
1938
1939	  len += fprintf (stderr, "%s%s", comma, "fixed");
1940	  comma = ", ";
1941	}
1942
1943      if (len > 70)
1944	{
1945	  fprintf (stderr, ",\n\t");
1946	  comma = "";
1947	}
1948
1949      len += fprintf (stderr, "%sreg-class = %s", comma,
1950		      reg_class_names[(int)rs6000_regno_regclass[r]]);
1951      comma = ", ";
1952
1953      if (len > 70)
1954	{
1955	  fprintf (stderr, ",\n\t");
1956	  comma = "";
1957	}
1958
1959      fprintf (stderr, "%sregno = %d\n", comma, r);
1960    }
1961}
1962
1963static const char *
1964rs6000_debug_vector_unit (enum rs6000_vector v)
1965{
1966  const char *ret;
1967
1968  switch (v)
1969    {
1970    case VECTOR_NONE:	   ret = "none";      break;
1971    case VECTOR_ALTIVEC:   ret = "altivec";   break;
1972    case VECTOR_VSX:	   ret = "vsx";       break;
1973    case VECTOR_P8_VECTOR: ret = "p8_vector"; break;
1974    case VECTOR_PAIRED:	   ret = "paired";    break;
1975    case VECTOR_SPE:	   ret = "spe";       break;
1976    case VECTOR_OTHER:	   ret = "other";     break;
1977    default:		   ret = "unknown";   break;
1978    }
1979
1980  return ret;
1981}
1982
1983/* Inner function printing just the address mask for a particular reload
1984   register class.  */
1985DEBUG_FUNCTION char *
1986rs6000_debug_addr_mask (addr_mask_type mask, bool keep_spaces)
1987{
1988  static char ret[8];
1989  char *p = ret;
1990
1991  if ((mask & RELOAD_REG_VALID) != 0)
1992    *p++ = 'v';
1993  else if (keep_spaces)
1994    *p++ = ' ';
1995
1996  if ((mask & RELOAD_REG_MULTIPLE) != 0)
1997    *p++ = 'm';
1998  else if (keep_spaces)
1999    *p++ = ' ';
2000
2001  if ((mask & RELOAD_REG_INDEXED) != 0)
2002    *p++ = 'i';
2003  else if (keep_spaces)
2004    *p++ = ' ';
2005
2006  if ((mask & RELOAD_REG_OFFSET) != 0)
2007    *p++ = 'o';
2008  else if (keep_spaces)
2009    *p++ = ' ';
2010
2011  if ((mask & RELOAD_REG_PRE_INCDEC) != 0)
2012    *p++ = '+';
2013  else if (keep_spaces)
2014    *p++ = ' ';
2015
2016  if ((mask & RELOAD_REG_PRE_MODIFY) != 0)
2017    *p++ = '+';
2018  else if (keep_spaces)
2019    *p++ = ' ';
2020
2021  if ((mask & RELOAD_REG_AND_M16) != 0)
2022    *p++ = '&';
2023  else if (keep_spaces)
2024    *p++ = ' ';
2025
2026  *p = '\0';
2027
2028  return ret;
2029}
2030
2031/* Print the address masks in a human readble fashion.  */
2032DEBUG_FUNCTION void
2033rs6000_debug_print_mode (ssize_t m)
2034{
2035  ssize_t rc;
2036
2037  fprintf (stderr, "Mode: %-5s", GET_MODE_NAME (m));
2038  for (rc = 0; rc < N_RELOAD_REG; rc++)
2039    fprintf (stderr, " %s: %s", reload_reg_map[rc].name,
2040	     rs6000_debug_addr_mask (reg_addr[m].addr_mask[rc], true));
2041
2042  if (rs6000_vector_unit[m] != VECTOR_NONE
2043      || rs6000_vector_mem[m] != VECTOR_NONE
2044      || (reg_addr[m].reload_store != CODE_FOR_nothing)
2045      || (reg_addr[m].reload_load != CODE_FOR_nothing)
2046      || reg_addr[m].scalar_in_vmx_p)
2047    {
2048      fprintf (stderr,
2049	       "  Vector-arith=%-10s Vector-mem=%-10s Reload=%c%c Upper=%c",
2050	       rs6000_debug_vector_unit (rs6000_vector_unit[m]),
2051	       rs6000_debug_vector_unit (rs6000_vector_mem[m]),
2052	       (reg_addr[m].reload_store != CODE_FOR_nothing) ? 's' : '*',
2053	       (reg_addr[m].reload_load != CODE_FOR_nothing) ? 'l' : '*',
2054	       (reg_addr[m].scalar_in_vmx_p) ? 'y' : 'n');
2055    }
2056
2057  fputs ("\n", stderr);
2058}
2059
2060#define DEBUG_FMT_ID "%-32s= "
2061#define DEBUG_FMT_D   DEBUG_FMT_ID "%d\n"
2062#define DEBUG_FMT_WX  DEBUG_FMT_ID "%#.12" HOST_WIDE_INT_PRINT "x: "
2063#define DEBUG_FMT_S   DEBUG_FMT_ID "%s\n"
2064
2065/* Print various interesting information with -mdebug=reg.  */
2066static void
2067rs6000_debug_reg_global (void)
2068{
2069  static const char *const tf[2] = { "false", "true" };
2070  const char *nl = (const char *)0;
2071  int m;
2072  size_t m1, m2, v;
2073  char costly_num[20];
2074  char nop_num[20];
2075  char flags_buffer[40];
2076  const char *costly_str;
2077  const char *nop_str;
2078  const char *trace_str;
2079  const char *abi_str;
2080  const char *cmodel_str;
2081  struct cl_target_option cl_opts;
2082
2083  /* Modes we want tieable information on.  */
2084  static const machine_mode print_tieable_modes[] = {
2085    QImode,
2086    HImode,
2087    SImode,
2088    DImode,
2089    TImode,
2090    PTImode,
2091    SFmode,
2092    DFmode,
2093    TFmode,
2094    SDmode,
2095    DDmode,
2096    TDmode,
2097    V8QImode,
2098    V4HImode,
2099    V2SImode,
2100    V16QImode,
2101    V8HImode,
2102    V4SImode,
2103    V2DImode,
2104    V1TImode,
2105    V32QImode,
2106    V16HImode,
2107    V8SImode,
2108    V4DImode,
2109    V2TImode,
2110    V2SFmode,
2111    V4SFmode,
2112    V2DFmode,
2113    V8SFmode,
2114    V4DFmode,
2115    CCmode,
2116    CCUNSmode,
2117    CCEQmode,
2118  };
2119
2120  /* Virtual regs we are interested in.  */
2121  const static struct {
2122    int regno;			/* register number.  */
2123    const char *name;		/* register name.  */
2124  } virtual_regs[] = {
2125    { STACK_POINTER_REGNUM,			"stack pointer:" },
2126    { TOC_REGNUM,				"toc:          " },
2127    { STATIC_CHAIN_REGNUM,			"static chain: " },
2128    { RS6000_PIC_OFFSET_TABLE_REGNUM,		"pic offset:   " },
2129    { HARD_FRAME_POINTER_REGNUM,		"hard frame:   " },
2130    { ARG_POINTER_REGNUM,			"arg pointer:  " },
2131    { FRAME_POINTER_REGNUM,			"frame pointer:" },
2132    { FIRST_PSEUDO_REGISTER,			"first pseudo: " },
2133    { FIRST_VIRTUAL_REGISTER,			"first virtual:" },
2134    { VIRTUAL_INCOMING_ARGS_REGNUM,		"incoming_args:" },
2135    { VIRTUAL_STACK_VARS_REGNUM,		"stack_vars:   " },
2136    { VIRTUAL_STACK_DYNAMIC_REGNUM,		"stack_dynamic:" },
2137    { VIRTUAL_OUTGOING_ARGS_REGNUM,		"outgoing_args:" },
2138    { VIRTUAL_CFA_REGNUM,			"cfa (frame):  " },
2139    { VIRTUAL_PREFERRED_STACK_BOUNDARY_REGNUM,	"stack boundry:" },
2140    { LAST_VIRTUAL_REGISTER,			"last virtual: " },
2141  };
2142
2143  fputs ("\nHard register information:\n", stderr);
2144  rs6000_debug_reg_print (FIRST_GPR_REGNO, LAST_GPR_REGNO, "gr");
2145  rs6000_debug_reg_print (FIRST_FPR_REGNO, LAST_FPR_REGNO, "fp");
2146  rs6000_debug_reg_print (FIRST_ALTIVEC_REGNO,
2147			  LAST_ALTIVEC_REGNO,
2148			  "vs");
2149  rs6000_debug_reg_print (LR_REGNO, LR_REGNO, "lr");
2150  rs6000_debug_reg_print (CTR_REGNO, CTR_REGNO, "ctr");
2151  rs6000_debug_reg_print (CR0_REGNO, CR7_REGNO, "cr");
2152  rs6000_debug_reg_print (CA_REGNO, CA_REGNO, "ca");
2153  rs6000_debug_reg_print (VRSAVE_REGNO, VRSAVE_REGNO, "vrsave");
2154  rs6000_debug_reg_print (VSCR_REGNO, VSCR_REGNO, "vscr");
2155  rs6000_debug_reg_print (SPE_ACC_REGNO, SPE_ACC_REGNO, "spe_a");
2156  rs6000_debug_reg_print (SPEFSCR_REGNO, SPEFSCR_REGNO, "spe_f");
2157
2158  fputs ("\nVirtual/stack/frame registers:\n", stderr);
2159  for (v = 0; v < ARRAY_SIZE (virtual_regs); v++)
2160    fprintf (stderr, "%s regno = %3d\n", virtual_regs[v].name, virtual_regs[v].regno);
2161
2162  fprintf (stderr,
2163	   "\n"
2164	   "d  reg_class = %s\n"
2165	   "f  reg_class = %s\n"
2166	   "v  reg_class = %s\n"
2167	   "wa reg_class = %s\n"
2168	   "wd reg_class = %s\n"
2169	   "wf reg_class = %s\n"
2170	   "wg reg_class = %s\n"
2171	   "wh reg_class = %s\n"
2172	   "wi reg_class = %s\n"
2173	   "wj reg_class = %s\n"
2174	   "wk reg_class = %s\n"
2175	   "wl reg_class = %s\n"
2176	   "wm reg_class = %s\n"
2177	   "wr reg_class = %s\n"
2178	   "ws reg_class = %s\n"
2179	   "wt reg_class = %s\n"
2180	   "wu reg_class = %s\n"
2181	   "wv reg_class = %s\n"
2182	   "ww reg_class = %s\n"
2183	   "wx reg_class = %s\n"
2184	   "wy reg_class = %s\n"
2185	   "wz reg_class = %s\n"
2186	   "\n",
2187	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_d]],
2188	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_f]],
2189	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_v]],
2190	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wa]],
2191	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wd]],
2192	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wf]],
2193	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wg]],
2194	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wh]],
2195	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wi]],
2196	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wj]],
2197	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wk]],
2198	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wl]],
2199	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wm]],
2200	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wr]],
2201	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_ws]],
2202	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wt]],
2203	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wu]],
2204	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wv]],
2205	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_ww]],
2206	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wx]],
2207	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wy]],
2208	   reg_class_names[rs6000_constraints[RS6000_CONSTRAINT_wz]]);
2209
2210  nl = "\n";
2211  for (m = 0; m < NUM_MACHINE_MODES; ++m)
2212    rs6000_debug_print_mode (m);
2213
2214  fputs ("\n", stderr);
2215
2216  for (m1 = 0; m1 < ARRAY_SIZE (print_tieable_modes); m1++)
2217    {
2218      machine_mode mode1 = print_tieable_modes[m1];
2219      bool first_time = true;
2220
2221      nl = (const char *)0;
2222      for (m2 = 0; m2 < ARRAY_SIZE (print_tieable_modes); m2++)
2223	{
2224	  machine_mode mode2 = print_tieable_modes[m2];
2225	  if (mode1 != mode2 && MODES_TIEABLE_P (mode1, mode2))
2226	    {
2227	      if (first_time)
2228		{
2229		  fprintf (stderr, "Tieable modes %s:", GET_MODE_NAME (mode1));
2230		  nl = "\n";
2231		  first_time = false;
2232		}
2233
2234	      fprintf (stderr, " %s", GET_MODE_NAME (mode2));
2235	    }
2236	}
2237
2238      if (!first_time)
2239	fputs ("\n", stderr);
2240    }
2241
2242  if (nl)
2243    fputs (nl, stderr);
2244
2245  if (rs6000_recip_control)
2246    {
2247      fprintf (stderr, "\nReciprocal mask = 0x%x\n", rs6000_recip_control);
2248
2249      for (m = 0; m < NUM_MACHINE_MODES; ++m)
2250	if (rs6000_recip_bits[m])
2251	  {
2252	    fprintf (stderr,
2253		     "Reciprocal estimate mode: %-5s divide: %s rsqrt: %s\n",
2254		     GET_MODE_NAME (m),
2255		     (RS6000_RECIP_AUTO_RE_P (m)
2256		      ? "auto"
2257		      : (RS6000_RECIP_HAVE_RE_P (m) ? "have" : "none")),
2258		     (RS6000_RECIP_AUTO_RSQRTE_P (m)
2259		      ? "auto"
2260		      : (RS6000_RECIP_HAVE_RSQRTE_P (m) ? "have" : "none")));
2261	  }
2262
2263      fputs ("\n", stderr);
2264    }
2265
2266  if (rs6000_cpu_index >= 0)
2267    {
2268      const char *name = processor_target_table[rs6000_cpu_index].name;
2269      HOST_WIDE_INT flags
2270	= processor_target_table[rs6000_cpu_index].target_enable;
2271
2272      sprintf (flags_buffer, "-mcpu=%s flags", name);
2273      rs6000_print_isa_options (stderr, 0, flags_buffer, flags);
2274    }
2275  else
2276    fprintf (stderr, DEBUG_FMT_S, "cpu", "<none>");
2277
2278  if (rs6000_tune_index >= 0)
2279    {
2280      const char *name = processor_target_table[rs6000_tune_index].name;
2281      HOST_WIDE_INT flags
2282	= processor_target_table[rs6000_tune_index].target_enable;
2283
2284      sprintf (flags_buffer, "-mtune=%s flags", name);
2285      rs6000_print_isa_options (stderr, 0, flags_buffer, flags);
2286    }
2287  else
2288    fprintf (stderr, DEBUG_FMT_S, "tune", "<none>");
2289
2290  cl_target_option_save (&cl_opts, &global_options);
2291  rs6000_print_isa_options (stderr, 0, "rs6000_isa_flags",
2292			    rs6000_isa_flags);
2293
2294  rs6000_print_isa_options (stderr, 0, "rs6000_isa_flags_explicit",
2295			    rs6000_isa_flags_explicit);
2296
2297  rs6000_print_builtin_options (stderr, 0, "rs6000_builtin_mask",
2298				rs6000_builtin_mask);
2299
2300  rs6000_print_isa_options (stderr, 0, "TARGET_DEFAULT", TARGET_DEFAULT);
2301
2302  fprintf (stderr, DEBUG_FMT_S, "--with-cpu default",
2303	   OPTION_TARGET_CPU_DEFAULT ? OPTION_TARGET_CPU_DEFAULT : "<none>");
2304
2305  switch (rs6000_sched_costly_dep)
2306    {
2307    case max_dep_latency:
2308      costly_str = "max_dep_latency";
2309      break;
2310
2311    case no_dep_costly:
2312      costly_str = "no_dep_costly";
2313      break;
2314
2315    case all_deps_costly:
2316      costly_str = "all_deps_costly";
2317      break;
2318
2319    case true_store_to_load_dep_costly:
2320      costly_str = "true_store_to_load_dep_costly";
2321      break;
2322
2323    case store_to_load_dep_costly:
2324      costly_str = "store_to_load_dep_costly";
2325      break;
2326
2327    default:
2328      costly_str = costly_num;
2329      sprintf (costly_num, "%d", (int)rs6000_sched_costly_dep);
2330      break;
2331    }
2332
2333  fprintf (stderr, DEBUG_FMT_S, "sched_costly_dep", costly_str);
2334
2335  switch (rs6000_sched_insert_nops)
2336    {
2337    case sched_finish_regroup_exact:
2338      nop_str = "sched_finish_regroup_exact";
2339      break;
2340
2341    case sched_finish_pad_groups:
2342      nop_str = "sched_finish_pad_groups";
2343      break;
2344
2345    case sched_finish_none:
2346      nop_str = "sched_finish_none";
2347      break;
2348
2349    default:
2350      nop_str = nop_num;
2351      sprintf (nop_num, "%d", (int)rs6000_sched_insert_nops);
2352      break;
2353    }
2354
2355  fprintf (stderr, DEBUG_FMT_S, "sched_insert_nops", nop_str);
2356
2357  switch (rs6000_sdata)
2358    {
2359    default:
2360    case SDATA_NONE:
2361      break;
2362
2363    case SDATA_DATA:
2364      fprintf (stderr, DEBUG_FMT_S, "sdata", "data");
2365      break;
2366
2367    case SDATA_SYSV:
2368      fprintf (stderr, DEBUG_FMT_S, "sdata", "sysv");
2369      break;
2370
2371    case SDATA_EABI:
2372      fprintf (stderr, DEBUG_FMT_S, "sdata", "eabi");
2373      break;
2374
2375    }
2376
2377  switch (rs6000_traceback)
2378    {
2379    case traceback_default:	trace_str = "default";	break;
2380    case traceback_none:	trace_str = "none";	break;
2381    case traceback_part:	trace_str = "part";	break;
2382    case traceback_full:	trace_str = "full";	break;
2383    default:			trace_str = "unknown";	break;
2384    }
2385
2386  fprintf (stderr, DEBUG_FMT_S, "traceback", trace_str);
2387
2388  switch (rs6000_current_cmodel)
2389    {
2390    case CMODEL_SMALL:	cmodel_str = "small";	break;
2391    case CMODEL_MEDIUM:	cmodel_str = "medium";	break;
2392    case CMODEL_LARGE:	cmodel_str = "large";	break;
2393    default:		cmodel_str = "unknown";	break;
2394    }
2395
2396  fprintf (stderr, DEBUG_FMT_S, "cmodel", cmodel_str);
2397
2398  switch (rs6000_current_abi)
2399    {
2400    case ABI_NONE:	abi_str = "none";	break;
2401    case ABI_AIX:	abi_str = "aix";	break;
2402    case ABI_ELFv2:	abi_str = "ELFv2";	break;
2403    case ABI_V4:	abi_str = "V4";		break;
2404    case ABI_DARWIN:	abi_str = "darwin";	break;
2405    default:		abi_str = "unknown";	break;
2406    }
2407
2408  fprintf (stderr, DEBUG_FMT_S, "abi", abi_str);
2409
2410  if (rs6000_altivec_abi)
2411    fprintf (stderr, DEBUG_FMT_S, "altivec_abi", "true");
2412
2413  if (rs6000_spe_abi)
2414    fprintf (stderr, DEBUG_FMT_S, "spe_abi", "true");
2415
2416  if (rs6000_darwin64_abi)
2417    fprintf (stderr, DEBUG_FMT_S, "darwin64_abi", "true");
2418
2419  if (rs6000_float_gprs)
2420    fprintf (stderr, DEBUG_FMT_S, "float_gprs", "true");
2421
2422  fprintf (stderr, DEBUG_FMT_S, "fprs",
2423	   (TARGET_FPRS ? "true" : "false"));
2424
2425  fprintf (stderr, DEBUG_FMT_S, "single_float",
2426	   (TARGET_SINGLE_FLOAT ? "true" : "false"));
2427
2428  fprintf (stderr, DEBUG_FMT_S, "double_float",
2429	   (TARGET_DOUBLE_FLOAT ? "true" : "false"));
2430
2431  fprintf (stderr, DEBUG_FMT_S, "soft_float",
2432	   (TARGET_SOFT_FLOAT ? "true" : "false"));
2433
2434  fprintf (stderr, DEBUG_FMT_S, "e500_single",
2435	   (TARGET_E500_SINGLE ? "true" : "false"));
2436
2437  fprintf (stderr, DEBUG_FMT_S, "e500_double",
2438	   (TARGET_E500_DOUBLE ? "true" : "false"));
2439
2440  if (TARGET_LINK_STACK)
2441    fprintf (stderr, DEBUG_FMT_S, "link_stack", "true");
2442
2443  if (targetm.lra_p ())
2444    fprintf (stderr, DEBUG_FMT_S, "lra", "true");
2445
2446  if (TARGET_P8_FUSION)
2447    fprintf (stderr, DEBUG_FMT_S, "p8 fusion",
2448	     (TARGET_P8_FUSION_SIGN) ? "zero+sign" : "zero");
2449
2450  fprintf (stderr, DEBUG_FMT_S, "plt-format",
2451	   TARGET_SECURE_PLT ? "secure" : "bss");
2452  fprintf (stderr, DEBUG_FMT_S, "struct-return",
2453	   aix_struct_return ? "aix" : "sysv");
2454  fprintf (stderr, DEBUG_FMT_S, "always_hint", tf[!!rs6000_always_hint]);
2455  fprintf (stderr, DEBUG_FMT_S, "sched_groups", tf[!!rs6000_sched_groups]);
2456  fprintf (stderr, DEBUG_FMT_S, "align_branch",
2457	   tf[!!rs6000_align_branch_targets]);
2458  fprintf (stderr, DEBUG_FMT_D, "tls_size", rs6000_tls_size);
2459  fprintf (stderr, DEBUG_FMT_D, "long_double_size",
2460	   rs6000_long_double_type_size);
2461  fprintf (stderr, DEBUG_FMT_D, "sched_restricted_insns_priority",
2462	   (int)rs6000_sched_restricted_insns_priority);
2463  fprintf (stderr, DEBUG_FMT_D, "Number of standard builtins",
2464	   (int)END_BUILTINS);
2465  fprintf (stderr, DEBUG_FMT_D, "Number of rs6000 builtins",
2466	   (int)RS6000_BUILTIN_COUNT);
2467
2468  if (TARGET_VSX)
2469    fprintf (stderr, DEBUG_FMT_D, "VSX easy 64-bit scalar element",
2470	     (int)VECTOR_ELEMENT_SCALAR_64BIT);
2471}
2472
2473
2474/* Update the addr mask bits in reg_addr to help secondary reload and go if
2475   legitimate address support to figure out the appropriate addressing to
2476   use.  */
2477
2478static void
2479rs6000_setup_reg_addr_masks (void)
2480{
2481  ssize_t rc, reg, m, nregs;
2482  addr_mask_type any_addr_mask, addr_mask;
2483
2484  for (m = 0; m < NUM_MACHINE_MODES; ++m)
2485    {
2486      machine_mode m2 = (machine_mode)m;
2487
2488      /* SDmode is special in that we want to access it only via REG+REG
2489	 addressing on power7 and above, since we want to use the LFIWZX and
2490	 STFIWZX instructions to load it.  */
2491      bool indexed_only_p = (m == SDmode && TARGET_NO_SDMODE_STACK);
2492
2493      any_addr_mask = 0;
2494      for (rc = FIRST_RELOAD_REG_CLASS; rc <= LAST_RELOAD_REG_CLASS; rc++)
2495	{
2496	  addr_mask = 0;
2497	  reg = reload_reg_map[rc].reg;
2498
2499	  /* Can mode values go in the GPR/FPR/Altivec registers?  */
2500	  if (reg >= 0 && rs6000_hard_regno_mode_ok_p[m][reg])
2501	    {
2502	      nregs = rs6000_hard_regno_nregs[m][reg];
2503	      addr_mask |= RELOAD_REG_VALID;
2504
2505	      /* Indicate if the mode takes more than 1 physical register.  If
2506		 it takes a single register, indicate it can do REG+REG
2507		 addressing.  */
2508	      if (nregs > 1 || m == BLKmode)
2509		addr_mask |= RELOAD_REG_MULTIPLE;
2510	      else
2511		addr_mask |= RELOAD_REG_INDEXED;
2512
2513	      /* Figure out if we can do PRE_INC, PRE_DEC, or PRE_MODIFY
2514		 addressing.  Restrict addressing on SPE for 64-bit types
2515		 because of the SUBREG hackery used to address 64-bit floats in
2516		 '32-bit' GPRs.  */
2517
2518	      if (TARGET_UPDATE
2519		  && (rc == RELOAD_REG_GPR || rc == RELOAD_REG_FPR)
2520		  && GET_MODE_SIZE (m2) <= 8
2521		  && !VECTOR_MODE_P (m2)
2522		  && !COMPLEX_MODE_P (m2)
2523		  && !indexed_only_p
2524		  && !(TARGET_E500_DOUBLE && GET_MODE_SIZE (m2) == 8))
2525		{
2526		  addr_mask |= RELOAD_REG_PRE_INCDEC;
2527
2528		  /* PRE_MODIFY is more restricted than PRE_INC/PRE_DEC in that
2529		     we don't allow PRE_MODIFY for some multi-register
2530		     operations.  */
2531		  switch (m)
2532		    {
2533		    default:
2534		      addr_mask |= RELOAD_REG_PRE_MODIFY;
2535		      break;
2536
2537		    case DImode:
2538		      if (TARGET_POWERPC64)
2539			addr_mask |= RELOAD_REG_PRE_MODIFY;
2540		      break;
2541
2542		    case DFmode:
2543		    case DDmode:
2544		      if (TARGET_DF_INSN)
2545			addr_mask |= RELOAD_REG_PRE_MODIFY;
2546		      break;
2547		    }
2548		}
2549	    }
2550
2551	  /* GPR and FPR registers can do REG+OFFSET addressing, except
2552	     possibly for SDmode.  */
2553	  if ((addr_mask != 0) && !indexed_only_p
2554	      && (rc == RELOAD_REG_GPR || rc == RELOAD_REG_FPR))
2555	    addr_mask |= RELOAD_REG_OFFSET;
2556
2557	  /* VMX registers can do (REG & -16) and ((REG+REG) & -16)
2558	     addressing on 128-bit types.  */
2559	  if (rc == RELOAD_REG_VMX && GET_MODE_SIZE (m2) == 16
2560	      && (addr_mask & RELOAD_REG_VALID) != 0)
2561	    addr_mask |= RELOAD_REG_AND_M16;
2562
2563	  reg_addr[m].addr_mask[rc] = addr_mask;
2564	  any_addr_mask |= addr_mask;
2565	}
2566
2567      reg_addr[m].addr_mask[RELOAD_REG_ANY] = any_addr_mask;
2568    }
2569}
2570
2571
2572/* Initialize the various global tables that are based on register size.  */
2573static void
2574rs6000_init_hard_regno_mode_ok (bool global_init_p)
2575{
2576  ssize_t r, m, c;
2577  int align64;
2578  int align32;
2579
2580  /* Precalculate REGNO_REG_CLASS.  */
2581  rs6000_regno_regclass[0] = GENERAL_REGS;
2582  for (r = 1; r < 32; ++r)
2583    rs6000_regno_regclass[r] = BASE_REGS;
2584
2585  for (r = 32; r < 64; ++r)
2586    rs6000_regno_regclass[r] = FLOAT_REGS;
2587
2588  for (r = 64; r < FIRST_PSEUDO_REGISTER; ++r)
2589    rs6000_regno_regclass[r] = NO_REGS;
2590
2591  for (r = FIRST_ALTIVEC_REGNO; r <= LAST_ALTIVEC_REGNO; ++r)
2592    rs6000_regno_regclass[r] = ALTIVEC_REGS;
2593
2594  rs6000_regno_regclass[CR0_REGNO] = CR0_REGS;
2595  for (r = CR1_REGNO; r <= CR7_REGNO; ++r)
2596    rs6000_regno_regclass[r] = CR_REGS;
2597
2598  rs6000_regno_regclass[LR_REGNO] = LINK_REGS;
2599  rs6000_regno_regclass[CTR_REGNO] = CTR_REGS;
2600  rs6000_regno_regclass[CA_REGNO] = NO_REGS;
2601  rs6000_regno_regclass[VRSAVE_REGNO] = VRSAVE_REGS;
2602  rs6000_regno_regclass[VSCR_REGNO] = VRSAVE_REGS;
2603  rs6000_regno_regclass[SPE_ACC_REGNO] = SPE_ACC_REGS;
2604  rs6000_regno_regclass[SPEFSCR_REGNO] = SPEFSCR_REGS;
2605  rs6000_regno_regclass[TFHAR_REGNO] = SPR_REGS;
2606  rs6000_regno_regclass[TFIAR_REGNO] = SPR_REGS;
2607  rs6000_regno_regclass[TEXASR_REGNO] = SPR_REGS;
2608  rs6000_regno_regclass[ARG_POINTER_REGNUM] = BASE_REGS;
2609  rs6000_regno_regclass[FRAME_POINTER_REGNUM] = BASE_REGS;
2610
2611  /* Precalculate register class to simpler reload register class.  We don't
2612     need all of the register classes that are combinations of different
2613     classes, just the simple ones that have constraint letters.  */
2614  for (c = 0; c < N_REG_CLASSES; c++)
2615    reg_class_to_reg_type[c] = NO_REG_TYPE;
2616
2617  reg_class_to_reg_type[(int)GENERAL_REGS] = GPR_REG_TYPE;
2618  reg_class_to_reg_type[(int)BASE_REGS] = GPR_REG_TYPE;
2619  reg_class_to_reg_type[(int)VSX_REGS] = VSX_REG_TYPE;
2620  reg_class_to_reg_type[(int)VRSAVE_REGS] = SPR_REG_TYPE;
2621  reg_class_to_reg_type[(int)VSCR_REGS] = SPR_REG_TYPE;
2622  reg_class_to_reg_type[(int)LINK_REGS] = SPR_REG_TYPE;
2623  reg_class_to_reg_type[(int)CTR_REGS] = SPR_REG_TYPE;
2624  reg_class_to_reg_type[(int)LINK_OR_CTR_REGS] = SPR_REG_TYPE;
2625  reg_class_to_reg_type[(int)CR_REGS] = CR_REG_TYPE;
2626  reg_class_to_reg_type[(int)CR0_REGS] = CR_REG_TYPE;
2627  reg_class_to_reg_type[(int)SPE_ACC_REGS] = SPE_ACC_TYPE;
2628  reg_class_to_reg_type[(int)SPEFSCR_REGS] = SPEFSCR_REG_TYPE;
2629
2630  if (TARGET_VSX)
2631    {
2632      reg_class_to_reg_type[(int)FLOAT_REGS] = VSX_REG_TYPE;
2633      reg_class_to_reg_type[(int)ALTIVEC_REGS] = VSX_REG_TYPE;
2634    }
2635  else
2636    {
2637      reg_class_to_reg_type[(int)FLOAT_REGS] = FPR_REG_TYPE;
2638      reg_class_to_reg_type[(int)ALTIVEC_REGS] = ALTIVEC_REG_TYPE;
2639    }
2640
2641  /* Precalculate the valid memory formats as well as the vector information,
2642     this must be set up before the rs6000_hard_regno_nregs_internal calls
2643     below.  */
2644  gcc_assert ((int)VECTOR_NONE == 0);
2645  memset ((void *) &rs6000_vector_unit[0], '\0', sizeof (rs6000_vector_unit));
2646  memset ((void *) &rs6000_vector_mem[0], '\0', sizeof (rs6000_vector_unit));
2647
2648  gcc_assert ((int)CODE_FOR_nothing == 0);
2649  memset ((void *) &reg_addr[0], '\0', sizeof (reg_addr));
2650
2651  gcc_assert ((int)NO_REGS == 0);
2652  memset ((void *) &rs6000_constraints[0], '\0', sizeof (rs6000_constraints));
2653
2654  /* The VSX hardware allows native alignment for vectors, but control whether the compiler
2655     believes it can use native alignment or still uses 128-bit alignment.  */
2656  if (TARGET_VSX && !TARGET_VSX_ALIGN_128)
2657    {
2658      align64 = 64;
2659      align32 = 32;
2660    }
2661  else
2662    {
2663      align64 = 128;
2664      align32 = 128;
2665    }
2666
2667  /* V2DF mode, VSX only.  */
2668  if (TARGET_VSX)
2669    {
2670      rs6000_vector_unit[V2DFmode] = VECTOR_VSX;
2671      rs6000_vector_mem[V2DFmode] = VECTOR_VSX;
2672      rs6000_vector_align[V2DFmode] = align64;
2673    }
2674
2675  /* V4SF mode, either VSX or Altivec.  */
2676  if (TARGET_VSX)
2677    {
2678      rs6000_vector_unit[V4SFmode] = VECTOR_VSX;
2679      rs6000_vector_mem[V4SFmode] = VECTOR_VSX;
2680      rs6000_vector_align[V4SFmode] = align32;
2681    }
2682  else if (TARGET_ALTIVEC)
2683    {
2684      rs6000_vector_unit[V4SFmode] = VECTOR_ALTIVEC;
2685      rs6000_vector_mem[V4SFmode] = VECTOR_ALTIVEC;
2686      rs6000_vector_align[V4SFmode] = align32;
2687    }
2688
2689  /* V16QImode, V8HImode, V4SImode are Altivec only, but possibly do VSX loads
2690     and stores. */
2691  if (TARGET_ALTIVEC)
2692    {
2693      rs6000_vector_unit[V4SImode] = VECTOR_ALTIVEC;
2694      rs6000_vector_unit[V8HImode] = VECTOR_ALTIVEC;
2695      rs6000_vector_unit[V16QImode] = VECTOR_ALTIVEC;
2696      rs6000_vector_align[V4SImode] = align32;
2697      rs6000_vector_align[V8HImode] = align32;
2698      rs6000_vector_align[V16QImode] = align32;
2699
2700      if (TARGET_VSX)
2701	{
2702	  rs6000_vector_mem[V4SImode] = VECTOR_VSX;
2703	  rs6000_vector_mem[V8HImode] = VECTOR_VSX;
2704	  rs6000_vector_mem[V16QImode] = VECTOR_VSX;
2705	}
2706      else
2707	{
2708	  rs6000_vector_mem[V4SImode] = VECTOR_ALTIVEC;
2709	  rs6000_vector_mem[V8HImode] = VECTOR_ALTIVEC;
2710	  rs6000_vector_mem[V16QImode] = VECTOR_ALTIVEC;
2711	}
2712    }
2713
2714  /* V2DImode, full mode depends on ISA 2.07 vector mode.  Allow under VSX to
2715     do insert/splat/extract.  Altivec doesn't have 64-bit integer support.  */
2716  if (TARGET_VSX)
2717    {
2718      rs6000_vector_mem[V2DImode] = VECTOR_VSX;
2719      rs6000_vector_unit[V2DImode]
2720	= (TARGET_P8_VECTOR) ? VECTOR_P8_VECTOR : VECTOR_NONE;
2721      rs6000_vector_align[V2DImode] = align64;
2722
2723      rs6000_vector_mem[V1TImode] = VECTOR_VSX;
2724      rs6000_vector_unit[V1TImode]
2725	= (TARGET_P8_VECTOR) ? VECTOR_P8_VECTOR : VECTOR_NONE;
2726      rs6000_vector_align[V1TImode] = 128;
2727    }
2728
2729  /* DFmode, see if we want to use the VSX unit.  Memory is handled
2730     differently, so don't set rs6000_vector_mem.  */
2731  if (TARGET_VSX && TARGET_VSX_SCALAR_DOUBLE)
2732    {
2733      rs6000_vector_unit[DFmode] = VECTOR_VSX;
2734      rs6000_vector_align[DFmode] = 64;
2735    }
2736
2737  /* SFmode, see if we want to use the VSX unit.  */
2738  if (TARGET_P8_VECTOR && TARGET_VSX_SCALAR_FLOAT)
2739    {
2740      rs6000_vector_unit[SFmode] = VECTOR_VSX;
2741      rs6000_vector_align[SFmode] = 32;
2742    }
2743
2744  /* Allow TImode in VSX register and set the VSX memory macros.  */
2745  if (TARGET_VSX && TARGET_VSX_TIMODE)
2746    {
2747      rs6000_vector_mem[TImode] = VECTOR_VSX;
2748      rs6000_vector_align[TImode] = align64;
2749    }
2750
2751  /* TODO add SPE and paired floating point vector support.  */
2752
2753  /* Register class constraints for the constraints that depend on compile
2754     switches. When the VSX code was added, different constraints were added
2755     based on the type (DFmode, V2DFmode, V4SFmode).  For the vector types, all
2756     of the VSX registers are used.  The register classes for scalar floating
2757     point types is set, based on whether we allow that type into the upper
2758     (Altivec) registers.  GCC has register classes to target the Altivec
2759     registers for load/store operations, to select using a VSX memory
2760     operation instead of the traditional floating point operation.  The
2761     constraints are:
2762
2763	d  - Register class to use with traditional DFmode instructions.
2764	f  - Register class to use with traditional SFmode instructions.
2765	v  - Altivec register.
2766	wa - Any VSX register.
2767	wc - Reserved to represent individual CR bits (used in LLVM).
2768	wd - Preferred register class for V2DFmode.
2769	wf - Preferred register class for V4SFmode.
2770	wg - Float register for power6x move insns.
2771	wh - FP register for direct move instructions.
2772	wi - FP or VSX register to hold 64-bit integers for VSX insns.
2773	wj - FP or VSX register to hold 64-bit integers for direct moves.
2774	wk - FP or VSX register to hold 64-bit doubles for direct moves.
2775	wl - Float register if we can do 32-bit signed int loads.
2776	wm - VSX register for ISA 2.07 direct move operations.
2777	wn - always NO_REGS.
2778	wr - GPR if 64-bit mode is permitted.
2779	ws - Register class to do ISA 2.06 DF operations.
2780	wt - VSX register for TImode in VSX registers.
2781	wu - Altivec register for ISA 2.07 VSX SF/SI load/stores.
2782	wv - Altivec register for ISA 2.06 VSX DF/DI load/stores.
2783	ww - Register class to do SF conversions in with VSX operations.
2784	wx - Float register if we can do 32-bit int stores.
2785	wy - Register class to do ISA 2.07 SF operations.
2786	wz - Float register if we can do 32-bit unsigned int loads.  */
2787
2788  if (TARGET_HARD_FLOAT && TARGET_FPRS)
2789    rs6000_constraints[RS6000_CONSTRAINT_f] = FLOAT_REGS;	/* SFmode  */
2790
2791  if (TARGET_HARD_FLOAT && TARGET_FPRS && TARGET_DOUBLE_FLOAT)
2792    rs6000_constraints[RS6000_CONSTRAINT_d]  = FLOAT_REGS;	/* DFmode  */
2793
2794  if (TARGET_VSX)
2795    {
2796      rs6000_constraints[RS6000_CONSTRAINT_wa] = VSX_REGS;
2797      rs6000_constraints[RS6000_CONSTRAINT_wd] = VSX_REGS;	/* V2DFmode  */
2798      rs6000_constraints[RS6000_CONSTRAINT_wf] = VSX_REGS;	/* V4SFmode  */
2799      rs6000_constraints[RS6000_CONSTRAINT_wi] = FLOAT_REGS;	/* DImode  */
2800
2801      if (TARGET_VSX_TIMODE)
2802	rs6000_constraints[RS6000_CONSTRAINT_wt] = VSX_REGS;	/* TImode  */
2803
2804      if (TARGET_UPPER_REGS_DF)					/* DFmode  */
2805	{
2806	  rs6000_constraints[RS6000_CONSTRAINT_ws] = VSX_REGS;
2807	  rs6000_constraints[RS6000_CONSTRAINT_wv] = ALTIVEC_REGS;
2808	}
2809      else
2810	rs6000_constraints[RS6000_CONSTRAINT_ws] = FLOAT_REGS;
2811    }
2812
2813  /* Add conditional constraints based on various options, to allow us to
2814     collapse multiple insn patterns.  */
2815  if (TARGET_ALTIVEC)
2816    rs6000_constraints[RS6000_CONSTRAINT_v] = ALTIVEC_REGS;
2817
2818  if (TARGET_MFPGPR)						/* DFmode  */
2819    rs6000_constraints[RS6000_CONSTRAINT_wg] = FLOAT_REGS;
2820
2821  if (TARGET_LFIWAX)
2822    rs6000_constraints[RS6000_CONSTRAINT_wl] = FLOAT_REGS;	/* DImode  */
2823
2824  if (TARGET_DIRECT_MOVE)
2825    {
2826      rs6000_constraints[RS6000_CONSTRAINT_wh] = FLOAT_REGS;
2827      rs6000_constraints[RS6000_CONSTRAINT_wj]			/* DImode  */
2828	= rs6000_constraints[RS6000_CONSTRAINT_wi];
2829      rs6000_constraints[RS6000_CONSTRAINT_wk]			/* DFmode  */
2830	= rs6000_constraints[RS6000_CONSTRAINT_ws];
2831      rs6000_constraints[RS6000_CONSTRAINT_wm] = VSX_REGS;
2832    }
2833
2834  if (TARGET_POWERPC64)
2835    rs6000_constraints[RS6000_CONSTRAINT_wr] = GENERAL_REGS;
2836
2837  if (TARGET_P8_VECTOR && TARGET_UPPER_REGS_SF)			/* SFmode  */
2838    {
2839      rs6000_constraints[RS6000_CONSTRAINT_wu] = ALTIVEC_REGS;
2840      rs6000_constraints[RS6000_CONSTRAINT_wy] = VSX_REGS;
2841      rs6000_constraints[RS6000_CONSTRAINT_ww] = VSX_REGS;
2842    }
2843  else if (TARGET_P8_VECTOR)
2844    {
2845      rs6000_constraints[RS6000_CONSTRAINT_wy] = FLOAT_REGS;
2846      rs6000_constraints[RS6000_CONSTRAINT_ww] = FLOAT_REGS;
2847    }
2848  else if (TARGET_VSX)
2849    rs6000_constraints[RS6000_CONSTRAINT_ww] = FLOAT_REGS;
2850
2851  if (TARGET_STFIWX)
2852    rs6000_constraints[RS6000_CONSTRAINT_wx] = FLOAT_REGS;	/* DImode  */
2853
2854  if (TARGET_LFIWZX)
2855    rs6000_constraints[RS6000_CONSTRAINT_wz] = FLOAT_REGS;	/* DImode  */
2856
2857  /* Set up the reload helper and direct move functions.  */
2858  if (TARGET_VSX || TARGET_ALTIVEC)
2859    {
2860      if (TARGET_64BIT)
2861	{
2862	  reg_addr[V16QImode].reload_store = CODE_FOR_reload_v16qi_di_store;
2863	  reg_addr[V16QImode].reload_load  = CODE_FOR_reload_v16qi_di_load;
2864	  reg_addr[V8HImode].reload_store  = CODE_FOR_reload_v8hi_di_store;
2865	  reg_addr[V8HImode].reload_load   = CODE_FOR_reload_v8hi_di_load;
2866	  reg_addr[V4SImode].reload_store  = CODE_FOR_reload_v4si_di_store;
2867	  reg_addr[V4SImode].reload_load   = CODE_FOR_reload_v4si_di_load;
2868	  reg_addr[V2DImode].reload_store  = CODE_FOR_reload_v2di_di_store;
2869	  reg_addr[V2DImode].reload_load   = CODE_FOR_reload_v2di_di_load;
2870	  reg_addr[V1TImode].reload_store  = CODE_FOR_reload_v1ti_di_store;
2871	  reg_addr[V1TImode].reload_load   = CODE_FOR_reload_v1ti_di_load;
2872	  reg_addr[V4SFmode].reload_store  = CODE_FOR_reload_v4sf_di_store;
2873	  reg_addr[V4SFmode].reload_load   = CODE_FOR_reload_v4sf_di_load;
2874	  reg_addr[V2DFmode].reload_store  = CODE_FOR_reload_v2df_di_store;
2875	  reg_addr[V2DFmode].reload_load   = CODE_FOR_reload_v2df_di_load;
2876	  reg_addr[DFmode].reload_store    = CODE_FOR_reload_df_di_store;
2877	  reg_addr[DFmode].reload_load     = CODE_FOR_reload_df_di_load;
2878	  reg_addr[DDmode].reload_store    = CODE_FOR_reload_dd_di_store;
2879	  reg_addr[DDmode].reload_load     = CODE_FOR_reload_dd_di_load;
2880	  reg_addr[SFmode].reload_store    = CODE_FOR_reload_sf_di_store;
2881	  reg_addr[SFmode].reload_load     = CODE_FOR_reload_sf_di_load;
2882
2883	  /* Only provide a reload handler for SDmode if lfiwzx/stfiwx are
2884	     available.  */
2885	  if (TARGET_NO_SDMODE_STACK)
2886	    {
2887	      reg_addr[SDmode].reload_store = CODE_FOR_reload_sd_di_store;
2888	      reg_addr[SDmode].reload_load  = CODE_FOR_reload_sd_di_load;
2889	    }
2890
2891	  if (TARGET_VSX_TIMODE)
2892	    {
2893	      reg_addr[TImode].reload_store  = CODE_FOR_reload_ti_di_store;
2894	      reg_addr[TImode].reload_load   = CODE_FOR_reload_ti_di_load;
2895	    }
2896
2897	  if (TARGET_DIRECT_MOVE)
2898	    {
2899	      reg_addr[TImode].reload_gpr_vsx    = CODE_FOR_reload_gpr_from_vsxti;
2900	      reg_addr[V1TImode].reload_gpr_vsx  = CODE_FOR_reload_gpr_from_vsxv1ti;
2901	      reg_addr[V2DFmode].reload_gpr_vsx  = CODE_FOR_reload_gpr_from_vsxv2df;
2902	      reg_addr[V2DImode].reload_gpr_vsx  = CODE_FOR_reload_gpr_from_vsxv2di;
2903	      reg_addr[V4SFmode].reload_gpr_vsx  = CODE_FOR_reload_gpr_from_vsxv4sf;
2904	      reg_addr[V4SImode].reload_gpr_vsx  = CODE_FOR_reload_gpr_from_vsxv4si;
2905	      reg_addr[V8HImode].reload_gpr_vsx  = CODE_FOR_reload_gpr_from_vsxv8hi;
2906	      reg_addr[V16QImode].reload_gpr_vsx = CODE_FOR_reload_gpr_from_vsxv16qi;
2907	      reg_addr[SFmode].reload_gpr_vsx    = CODE_FOR_reload_gpr_from_vsxsf;
2908
2909	      reg_addr[TImode].reload_vsx_gpr    = CODE_FOR_reload_vsx_from_gprti;
2910	      reg_addr[V1TImode].reload_vsx_gpr  = CODE_FOR_reload_vsx_from_gprv1ti;
2911	      reg_addr[V2DFmode].reload_vsx_gpr  = CODE_FOR_reload_vsx_from_gprv2df;
2912	      reg_addr[V2DImode].reload_vsx_gpr  = CODE_FOR_reload_vsx_from_gprv2di;
2913	      reg_addr[V4SFmode].reload_vsx_gpr  = CODE_FOR_reload_vsx_from_gprv4sf;
2914	      reg_addr[V4SImode].reload_vsx_gpr  = CODE_FOR_reload_vsx_from_gprv4si;
2915	      reg_addr[V8HImode].reload_vsx_gpr  = CODE_FOR_reload_vsx_from_gprv8hi;
2916	      reg_addr[V16QImode].reload_vsx_gpr = CODE_FOR_reload_vsx_from_gprv16qi;
2917	      reg_addr[SFmode].reload_vsx_gpr    = CODE_FOR_reload_vsx_from_gprsf;
2918	    }
2919	}
2920      else
2921	{
2922	  reg_addr[V16QImode].reload_store = CODE_FOR_reload_v16qi_si_store;
2923	  reg_addr[V16QImode].reload_load  = CODE_FOR_reload_v16qi_si_load;
2924	  reg_addr[V8HImode].reload_store  = CODE_FOR_reload_v8hi_si_store;
2925	  reg_addr[V8HImode].reload_load   = CODE_FOR_reload_v8hi_si_load;
2926	  reg_addr[V4SImode].reload_store  = CODE_FOR_reload_v4si_si_store;
2927	  reg_addr[V4SImode].reload_load   = CODE_FOR_reload_v4si_si_load;
2928	  reg_addr[V2DImode].reload_store  = CODE_FOR_reload_v2di_si_store;
2929	  reg_addr[V2DImode].reload_load   = CODE_FOR_reload_v2di_si_load;
2930	  reg_addr[V1TImode].reload_store  = CODE_FOR_reload_v1ti_si_store;
2931	  reg_addr[V1TImode].reload_load   = CODE_FOR_reload_v1ti_si_load;
2932	  reg_addr[V4SFmode].reload_store  = CODE_FOR_reload_v4sf_si_store;
2933	  reg_addr[V4SFmode].reload_load   = CODE_FOR_reload_v4sf_si_load;
2934	  reg_addr[V2DFmode].reload_store  = CODE_FOR_reload_v2df_si_store;
2935	  reg_addr[V2DFmode].reload_load   = CODE_FOR_reload_v2df_si_load;
2936	  reg_addr[DFmode].reload_store    = CODE_FOR_reload_df_si_store;
2937	  reg_addr[DFmode].reload_load     = CODE_FOR_reload_df_si_load;
2938	  reg_addr[DDmode].reload_store    = CODE_FOR_reload_dd_si_store;
2939	  reg_addr[DDmode].reload_load     = CODE_FOR_reload_dd_si_load;
2940	  reg_addr[SFmode].reload_store    = CODE_FOR_reload_sf_si_store;
2941	  reg_addr[SFmode].reload_load     = CODE_FOR_reload_sf_si_load;
2942
2943	  /* Only provide a reload handler for SDmode if lfiwzx/stfiwx are
2944	     available.  */
2945	  if (TARGET_NO_SDMODE_STACK)
2946	    {
2947	      reg_addr[SDmode].reload_store = CODE_FOR_reload_sd_si_store;
2948	      reg_addr[SDmode].reload_load  = CODE_FOR_reload_sd_si_load;
2949	    }
2950
2951	  if (TARGET_VSX_TIMODE)
2952	    {
2953	      reg_addr[TImode].reload_store  = CODE_FOR_reload_ti_si_store;
2954	      reg_addr[TImode].reload_load   = CODE_FOR_reload_ti_si_load;
2955	    }
2956
2957	  if (TARGET_DIRECT_MOVE)
2958	    {
2959	      reg_addr[DImode].reload_fpr_gpr = CODE_FOR_reload_fpr_from_gprdi;
2960	      reg_addr[DDmode].reload_fpr_gpr = CODE_FOR_reload_fpr_from_gprdd;
2961	      reg_addr[DFmode].reload_fpr_gpr = CODE_FOR_reload_fpr_from_gprdf;
2962	    }
2963	}
2964
2965      if (TARGET_UPPER_REGS_DF)
2966	reg_addr[DFmode].scalar_in_vmx_p = true;
2967
2968      if (TARGET_UPPER_REGS_SF)
2969	reg_addr[SFmode].scalar_in_vmx_p = true;
2970    }
2971
2972  /* Precalculate HARD_REGNO_NREGS.  */
2973  for (r = 0; r < FIRST_PSEUDO_REGISTER; ++r)
2974    for (m = 0; m < NUM_MACHINE_MODES; ++m)
2975      rs6000_hard_regno_nregs[m][r]
2976	= rs6000_hard_regno_nregs_internal (r, (machine_mode)m);
2977
2978  /* Precalculate HARD_REGNO_MODE_OK.  */
2979  for (r = 0; r < FIRST_PSEUDO_REGISTER; ++r)
2980    for (m = 0; m < NUM_MACHINE_MODES; ++m)
2981      if (rs6000_hard_regno_mode_ok (r, (machine_mode)m))
2982	rs6000_hard_regno_mode_ok_p[m][r] = true;
2983
2984  /* Precalculate CLASS_MAX_NREGS sizes.  */
2985  for (c = 0; c < LIM_REG_CLASSES; ++c)
2986    {
2987      int reg_size;
2988
2989      if (TARGET_VSX && VSX_REG_CLASS_P (c))
2990	reg_size = UNITS_PER_VSX_WORD;
2991
2992      else if (c == ALTIVEC_REGS)
2993	reg_size = UNITS_PER_ALTIVEC_WORD;
2994
2995      else if (c == FLOAT_REGS)
2996	reg_size = UNITS_PER_FP_WORD;
2997
2998      else
2999	reg_size = UNITS_PER_WORD;
3000
3001      for (m = 0; m < NUM_MACHINE_MODES; ++m)
3002	{
3003	  machine_mode m2 = (machine_mode)m;
3004	  int reg_size2 = reg_size;
3005
3006	  /* TFmode/TDmode always takes 2 registers, even in VSX.  */
3007	  if (TARGET_VSX && VSX_REG_CLASS_P (c)
3008	      && (m == TDmode || m == TFmode))
3009	    reg_size2 = UNITS_PER_FP_WORD;
3010
3011	  rs6000_class_max_nregs[m][c]
3012	    = (GET_MODE_SIZE (m2) + reg_size2 - 1) / reg_size2;
3013	}
3014    }
3015
3016  if (TARGET_E500_DOUBLE)
3017    rs6000_class_max_nregs[DFmode][GENERAL_REGS] = 1;
3018
3019  /* Calculate which modes to automatically generate code to use a the
3020     reciprocal divide and square root instructions.  In the future, possibly
3021     automatically generate the instructions even if the user did not specify
3022     -mrecip.  The older machines double precision reciprocal sqrt estimate is
3023     not accurate enough.  */
3024  memset (rs6000_recip_bits, 0, sizeof (rs6000_recip_bits));
3025  if (TARGET_FRES)
3026    rs6000_recip_bits[SFmode] = RS6000_RECIP_MASK_HAVE_RE;
3027  if (TARGET_FRE)
3028    rs6000_recip_bits[DFmode] = RS6000_RECIP_MASK_HAVE_RE;
3029  if (VECTOR_UNIT_ALTIVEC_OR_VSX_P (V4SFmode))
3030    rs6000_recip_bits[V4SFmode] = RS6000_RECIP_MASK_HAVE_RE;
3031  if (VECTOR_UNIT_VSX_P (V2DFmode))
3032    rs6000_recip_bits[V2DFmode] = RS6000_RECIP_MASK_HAVE_RE;
3033
3034  if (TARGET_FRSQRTES)
3035    rs6000_recip_bits[SFmode] |= RS6000_RECIP_MASK_HAVE_RSQRTE;
3036  if (TARGET_FRSQRTE)
3037    rs6000_recip_bits[DFmode] |= RS6000_RECIP_MASK_HAVE_RSQRTE;
3038  if (VECTOR_UNIT_ALTIVEC_OR_VSX_P (V4SFmode))
3039    rs6000_recip_bits[V4SFmode] |= RS6000_RECIP_MASK_HAVE_RSQRTE;
3040  if (VECTOR_UNIT_VSX_P (V2DFmode))
3041    rs6000_recip_bits[V2DFmode] |= RS6000_RECIP_MASK_HAVE_RSQRTE;
3042
3043  if (rs6000_recip_control)
3044    {
3045      if (!flag_finite_math_only)
3046	warning (0, "-mrecip requires -ffinite-math or -ffast-math");
3047      if (flag_trapping_math)
3048	warning (0, "-mrecip requires -fno-trapping-math or -ffast-math");
3049      if (!flag_reciprocal_math)
3050	warning (0, "-mrecip requires -freciprocal-math or -ffast-math");
3051      if (flag_finite_math_only && !flag_trapping_math && flag_reciprocal_math)
3052	{
3053	  if (RS6000_RECIP_HAVE_RE_P (SFmode)
3054	      && (rs6000_recip_control & RECIP_SF_DIV) != 0)
3055	    rs6000_recip_bits[SFmode] |= RS6000_RECIP_MASK_AUTO_RE;
3056
3057	  if (RS6000_RECIP_HAVE_RE_P (DFmode)
3058	      && (rs6000_recip_control & RECIP_DF_DIV) != 0)
3059	    rs6000_recip_bits[DFmode] |= RS6000_RECIP_MASK_AUTO_RE;
3060
3061	  if (RS6000_RECIP_HAVE_RE_P (V4SFmode)
3062	      && (rs6000_recip_control & RECIP_V4SF_DIV) != 0)
3063	    rs6000_recip_bits[V4SFmode] |= RS6000_RECIP_MASK_AUTO_RE;
3064
3065	  if (RS6000_RECIP_HAVE_RE_P (V2DFmode)
3066	      && (rs6000_recip_control & RECIP_V2DF_DIV) != 0)
3067	    rs6000_recip_bits[V2DFmode] |= RS6000_RECIP_MASK_AUTO_RE;
3068
3069	  if (RS6000_RECIP_HAVE_RSQRTE_P (SFmode)
3070	      && (rs6000_recip_control & RECIP_SF_RSQRT) != 0)
3071	    rs6000_recip_bits[SFmode] |= RS6000_RECIP_MASK_AUTO_RSQRTE;
3072
3073	  if (RS6000_RECIP_HAVE_RSQRTE_P (DFmode)
3074	      && (rs6000_recip_control & RECIP_DF_RSQRT) != 0)
3075	    rs6000_recip_bits[DFmode] |= RS6000_RECIP_MASK_AUTO_RSQRTE;
3076
3077	  if (RS6000_RECIP_HAVE_RSQRTE_P (V4SFmode)
3078	      && (rs6000_recip_control & RECIP_V4SF_RSQRT) != 0)
3079	    rs6000_recip_bits[V4SFmode] |= RS6000_RECIP_MASK_AUTO_RSQRTE;
3080
3081	  if (RS6000_RECIP_HAVE_RSQRTE_P (V2DFmode)
3082	      && (rs6000_recip_control & RECIP_V2DF_RSQRT) != 0)
3083	    rs6000_recip_bits[V2DFmode] |= RS6000_RECIP_MASK_AUTO_RSQRTE;
3084	}
3085    }
3086
3087  /* Update the addr mask bits in reg_addr to help secondary reload and go if
3088     legitimate address support to figure out the appropriate addressing to
3089     use.  */
3090  rs6000_setup_reg_addr_masks ();
3091
3092  if (global_init_p || TARGET_DEBUG_TARGET)
3093    {
3094      if (TARGET_DEBUG_REG)
3095	rs6000_debug_reg_global ();
3096
3097      if (TARGET_DEBUG_COST || TARGET_DEBUG_REG)
3098	fprintf (stderr,
3099		 "SImode variable mult cost       = %d\n"
3100		 "SImode constant mult cost       = %d\n"
3101		 "SImode short constant mult cost = %d\n"
3102		 "DImode multipliciation cost     = %d\n"
3103		 "SImode division cost            = %d\n"
3104		 "DImode division cost            = %d\n"
3105		 "Simple fp operation cost        = %d\n"
3106		 "DFmode multiplication cost      = %d\n"
3107		 "SFmode division cost            = %d\n"
3108		 "DFmode division cost            = %d\n"
3109		 "cache line size                 = %d\n"
3110		 "l1 cache size                   = %d\n"
3111		 "l2 cache size                   = %d\n"
3112		 "simultaneous prefetches         = %d\n"
3113		 "\n",
3114		 rs6000_cost->mulsi,
3115		 rs6000_cost->mulsi_const,
3116		 rs6000_cost->mulsi_const9,
3117		 rs6000_cost->muldi,
3118		 rs6000_cost->divsi,
3119		 rs6000_cost->divdi,
3120		 rs6000_cost->fp,
3121		 rs6000_cost->dmul,
3122		 rs6000_cost->sdiv,
3123		 rs6000_cost->ddiv,
3124		 rs6000_cost->cache_line_size,
3125		 rs6000_cost->l1_cache_size,
3126		 rs6000_cost->l2_cache_size,
3127		 rs6000_cost->simultaneous_prefetches);
3128    }
3129}
3130
3131#if TARGET_MACHO
3132/* The Darwin version of SUBTARGET_OVERRIDE_OPTIONS.  */
3133
3134static void
3135darwin_rs6000_override_options (void)
3136{
3137  /* The Darwin ABI always includes AltiVec, can't be (validly) turned
3138     off.  */
3139  rs6000_altivec_abi = 1;
3140  TARGET_ALTIVEC_VRSAVE = 1;
3141  rs6000_current_abi = ABI_DARWIN;
3142
3143  if (DEFAULT_ABI == ABI_DARWIN
3144      && TARGET_64BIT)
3145      darwin_one_byte_bool = 1;
3146
3147  if (TARGET_64BIT && ! TARGET_POWERPC64)
3148    {
3149      rs6000_isa_flags |= OPTION_MASK_POWERPC64;
3150      warning (0, "-m64 requires PowerPC64 architecture, enabling");
3151    }
3152  if (flag_mkernel)
3153    {
3154      rs6000_default_long_calls = 1;
3155      rs6000_isa_flags |= OPTION_MASK_SOFT_FLOAT;
3156    }
3157
3158  /* Make -m64 imply -maltivec.  Darwin's 64-bit ABI includes
3159     Altivec.  */
3160  if (!flag_mkernel && !flag_apple_kext
3161      && TARGET_64BIT
3162      && ! (rs6000_isa_flags_explicit & OPTION_MASK_ALTIVEC))
3163    rs6000_isa_flags |= OPTION_MASK_ALTIVEC;
3164
3165  /* Unless the user (not the configurer) has explicitly overridden
3166     it with -mcpu=G3 or -mno-altivec, then 10.5+ targets default to
3167     G4 unless targeting the kernel.  */
3168  if (!flag_mkernel
3169      && !flag_apple_kext
3170      && strverscmp (darwin_macosx_version_min, "10.5") >= 0
3171      && ! (rs6000_isa_flags_explicit & OPTION_MASK_ALTIVEC)
3172      && ! global_options_set.x_rs6000_cpu_index)
3173    {
3174      rs6000_isa_flags |= OPTION_MASK_ALTIVEC;
3175    }
3176}
3177#endif
3178
3179/* If not otherwise specified by a target, make 'long double' equivalent to
3180   'double'.  */
3181
3182#ifndef RS6000_DEFAULT_LONG_DOUBLE_SIZE
3183#define RS6000_DEFAULT_LONG_DOUBLE_SIZE 64
3184#endif
3185
3186/* Return the builtin mask of the various options used that could affect which
3187   builtins were used.  In the past we used target_flags, but we've run out of
3188   bits, and some options like SPE and PAIRED are no longer in
3189   target_flags.  */
3190
3191HOST_WIDE_INT
3192rs6000_builtin_mask_calculate (void)
3193{
3194  return (((TARGET_ALTIVEC)		    ? RS6000_BTM_ALTIVEC   : 0)
3195	  | ((TARGET_VSX)		    ? RS6000_BTM_VSX	   : 0)
3196	  | ((TARGET_SPE)		    ? RS6000_BTM_SPE	   : 0)
3197	  | ((TARGET_PAIRED_FLOAT)	    ? RS6000_BTM_PAIRED	   : 0)
3198	  | ((TARGET_FRE)		    ? RS6000_BTM_FRE	   : 0)
3199	  | ((TARGET_FRES)		    ? RS6000_BTM_FRES	   : 0)
3200	  | ((TARGET_FRSQRTE)		    ? RS6000_BTM_FRSQRTE   : 0)
3201	  | ((TARGET_FRSQRTES)		    ? RS6000_BTM_FRSQRTES  : 0)
3202	  | ((TARGET_POPCNTD)		    ? RS6000_BTM_POPCNTD   : 0)
3203	  | ((rs6000_cpu == PROCESSOR_CELL) ? RS6000_BTM_CELL      : 0)
3204	  | ((TARGET_P8_VECTOR)		    ? RS6000_BTM_P8_VECTOR : 0)
3205	  | ((TARGET_CRYPTO)		    ? RS6000_BTM_CRYPTO	   : 0)
3206	  | ((TARGET_HTM)		    ? RS6000_BTM_HTM	   : 0)
3207	  | ((TARGET_DFP)		    ? RS6000_BTM_DFP	   : 0)
3208	  | ((TARGET_HARD_FLOAT)	    ? RS6000_BTM_HARD_FLOAT : 0)
3209	  | ((TARGET_LONG_DOUBLE_128)	    ? RS6000_BTM_LDBL128 : 0));
3210}
3211
3212/* Implement TARGET_MD_ASM_CLOBBERS.  All asm statements are considered
3213   to clobber the XER[CA] bit because clobbering that bit without telling
3214   the compiler worked just fine with versions of GCC before GCC 5, and
3215   breaking a lot of older code in ways that are hard to track down is
3216   not such a great idea.  */
3217
3218static tree
3219rs6000_md_asm_clobbers (tree, tree, tree clobbers)
3220{
3221  tree s = build_string (strlen (reg_names[CA_REGNO]), reg_names[CA_REGNO]);
3222  return tree_cons (NULL_TREE, s, clobbers);
3223}
3224
3225/* Override command line options.  Mostly we process the processor type and
3226   sometimes adjust other TARGET_ options.  */
3227
3228static bool
3229rs6000_option_override_internal (bool global_init_p)
3230{
3231  bool ret = true;
3232  bool have_cpu = false;
3233
3234  /* The default cpu requested at configure time, if any.  */
3235  const char *implicit_cpu = OPTION_TARGET_CPU_DEFAULT;
3236
3237  HOST_WIDE_INT set_masks;
3238  int cpu_index;
3239  int tune_index;
3240  struct cl_target_option *main_target_opt
3241    = ((global_init_p || target_option_default_node == NULL)
3242       ? NULL : TREE_TARGET_OPTION (target_option_default_node));
3243
3244  /* Print defaults.  */
3245  if ((TARGET_DEBUG_REG || TARGET_DEBUG_TARGET) && global_init_p)
3246    rs6000_print_isa_options (stderr, 0, "TARGET_DEFAULT", TARGET_DEFAULT);
3247
3248  /* Remember the explicit arguments.  */
3249  if (global_init_p)
3250    rs6000_isa_flags_explicit = global_options_set.x_rs6000_isa_flags;
3251
3252  /* On 64-bit Darwin, power alignment is ABI-incompatible with some C
3253     library functions, so warn about it. The flag may be useful for
3254     performance studies from time to time though, so don't disable it
3255     entirely.  */
3256  if (global_options_set.x_rs6000_alignment_flags
3257      && rs6000_alignment_flags == MASK_ALIGN_POWER
3258      && DEFAULT_ABI == ABI_DARWIN
3259      && TARGET_64BIT)
3260    warning (0, "-malign-power is not supported for 64-bit Darwin;"
3261	     " it is incompatible with the installed C and C++ libraries");
3262
3263  /* Numerous experiment shows that IRA based loop pressure
3264     calculation works better for RTL loop invariant motion on targets
3265     with enough (>= 32) registers.  It is an expensive optimization.
3266     So it is on only for peak performance.  */
3267  if (optimize >= 3 && global_init_p
3268      && !global_options_set.x_flag_ira_loop_pressure)
3269    flag_ira_loop_pressure = 1;
3270
3271  /* Set the pointer size.  */
3272  if (TARGET_64BIT)
3273    {
3274      rs6000_pmode = (int)DImode;
3275      rs6000_pointer_size = 64;
3276    }
3277  else
3278    {
3279      rs6000_pmode = (int)SImode;
3280      rs6000_pointer_size = 32;
3281    }
3282
3283  /* Some OSs don't support saving the high part of 64-bit registers on context
3284     switch.  Other OSs don't support saving Altivec registers.  On those OSs,
3285     we don't touch the OPTION_MASK_POWERPC64 or OPTION_MASK_ALTIVEC settings;
3286     if the user wants either, the user must explicitly specify them and we
3287     won't interfere with the user's specification.  */
3288
3289  set_masks = POWERPC_MASKS;
3290#ifdef OS_MISSING_POWERPC64
3291  if (OS_MISSING_POWERPC64)
3292    set_masks &= ~OPTION_MASK_POWERPC64;
3293#endif
3294#ifdef OS_MISSING_ALTIVEC
3295  if (OS_MISSING_ALTIVEC)
3296    set_masks &= ~(OPTION_MASK_ALTIVEC | OPTION_MASK_VSX);
3297#endif
3298
3299  /* Don't override by the processor default if given explicitly.  */
3300  set_masks &= ~rs6000_isa_flags_explicit;
3301
3302  /* Process the -mcpu=<xxx> and -mtune=<xxx> argument.  If the user changed
3303     the cpu in a target attribute or pragma, but did not specify a tuning
3304     option, use the cpu for the tuning option rather than the option specified
3305     with -mtune on the command line.  Process a '--with-cpu' configuration
3306     request as an implicit --cpu.  */
3307  if (rs6000_cpu_index >= 0)
3308    {
3309      cpu_index = rs6000_cpu_index;
3310      have_cpu = true;
3311    }
3312  else if (main_target_opt != NULL && main_target_opt->x_rs6000_cpu_index >= 0)
3313    {
3314      rs6000_cpu_index = cpu_index = main_target_opt->x_rs6000_cpu_index;
3315      have_cpu = true;
3316    }
3317  else if (implicit_cpu)
3318    {
3319      rs6000_cpu_index = cpu_index = rs6000_cpu_name_lookup (implicit_cpu);
3320      have_cpu = true;
3321    }
3322  else
3323    {
3324      /* PowerPC 64-bit LE requires at least ISA 2.07.  */
3325      const char *default_cpu = ((!TARGET_POWERPC64)
3326				 ? "powerpc"
3327				 : ((BYTES_BIG_ENDIAN)
3328				    ? "powerpc64"
3329				    : "powerpc64le"));
3330
3331      rs6000_cpu_index = cpu_index = rs6000_cpu_name_lookup (default_cpu);
3332      have_cpu = false;
3333    }
3334
3335  gcc_assert (cpu_index >= 0);
3336
3337  /* If we have a cpu, either through an explicit -mcpu=<xxx> or if the
3338     compiler was configured with --with-cpu=<xxx>, replace all of the ISA bits
3339     with those from the cpu, except for options that were explicitly set.  If
3340     we don't have a cpu, do not override the target bits set in
3341     TARGET_DEFAULT.  */
3342  if (have_cpu)
3343    {
3344      rs6000_isa_flags &= ~set_masks;
3345      rs6000_isa_flags |= (processor_target_table[cpu_index].target_enable
3346			   & set_masks);
3347    }
3348  else
3349    {
3350      /* If no -mcpu=<xxx>, inherit any default options that were cleared via
3351	 POWERPC_MASKS.  Originally, TARGET_DEFAULT was used to initialize
3352	 target_flags via the TARGET_DEFAULT_TARGET_FLAGS hook.  When we switched
3353	 to using rs6000_isa_flags, we need to do the initialization here.
3354
3355	 If there is a TARGET_DEFAULT, use that.  Otherwise fall back to using
3356	 -mcpu=powerpc, -mcpu=powerpc64, or -mcpu=powerpc64le defaults.  */
3357      HOST_WIDE_INT flags = ((TARGET_DEFAULT) ? TARGET_DEFAULT
3358			     : processor_target_table[cpu_index].target_enable);
3359      rs6000_isa_flags |= (flags & ~rs6000_isa_flags_explicit);
3360    }
3361
3362  if (rs6000_tune_index >= 0)
3363    tune_index = rs6000_tune_index;
3364  else if (have_cpu)
3365    rs6000_tune_index = tune_index = cpu_index;
3366  else
3367    {
3368      size_t i;
3369      enum processor_type tune_proc
3370	= (TARGET_POWERPC64 ? PROCESSOR_DEFAULT64 : PROCESSOR_DEFAULT);
3371
3372      tune_index = -1;
3373      for (i = 0; i < ARRAY_SIZE (processor_target_table); i++)
3374	if (processor_target_table[i].processor == tune_proc)
3375	  {
3376	    rs6000_tune_index = tune_index = i;
3377	    break;
3378	  }
3379    }
3380
3381  gcc_assert (tune_index >= 0);
3382  rs6000_cpu = processor_target_table[tune_index].processor;
3383
3384  /* Pick defaults for SPE related control flags.  Do this early to make sure
3385     that the TARGET_ macros are representative ASAP.  */
3386  {
3387    int spe_capable_cpu =
3388      (rs6000_cpu == PROCESSOR_PPC8540
3389       || rs6000_cpu == PROCESSOR_PPC8548);
3390
3391    if (!global_options_set.x_rs6000_spe_abi)
3392      rs6000_spe_abi = spe_capable_cpu;
3393
3394    if (!global_options_set.x_rs6000_spe)
3395      rs6000_spe = spe_capable_cpu;
3396
3397    if (!global_options_set.x_rs6000_float_gprs)
3398      rs6000_float_gprs =
3399        (rs6000_cpu == PROCESSOR_PPC8540 ? 1
3400         : rs6000_cpu == PROCESSOR_PPC8548 ? 2
3401         : 0);
3402  }
3403
3404  if (global_options_set.x_rs6000_spe_abi
3405      && rs6000_spe_abi
3406      && !TARGET_SPE_ABI)
3407    error ("not configured for SPE ABI");
3408
3409  if (global_options_set.x_rs6000_spe
3410      && rs6000_spe
3411      && !TARGET_SPE)
3412    error ("not configured for SPE instruction set");
3413
3414  if (main_target_opt != NULL
3415      && ((main_target_opt->x_rs6000_spe_abi != rs6000_spe_abi)
3416          || (main_target_opt->x_rs6000_spe != rs6000_spe)
3417          || (main_target_opt->x_rs6000_float_gprs != rs6000_float_gprs)))
3418    error ("target attribute or pragma changes SPE ABI");
3419
3420  if (rs6000_cpu == PROCESSOR_PPCE300C2 || rs6000_cpu == PROCESSOR_PPCE300C3
3421      || rs6000_cpu == PROCESSOR_PPCE500MC || rs6000_cpu == PROCESSOR_PPCE500MC64
3422      || rs6000_cpu == PROCESSOR_PPCE5500)
3423    {
3424      if (TARGET_ALTIVEC)
3425	error ("AltiVec not supported in this target");
3426      if (TARGET_SPE)
3427	error ("SPE not supported in this target");
3428    }
3429  if (rs6000_cpu == PROCESSOR_PPCE6500)
3430    {
3431      if (TARGET_SPE)
3432	error ("SPE not supported in this target");
3433    }
3434
3435  /* Disable Cell microcode if we are optimizing for the Cell
3436     and not optimizing for size.  */
3437  if (rs6000_gen_cell_microcode == -1)
3438    rs6000_gen_cell_microcode = !(rs6000_cpu == PROCESSOR_CELL
3439                                  && !optimize_size);
3440
3441  /* If we are optimizing big endian systems for space and it's OK to
3442     use instructions that would be microcoded on the Cell, use the
3443     load/store multiple and string instructions.  */
3444  if (BYTES_BIG_ENDIAN && optimize_size && rs6000_gen_cell_microcode)
3445    rs6000_isa_flags |= ~rs6000_isa_flags_explicit & (OPTION_MASK_MULTIPLE
3446						      | OPTION_MASK_STRING);
3447
3448  /* Don't allow -mmultiple or -mstring on little endian systems
3449     unless the cpu is a 750, because the hardware doesn't support the
3450     instructions used in little endian mode, and causes an alignment
3451     trap.  The 750 does not cause an alignment trap (except when the
3452     target is unaligned).  */
3453
3454  if (!BYTES_BIG_ENDIAN && rs6000_cpu != PROCESSOR_PPC750)
3455    {
3456      if (TARGET_MULTIPLE)
3457	{
3458	  rs6000_isa_flags &= ~OPTION_MASK_MULTIPLE;
3459	  if ((rs6000_isa_flags_explicit & OPTION_MASK_MULTIPLE) != 0)
3460	    warning (0, "-mmultiple is not supported on little endian systems");
3461	}
3462
3463      if (TARGET_STRING)
3464	{
3465	  rs6000_isa_flags &= ~OPTION_MASK_STRING;
3466	  if ((rs6000_isa_flags_explicit & OPTION_MASK_STRING) != 0)
3467	    warning (0, "-mstring is not supported on little endian systems");
3468	}
3469    }
3470
3471  /* If little-endian, default to -mstrict-align on older processors.
3472     Testing for htm matches power8 and later.  */
3473  if (!BYTES_BIG_ENDIAN
3474      && !(processor_target_table[tune_index].target_enable & OPTION_MASK_HTM))
3475    rs6000_isa_flags |= ~rs6000_isa_flags_explicit & OPTION_MASK_STRICT_ALIGN;
3476
3477  /* -maltivec={le,be} implies -maltivec.  */
3478  if (rs6000_altivec_element_order != 0)
3479    rs6000_isa_flags |= OPTION_MASK_ALTIVEC;
3480
3481  /* Disallow -maltivec=le in big endian mode for now.  This is not
3482     known to be useful for anyone.  */
3483  if (BYTES_BIG_ENDIAN && rs6000_altivec_element_order == 1)
3484    {
3485      warning (0, N_("-maltivec=le not allowed for big-endian targets"));
3486      rs6000_altivec_element_order = 0;
3487    }
3488
3489  /* Add some warnings for VSX.  */
3490  if (TARGET_VSX)
3491    {
3492      const char *msg = NULL;
3493      if (!TARGET_HARD_FLOAT || !TARGET_FPRS
3494	  || !TARGET_SINGLE_FLOAT || !TARGET_DOUBLE_FLOAT)
3495	{
3496	  if (rs6000_isa_flags_explicit & OPTION_MASK_VSX)
3497	    msg = N_("-mvsx requires hardware floating point");
3498	  else
3499	    {
3500	      rs6000_isa_flags &= ~ OPTION_MASK_VSX;
3501	      rs6000_isa_flags_explicit |= OPTION_MASK_VSX;
3502	    }
3503	}
3504      else if (TARGET_PAIRED_FLOAT)
3505	msg = N_("-mvsx and -mpaired are incompatible");
3506      else if (TARGET_AVOID_XFORM > 0)
3507	msg = N_("-mvsx needs indexed addressing");
3508      else if (!TARGET_ALTIVEC && (rs6000_isa_flags_explicit
3509				   & OPTION_MASK_ALTIVEC))
3510        {
3511	  if (rs6000_isa_flags_explicit & OPTION_MASK_VSX)
3512	    msg = N_("-mvsx and -mno-altivec are incompatible");
3513	  else
3514	    msg = N_("-mno-altivec disables vsx");
3515        }
3516
3517      if (msg)
3518	{
3519	  warning (0, msg);
3520	  rs6000_isa_flags &= ~ OPTION_MASK_VSX;
3521	  rs6000_isa_flags_explicit |= OPTION_MASK_VSX;
3522	}
3523    }
3524
3525  /* If hard-float/altivec/vsx were explicitly turned off then don't allow
3526     the -mcpu setting to enable options that conflict. */
3527  if ((!TARGET_HARD_FLOAT || !TARGET_ALTIVEC || !TARGET_VSX)
3528      && (rs6000_isa_flags_explicit & (OPTION_MASK_SOFT_FLOAT
3529				       | OPTION_MASK_ALTIVEC
3530				       | OPTION_MASK_VSX)) != 0)
3531    rs6000_isa_flags &= ~((OPTION_MASK_P8_VECTOR | OPTION_MASK_CRYPTO
3532			   | OPTION_MASK_DIRECT_MOVE)
3533		         & ~rs6000_isa_flags_explicit);
3534
3535  if (TARGET_DEBUG_REG || TARGET_DEBUG_TARGET)
3536    rs6000_print_isa_options (stderr, 0, "before defaults", rs6000_isa_flags);
3537
3538  /* For the newer switches (vsx, dfp, etc.) set some of the older options,
3539     unless the user explicitly used the -mno-<option> to disable the code.  */
3540  if (TARGET_P8_VECTOR || TARGET_DIRECT_MOVE || TARGET_CRYPTO)
3541    rs6000_isa_flags |= (ISA_2_7_MASKS_SERVER & ~rs6000_isa_flags_explicit);
3542  else if (TARGET_VSX)
3543    rs6000_isa_flags |= (ISA_2_6_MASKS_SERVER & ~rs6000_isa_flags_explicit);
3544  else if (TARGET_POPCNTD)
3545    rs6000_isa_flags |= (ISA_2_6_MASKS_EMBEDDED & ~rs6000_isa_flags_explicit);
3546  else if (TARGET_DFP)
3547    rs6000_isa_flags |= (ISA_2_5_MASKS_SERVER & ~rs6000_isa_flags_explicit);
3548  else if (TARGET_CMPB)
3549    rs6000_isa_flags |= (ISA_2_5_MASKS_EMBEDDED & ~rs6000_isa_flags_explicit);
3550  else if (TARGET_FPRND)
3551    rs6000_isa_flags |= (ISA_2_4_MASKS & ~rs6000_isa_flags_explicit);
3552  else if (TARGET_POPCNTB)
3553    rs6000_isa_flags |= (ISA_2_2_MASKS & ~rs6000_isa_flags_explicit);
3554  else if (TARGET_ALTIVEC)
3555    rs6000_isa_flags |= (OPTION_MASK_PPC_GFXOPT & ~rs6000_isa_flags_explicit);
3556
3557  if (TARGET_CRYPTO && !TARGET_ALTIVEC)
3558    {
3559      if (rs6000_isa_flags_explicit & OPTION_MASK_CRYPTO)
3560	error ("-mcrypto requires -maltivec");
3561      rs6000_isa_flags &= ~OPTION_MASK_CRYPTO;
3562    }
3563
3564  if (TARGET_DIRECT_MOVE && !TARGET_VSX)
3565    {
3566      if (rs6000_isa_flags_explicit & OPTION_MASK_DIRECT_MOVE)
3567	error ("-mdirect-move requires -mvsx");
3568      rs6000_isa_flags &= ~OPTION_MASK_DIRECT_MOVE;
3569    }
3570
3571  if (TARGET_P8_VECTOR && !TARGET_ALTIVEC)
3572    {
3573      if (rs6000_isa_flags_explicit & OPTION_MASK_P8_VECTOR)
3574	error ("-mpower8-vector requires -maltivec");
3575      rs6000_isa_flags &= ~OPTION_MASK_P8_VECTOR;
3576    }
3577
3578  if (TARGET_P8_VECTOR && !TARGET_VSX)
3579    {
3580      if (rs6000_isa_flags_explicit & OPTION_MASK_P8_VECTOR)
3581	error ("-mpower8-vector requires -mvsx");
3582      rs6000_isa_flags &= ~OPTION_MASK_P8_VECTOR;
3583    }
3584
3585  if (TARGET_VSX_TIMODE && !TARGET_VSX)
3586    {
3587      if (rs6000_isa_flags_explicit & OPTION_MASK_VSX_TIMODE)
3588	error ("-mvsx-timode requires -mvsx");
3589      rs6000_isa_flags &= ~OPTION_MASK_VSX_TIMODE;
3590    }
3591
3592  if (TARGET_DFP && !TARGET_HARD_FLOAT)
3593    {
3594      if (rs6000_isa_flags_explicit & OPTION_MASK_DFP)
3595	error ("-mhard-dfp requires -mhard-float");
3596      rs6000_isa_flags &= ~OPTION_MASK_DFP;
3597    }
3598
3599  /* Allow an explicit -mupper-regs to set both -mupper-regs-df and
3600     -mupper-regs-sf, depending on the cpu, unless the user explicitly also set
3601     the individual option.  */
3602  if (TARGET_UPPER_REGS > 0)
3603    {
3604      if (TARGET_VSX
3605	  && !(rs6000_isa_flags_explicit & OPTION_MASK_UPPER_REGS_DF))
3606	{
3607	  rs6000_isa_flags |= OPTION_MASK_UPPER_REGS_DF;
3608	  rs6000_isa_flags_explicit |= OPTION_MASK_UPPER_REGS_DF;
3609	}
3610      if (TARGET_P8_VECTOR
3611	  && !(rs6000_isa_flags_explicit & OPTION_MASK_UPPER_REGS_SF))
3612	{
3613	  rs6000_isa_flags |= OPTION_MASK_UPPER_REGS_SF;
3614	  rs6000_isa_flags_explicit |= OPTION_MASK_UPPER_REGS_SF;
3615	}
3616    }
3617  else if (TARGET_UPPER_REGS == 0)
3618    {
3619      if (TARGET_VSX
3620	  && !(rs6000_isa_flags_explicit & OPTION_MASK_UPPER_REGS_DF))
3621	{
3622	  rs6000_isa_flags &= ~OPTION_MASK_UPPER_REGS_DF;
3623	  rs6000_isa_flags_explicit |= OPTION_MASK_UPPER_REGS_DF;
3624	}
3625      if (TARGET_P8_VECTOR
3626	  && !(rs6000_isa_flags_explicit & OPTION_MASK_UPPER_REGS_SF))
3627	{
3628	  rs6000_isa_flags &= ~OPTION_MASK_UPPER_REGS_SF;
3629	  rs6000_isa_flags_explicit |= OPTION_MASK_UPPER_REGS_SF;
3630	}
3631    }
3632
3633  if (TARGET_UPPER_REGS_DF && !TARGET_VSX)
3634    {
3635      if (rs6000_isa_flags_explicit & OPTION_MASK_UPPER_REGS_DF)
3636	error ("-mupper-regs-df requires -mvsx");
3637      rs6000_isa_flags &= ~OPTION_MASK_UPPER_REGS_DF;
3638    }
3639
3640  if (TARGET_UPPER_REGS_SF && !TARGET_P8_VECTOR)
3641    {
3642      if (rs6000_isa_flags_explicit & OPTION_MASK_UPPER_REGS_SF)
3643	error ("-mupper-regs-sf requires -mpower8-vector");
3644      rs6000_isa_flags &= ~OPTION_MASK_UPPER_REGS_SF;
3645    }
3646
3647  /* The quad memory instructions only works in 64-bit mode. In 32-bit mode,
3648     silently turn off quad memory mode.  */
3649  if ((TARGET_QUAD_MEMORY || TARGET_QUAD_MEMORY_ATOMIC) && !TARGET_POWERPC64)
3650    {
3651      if ((rs6000_isa_flags_explicit & OPTION_MASK_QUAD_MEMORY) != 0)
3652	warning (0, N_("-mquad-memory requires 64-bit mode"));
3653
3654      if ((rs6000_isa_flags_explicit & OPTION_MASK_QUAD_MEMORY_ATOMIC) != 0)
3655	warning (0, N_("-mquad-memory-atomic requires 64-bit mode"));
3656
3657      rs6000_isa_flags &= ~(OPTION_MASK_QUAD_MEMORY
3658			    | OPTION_MASK_QUAD_MEMORY_ATOMIC);
3659    }
3660
3661  /* Non-atomic quad memory load/store are disabled for little endian, since
3662     the words are reversed, but atomic operations can still be done by
3663     swapping the words.  */
3664  if (TARGET_QUAD_MEMORY && !WORDS_BIG_ENDIAN)
3665    {
3666      if ((rs6000_isa_flags_explicit & OPTION_MASK_QUAD_MEMORY) != 0)
3667	warning (0, N_("-mquad-memory is not available in little endian mode"));
3668
3669      rs6000_isa_flags &= ~OPTION_MASK_QUAD_MEMORY;
3670    }
3671
3672  /* Assume if the user asked for normal quad memory instructions, they want
3673     the atomic versions as well, unless they explicity told us not to use quad
3674     word atomic instructions.  */
3675  if (TARGET_QUAD_MEMORY
3676      && !TARGET_QUAD_MEMORY_ATOMIC
3677      && ((rs6000_isa_flags_explicit & OPTION_MASK_QUAD_MEMORY_ATOMIC) == 0))
3678    rs6000_isa_flags |= OPTION_MASK_QUAD_MEMORY_ATOMIC;
3679
3680  /* Enable power8 fusion if we are tuning for power8, even if we aren't
3681     generating power8 instructions.  */
3682  if (!(rs6000_isa_flags_explicit & OPTION_MASK_P8_FUSION))
3683    rs6000_isa_flags |= (processor_target_table[tune_index].target_enable
3684			 & OPTION_MASK_P8_FUSION);
3685
3686  /* Power8 does not fuse sign extended loads with the addis.  If we are
3687     optimizing at high levels for speed, convert a sign extended load into a
3688     zero extending load, and an explicit sign extension.  */
3689  if (TARGET_P8_FUSION
3690      && !(rs6000_isa_flags_explicit & OPTION_MASK_P8_FUSION_SIGN)
3691      && optimize_function_for_speed_p (cfun)
3692      && optimize >= 3)
3693    rs6000_isa_flags |= OPTION_MASK_P8_FUSION_SIGN;
3694
3695  /* Set -mallow-movmisalign to explicitly on if we have full ISA 2.07
3696     support. If we only have ISA 2.06 support, and the user did not specify
3697     the switch, leave it set to -1 so the movmisalign patterns are enabled,
3698     but we don't enable the full vectorization support  */
3699  if (TARGET_ALLOW_MOVMISALIGN == -1 && TARGET_P8_VECTOR && TARGET_DIRECT_MOVE)
3700    TARGET_ALLOW_MOVMISALIGN = 1;
3701
3702  else if (TARGET_ALLOW_MOVMISALIGN && !TARGET_VSX)
3703    {
3704      if (TARGET_ALLOW_MOVMISALIGN > 0
3705	  && global_options_set.x_TARGET_ALLOW_MOVMISALIGN)
3706	error ("-mallow-movmisalign requires -mvsx");
3707
3708      TARGET_ALLOW_MOVMISALIGN = 0;
3709    }
3710
3711  /* Determine when unaligned vector accesses are permitted, and when
3712     they are preferred over masked Altivec loads.  Note that if
3713     TARGET_ALLOW_MOVMISALIGN has been disabled by the user, then
3714     TARGET_EFFICIENT_UNALIGNED_VSX must be as well.  The converse is
3715     not true.  */
3716  if (TARGET_EFFICIENT_UNALIGNED_VSX)
3717    {
3718      if (!TARGET_VSX)
3719	{
3720	  if (rs6000_isa_flags_explicit & OPTION_MASK_EFFICIENT_UNALIGNED_VSX)
3721	    error ("-mefficient-unaligned-vsx requires -mvsx");
3722
3723	  rs6000_isa_flags &= ~OPTION_MASK_EFFICIENT_UNALIGNED_VSX;
3724	}
3725
3726      else if (!TARGET_ALLOW_MOVMISALIGN)
3727	{
3728	  if (rs6000_isa_flags_explicit & OPTION_MASK_EFFICIENT_UNALIGNED_VSX)
3729	    error ("-mefficient-unaligned-vsx requires -mallow-movmisalign");
3730
3731	  rs6000_isa_flags &= ~OPTION_MASK_EFFICIENT_UNALIGNED_VSX;
3732	}
3733    }
3734
3735  if (TARGET_DEBUG_REG || TARGET_DEBUG_TARGET)
3736    rs6000_print_isa_options (stderr, 0, "after defaults", rs6000_isa_flags);
3737
3738  /* E500mc does "better" if we inline more aggressively.  Respect the
3739     user's opinion, though.  */
3740  if (rs6000_block_move_inline_limit == 0
3741      && (rs6000_cpu == PROCESSOR_PPCE500MC
3742	  || rs6000_cpu == PROCESSOR_PPCE500MC64
3743	  || rs6000_cpu == PROCESSOR_PPCE5500
3744	  || rs6000_cpu == PROCESSOR_PPCE6500))
3745    rs6000_block_move_inline_limit = 128;
3746
3747  /* store_one_arg depends on expand_block_move to handle at least the
3748     size of reg_parm_stack_space.  */
3749  if (rs6000_block_move_inline_limit < (TARGET_POWERPC64 ? 64 : 32))
3750    rs6000_block_move_inline_limit = (TARGET_POWERPC64 ? 64 : 32);
3751
3752  if (global_init_p)
3753    {
3754      /* If the appropriate debug option is enabled, replace the target hooks
3755	 with debug versions that call the real version and then prints
3756	 debugging information.  */
3757      if (TARGET_DEBUG_COST)
3758	{
3759	  targetm.rtx_costs = rs6000_debug_rtx_costs;
3760	  targetm.address_cost = rs6000_debug_address_cost;
3761	  targetm.sched.adjust_cost = rs6000_debug_adjust_cost;
3762	}
3763
3764      if (TARGET_DEBUG_ADDR)
3765	{
3766	  targetm.legitimate_address_p = rs6000_debug_legitimate_address_p;
3767	  targetm.legitimize_address = rs6000_debug_legitimize_address;
3768	  rs6000_secondary_reload_class_ptr
3769	    = rs6000_debug_secondary_reload_class;
3770	  rs6000_secondary_memory_needed_ptr
3771	    = rs6000_debug_secondary_memory_needed;
3772	  rs6000_cannot_change_mode_class_ptr
3773	    = rs6000_debug_cannot_change_mode_class;
3774	  rs6000_preferred_reload_class_ptr
3775	    = rs6000_debug_preferred_reload_class;
3776	  rs6000_legitimize_reload_address_ptr
3777	    = rs6000_debug_legitimize_reload_address;
3778	  rs6000_mode_dependent_address_ptr
3779	    = rs6000_debug_mode_dependent_address;
3780	}
3781
3782      if (rs6000_veclibabi_name)
3783	{
3784	  if (strcmp (rs6000_veclibabi_name, "mass") == 0)
3785	    rs6000_veclib_handler = rs6000_builtin_vectorized_libmass;
3786	  else
3787	    {
3788	      error ("unknown vectorization library ABI type (%s) for "
3789		     "-mveclibabi= switch", rs6000_veclibabi_name);
3790	      ret = false;
3791	    }
3792	}
3793    }
3794
3795  if (!global_options_set.x_rs6000_long_double_type_size)
3796    {
3797      if (main_target_opt != NULL
3798	  && (main_target_opt->x_rs6000_long_double_type_size
3799	      != RS6000_DEFAULT_LONG_DOUBLE_SIZE))
3800	error ("target attribute or pragma changes long double size");
3801      else
3802	rs6000_long_double_type_size = RS6000_DEFAULT_LONG_DOUBLE_SIZE;
3803    }
3804
3805#if !defined (POWERPC_LINUX) && !defined (POWERPC_FREEBSD)
3806  if (!global_options_set.x_rs6000_ieeequad)
3807    rs6000_ieeequad = 1;
3808#endif
3809
3810  /* Disable VSX and Altivec silently if the user switched cpus to power7 in a
3811     target attribute or pragma which automatically enables both options,
3812     unless the altivec ABI was set.  This is set by default for 64-bit, but
3813     not for 32-bit.  */
3814  if (main_target_opt != NULL && !main_target_opt->x_rs6000_altivec_abi)
3815    rs6000_isa_flags &= ~((OPTION_MASK_VSX | OPTION_MASK_ALTIVEC)
3816			  & ~rs6000_isa_flags_explicit);
3817
3818  /* Enable Altivec ABI for AIX -maltivec.  */
3819  if (TARGET_XCOFF && (TARGET_ALTIVEC || TARGET_VSX))
3820    {
3821      if (main_target_opt != NULL && !main_target_opt->x_rs6000_altivec_abi)
3822	error ("target attribute or pragma changes AltiVec ABI");
3823      else
3824	rs6000_altivec_abi = 1;
3825    }
3826
3827  /* The AltiVec ABI is the default for PowerPC-64 GNU/Linux.  For
3828     PowerPC-32 GNU/Linux, -maltivec implies the AltiVec ABI.  It can
3829     be explicitly overridden in either case.  */
3830  if (TARGET_ELF)
3831    {
3832      if (!global_options_set.x_rs6000_altivec_abi
3833	  && (TARGET_64BIT || TARGET_ALTIVEC || TARGET_VSX))
3834	{
3835	  if (main_target_opt != NULL &&
3836	      !main_target_opt->x_rs6000_altivec_abi)
3837	    error ("target attribute or pragma changes AltiVec ABI");
3838	  else
3839	    rs6000_altivec_abi = 1;
3840	}
3841    }
3842
3843  /* Set the Darwin64 ABI as default for 64-bit Darwin.
3844     So far, the only darwin64 targets are also MACH-O.  */
3845  if (TARGET_MACHO
3846      && DEFAULT_ABI == ABI_DARWIN
3847      && TARGET_64BIT)
3848    {
3849      if (main_target_opt != NULL && !main_target_opt->x_rs6000_darwin64_abi)
3850	error ("target attribute or pragma changes darwin64 ABI");
3851      else
3852	{
3853	  rs6000_darwin64_abi = 1;
3854	  /* Default to natural alignment, for better performance.  */
3855	  rs6000_alignment_flags = MASK_ALIGN_NATURAL;
3856	}
3857    }
3858
3859  /* Place FP constants in the constant pool instead of TOC
3860     if section anchors enabled.  */
3861  if (flag_section_anchors
3862      && !global_options_set.x_TARGET_NO_FP_IN_TOC)
3863    TARGET_NO_FP_IN_TOC = 1;
3864
3865  if (TARGET_DEBUG_REG || TARGET_DEBUG_TARGET)
3866    rs6000_print_isa_options (stderr, 0, "before subtarget", rs6000_isa_flags);
3867
3868#ifdef SUBTARGET_OVERRIDE_OPTIONS
3869  SUBTARGET_OVERRIDE_OPTIONS;
3870#endif
3871#ifdef SUBSUBTARGET_OVERRIDE_OPTIONS
3872  SUBSUBTARGET_OVERRIDE_OPTIONS;
3873#endif
3874#ifdef SUB3TARGET_OVERRIDE_OPTIONS
3875  SUB3TARGET_OVERRIDE_OPTIONS;
3876#endif
3877
3878  if (TARGET_DEBUG_REG || TARGET_DEBUG_TARGET)
3879    rs6000_print_isa_options (stderr, 0, "after subtarget", rs6000_isa_flags);
3880
3881  /* For the E500 family of cores, reset the single/double FP flags to let us
3882     check that they remain constant across attributes or pragmas.  Also,
3883     clear a possible request for string instructions, not supported and which
3884     we might have silently queried above for -Os.
3885
3886     For other families, clear ISEL in case it was set implicitly.
3887  */
3888
3889  switch (rs6000_cpu)
3890    {
3891    case PROCESSOR_PPC8540:
3892    case PROCESSOR_PPC8548:
3893    case PROCESSOR_PPCE500MC:
3894    case PROCESSOR_PPCE500MC64:
3895    case PROCESSOR_PPCE5500:
3896    case PROCESSOR_PPCE6500:
3897
3898      rs6000_single_float = TARGET_E500_SINGLE || TARGET_E500_DOUBLE;
3899      rs6000_double_float = TARGET_E500_DOUBLE;
3900
3901      rs6000_isa_flags &= ~OPTION_MASK_STRING;
3902
3903      break;
3904
3905    default:
3906
3907      if (have_cpu && !(rs6000_isa_flags_explicit & OPTION_MASK_ISEL))
3908	rs6000_isa_flags &= ~OPTION_MASK_ISEL;
3909
3910      break;
3911    }
3912
3913  if (main_target_opt)
3914    {
3915      if (main_target_opt->x_rs6000_single_float != rs6000_single_float)
3916	error ("target attribute or pragma changes single precision floating "
3917	       "point");
3918      if (main_target_opt->x_rs6000_double_float != rs6000_double_float)
3919	error ("target attribute or pragma changes double precision floating "
3920	       "point");
3921    }
3922
3923  /* Detect invalid option combinations with E500.  */
3924  CHECK_E500_OPTIONS;
3925
3926  rs6000_always_hint = (rs6000_cpu != PROCESSOR_POWER4
3927			&& rs6000_cpu != PROCESSOR_POWER5
3928			&& rs6000_cpu != PROCESSOR_POWER6
3929			&& rs6000_cpu != PROCESSOR_POWER7
3930			&& rs6000_cpu != PROCESSOR_POWER8
3931			&& rs6000_cpu != PROCESSOR_PPCA2
3932			&& rs6000_cpu != PROCESSOR_CELL
3933			&& rs6000_cpu != PROCESSOR_PPC476);
3934  rs6000_sched_groups = (rs6000_cpu == PROCESSOR_POWER4
3935			 || rs6000_cpu == PROCESSOR_POWER5
3936			 || rs6000_cpu == PROCESSOR_POWER7
3937			 || rs6000_cpu == PROCESSOR_POWER8);
3938  rs6000_align_branch_targets = (rs6000_cpu == PROCESSOR_POWER4
3939				 || rs6000_cpu == PROCESSOR_POWER5
3940				 || rs6000_cpu == PROCESSOR_POWER6
3941				 || rs6000_cpu == PROCESSOR_POWER7
3942				 || rs6000_cpu == PROCESSOR_POWER8
3943				 || rs6000_cpu == PROCESSOR_PPCE500MC
3944				 || rs6000_cpu == PROCESSOR_PPCE500MC64
3945				 || rs6000_cpu == PROCESSOR_PPCE5500
3946				 || rs6000_cpu == PROCESSOR_PPCE6500);
3947
3948  /* Allow debug switches to override the above settings.  These are set to -1
3949     in rs6000.opt to indicate the user hasn't directly set the switch.  */
3950  if (TARGET_ALWAYS_HINT >= 0)
3951    rs6000_always_hint = TARGET_ALWAYS_HINT;
3952
3953  if (TARGET_SCHED_GROUPS >= 0)
3954    rs6000_sched_groups = TARGET_SCHED_GROUPS;
3955
3956  if (TARGET_ALIGN_BRANCH_TARGETS >= 0)
3957    rs6000_align_branch_targets = TARGET_ALIGN_BRANCH_TARGETS;
3958
3959  rs6000_sched_restricted_insns_priority
3960    = (rs6000_sched_groups ? 1 : 0);
3961
3962  /* Handle -msched-costly-dep option.  */
3963  rs6000_sched_costly_dep
3964    = (rs6000_sched_groups ? true_store_to_load_dep_costly : no_dep_costly);
3965
3966  if (rs6000_sched_costly_dep_str)
3967    {
3968      if (! strcmp (rs6000_sched_costly_dep_str, "no"))
3969	rs6000_sched_costly_dep = no_dep_costly;
3970      else if (! strcmp (rs6000_sched_costly_dep_str, "all"))
3971	rs6000_sched_costly_dep = all_deps_costly;
3972      else if (! strcmp (rs6000_sched_costly_dep_str, "true_store_to_load"))
3973	rs6000_sched_costly_dep = true_store_to_load_dep_costly;
3974      else if (! strcmp (rs6000_sched_costly_dep_str, "store_to_load"))
3975	rs6000_sched_costly_dep = store_to_load_dep_costly;
3976      else
3977	rs6000_sched_costly_dep = ((enum rs6000_dependence_cost)
3978				   atoi (rs6000_sched_costly_dep_str));
3979    }
3980
3981  /* Handle -minsert-sched-nops option.  */
3982  rs6000_sched_insert_nops
3983    = (rs6000_sched_groups ? sched_finish_regroup_exact : sched_finish_none);
3984
3985  if (rs6000_sched_insert_nops_str)
3986    {
3987      if (! strcmp (rs6000_sched_insert_nops_str, "no"))
3988	rs6000_sched_insert_nops = sched_finish_none;
3989      else if (! strcmp (rs6000_sched_insert_nops_str, "pad"))
3990	rs6000_sched_insert_nops = sched_finish_pad_groups;
3991      else if (! strcmp (rs6000_sched_insert_nops_str, "regroup_exact"))
3992	rs6000_sched_insert_nops = sched_finish_regroup_exact;
3993      else
3994	rs6000_sched_insert_nops = ((enum rs6000_nop_insertion)
3995				    atoi (rs6000_sched_insert_nops_str));
3996    }
3997
3998  if (global_init_p)
3999    {
4000#ifdef TARGET_REGNAMES
4001      /* If the user desires alternate register names, copy in the
4002	 alternate names now.  */
4003      if (TARGET_REGNAMES)
4004	memcpy (rs6000_reg_names, alt_reg_names, sizeof (rs6000_reg_names));
4005#endif
4006
4007      /* Set aix_struct_return last, after the ABI is determined.
4008	 If -maix-struct-return or -msvr4-struct-return was explicitly
4009	 used, don't override with the ABI default.  */
4010      if (!global_options_set.x_aix_struct_return)
4011	aix_struct_return = (DEFAULT_ABI != ABI_V4 || DRAFT_V4_STRUCT_RET);
4012
4013#if 0
4014      /* IBM XL compiler defaults to unsigned bitfields.  */
4015      if (TARGET_XL_COMPAT)
4016	flag_signed_bitfields = 0;
4017#endif
4018
4019      if (TARGET_LONG_DOUBLE_128 && !TARGET_IEEEQUAD)
4020	REAL_MODE_FORMAT (TFmode) = &ibm_extended_format;
4021
4022      if (TARGET_TOC)
4023	ASM_GENERATE_INTERNAL_LABEL (toc_label_name, "LCTOC", 1);
4024
4025      /* We can only guarantee the availability of DI pseudo-ops when
4026	 assembling for 64-bit targets.  */
4027      if (!TARGET_64BIT)
4028	{
4029	  targetm.asm_out.aligned_op.di = NULL;
4030	  targetm.asm_out.unaligned_op.di = NULL;
4031	}
4032
4033
4034      /* Set branch target alignment, if not optimizing for size.  */
4035      if (!optimize_size)
4036	{
4037	  /* Cell wants to be aligned 8byte for dual issue.  Titan wants to be
4038	     aligned 8byte to avoid misprediction by the branch predictor.  */
4039	  if (rs6000_cpu == PROCESSOR_TITAN
4040	      || rs6000_cpu == PROCESSOR_CELL)
4041	    {
4042	      if (align_functions <= 0)
4043		align_functions = 8;
4044	      if (align_jumps <= 0)
4045		align_jumps = 8;
4046	      if (align_loops <= 0)
4047		align_loops = 8;
4048	    }
4049	  if (rs6000_align_branch_targets)
4050	    {
4051	      if (align_functions <= 0)
4052		align_functions = 16;
4053	      if (align_jumps <= 0)
4054		align_jumps = 16;
4055	      if (align_loops <= 0)
4056		{
4057		  can_override_loop_align = 1;
4058		  align_loops = 16;
4059		}
4060	    }
4061	  if (align_jumps_max_skip <= 0)
4062	    align_jumps_max_skip = 15;
4063	  if (align_loops_max_skip <= 0)
4064	    align_loops_max_skip = 15;
4065	}
4066
4067      /* Arrange to save and restore machine status around nested functions.  */
4068      init_machine_status = rs6000_init_machine_status;
4069
4070      /* We should always be splitting complex arguments, but we can't break
4071	 Linux and Darwin ABIs at the moment.  For now, only AIX is fixed.  */
4072      if (DEFAULT_ABI == ABI_V4 || DEFAULT_ABI == ABI_DARWIN)
4073	targetm.calls.split_complex_arg = NULL;
4074    }
4075
4076  /* Initialize rs6000_cost with the appropriate target costs.  */
4077  if (optimize_size)
4078    rs6000_cost = TARGET_POWERPC64 ? &size64_cost : &size32_cost;
4079  else
4080    switch (rs6000_cpu)
4081      {
4082      case PROCESSOR_RS64A:
4083	rs6000_cost = &rs64a_cost;
4084	break;
4085
4086      case PROCESSOR_MPCCORE:
4087	rs6000_cost = &mpccore_cost;
4088	break;
4089
4090      case PROCESSOR_PPC403:
4091	rs6000_cost = &ppc403_cost;
4092	break;
4093
4094      case PROCESSOR_PPC405:
4095	rs6000_cost = &ppc405_cost;
4096	break;
4097
4098      case PROCESSOR_PPC440:
4099	rs6000_cost = &ppc440_cost;
4100	break;
4101
4102      case PROCESSOR_PPC476:
4103	rs6000_cost = &ppc476_cost;
4104	break;
4105
4106      case PROCESSOR_PPC601:
4107	rs6000_cost = &ppc601_cost;
4108	break;
4109
4110      case PROCESSOR_PPC603:
4111	rs6000_cost = &ppc603_cost;
4112	break;
4113
4114      case PROCESSOR_PPC604:
4115	rs6000_cost = &ppc604_cost;
4116	break;
4117
4118      case PROCESSOR_PPC604e:
4119	rs6000_cost = &ppc604e_cost;
4120	break;
4121
4122      case PROCESSOR_PPC620:
4123	rs6000_cost = &ppc620_cost;
4124	break;
4125
4126      case PROCESSOR_PPC630:
4127	rs6000_cost = &ppc630_cost;
4128	break;
4129
4130      case PROCESSOR_CELL:
4131	rs6000_cost = &ppccell_cost;
4132	break;
4133
4134      case PROCESSOR_PPC750:
4135      case PROCESSOR_PPC7400:
4136	rs6000_cost = &ppc750_cost;
4137	break;
4138
4139      case PROCESSOR_PPC7450:
4140	rs6000_cost = &ppc7450_cost;
4141	break;
4142
4143      case PROCESSOR_PPC8540:
4144      case PROCESSOR_PPC8548:
4145	rs6000_cost = &ppc8540_cost;
4146	break;
4147
4148      case PROCESSOR_PPCE300C2:
4149      case PROCESSOR_PPCE300C3:
4150	rs6000_cost = &ppce300c2c3_cost;
4151	break;
4152
4153      case PROCESSOR_PPCE500MC:
4154	rs6000_cost = &ppce500mc_cost;
4155	break;
4156
4157      case PROCESSOR_PPCE500MC64:
4158	rs6000_cost = &ppce500mc64_cost;
4159	break;
4160
4161      case PROCESSOR_PPCE5500:
4162	rs6000_cost = &ppce5500_cost;
4163	break;
4164
4165      case PROCESSOR_PPCE6500:
4166	rs6000_cost = &ppce6500_cost;
4167	break;
4168
4169      case PROCESSOR_TITAN:
4170	rs6000_cost = &titan_cost;
4171	break;
4172
4173      case PROCESSOR_POWER4:
4174      case PROCESSOR_POWER5:
4175	rs6000_cost = &power4_cost;
4176	break;
4177
4178      case PROCESSOR_POWER6:
4179	rs6000_cost = &power6_cost;
4180	break;
4181
4182      case PROCESSOR_POWER7:
4183	rs6000_cost = &power7_cost;
4184	break;
4185
4186      case PROCESSOR_POWER8:
4187	rs6000_cost = &power8_cost;
4188	break;
4189
4190      case PROCESSOR_PPCA2:
4191	rs6000_cost = &ppca2_cost;
4192	break;
4193
4194      default:
4195	gcc_unreachable ();
4196      }
4197
4198  if (global_init_p)
4199    {
4200      maybe_set_param_value (PARAM_SIMULTANEOUS_PREFETCHES,
4201			     rs6000_cost->simultaneous_prefetches,
4202			     global_options.x_param_values,
4203			     global_options_set.x_param_values);
4204      maybe_set_param_value (PARAM_L1_CACHE_SIZE, rs6000_cost->l1_cache_size,
4205			     global_options.x_param_values,
4206			     global_options_set.x_param_values);
4207      maybe_set_param_value (PARAM_L1_CACHE_LINE_SIZE,
4208			     rs6000_cost->cache_line_size,
4209			     global_options.x_param_values,
4210			     global_options_set.x_param_values);
4211      maybe_set_param_value (PARAM_L2_CACHE_SIZE, rs6000_cost->l2_cache_size,
4212			     global_options.x_param_values,
4213			     global_options_set.x_param_values);
4214
4215      /* Increase loop peeling limits based on performance analysis. */
4216      maybe_set_param_value (PARAM_MAX_PEELED_INSNS, 400,
4217			     global_options.x_param_values,
4218			     global_options_set.x_param_values);
4219      maybe_set_param_value (PARAM_MAX_COMPLETELY_PEELED_INSNS, 400,
4220			     global_options.x_param_values,
4221			     global_options_set.x_param_values);
4222
4223      /* If using typedef char *va_list, signal that
4224	 __builtin_va_start (&ap, 0) can be optimized to
4225	 ap = __builtin_next_arg (0).  */
4226      if (DEFAULT_ABI != ABI_V4)
4227	targetm.expand_builtin_va_start = NULL;
4228    }
4229
4230  /* Set up single/double float flags.
4231     If TARGET_HARD_FLOAT is set, but neither single or double is set,
4232     then set both flags. */
4233  if (TARGET_HARD_FLOAT && TARGET_FPRS
4234      && rs6000_single_float == 0 && rs6000_double_float == 0)
4235    rs6000_single_float = rs6000_double_float = 1;
4236
4237  /* If not explicitly specified via option, decide whether to generate indexed
4238     load/store instructions.  */
4239  if (TARGET_AVOID_XFORM == -1)
4240    /* Avoid indexed addressing when targeting Power6 in order to avoid the
4241     DERAT mispredict penalty.  However the LVE and STVE altivec instructions
4242     need indexed accesses and the type used is the scalar type of the element
4243     being loaded or stored.  */
4244    TARGET_AVOID_XFORM = (rs6000_cpu == PROCESSOR_POWER6 && TARGET_CMPB
4245			  && !TARGET_ALTIVEC);
4246
4247  /* Set the -mrecip options.  */
4248  if (rs6000_recip_name)
4249    {
4250      char *p = ASTRDUP (rs6000_recip_name);
4251      char *q;
4252      unsigned int mask, i;
4253      bool invert;
4254
4255      while ((q = strtok (p, ",")) != NULL)
4256	{
4257	  p = NULL;
4258	  if (*q == '!')
4259	    {
4260	      invert = true;
4261	      q++;
4262	    }
4263	  else
4264	    invert = false;
4265
4266	  if (!strcmp (q, "default"))
4267	    mask = ((TARGET_RECIP_PRECISION)
4268		    ? RECIP_HIGH_PRECISION : RECIP_LOW_PRECISION);
4269	  else
4270	    {
4271	      for (i = 0; i < ARRAY_SIZE (recip_options); i++)
4272		if (!strcmp (q, recip_options[i].string))
4273		  {
4274		    mask = recip_options[i].mask;
4275		    break;
4276		  }
4277
4278	      if (i == ARRAY_SIZE (recip_options))
4279		{
4280		  error ("unknown option for -mrecip=%s", q);
4281		  invert = false;
4282		  mask = 0;
4283		  ret = false;
4284		}
4285	    }
4286
4287	  if (invert)
4288	    rs6000_recip_control &= ~mask;
4289	  else
4290	    rs6000_recip_control |= mask;
4291	}
4292    }
4293
4294  /* Set the builtin mask of the various options used that could affect which
4295     builtins were used.  In the past we used target_flags, but we've run out
4296     of bits, and some options like SPE and PAIRED are no longer in
4297     target_flags.  */
4298  rs6000_builtin_mask = rs6000_builtin_mask_calculate ();
4299  if (TARGET_DEBUG_BUILTIN || TARGET_DEBUG_TARGET)
4300    rs6000_print_builtin_options (stderr, 0, "builtin mask",
4301				  rs6000_builtin_mask);
4302
4303  /* Initialize all of the registers.  */
4304  rs6000_init_hard_regno_mode_ok (global_init_p);
4305
4306  /* Save the initial options in case the user does function specific options */
4307  if (global_init_p)
4308    target_option_default_node = target_option_current_node
4309      = build_target_option_node (&global_options);
4310
4311  /* If not explicitly specified via option, decide whether to generate the
4312     extra blr's required to preserve the link stack on some cpus (eg, 476).  */
4313  if (TARGET_LINK_STACK == -1)
4314    SET_TARGET_LINK_STACK (rs6000_cpu == PROCESSOR_PPC476 && flag_pic);
4315
4316  return ret;
4317}
4318
4319/* Implement TARGET_OPTION_OVERRIDE.  On the RS/6000 this is used to
4320   define the target cpu type.  */
4321
4322static void
4323rs6000_option_override (void)
4324{
4325  (void) rs6000_option_override_internal (true);
4326
4327  /* Register machine-specific passes.  This needs to be done at start-up.
4328     It's convenient to do it here (like i386 does).  */
4329  opt_pass *pass_analyze_swaps = make_pass_analyze_swaps (g);
4330
4331  struct register_pass_info analyze_swaps_info
4332    = { pass_analyze_swaps, "cse1", 1, PASS_POS_INSERT_BEFORE };
4333
4334  register_pass (&analyze_swaps_info);
4335}
4336
4337
4338/* Implement targetm.vectorize.builtin_mask_for_load.  */
4339static tree
4340rs6000_builtin_mask_for_load (void)
4341{
4342  /* Don't use lvsl/vperm for P8 and similarly efficient machines.  */
4343  if ((TARGET_ALTIVEC && !TARGET_VSX)
4344      || (TARGET_VSX && !TARGET_EFFICIENT_UNALIGNED_VSX))
4345    return altivec_builtin_mask_for_load;
4346  else
4347    return 0;
4348}
4349
4350/* Implement LOOP_ALIGN. */
4351int
4352rs6000_loop_align (rtx label)
4353{
4354  basic_block bb;
4355  int ninsns;
4356
4357  /* Don't override loop alignment if -falign-loops was specified. */
4358  if (!can_override_loop_align)
4359    return align_loops_log;
4360
4361  bb = BLOCK_FOR_INSN (label);
4362  ninsns = num_loop_insns(bb->loop_father);
4363
4364  /* Align small loops to 32 bytes to fit in an icache sector, otherwise return default. */
4365  if (ninsns > 4 && ninsns <= 8
4366      && (rs6000_cpu == PROCESSOR_POWER4
4367	  || rs6000_cpu == PROCESSOR_POWER5
4368	  || rs6000_cpu == PROCESSOR_POWER6
4369	  || rs6000_cpu == PROCESSOR_POWER7
4370	  || rs6000_cpu == PROCESSOR_POWER8))
4371    return 5;
4372  else
4373    return align_loops_log;
4374}
4375
4376/* Implement TARGET_LOOP_ALIGN_MAX_SKIP. */
4377static int
4378rs6000_loop_align_max_skip (rtx_insn *label)
4379{
4380  return (1 << rs6000_loop_align (label)) - 1;
4381}
4382
4383/* Return true iff, data reference of TYPE can reach vector alignment (16)
4384   after applying N number of iterations.  This routine does not determine
4385   how may iterations are required to reach desired alignment.  */
4386
4387static bool
4388rs6000_vector_alignment_reachable (const_tree type ATTRIBUTE_UNUSED, bool is_packed)
4389{
4390  if (is_packed)
4391    return false;
4392
4393  if (TARGET_32BIT)
4394    {
4395      if (rs6000_alignment_flags == MASK_ALIGN_NATURAL)
4396        return true;
4397
4398      if (rs6000_alignment_flags ==  MASK_ALIGN_POWER)
4399        return true;
4400
4401      return false;
4402    }
4403  else
4404    {
4405      if (TARGET_MACHO)
4406        return false;
4407
4408      /* Assuming that all other types are naturally aligned. CHECKME!  */
4409      return true;
4410    }
4411}
4412
4413/* Return true if the vector misalignment factor is supported by the
4414   target.  */
4415static bool
4416rs6000_builtin_support_vector_misalignment (machine_mode mode,
4417					    const_tree type,
4418					    int misalignment,
4419					    bool is_packed)
4420{
4421  if (TARGET_VSX)
4422    {
4423      if (TARGET_EFFICIENT_UNALIGNED_VSX)
4424	return true;
4425
4426      /* Return if movmisalign pattern is not supported for this mode.  */
4427      if (optab_handler (movmisalign_optab, mode) == CODE_FOR_nothing)
4428        return false;
4429
4430      if (misalignment == -1)
4431	{
4432	  /* Misalignment factor is unknown at compile time but we know
4433	     it's word aligned.  */
4434	  if (rs6000_vector_alignment_reachable (type, is_packed))
4435            {
4436              int element_size = TREE_INT_CST_LOW (TYPE_SIZE (type));
4437
4438              if (element_size == 64 || element_size == 32)
4439               return true;
4440            }
4441
4442	  return false;
4443	}
4444
4445      /* VSX supports word-aligned vector.  */
4446      if (misalignment % 4 == 0)
4447	return true;
4448    }
4449  return false;
4450}
4451
4452/* Implement targetm.vectorize.builtin_vectorization_cost.  */
4453static int
4454rs6000_builtin_vectorization_cost (enum vect_cost_for_stmt type_of_cost,
4455                                   tree vectype, int misalign)
4456{
4457  unsigned elements;
4458  tree elem_type;
4459
4460  switch (type_of_cost)
4461    {
4462      case scalar_stmt:
4463      case scalar_load:
4464      case scalar_store:
4465      case vector_stmt:
4466      case vector_load:
4467      case vector_store:
4468      case vec_to_scalar:
4469      case scalar_to_vec:
4470      case cond_branch_not_taken:
4471        return 1;
4472
4473      case vec_perm:
4474	if (TARGET_VSX)
4475	  return 3;
4476	else
4477	  return 1;
4478
4479      case vec_promote_demote:
4480        if (TARGET_VSX)
4481          return 4;
4482        else
4483          return 1;
4484
4485      case cond_branch_taken:
4486        return 3;
4487
4488      case unaligned_load:
4489	if (TARGET_EFFICIENT_UNALIGNED_VSX)
4490	  return 1;
4491
4492        if (TARGET_VSX && TARGET_ALLOW_MOVMISALIGN)
4493          {
4494            elements = TYPE_VECTOR_SUBPARTS (vectype);
4495            if (elements == 2)
4496              /* Double word aligned.  */
4497              return 2;
4498
4499            if (elements == 4)
4500              {
4501                switch (misalign)
4502                  {
4503                    case 8:
4504                      /* Double word aligned.  */
4505                      return 2;
4506
4507                    case -1:
4508                      /* Unknown misalignment.  */
4509                    case 4:
4510                    case 12:
4511                      /* Word aligned.  */
4512                      return 22;
4513
4514                    default:
4515                      gcc_unreachable ();
4516                  }
4517              }
4518          }
4519
4520        if (TARGET_ALTIVEC)
4521          /* Misaligned loads are not supported.  */
4522          gcc_unreachable ();
4523
4524        return 2;
4525
4526      case unaligned_store:
4527	if (TARGET_EFFICIENT_UNALIGNED_VSX)
4528	  return 1;
4529
4530        if (TARGET_VSX && TARGET_ALLOW_MOVMISALIGN)
4531          {
4532            elements = TYPE_VECTOR_SUBPARTS (vectype);
4533            if (elements == 2)
4534              /* Double word aligned.  */
4535              return 2;
4536
4537            if (elements == 4)
4538              {
4539                switch (misalign)
4540                  {
4541                    case 8:
4542                      /* Double word aligned.  */
4543                      return 2;
4544
4545                    case -1:
4546                      /* Unknown misalignment.  */
4547                    case 4:
4548                    case 12:
4549                      /* Word aligned.  */
4550                      return 23;
4551
4552                    default:
4553                      gcc_unreachable ();
4554                  }
4555              }
4556          }
4557
4558        if (TARGET_ALTIVEC)
4559          /* Misaligned stores are not supported.  */
4560          gcc_unreachable ();
4561
4562        return 2;
4563
4564      case vec_construct:
4565	elements = TYPE_VECTOR_SUBPARTS (vectype);
4566	elem_type = TREE_TYPE (vectype);
4567	/* 32-bit vectors loaded into registers are stored as double
4568	   precision, so we need n/2 converts in addition to the usual
4569	   n/2 merges to construct a vector of short floats from them.  */
4570	if (SCALAR_FLOAT_TYPE_P (elem_type)
4571	    && TYPE_PRECISION (elem_type) == 32)
4572	  return elements + 1;
4573	else
4574	  return elements / 2 + 1;
4575
4576      default:
4577        gcc_unreachable ();
4578    }
4579}
4580
4581/* Implement targetm.vectorize.preferred_simd_mode.  */
4582
4583static machine_mode
4584rs6000_preferred_simd_mode (machine_mode mode)
4585{
4586  if (TARGET_VSX)
4587    switch (mode)
4588      {
4589      case DFmode:
4590	return V2DFmode;
4591      default:;
4592      }
4593  if (TARGET_ALTIVEC || TARGET_VSX)
4594    switch (mode)
4595      {
4596      case SFmode:
4597	return V4SFmode;
4598      case TImode:
4599	return V1TImode;
4600      case DImode:
4601	return V2DImode;
4602      case SImode:
4603	return V4SImode;
4604      case HImode:
4605	return V8HImode;
4606      case QImode:
4607	return V16QImode;
4608      default:;
4609      }
4610  if (TARGET_SPE)
4611    switch (mode)
4612      {
4613      case SFmode:
4614	return V2SFmode;
4615      case SImode:
4616	return V2SImode;
4617      default:;
4618      }
4619  if (TARGET_PAIRED_FLOAT
4620      && mode == SFmode)
4621    return V2SFmode;
4622  return word_mode;
4623}
4624
4625typedef struct _rs6000_cost_data
4626{
4627  struct loop *loop_info;
4628  unsigned cost[3];
4629} rs6000_cost_data;
4630
4631/* Test for likely overcommitment of vector hardware resources.  If a
4632   loop iteration is relatively large, and too large a percentage of
4633   instructions in the loop are vectorized, the cost model may not
4634   adequately reflect delays from unavailable vector resources.
4635   Penalize the loop body cost for this case.  */
4636
4637static void
4638rs6000_density_test (rs6000_cost_data *data)
4639{
4640  const int DENSITY_PCT_THRESHOLD = 85;
4641  const int DENSITY_SIZE_THRESHOLD = 70;
4642  const int DENSITY_PENALTY = 10;
4643  struct loop *loop = data->loop_info;
4644  basic_block *bbs = get_loop_body (loop);
4645  int nbbs = loop->num_nodes;
4646  int vec_cost = data->cost[vect_body], not_vec_cost = 0;
4647  int i, density_pct;
4648
4649  for (i = 0; i < nbbs; i++)
4650    {
4651      basic_block bb = bbs[i];
4652      gimple_stmt_iterator gsi;
4653
4654      for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
4655	{
4656	  gimple stmt = gsi_stmt (gsi);
4657	  stmt_vec_info stmt_info = vinfo_for_stmt (stmt);
4658
4659	  if (!STMT_VINFO_RELEVANT_P (stmt_info)
4660	      && !STMT_VINFO_IN_PATTERN_P (stmt_info))
4661	    not_vec_cost++;
4662	}
4663    }
4664
4665  free (bbs);
4666  density_pct = (vec_cost * 100) / (vec_cost + not_vec_cost);
4667
4668  if (density_pct > DENSITY_PCT_THRESHOLD
4669      && vec_cost + not_vec_cost > DENSITY_SIZE_THRESHOLD)
4670    {
4671      data->cost[vect_body] = vec_cost * (100 + DENSITY_PENALTY) / 100;
4672      if (dump_enabled_p ())
4673	dump_printf_loc (MSG_NOTE, vect_location,
4674			 "density %d%%, cost %d exceeds threshold, penalizing "
4675			 "loop body cost by %d%%", density_pct,
4676			 vec_cost + not_vec_cost, DENSITY_PENALTY);
4677    }
4678}
4679
4680/* Implement targetm.vectorize.init_cost.  */
4681
4682static void *
4683rs6000_init_cost (struct loop *loop_info)
4684{
4685  rs6000_cost_data *data = XNEW (struct _rs6000_cost_data);
4686  data->loop_info = loop_info;
4687  data->cost[vect_prologue] = 0;
4688  data->cost[vect_body]     = 0;
4689  data->cost[vect_epilogue] = 0;
4690  return data;
4691}
4692
4693/* Implement targetm.vectorize.add_stmt_cost.  */
4694
4695static unsigned
4696rs6000_add_stmt_cost (void *data, int count, enum vect_cost_for_stmt kind,
4697		      struct _stmt_vec_info *stmt_info, int misalign,
4698		      enum vect_cost_model_location where)
4699{
4700  rs6000_cost_data *cost_data = (rs6000_cost_data*) data;
4701  unsigned retval = 0;
4702
4703  if (flag_vect_cost_model)
4704    {
4705      tree vectype = stmt_info ? stmt_vectype (stmt_info) : NULL_TREE;
4706      int stmt_cost = rs6000_builtin_vectorization_cost (kind, vectype,
4707							 misalign);
4708      /* Statements in an inner loop relative to the loop being
4709	 vectorized are weighted more heavily.  The value here is
4710	 arbitrary and could potentially be improved with analysis.  */
4711      if (where == vect_body && stmt_info && stmt_in_inner_loop_p (stmt_info))
4712	count *= 50;  /* FIXME.  */
4713
4714      retval = (unsigned) (count * stmt_cost);
4715      cost_data->cost[where] += retval;
4716    }
4717
4718  return retval;
4719}
4720
4721/* Implement targetm.vectorize.finish_cost.  */
4722
4723static void
4724rs6000_finish_cost (void *data, unsigned *prologue_cost,
4725		    unsigned *body_cost, unsigned *epilogue_cost)
4726{
4727  rs6000_cost_data *cost_data = (rs6000_cost_data*) data;
4728
4729  if (cost_data->loop_info)
4730    rs6000_density_test (cost_data);
4731
4732  *prologue_cost = cost_data->cost[vect_prologue];
4733  *body_cost     = cost_data->cost[vect_body];
4734  *epilogue_cost = cost_data->cost[vect_epilogue];
4735}
4736
4737/* Implement targetm.vectorize.destroy_cost_data.  */
4738
4739static void
4740rs6000_destroy_cost_data (void *data)
4741{
4742  free (data);
4743}
4744
4745/* Handler for the Mathematical Acceleration Subsystem (mass) interface to a
4746   library with vectorized intrinsics.  */
4747
4748static tree
4749rs6000_builtin_vectorized_libmass (tree fndecl, tree type_out, tree type_in)
4750{
4751  char name[32];
4752  const char *suffix = NULL;
4753  tree fntype, new_fndecl, bdecl = NULL_TREE;
4754  int n_args = 1;
4755  const char *bname;
4756  machine_mode el_mode, in_mode;
4757  int n, in_n;
4758
4759  /* Libmass is suitable for unsafe math only as it does not correctly support
4760     parts of IEEE with the required precision such as denormals.  Only support
4761     it if we have VSX to use the simd d2 or f4 functions.
4762     XXX: Add variable length support.  */
4763  if (!flag_unsafe_math_optimizations || !TARGET_VSX)
4764    return NULL_TREE;
4765
4766  el_mode = TYPE_MODE (TREE_TYPE (type_out));
4767  n = TYPE_VECTOR_SUBPARTS (type_out);
4768  in_mode = TYPE_MODE (TREE_TYPE (type_in));
4769  in_n = TYPE_VECTOR_SUBPARTS (type_in);
4770  if (el_mode != in_mode
4771      || n != in_n)
4772    return NULL_TREE;
4773
4774  if (DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL)
4775    {
4776      enum built_in_function fn = DECL_FUNCTION_CODE (fndecl);
4777      switch (fn)
4778	{
4779	case BUILT_IN_ATAN2:
4780	case BUILT_IN_HYPOT:
4781	case BUILT_IN_POW:
4782	  n_args = 2;
4783	  /* fall through */
4784
4785	case BUILT_IN_ACOS:
4786	case BUILT_IN_ACOSH:
4787	case BUILT_IN_ASIN:
4788	case BUILT_IN_ASINH:
4789	case BUILT_IN_ATAN:
4790	case BUILT_IN_ATANH:
4791	case BUILT_IN_CBRT:
4792	case BUILT_IN_COS:
4793	case BUILT_IN_COSH:
4794	case BUILT_IN_ERF:
4795	case BUILT_IN_ERFC:
4796	case BUILT_IN_EXP2:
4797	case BUILT_IN_EXP:
4798	case BUILT_IN_EXPM1:
4799	case BUILT_IN_LGAMMA:
4800	case BUILT_IN_LOG10:
4801	case BUILT_IN_LOG1P:
4802	case BUILT_IN_LOG2:
4803	case BUILT_IN_LOG:
4804	case BUILT_IN_SIN:
4805	case BUILT_IN_SINH:
4806	case BUILT_IN_SQRT:
4807	case BUILT_IN_TAN:
4808	case BUILT_IN_TANH:
4809	  bdecl = builtin_decl_implicit (fn);
4810	  suffix = "d2";				/* pow -> powd2 */
4811	  if (el_mode != DFmode
4812	      || n != 2
4813	      || !bdecl)
4814	    return NULL_TREE;
4815	  break;
4816
4817	case BUILT_IN_ATAN2F:
4818	case BUILT_IN_HYPOTF:
4819	case BUILT_IN_POWF:
4820	  n_args = 2;
4821	  /* fall through */
4822
4823	case BUILT_IN_ACOSF:
4824	case BUILT_IN_ACOSHF:
4825	case BUILT_IN_ASINF:
4826	case BUILT_IN_ASINHF:
4827	case BUILT_IN_ATANF:
4828	case BUILT_IN_ATANHF:
4829	case BUILT_IN_CBRTF:
4830	case BUILT_IN_COSF:
4831	case BUILT_IN_COSHF:
4832	case BUILT_IN_ERFF:
4833	case BUILT_IN_ERFCF:
4834	case BUILT_IN_EXP2F:
4835	case BUILT_IN_EXPF:
4836	case BUILT_IN_EXPM1F:
4837	case BUILT_IN_LGAMMAF:
4838	case BUILT_IN_LOG10F:
4839	case BUILT_IN_LOG1PF:
4840	case BUILT_IN_LOG2F:
4841	case BUILT_IN_LOGF:
4842	case BUILT_IN_SINF:
4843	case BUILT_IN_SINHF:
4844	case BUILT_IN_SQRTF:
4845	case BUILT_IN_TANF:
4846	case BUILT_IN_TANHF:
4847	  bdecl = builtin_decl_implicit (fn);
4848	  suffix = "4";					/* powf -> powf4 */
4849	  if (el_mode != SFmode
4850	      || n != 4
4851	      || !bdecl)
4852	    return NULL_TREE;
4853	  break;
4854
4855	default:
4856	  return NULL_TREE;
4857	}
4858    }
4859  else
4860    return NULL_TREE;
4861
4862  gcc_assert (suffix != NULL);
4863  bname = IDENTIFIER_POINTER (DECL_NAME (bdecl));
4864  if (!bname)
4865    return NULL_TREE;
4866
4867  strcpy (name, bname + sizeof ("__builtin_") - 1);
4868  strcat (name, suffix);
4869
4870  if (n_args == 1)
4871    fntype = build_function_type_list (type_out, type_in, NULL);
4872  else if (n_args == 2)
4873    fntype = build_function_type_list (type_out, type_in, type_in, NULL);
4874  else
4875    gcc_unreachable ();
4876
4877  /* Build a function declaration for the vectorized function.  */
4878  new_fndecl = build_decl (BUILTINS_LOCATION,
4879			   FUNCTION_DECL, get_identifier (name), fntype);
4880  TREE_PUBLIC (new_fndecl) = 1;
4881  DECL_EXTERNAL (new_fndecl) = 1;
4882  DECL_IS_NOVOPS (new_fndecl) = 1;
4883  TREE_READONLY (new_fndecl) = 1;
4884
4885  return new_fndecl;
4886}
4887
4888/* Returns a function decl for a vectorized version of the builtin function
4889   with builtin function code FN and the result vector type TYPE, or NULL_TREE
4890   if it is not available.  */
4891
4892static tree
4893rs6000_builtin_vectorized_function (tree fndecl, tree type_out,
4894				    tree type_in)
4895{
4896  machine_mode in_mode, out_mode;
4897  int in_n, out_n;
4898
4899  if (TARGET_DEBUG_BUILTIN)
4900    fprintf (stderr, "rs6000_builtin_vectorized_function (%s, %s, %s)\n",
4901	     IDENTIFIER_POINTER (DECL_NAME (fndecl)),
4902	     GET_MODE_NAME (TYPE_MODE (type_out)),
4903	     GET_MODE_NAME (TYPE_MODE (type_in)));
4904
4905  if (TREE_CODE (type_out) != VECTOR_TYPE
4906      || TREE_CODE (type_in) != VECTOR_TYPE
4907      || !TARGET_VECTORIZE_BUILTINS)
4908    return NULL_TREE;
4909
4910  out_mode = TYPE_MODE (TREE_TYPE (type_out));
4911  out_n = TYPE_VECTOR_SUBPARTS (type_out);
4912  in_mode = TYPE_MODE (TREE_TYPE (type_in));
4913  in_n = TYPE_VECTOR_SUBPARTS (type_in);
4914
4915  if (DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL)
4916    {
4917      enum built_in_function fn = DECL_FUNCTION_CODE (fndecl);
4918      switch (fn)
4919	{
4920	case BUILT_IN_CLZIMAX:
4921	case BUILT_IN_CLZLL:
4922	case BUILT_IN_CLZL:
4923	case BUILT_IN_CLZ:
4924	  if (TARGET_P8_VECTOR && in_mode == out_mode && out_n == in_n)
4925	    {
4926	      if (out_mode == QImode && out_n == 16)
4927		return rs6000_builtin_decls[P8V_BUILTIN_VCLZB];
4928	      else if (out_mode == HImode && out_n == 8)
4929		return rs6000_builtin_decls[P8V_BUILTIN_VCLZH];
4930	      else if (out_mode == SImode && out_n == 4)
4931		return rs6000_builtin_decls[P8V_BUILTIN_VCLZW];
4932	      else if (out_mode == DImode && out_n == 2)
4933		return rs6000_builtin_decls[P8V_BUILTIN_VCLZD];
4934	    }
4935	  break;
4936	case BUILT_IN_COPYSIGN:
4937	  if (VECTOR_UNIT_VSX_P (V2DFmode)
4938	      && out_mode == DFmode && out_n == 2
4939	      && in_mode == DFmode && in_n == 2)
4940	    return rs6000_builtin_decls[VSX_BUILTIN_CPSGNDP];
4941	  break;
4942	case BUILT_IN_COPYSIGNF:
4943	  if (out_mode != SFmode || out_n != 4
4944	      || in_mode != SFmode || in_n != 4)
4945	    break;
4946	  if (VECTOR_UNIT_VSX_P (V4SFmode))
4947	    return rs6000_builtin_decls[VSX_BUILTIN_CPSGNSP];
4948	  if (VECTOR_UNIT_ALTIVEC_P (V4SFmode))
4949	    return rs6000_builtin_decls[ALTIVEC_BUILTIN_COPYSIGN_V4SF];
4950	  break;
4951	case BUILT_IN_POPCOUNTIMAX:
4952	case BUILT_IN_POPCOUNTLL:
4953	case BUILT_IN_POPCOUNTL:
4954	case BUILT_IN_POPCOUNT:
4955	  if (TARGET_P8_VECTOR && in_mode == out_mode && out_n == in_n)
4956	    {
4957	      if (out_mode == QImode && out_n == 16)
4958		return rs6000_builtin_decls[P8V_BUILTIN_VPOPCNTB];
4959	      else if (out_mode == HImode && out_n == 8)
4960		return rs6000_builtin_decls[P8V_BUILTIN_VPOPCNTH];
4961	      else if (out_mode == SImode && out_n == 4)
4962		return rs6000_builtin_decls[P8V_BUILTIN_VPOPCNTW];
4963	      else if (out_mode == DImode && out_n == 2)
4964		return rs6000_builtin_decls[P8V_BUILTIN_VPOPCNTD];
4965	    }
4966	  break;
4967	case BUILT_IN_SQRT:
4968	  if (VECTOR_UNIT_VSX_P (V2DFmode)
4969	      && out_mode == DFmode && out_n == 2
4970	      && in_mode == DFmode && in_n == 2)
4971	    return rs6000_builtin_decls[VSX_BUILTIN_XVSQRTDP];
4972	  break;
4973	case BUILT_IN_SQRTF:
4974	  if (VECTOR_UNIT_VSX_P (V4SFmode)
4975	      && out_mode == SFmode && out_n == 4
4976	      && in_mode == SFmode && in_n == 4)
4977	    return rs6000_builtin_decls[VSX_BUILTIN_XVSQRTSP];
4978	  break;
4979	case BUILT_IN_CEIL:
4980	  if (VECTOR_UNIT_VSX_P (V2DFmode)
4981	      && out_mode == DFmode && out_n == 2
4982	      && in_mode == DFmode && in_n == 2)
4983	    return rs6000_builtin_decls[VSX_BUILTIN_XVRDPIP];
4984	  break;
4985	case BUILT_IN_CEILF:
4986	  if (out_mode != SFmode || out_n != 4
4987	      || in_mode != SFmode || in_n != 4)
4988	    break;
4989	  if (VECTOR_UNIT_VSX_P (V4SFmode))
4990	    return rs6000_builtin_decls[VSX_BUILTIN_XVRSPIP];
4991	  if (VECTOR_UNIT_ALTIVEC_P (V4SFmode))
4992	    return rs6000_builtin_decls[ALTIVEC_BUILTIN_VRFIP];
4993	  break;
4994	case BUILT_IN_FLOOR:
4995	  if (VECTOR_UNIT_VSX_P (V2DFmode)
4996	      && out_mode == DFmode && out_n == 2
4997	      && in_mode == DFmode && in_n == 2)
4998	    return rs6000_builtin_decls[VSX_BUILTIN_XVRDPIM];
4999	  break;
5000	case BUILT_IN_FLOORF:
5001	  if (out_mode != SFmode || out_n != 4
5002	      || in_mode != SFmode || in_n != 4)
5003	    break;
5004	  if (VECTOR_UNIT_VSX_P (V4SFmode))
5005	    return rs6000_builtin_decls[VSX_BUILTIN_XVRSPIM];
5006	  if (VECTOR_UNIT_ALTIVEC_P (V4SFmode))
5007	    return rs6000_builtin_decls[ALTIVEC_BUILTIN_VRFIM];
5008	  break;
5009	case BUILT_IN_FMA:
5010	  if (VECTOR_UNIT_VSX_P (V2DFmode)
5011	      && out_mode == DFmode && out_n == 2
5012	      && in_mode == DFmode && in_n == 2)
5013	    return rs6000_builtin_decls[VSX_BUILTIN_XVMADDDP];
5014	  break;
5015	case BUILT_IN_FMAF:
5016	  if (VECTOR_UNIT_VSX_P (V4SFmode)
5017	      && out_mode == SFmode && out_n == 4
5018	      && in_mode == SFmode && in_n == 4)
5019	    return rs6000_builtin_decls[VSX_BUILTIN_XVMADDSP];
5020	  else if (VECTOR_UNIT_ALTIVEC_P (V4SFmode)
5021	      && out_mode == SFmode && out_n == 4
5022	      && in_mode == SFmode && in_n == 4)
5023	    return rs6000_builtin_decls[ALTIVEC_BUILTIN_VMADDFP];
5024	  break;
5025	case BUILT_IN_TRUNC:
5026	  if (VECTOR_UNIT_VSX_P (V2DFmode)
5027	      && out_mode == DFmode && out_n == 2
5028	      && in_mode == DFmode && in_n == 2)
5029	    return rs6000_builtin_decls[VSX_BUILTIN_XVRDPIZ];
5030	  break;
5031	case BUILT_IN_TRUNCF:
5032	  if (out_mode != SFmode || out_n != 4
5033	      || in_mode != SFmode || in_n != 4)
5034	    break;
5035	  if (VECTOR_UNIT_VSX_P (V4SFmode))
5036	    return rs6000_builtin_decls[VSX_BUILTIN_XVRSPIZ];
5037	  if (VECTOR_UNIT_ALTIVEC_P (V4SFmode))
5038	    return rs6000_builtin_decls[ALTIVEC_BUILTIN_VRFIZ];
5039	  break;
5040	case BUILT_IN_NEARBYINT:
5041	  if (VECTOR_UNIT_VSX_P (V2DFmode)
5042	      && flag_unsafe_math_optimizations
5043	      && out_mode == DFmode && out_n == 2
5044	      && in_mode == DFmode && in_n == 2)
5045	    return rs6000_builtin_decls[VSX_BUILTIN_XVRDPI];
5046	  break;
5047	case BUILT_IN_NEARBYINTF:
5048	  if (VECTOR_UNIT_VSX_P (V4SFmode)
5049	      && flag_unsafe_math_optimizations
5050	      && out_mode == SFmode && out_n == 4
5051	      && in_mode == SFmode && in_n == 4)
5052	    return rs6000_builtin_decls[VSX_BUILTIN_XVRSPI];
5053	  break;
5054	case BUILT_IN_RINT:
5055	  if (VECTOR_UNIT_VSX_P (V2DFmode)
5056	      && !flag_trapping_math
5057	      && out_mode == DFmode && out_n == 2
5058	      && in_mode == DFmode && in_n == 2)
5059	    return rs6000_builtin_decls[VSX_BUILTIN_XVRDPIC];
5060	  break;
5061	case BUILT_IN_RINTF:
5062	  if (VECTOR_UNIT_VSX_P (V4SFmode)
5063	      && !flag_trapping_math
5064	      && out_mode == SFmode && out_n == 4
5065	      && in_mode == SFmode && in_n == 4)
5066	    return rs6000_builtin_decls[VSX_BUILTIN_XVRSPIC];
5067	  break;
5068	default:
5069	  break;
5070	}
5071    }
5072
5073  else if (DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_MD)
5074    {
5075      enum rs6000_builtins fn
5076	= (enum rs6000_builtins)DECL_FUNCTION_CODE (fndecl);
5077      switch (fn)
5078	{
5079	case RS6000_BUILTIN_RSQRTF:
5080	  if (VECTOR_UNIT_ALTIVEC_OR_VSX_P (V4SFmode)
5081	      && out_mode == SFmode && out_n == 4
5082	      && in_mode == SFmode && in_n == 4)
5083	    return rs6000_builtin_decls[ALTIVEC_BUILTIN_VRSQRTFP];
5084	  break;
5085	case RS6000_BUILTIN_RSQRT:
5086	  if (VECTOR_UNIT_VSX_P (V2DFmode)
5087	      && out_mode == DFmode && out_n == 2
5088	      && in_mode == DFmode && in_n == 2)
5089	    return rs6000_builtin_decls[VSX_BUILTIN_RSQRT_2DF];
5090	  break;
5091	case RS6000_BUILTIN_RECIPF:
5092	  if (VECTOR_UNIT_ALTIVEC_OR_VSX_P (V4SFmode)
5093	      && out_mode == SFmode && out_n == 4
5094	      && in_mode == SFmode && in_n == 4)
5095	    return rs6000_builtin_decls[ALTIVEC_BUILTIN_VRECIPFP];
5096	  break;
5097	case RS6000_BUILTIN_RECIP:
5098	  if (VECTOR_UNIT_VSX_P (V2DFmode)
5099	      && out_mode == DFmode && out_n == 2
5100	      && in_mode == DFmode && in_n == 2)
5101	    return rs6000_builtin_decls[VSX_BUILTIN_RECIP_V2DF];
5102	  break;
5103	default:
5104	  break;
5105	}
5106    }
5107
5108  /* Generate calls to libmass if appropriate.  */
5109  if (rs6000_veclib_handler)
5110    return rs6000_veclib_handler (fndecl, type_out, type_in);
5111
5112  return NULL_TREE;
5113}
5114
5115/* Default CPU string for rs6000*_file_start functions.  */
5116static const char *rs6000_default_cpu;
5117
5118/* Do anything needed at the start of the asm file.  */
5119
5120static void
5121rs6000_file_start (void)
5122{
5123  char buffer[80];
5124  const char *start = buffer;
5125  FILE *file = asm_out_file;
5126
5127  rs6000_default_cpu = TARGET_CPU_DEFAULT;
5128
5129  default_file_start ();
5130
5131  if (flag_verbose_asm)
5132    {
5133      sprintf (buffer, "\n%s rs6000/powerpc options:", ASM_COMMENT_START);
5134
5135      if (rs6000_default_cpu != 0 && rs6000_default_cpu[0] != '\0')
5136	{
5137	  fprintf (file, "%s --with-cpu=%s", start, rs6000_default_cpu);
5138	  start = "";
5139	}
5140
5141      if (global_options_set.x_rs6000_cpu_index)
5142	{
5143	  fprintf (file, "%s -mcpu=%s", start,
5144		   processor_target_table[rs6000_cpu_index].name);
5145	  start = "";
5146	}
5147
5148      if (global_options_set.x_rs6000_tune_index)
5149	{
5150	  fprintf (file, "%s -mtune=%s", start,
5151		   processor_target_table[rs6000_tune_index].name);
5152	  start = "";
5153	}
5154
5155      if (PPC405_ERRATUM77)
5156	{
5157	  fprintf (file, "%s PPC405CR_ERRATUM77", start);
5158	  start = "";
5159	}
5160
5161#ifdef USING_ELFOS_H
5162      switch (rs6000_sdata)
5163	{
5164	case SDATA_NONE: fprintf (file, "%s -msdata=none", start); start = ""; break;
5165	case SDATA_DATA: fprintf (file, "%s -msdata=data", start); start = ""; break;
5166	case SDATA_SYSV: fprintf (file, "%s -msdata=sysv", start); start = ""; break;
5167	case SDATA_EABI: fprintf (file, "%s -msdata=eabi", start); start = ""; break;
5168	}
5169
5170      if (rs6000_sdata && g_switch_value)
5171	{
5172	  fprintf (file, "%s -G %d", start,
5173		   g_switch_value);
5174	  start = "";
5175	}
5176#endif
5177
5178      if (*start == '\0')
5179	putc ('\n', file);
5180    }
5181
5182#ifdef USING_ELFOS_H
5183  if (rs6000_default_cpu == 0 || rs6000_default_cpu[0] == '\0'
5184      || !global_options_set.x_rs6000_cpu_index)
5185    {
5186      fputs ("\t.machine ", asm_out_file);
5187      if ((rs6000_isa_flags & OPTION_MASK_DIRECT_MOVE) != 0)
5188	fputs ("power8\n", asm_out_file);
5189      else if ((rs6000_isa_flags & OPTION_MASK_POPCNTD) != 0)
5190	fputs ("power7\n", asm_out_file);
5191      else if ((rs6000_isa_flags & OPTION_MASK_CMPB) != 0)
5192	fputs ("power6\n", asm_out_file);
5193      else if ((rs6000_isa_flags & OPTION_MASK_POPCNTB) != 0)
5194	fputs ("power5\n", asm_out_file);
5195      else if ((rs6000_isa_flags & OPTION_MASK_MFCRF) != 0)
5196	fputs ("power4\n", asm_out_file);
5197      else if ((rs6000_isa_flags & OPTION_MASK_POWERPC64) != 0)
5198	fputs ("ppc64\n", asm_out_file);
5199      else
5200	fputs ("ppc\n", asm_out_file);
5201    }
5202#endif
5203
5204  if (DEFAULT_ABI == ABI_ELFv2)
5205    fprintf (file, "\t.abiversion 2\n");
5206
5207  if (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2
5208      || (TARGET_ELF && flag_pic == 2))
5209    {
5210      switch_to_section (toc_section);
5211      switch_to_section (text_section);
5212    }
5213}
5214
5215
5216/* Return nonzero if this function is known to have a null epilogue.  */
5217
5218int
5219direct_return (void)
5220{
5221  if (reload_completed)
5222    {
5223      rs6000_stack_t *info = rs6000_stack_info ();
5224
5225      if (info->first_gp_reg_save == 32
5226	  && info->first_fp_reg_save == 64
5227	  && info->first_altivec_reg_save == LAST_ALTIVEC_REGNO + 1
5228	  && ! info->lr_save_p
5229	  && ! info->cr_save_p
5230	  && info->vrsave_mask == 0
5231	  && ! info->push_p)
5232	return 1;
5233    }
5234
5235  return 0;
5236}
5237
5238/* Return the number of instructions it takes to form a constant in an
5239   integer register.  */
5240
5241int
5242num_insns_constant_wide (HOST_WIDE_INT value)
5243{
5244  /* signed constant loadable with addi */
5245  if (((unsigned HOST_WIDE_INT) value + 0x8000) < 0x10000)
5246    return 1;
5247
5248  /* constant loadable with addis */
5249  else if ((value & 0xffff) == 0
5250	   && (value >> 31 == -1 || value >> 31 == 0))
5251    return 1;
5252
5253  else if (TARGET_POWERPC64)
5254    {
5255      HOST_WIDE_INT low  = ((value & 0xffffffff) ^ 0x80000000) - 0x80000000;
5256      HOST_WIDE_INT high = value >> 31;
5257
5258      if (high == 0 || high == -1)
5259	return 2;
5260
5261      high >>= 1;
5262
5263      if (low == 0)
5264	return num_insns_constant_wide (high) + 1;
5265      else if (high == 0)
5266	return num_insns_constant_wide (low) + 1;
5267      else
5268	return (num_insns_constant_wide (high)
5269		+ num_insns_constant_wide (low) + 1);
5270    }
5271
5272  else
5273    return 2;
5274}
5275
5276int
5277num_insns_constant (rtx op, machine_mode mode)
5278{
5279  HOST_WIDE_INT low, high;
5280
5281  switch (GET_CODE (op))
5282    {
5283    case CONST_INT:
5284      if ((INTVAL (op) >> 31) != 0 && (INTVAL (op) >> 31) != -1
5285	  && mask64_operand (op, mode))
5286	return 2;
5287      else
5288	return num_insns_constant_wide (INTVAL (op));
5289
5290    case CONST_WIDE_INT:
5291      {
5292	int i;
5293	int ins = CONST_WIDE_INT_NUNITS (op) - 1;
5294	for (i = 0; i < CONST_WIDE_INT_NUNITS (op); i++)
5295	  ins += num_insns_constant_wide (CONST_WIDE_INT_ELT (op, i));
5296	return ins;
5297      }
5298
5299      case CONST_DOUBLE:
5300	if (mode == SFmode || mode == SDmode)
5301	  {
5302	    long l;
5303	    REAL_VALUE_TYPE rv;
5304
5305	    REAL_VALUE_FROM_CONST_DOUBLE (rv, op);
5306	    if (DECIMAL_FLOAT_MODE_P (mode))
5307	      REAL_VALUE_TO_TARGET_DECIMAL32 (rv, l);
5308	    else
5309	      REAL_VALUE_TO_TARGET_SINGLE (rv, l);
5310	    return num_insns_constant_wide ((HOST_WIDE_INT) l);
5311	  }
5312
5313	long l[2];
5314	REAL_VALUE_TYPE rv;
5315
5316	REAL_VALUE_FROM_CONST_DOUBLE (rv, op);
5317	if (DECIMAL_FLOAT_MODE_P (mode))
5318	  REAL_VALUE_TO_TARGET_DECIMAL64 (rv, l);
5319	else
5320	  REAL_VALUE_TO_TARGET_DOUBLE (rv, l);
5321	high = l[WORDS_BIG_ENDIAN == 0];
5322	low  = l[WORDS_BIG_ENDIAN != 0];
5323
5324	if (TARGET_32BIT)
5325	  return (num_insns_constant_wide (low)
5326		  + num_insns_constant_wide (high));
5327	else
5328	  {
5329	    if ((high == 0 && low >= 0)
5330		|| (high == -1 && low < 0))
5331	      return num_insns_constant_wide (low);
5332
5333	    else if (mask64_operand (op, mode))
5334	      return 2;
5335
5336	    else if (low == 0)
5337	      return num_insns_constant_wide (high) + 1;
5338
5339	    else
5340	      return (num_insns_constant_wide (high)
5341		      + num_insns_constant_wide (low) + 1);
5342	  }
5343
5344    default:
5345      gcc_unreachable ();
5346    }
5347}
5348
5349/* Interpret element ELT of the CONST_VECTOR OP as an integer value.
5350   If the mode of OP is MODE_VECTOR_INT, this simply returns the
5351   corresponding element of the vector, but for V4SFmode and V2SFmode,
5352   the corresponding "float" is interpreted as an SImode integer.  */
5353
5354HOST_WIDE_INT
5355const_vector_elt_as_int (rtx op, unsigned int elt)
5356{
5357  rtx tmp;
5358
5359  /* We can't handle V2DImode and V2DFmode vector constants here yet.  */
5360  gcc_assert (GET_MODE (op) != V2DImode
5361	      && GET_MODE (op) != V2DFmode);
5362
5363  tmp = CONST_VECTOR_ELT (op, elt);
5364  if (GET_MODE (op) == V4SFmode
5365      || GET_MODE (op) == V2SFmode)
5366    tmp = gen_lowpart (SImode, tmp);
5367  return INTVAL (tmp);
5368}
5369
5370/* Return true if OP can be synthesized with a particular vspltisb, vspltish
5371   or vspltisw instruction.  OP is a CONST_VECTOR.  Which instruction is used
5372   depends on STEP and COPIES, one of which will be 1.  If COPIES > 1,
5373   all items are set to the same value and contain COPIES replicas of the
5374   vsplt's operand; if STEP > 1, one in STEP elements is set to the vsplt's
5375   operand and the others are set to the value of the operand's msb.  */
5376
5377static bool
5378vspltis_constant (rtx op, unsigned step, unsigned copies)
5379{
5380  machine_mode mode = GET_MODE (op);
5381  machine_mode inner = GET_MODE_INNER (mode);
5382
5383  unsigned i;
5384  unsigned nunits;
5385  unsigned bitsize;
5386  unsigned mask;
5387
5388  HOST_WIDE_INT val;
5389  HOST_WIDE_INT splat_val;
5390  HOST_WIDE_INT msb_val;
5391
5392  if (mode == V2DImode || mode == V2DFmode || mode == V1TImode)
5393    return false;
5394
5395  nunits = GET_MODE_NUNITS (mode);
5396  bitsize = GET_MODE_BITSIZE (inner);
5397  mask = GET_MODE_MASK (inner);
5398
5399  val = const_vector_elt_as_int (op, BYTES_BIG_ENDIAN ? nunits - 1 : 0);
5400  splat_val = val;
5401  msb_val = val >= 0 ? 0 : -1;
5402
5403  /* Construct the value to be splatted, if possible.  If not, return 0.  */
5404  for (i = 2; i <= copies; i *= 2)
5405    {
5406      HOST_WIDE_INT small_val;
5407      bitsize /= 2;
5408      small_val = splat_val >> bitsize;
5409      mask >>= bitsize;
5410      if (splat_val != ((small_val << bitsize) | (small_val & mask)))
5411	return false;
5412      splat_val = small_val;
5413    }
5414
5415  /* Check if SPLAT_VAL can really be the operand of a vspltis[bhw].  */
5416  if (EASY_VECTOR_15 (splat_val))
5417    ;
5418
5419  /* Also check if we can splat, and then add the result to itself.  Do so if
5420     the value is positive, of if the splat instruction is using OP's mode;
5421     for splat_val < 0, the splat and the add should use the same mode.  */
5422  else if (EASY_VECTOR_15_ADD_SELF (splat_val)
5423           && (splat_val >= 0 || (step == 1 && copies == 1)))
5424    ;
5425
5426  /* Also check if are loading up the most significant bit which can be done by
5427     loading up -1 and shifting the value left by -1.  */
5428  else if (EASY_VECTOR_MSB (splat_val, inner))
5429    ;
5430
5431  else
5432    return false;
5433
5434  /* Check if VAL is present in every STEP-th element, and the
5435     other elements are filled with its most significant bit.  */
5436  for (i = 1; i < nunits; ++i)
5437    {
5438      HOST_WIDE_INT desired_val;
5439      unsigned elt = BYTES_BIG_ENDIAN ? nunits - 1 - i : i;
5440      if ((i & (step - 1)) == 0)
5441	desired_val = val;
5442      else
5443	desired_val = msb_val;
5444
5445      if (desired_val != const_vector_elt_as_int (op, elt))
5446	return false;
5447    }
5448
5449  return true;
5450}
5451
5452
5453/* Return true if OP is of the given MODE and can be synthesized
5454   with a vspltisb, vspltish or vspltisw.  */
5455
5456bool
5457easy_altivec_constant (rtx op, machine_mode mode)
5458{
5459  unsigned step, copies;
5460
5461  if (mode == VOIDmode)
5462    mode = GET_MODE (op);
5463  else if (mode != GET_MODE (op))
5464    return false;
5465
5466  /* V2DI/V2DF was added with VSX.  Only allow 0 and all 1's as easy
5467     constants.  */
5468  if (mode == V2DFmode)
5469    return zero_constant (op, mode);
5470
5471  else if (mode == V2DImode)
5472    {
5473      if (GET_CODE (CONST_VECTOR_ELT (op, 0)) != CONST_INT
5474	  || GET_CODE (CONST_VECTOR_ELT (op, 1)) != CONST_INT)
5475	return false;
5476
5477      if (zero_constant (op, mode))
5478	return true;
5479
5480      if (INTVAL (CONST_VECTOR_ELT (op, 0)) == -1
5481	  && INTVAL (CONST_VECTOR_ELT (op, 1)) == -1)
5482	return true;
5483
5484      return false;
5485    }
5486
5487  /* V1TImode is a special container for TImode.  Ignore for now.  */
5488  else if (mode == V1TImode)
5489    return false;
5490
5491  /* Start with a vspltisw.  */
5492  step = GET_MODE_NUNITS (mode) / 4;
5493  copies = 1;
5494
5495  if (vspltis_constant (op, step, copies))
5496    return true;
5497
5498  /* Then try with a vspltish.  */
5499  if (step == 1)
5500    copies <<= 1;
5501  else
5502    step >>= 1;
5503
5504  if (vspltis_constant (op, step, copies))
5505    return true;
5506
5507  /* And finally a vspltisb.  */
5508  if (step == 1)
5509    copies <<= 1;
5510  else
5511    step >>= 1;
5512
5513  if (vspltis_constant (op, step, copies))
5514    return true;
5515
5516  return false;
5517}
5518
5519/* Generate a VEC_DUPLICATE representing a vspltis[bhw] instruction whose
5520   result is OP.  Abort if it is not possible.  */
5521
5522rtx
5523gen_easy_altivec_constant (rtx op)
5524{
5525  machine_mode mode = GET_MODE (op);
5526  int nunits = GET_MODE_NUNITS (mode);
5527  rtx val = CONST_VECTOR_ELT (op, BYTES_BIG_ENDIAN ? nunits - 1 : 0);
5528  unsigned step = nunits / 4;
5529  unsigned copies = 1;
5530
5531  /* Start with a vspltisw.  */
5532  if (vspltis_constant (op, step, copies))
5533    return gen_rtx_VEC_DUPLICATE (V4SImode, gen_lowpart (SImode, val));
5534
5535  /* Then try with a vspltish.  */
5536  if (step == 1)
5537    copies <<= 1;
5538  else
5539    step >>= 1;
5540
5541  if (vspltis_constant (op, step, copies))
5542    return gen_rtx_VEC_DUPLICATE (V8HImode, gen_lowpart (HImode, val));
5543
5544  /* And finally a vspltisb.  */
5545  if (step == 1)
5546    copies <<= 1;
5547  else
5548    step >>= 1;
5549
5550  if (vspltis_constant (op, step, copies))
5551    return gen_rtx_VEC_DUPLICATE (V16QImode, gen_lowpart (QImode, val));
5552
5553  gcc_unreachable ();
5554}
5555
5556const char *
5557output_vec_const_move (rtx *operands)
5558{
5559  int cst, cst2;
5560  machine_mode mode;
5561  rtx dest, vec;
5562
5563  dest = operands[0];
5564  vec = operands[1];
5565  mode = GET_MODE (dest);
5566
5567  if (TARGET_VSX)
5568    {
5569      if (zero_constant (vec, mode))
5570	return "xxlxor %x0,%x0,%x0";
5571
5572      if ((mode == V2DImode || mode == V1TImode)
5573	  && INTVAL (CONST_VECTOR_ELT (vec, 0)) == -1
5574	  && INTVAL (CONST_VECTOR_ELT (vec, 1)) == -1)
5575	return "vspltisw %0,-1";
5576    }
5577
5578  if (TARGET_ALTIVEC)
5579    {
5580      rtx splat_vec;
5581      if (zero_constant (vec, mode))
5582	return "vxor %0,%0,%0";
5583
5584      splat_vec = gen_easy_altivec_constant (vec);
5585      gcc_assert (GET_CODE (splat_vec) == VEC_DUPLICATE);
5586      operands[1] = XEXP (splat_vec, 0);
5587      if (!EASY_VECTOR_15 (INTVAL (operands[1])))
5588	return "#";
5589
5590      switch (GET_MODE (splat_vec))
5591	{
5592	case V4SImode:
5593	  return "vspltisw %0,%1";
5594
5595	case V8HImode:
5596	  return "vspltish %0,%1";
5597
5598	case V16QImode:
5599	  return "vspltisb %0,%1";
5600
5601	default:
5602	  gcc_unreachable ();
5603	}
5604    }
5605
5606  gcc_assert (TARGET_SPE);
5607
5608  /* Vector constant 0 is handled as a splitter of V2SI, and in the
5609     pattern of V1DI, V4HI, and V2SF.
5610
5611     FIXME: We should probably return # and add post reload
5612     splitters for these, but this way is so easy ;-).  */
5613  cst = INTVAL (CONST_VECTOR_ELT (vec, 0));
5614  cst2 = INTVAL (CONST_VECTOR_ELT (vec, 1));
5615  operands[1] = CONST_VECTOR_ELT (vec, 0);
5616  operands[2] = CONST_VECTOR_ELT (vec, 1);
5617  if (cst == cst2)
5618    return "li %0,%1\n\tevmergelo %0,%0,%0";
5619  else if (WORDS_BIG_ENDIAN)
5620    return "li %0,%1\n\tevmergelo %0,%0,%0\n\tli %0,%2";
5621  else
5622    return "li %0,%2\n\tevmergelo %0,%0,%0\n\tli %0,%1";
5623}
5624
5625/* Initialize TARGET of vector PAIRED to VALS.  */
5626
5627void
5628paired_expand_vector_init (rtx target, rtx vals)
5629{
5630  machine_mode mode = GET_MODE (target);
5631  int n_elts = GET_MODE_NUNITS (mode);
5632  int n_var = 0;
5633  rtx x, new_rtx, tmp, constant_op, op1, op2;
5634  int i;
5635
5636  for (i = 0; i < n_elts; ++i)
5637    {
5638      x = XVECEXP (vals, 0, i);
5639      if (!(CONST_SCALAR_INT_P (x) || CONST_DOUBLE_P (x) || CONST_FIXED_P (x)))
5640	++n_var;
5641    }
5642  if (n_var == 0)
5643    {
5644      /* Load from constant pool.  */
5645      emit_move_insn (target, gen_rtx_CONST_VECTOR (mode, XVEC (vals, 0)));
5646      return;
5647    }
5648
5649  if (n_var == 2)
5650    {
5651      /* The vector is initialized only with non-constants.  */
5652      new_rtx = gen_rtx_VEC_CONCAT (V2SFmode, XVECEXP (vals, 0, 0),
5653				XVECEXP (vals, 0, 1));
5654
5655      emit_move_insn (target, new_rtx);
5656      return;
5657    }
5658
5659  /* One field is non-constant and the other one is a constant.  Load the
5660     constant from the constant pool and use ps_merge instruction to
5661     construct the whole vector.  */
5662  op1 = XVECEXP (vals, 0, 0);
5663  op2 = XVECEXP (vals, 0, 1);
5664
5665  constant_op = (CONSTANT_P (op1)) ? op1 : op2;
5666
5667  tmp = gen_reg_rtx (GET_MODE (constant_op));
5668  emit_move_insn (tmp, constant_op);
5669
5670  if (CONSTANT_P (op1))
5671    new_rtx = gen_rtx_VEC_CONCAT (V2SFmode, tmp, op2);
5672  else
5673    new_rtx = gen_rtx_VEC_CONCAT (V2SFmode, op1, tmp);
5674
5675  emit_move_insn (target, new_rtx);
5676}
5677
5678void
5679paired_expand_vector_move (rtx operands[])
5680{
5681  rtx op0 = operands[0], op1 = operands[1];
5682
5683  emit_move_insn (op0, op1);
5684}
5685
5686/* Emit vector compare for code RCODE.  DEST is destination, OP1 and
5687   OP2 are two VEC_COND_EXPR operands, CC_OP0 and CC_OP1 are the two
5688   operands for the relation operation COND.  This is a recursive
5689   function.  */
5690
5691static void
5692paired_emit_vector_compare (enum rtx_code rcode,
5693                            rtx dest, rtx op0, rtx op1,
5694                            rtx cc_op0, rtx cc_op1)
5695{
5696  rtx tmp = gen_reg_rtx (V2SFmode);
5697  rtx tmp1, max, min;
5698
5699  gcc_assert (TARGET_PAIRED_FLOAT);
5700  gcc_assert (GET_MODE (op0) == GET_MODE (op1));
5701
5702  switch (rcode)
5703    {
5704    case LT:
5705    case LTU:
5706      paired_emit_vector_compare (GE, dest, op1, op0, cc_op0, cc_op1);
5707      return;
5708    case GE:
5709    case GEU:
5710      emit_insn (gen_subv2sf3 (tmp, cc_op0, cc_op1));
5711      emit_insn (gen_selv2sf4 (dest, tmp, op0, op1, CONST0_RTX (SFmode)));
5712      return;
5713    case LE:
5714    case LEU:
5715      paired_emit_vector_compare (GE, dest, op0, op1, cc_op1, cc_op0);
5716      return;
5717    case GT:
5718      paired_emit_vector_compare (LE, dest, op1, op0, cc_op0, cc_op1);
5719      return;
5720    case EQ:
5721      tmp1 = gen_reg_rtx (V2SFmode);
5722      max = gen_reg_rtx (V2SFmode);
5723      min = gen_reg_rtx (V2SFmode);
5724      gen_reg_rtx (V2SFmode);
5725
5726      emit_insn (gen_subv2sf3 (tmp, cc_op0, cc_op1));
5727      emit_insn (gen_selv2sf4
5728                 (max, tmp, cc_op0, cc_op1, CONST0_RTX (SFmode)));
5729      emit_insn (gen_subv2sf3 (tmp, cc_op1, cc_op0));
5730      emit_insn (gen_selv2sf4
5731                 (min, tmp, cc_op0, cc_op1, CONST0_RTX (SFmode)));
5732      emit_insn (gen_subv2sf3 (tmp1, min, max));
5733      emit_insn (gen_selv2sf4 (dest, tmp1, op0, op1, CONST0_RTX (SFmode)));
5734      return;
5735    case NE:
5736      paired_emit_vector_compare (EQ, dest, op1, op0, cc_op0, cc_op1);
5737      return;
5738    case UNLE:
5739      paired_emit_vector_compare (LE, dest, op1, op0, cc_op0, cc_op1);
5740      return;
5741    case UNLT:
5742      paired_emit_vector_compare (LT, dest, op1, op0, cc_op0, cc_op1);
5743      return;
5744    case UNGE:
5745      paired_emit_vector_compare (GE, dest, op1, op0, cc_op0, cc_op1);
5746      return;
5747    case UNGT:
5748      paired_emit_vector_compare (GT, dest, op1, op0, cc_op0, cc_op1);
5749      return;
5750    default:
5751      gcc_unreachable ();
5752    }
5753
5754  return;
5755}
5756
5757/* Emit vector conditional expression.
5758   DEST is destination. OP1 and OP2 are two VEC_COND_EXPR operands.
5759   CC_OP0 and CC_OP1 are the two operands for the relation operation COND.  */
5760
5761int
5762paired_emit_vector_cond_expr (rtx dest, rtx op1, rtx op2,
5763			      rtx cond, rtx cc_op0, rtx cc_op1)
5764{
5765  enum rtx_code rcode = GET_CODE (cond);
5766
5767  if (!TARGET_PAIRED_FLOAT)
5768    return 0;
5769
5770  paired_emit_vector_compare (rcode, dest, op1, op2, cc_op0, cc_op1);
5771
5772  return 1;
5773}
5774
5775/* Initialize vector TARGET to VALS.  */
5776
5777void
5778rs6000_expand_vector_init (rtx target, rtx vals)
5779{
5780  machine_mode mode = GET_MODE (target);
5781  machine_mode inner_mode = GET_MODE_INNER (mode);
5782  int n_elts = GET_MODE_NUNITS (mode);
5783  int n_var = 0, one_var = -1;
5784  bool all_same = true, all_const_zero = true;
5785  rtx x, mem;
5786  int i;
5787
5788  for (i = 0; i < n_elts; ++i)
5789    {
5790      x = XVECEXP (vals, 0, i);
5791      if (!(CONST_SCALAR_INT_P (x) || CONST_DOUBLE_P (x) || CONST_FIXED_P (x)))
5792	++n_var, one_var = i;
5793      else if (x != CONST0_RTX (inner_mode))
5794	all_const_zero = false;
5795
5796      if (i > 0 && !rtx_equal_p (x, XVECEXP (vals, 0, 0)))
5797	all_same = false;
5798    }
5799
5800  if (n_var == 0)
5801    {
5802      rtx const_vec = gen_rtx_CONST_VECTOR (mode, XVEC (vals, 0));
5803      bool int_vector_p = (GET_MODE_CLASS (mode) == MODE_VECTOR_INT);
5804      if ((int_vector_p || TARGET_VSX) && all_const_zero)
5805	{
5806	  /* Zero register.  */
5807	  emit_insn (gen_rtx_SET (VOIDmode, target,
5808				  gen_rtx_XOR (mode, target, target)));
5809	  return;
5810	}
5811      else if (int_vector_p && easy_vector_constant (const_vec, mode))
5812	{
5813	  /* Splat immediate.  */
5814	  emit_insn (gen_rtx_SET (VOIDmode, target, const_vec));
5815	  return;
5816	}
5817      else
5818	{
5819	  /* Load from constant pool.  */
5820	  emit_move_insn (target, const_vec);
5821	  return;
5822	}
5823    }
5824
5825  /* Double word values on VSX can use xxpermdi or lxvdsx.  */
5826  if (VECTOR_MEM_VSX_P (mode) && (mode == V2DFmode || mode == V2DImode))
5827    {
5828      rtx op0 = XVECEXP (vals, 0, 0);
5829      rtx op1 = XVECEXP (vals, 0, 1);
5830      if (all_same)
5831	{
5832	  if (!MEM_P (op0) && !REG_P (op0))
5833	    op0 = force_reg (inner_mode, op0);
5834	  if (mode == V2DFmode)
5835	    emit_insn (gen_vsx_splat_v2df (target, op0));
5836	  else
5837	    emit_insn (gen_vsx_splat_v2di (target, op0));
5838	}
5839      else
5840	{
5841	  op0 = force_reg (inner_mode, op0);
5842	  op1 = force_reg (inner_mode, op1);
5843	  if (mode == V2DFmode)
5844	    emit_insn (gen_vsx_concat_v2df (target, op0, op1));
5845	  else
5846	    emit_insn (gen_vsx_concat_v2di (target, op0, op1));
5847	}
5848      return;
5849    }
5850
5851  /* With single precision floating point on VSX, know that internally single
5852     precision is actually represented as a double, and either make 2 V2DF
5853     vectors, and convert these vectors to single precision, or do one
5854     conversion, and splat the result to the other elements.  */
5855  if (mode == V4SFmode && VECTOR_MEM_VSX_P (mode))
5856    {
5857      if (all_same)
5858	{
5859	  rtx freg = gen_reg_rtx (V4SFmode);
5860	  rtx sreg = force_reg (SFmode, XVECEXP (vals, 0, 0));
5861	  rtx cvt  = ((TARGET_XSCVDPSPN)
5862		      ? gen_vsx_xscvdpspn_scalar (freg, sreg)
5863		      : gen_vsx_xscvdpsp_scalar (freg, sreg));
5864
5865	  emit_insn (cvt);
5866	  emit_insn (gen_vsx_xxspltw_v4sf_direct (target, freg, const0_rtx));
5867	}
5868      else
5869	{
5870	  rtx dbl_even = gen_reg_rtx (V2DFmode);
5871	  rtx dbl_odd  = gen_reg_rtx (V2DFmode);
5872	  rtx flt_even = gen_reg_rtx (V4SFmode);
5873	  rtx flt_odd  = gen_reg_rtx (V4SFmode);
5874	  rtx op0 = force_reg (SFmode, XVECEXP (vals, 0, 0));
5875	  rtx op1 = force_reg (SFmode, XVECEXP (vals, 0, 1));
5876	  rtx op2 = force_reg (SFmode, XVECEXP (vals, 0, 2));
5877	  rtx op3 = force_reg (SFmode, XVECEXP (vals, 0, 3));
5878
5879	  emit_insn (gen_vsx_concat_v2sf (dbl_even, op0, op1));
5880	  emit_insn (gen_vsx_concat_v2sf (dbl_odd, op2, op3));
5881	  emit_insn (gen_vsx_xvcvdpsp (flt_even, dbl_even));
5882	  emit_insn (gen_vsx_xvcvdpsp (flt_odd, dbl_odd));
5883	  rs6000_expand_extract_even (target, flt_even, flt_odd);
5884	}
5885      return;
5886    }
5887
5888  /* Store value to stack temp.  Load vector element.  Splat.  However, splat
5889     of 64-bit items is not supported on Altivec.  */
5890  if (all_same && GET_MODE_SIZE (inner_mode) <= 4)
5891    {
5892      mem = assign_stack_temp (mode, GET_MODE_SIZE (inner_mode));
5893      emit_move_insn (adjust_address_nv (mem, inner_mode, 0),
5894		      XVECEXP (vals, 0, 0));
5895      x = gen_rtx_UNSPEC (VOIDmode,
5896			  gen_rtvec (1, const0_rtx), UNSPEC_LVE);
5897      emit_insn (gen_rtx_PARALLEL (VOIDmode,
5898				   gen_rtvec (2,
5899					      gen_rtx_SET (VOIDmode,
5900							   target, mem),
5901					      x)));
5902      x = gen_rtx_VEC_SELECT (inner_mode, target,
5903			      gen_rtx_PARALLEL (VOIDmode,
5904						gen_rtvec (1, const0_rtx)));
5905      emit_insn (gen_rtx_SET (VOIDmode, target,
5906			      gen_rtx_VEC_DUPLICATE (mode, x)));
5907      return;
5908    }
5909
5910  /* One field is non-constant.  Load constant then overwrite
5911     varying field.  */
5912  if (n_var == 1)
5913    {
5914      rtx copy = copy_rtx (vals);
5915
5916      /* Load constant part of vector, substitute neighboring value for
5917	 varying element.  */
5918      XVECEXP (copy, 0, one_var) = XVECEXP (vals, 0, (one_var + 1) % n_elts);
5919      rs6000_expand_vector_init (target, copy);
5920
5921      /* Insert variable.  */
5922      rs6000_expand_vector_set (target, XVECEXP (vals, 0, one_var), one_var);
5923      return;
5924    }
5925
5926  /* Construct the vector in memory one field at a time
5927     and load the whole vector.  */
5928  mem = assign_stack_temp (mode, GET_MODE_SIZE (mode));
5929  for (i = 0; i < n_elts; i++)
5930    emit_move_insn (adjust_address_nv (mem, inner_mode,
5931				    i * GET_MODE_SIZE (inner_mode)),
5932		    XVECEXP (vals, 0, i));
5933  emit_move_insn (target, mem);
5934}
5935
5936/* Set field ELT of TARGET to VAL.  */
5937
5938void
5939rs6000_expand_vector_set (rtx target, rtx val, int elt)
5940{
5941  machine_mode mode = GET_MODE (target);
5942  machine_mode inner_mode = GET_MODE_INNER (mode);
5943  rtx reg = gen_reg_rtx (mode);
5944  rtx mask, mem, x;
5945  int width = GET_MODE_SIZE (inner_mode);
5946  int i;
5947
5948  if (VECTOR_MEM_VSX_P (mode) && (mode == V2DFmode || mode == V2DImode))
5949    {
5950      rtx (*set_func) (rtx, rtx, rtx, rtx)
5951	= ((mode == V2DFmode) ? gen_vsx_set_v2df : gen_vsx_set_v2di);
5952      emit_insn (set_func (target, target, val, GEN_INT (elt)));
5953      return;
5954    }
5955
5956  /* Simplify setting single element vectors like V1TImode.  */
5957  if (GET_MODE_SIZE (mode) == GET_MODE_SIZE (inner_mode) && elt == 0)
5958    {
5959      emit_move_insn (target, gen_lowpart (mode, val));
5960      return;
5961    }
5962
5963  /* Load single variable value.  */
5964  mem = assign_stack_temp (mode, GET_MODE_SIZE (inner_mode));
5965  emit_move_insn (adjust_address_nv (mem, inner_mode, 0), val);
5966  x = gen_rtx_UNSPEC (VOIDmode,
5967		      gen_rtvec (1, const0_rtx), UNSPEC_LVE);
5968  emit_insn (gen_rtx_PARALLEL (VOIDmode,
5969			       gen_rtvec (2,
5970					  gen_rtx_SET (VOIDmode,
5971						       reg, mem),
5972					  x)));
5973
5974  /* Linear sequence.  */
5975  mask = gen_rtx_PARALLEL (V16QImode, rtvec_alloc (16));
5976  for (i = 0; i < 16; ++i)
5977    XVECEXP (mask, 0, i) = GEN_INT (i);
5978
5979  /* Set permute mask to insert element into target.  */
5980  for (i = 0; i < width; ++i)
5981    XVECEXP (mask, 0, elt*width + i)
5982      = GEN_INT (i + 0x10);
5983  x = gen_rtx_CONST_VECTOR (V16QImode, XVEC (mask, 0));
5984
5985  if (BYTES_BIG_ENDIAN)
5986    x = gen_rtx_UNSPEC (mode,
5987			gen_rtvec (3, target, reg,
5988				   force_reg (V16QImode, x)),
5989			UNSPEC_VPERM);
5990  else
5991    {
5992      /* Invert selector.  We prefer to generate VNAND on P8 so
5993         that future fusion opportunities can kick in, but must
5994         generate VNOR elsewhere.  */
5995      rtx notx = gen_rtx_NOT (V16QImode, force_reg (V16QImode, x));
5996      rtx iorx = (TARGET_P8_VECTOR
5997		  ? gen_rtx_IOR (V16QImode, notx, notx)
5998		  : gen_rtx_AND (V16QImode, notx, notx));
5999      rtx tmp = gen_reg_rtx (V16QImode);
6000      emit_insn (gen_rtx_SET (VOIDmode, tmp, iorx));
6001
6002      /* Permute with operands reversed and adjusted selector.  */
6003      x = gen_rtx_UNSPEC (mode, gen_rtvec (3, reg, target, tmp),
6004			  UNSPEC_VPERM);
6005    }
6006
6007  emit_insn (gen_rtx_SET (VOIDmode, target, x));
6008}
6009
6010/* Extract field ELT from VEC into TARGET.  */
6011
6012void
6013rs6000_expand_vector_extract (rtx target, rtx vec, int elt)
6014{
6015  machine_mode mode = GET_MODE (vec);
6016  machine_mode inner_mode = GET_MODE_INNER (mode);
6017  rtx mem;
6018
6019  if (VECTOR_MEM_VSX_P (mode))
6020    {
6021      switch (mode)
6022	{
6023	default:
6024	  break;
6025	case V1TImode:
6026	  gcc_assert (elt == 0 && inner_mode == TImode);
6027	  emit_move_insn (target, gen_lowpart (TImode, vec));
6028	  break;
6029	case V2DFmode:
6030	  emit_insn (gen_vsx_extract_v2df (target, vec, GEN_INT (elt)));
6031	  return;
6032	case V2DImode:
6033	  emit_insn (gen_vsx_extract_v2di (target, vec, GEN_INT (elt)));
6034	  return;
6035	case V4SFmode:
6036	  emit_insn (gen_vsx_extract_v4sf (target, vec, GEN_INT (elt)));
6037	  return;
6038	}
6039    }
6040
6041  /* Allocate mode-sized buffer.  */
6042  mem = assign_stack_temp (mode, GET_MODE_SIZE (mode));
6043
6044  emit_move_insn (mem, vec);
6045
6046  /* Add offset to field within buffer matching vector element.  */
6047  mem = adjust_address_nv (mem, inner_mode, elt * GET_MODE_SIZE (inner_mode));
6048
6049  emit_move_insn (target, adjust_address_nv (mem, inner_mode, 0));
6050}
6051
6052/* Generates shifts and masks for a pair of rldicl or rldicr insns to
6053   implement ANDing by the mask IN.  */
6054void
6055build_mask64_2_operands (rtx in, rtx *out)
6056{
6057  unsigned HOST_WIDE_INT c, lsb, m1, m2;
6058  int shift;
6059
6060  gcc_assert (GET_CODE (in) == CONST_INT);
6061
6062  c = INTVAL (in);
6063  if (c & 1)
6064    {
6065      /* Assume c initially something like 0x00fff000000fffff.  The idea
6066	 is to rotate the word so that the middle ^^^^^^ group of zeros
6067	 is at the MS end and can be cleared with an rldicl mask.  We then
6068	 rotate back and clear off the MS    ^^ group of zeros with a
6069	 second rldicl.  */
6070      c = ~c;			/*   c == 0xff000ffffff00000 */
6071      lsb = c & -c;		/* lsb == 0x0000000000100000 */
6072      m1 = -lsb;		/*  m1 == 0xfffffffffff00000 */
6073      c = ~c;			/*   c == 0x00fff000000fffff */
6074      c &= -lsb;		/*   c == 0x00fff00000000000 */
6075      lsb = c & -c;		/* lsb == 0x0000100000000000 */
6076      c = ~c;			/*   c == 0xff000fffffffffff */
6077      c &= -lsb;		/*   c == 0xff00000000000000 */
6078      shift = 0;
6079      while ((lsb >>= 1) != 0)
6080	shift++;		/* shift == 44 on exit from loop */
6081      m1 <<= 64 - shift;	/*  m1 == 0xffffff0000000000 */
6082      m1 = ~m1;			/*  m1 == 0x000000ffffffffff */
6083      m2 = ~c;			/*  m2 == 0x00ffffffffffffff */
6084    }
6085  else
6086    {
6087      /* Assume c initially something like 0xff000f0000000000.  The idea
6088	 is to rotate the word so that the     ^^^  middle group of zeros
6089	 is at the LS end and can be cleared with an rldicr mask.  We then
6090	 rotate back and clear off the LS group of ^^^^^^^^^^ zeros with
6091	 a second rldicr.  */
6092      lsb = c & -c;		/* lsb == 0x0000010000000000 */
6093      m2 = -lsb;		/*  m2 == 0xffffff0000000000 */
6094      c = ~c;			/*   c == 0x00fff0ffffffffff */
6095      c &= -lsb;		/*   c == 0x00fff00000000000 */
6096      lsb = c & -c;		/* lsb == 0x0000100000000000 */
6097      c = ~c;			/*   c == 0xff000fffffffffff */
6098      c &= -lsb;		/*   c == 0xff00000000000000 */
6099      shift = 0;
6100      while ((lsb >>= 1) != 0)
6101	shift++;		/* shift == 44 on exit from loop */
6102      m1 = ~c;			/*  m1 == 0x00ffffffffffffff */
6103      m1 >>= shift;		/*  m1 == 0x0000000000000fff */
6104      m1 = ~m1;			/*  m1 == 0xfffffffffffff000 */
6105    }
6106
6107  /* Note that when we only have two 0->1 and 1->0 transitions, one of the
6108     masks will be all 1's.  We are guaranteed more than one transition.  */
6109  out[0] = GEN_INT (64 - shift);
6110  out[1] = GEN_INT (m1);
6111  out[2] = GEN_INT (shift);
6112  out[3] = GEN_INT (m2);
6113}
6114
6115/* Return TRUE if OP is an invalid SUBREG operation on the e500.  */
6116
6117bool
6118invalid_e500_subreg (rtx op, machine_mode mode)
6119{
6120  if (TARGET_E500_DOUBLE)
6121    {
6122      /* Reject (subreg:SI (reg:DF)); likewise with subreg:DI or
6123	 subreg:TI and reg:TF.  Decimal float modes are like integer
6124	 modes (only low part of each register used) for this
6125	 purpose.  */
6126      if (GET_CODE (op) == SUBREG
6127	  && (mode == SImode || mode == DImode || mode == TImode
6128	      || mode == DDmode || mode == TDmode || mode == PTImode)
6129	  && REG_P (SUBREG_REG (op))
6130	  && (GET_MODE (SUBREG_REG (op)) == DFmode
6131	      || GET_MODE (SUBREG_REG (op)) == TFmode))
6132	return true;
6133
6134      /* Reject (subreg:DF (reg:DI)); likewise with subreg:TF and
6135	 reg:TI.  */
6136      if (GET_CODE (op) == SUBREG
6137	  && (mode == DFmode || mode == TFmode)
6138	  && REG_P (SUBREG_REG (op))
6139	  && (GET_MODE (SUBREG_REG (op)) == DImode
6140	      || GET_MODE (SUBREG_REG (op)) == TImode
6141	      || GET_MODE (SUBREG_REG (op)) == PTImode
6142	      || GET_MODE (SUBREG_REG (op)) == DDmode
6143	      || GET_MODE (SUBREG_REG (op)) == TDmode))
6144	return true;
6145    }
6146
6147  if (TARGET_SPE
6148      && GET_CODE (op) == SUBREG
6149      && mode == SImode
6150      && REG_P (SUBREG_REG (op))
6151      && SPE_VECTOR_MODE (GET_MODE (SUBREG_REG (op))))
6152    return true;
6153
6154  return false;
6155}
6156
6157/* Return alignment of TYPE.  Existing alignment is ALIGN.  HOW
6158   selects whether the alignment is abi mandated, optional, or
6159   both abi and optional alignment.  */
6160
6161unsigned int
6162rs6000_data_alignment (tree type, unsigned int align, enum data_align how)
6163{
6164  if (how != align_opt)
6165    {
6166      if (TREE_CODE (type) == VECTOR_TYPE)
6167	{
6168	  if ((TARGET_SPE && SPE_VECTOR_MODE (TYPE_MODE (type)))
6169	      || (TARGET_PAIRED_FLOAT && PAIRED_VECTOR_MODE (TYPE_MODE (type))))
6170	    {
6171	      if (align < 64)
6172		align = 64;
6173	    }
6174	  else if (align < 128)
6175	    align = 128;
6176	}
6177      else if (TARGET_E500_DOUBLE
6178	       && TREE_CODE (type) == REAL_TYPE
6179	       && TYPE_MODE (type) == DFmode)
6180	{
6181	  if (align < 64)
6182	    align = 64;
6183	}
6184    }
6185
6186  if (how != align_abi)
6187    {
6188      if (TREE_CODE (type) == ARRAY_TYPE
6189	  && TYPE_MODE (TREE_TYPE (type)) == QImode)
6190	{
6191	  if (align < BITS_PER_WORD)
6192	    align = BITS_PER_WORD;
6193	}
6194    }
6195
6196  return align;
6197}
6198
6199/* Previous GCC releases forced all vector types to have 16-byte alignment.  */
6200
6201bool
6202rs6000_special_adjust_field_align_p (tree field, unsigned int computed)
6203{
6204  if (TARGET_ALTIVEC && TREE_CODE (TREE_TYPE (field)) == VECTOR_TYPE)
6205    {
6206      if (computed != 128)
6207	{
6208	  static bool warned;
6209	  if (!warned && warn_psabi)
6210	    {
6211	      warned = true;
6212	      inform (input_location,
6213		      "the layout of aggregates containing vectors with"
6214		      " %d-byte alignment has changed in GCC 5",
6215		      computed / BITS_PER_UNIT);
6216	    }
6217	}
6218      /* In current GCC there is no special case.  */
6219      return false;
6220    }
6221
6222  return false;
6223}
6224
6225/* AIX increases natural record alignment to doubleword if the first
6226   field is an FP double while the FP fields remain word aligned.  */
6227
6228unsigned int
6229rs6000_special_round_type_align (tree type, unsigned int computed,
6230				 unsigned int specified)
6231{
6232  unsigned int align = MAX (computed, specified);
6233  tree field = TYPE_FIELDS (type);
6234
6235  /* Skip all non field decls */
6236  while (field != NULL && TREE_CODE (field) != FIELD_DECL)
6237    field = DECL_CHAIN (field);
6238
6239  if (field != NULL && field != type)
6240    {
6241      type = TREE_TYPE (field);
6242      while (TREE_CODE (type) == ARRAY_TYPE)
6243	type = TREE_TYPE (type);
6244
6245      if (type != error_mark_node && TYPE_MODE (type) == DFmode)
6246	align = MAX (align, 64);
6247    }
6248
6249  return align;
6250}
6251
6252/* Darwin increases record alignment to the natural alignment of
6253   the first field.  */
6254
6255unsigned int
6256darwin_rs6000_special_round_type_align (tree type, unsigned int computed,
6257					unsigned int specified)
6258{
6259  unsigned int align = MAX (computed, specified);
6260
6261  if (TYPE_PACKED (type))
6262    return align;
6263
6264  /* Find the first field, looking down into aggregates.  */
6265  do {
6266    tree field = TYPE_FIELDS (type);
6267    /* Skip all non field decls */
6268    while (field != NULL && TREE_CODE (field) != FIELD_DECL)
6269      field = DECL_CHAIN (field);
6270    if (! field)
6271      break;
6272    /* A packed field does not contribute any extra alignment.  */
6273    if (DECL_PACKED (field))
6274      return align;
6275    type = TREE_TYPE (field);
6276    while (TREE_CODE (type) == ARRAY_TYPE)
6277      type = TREE_TYPE (type);
6278  } while (AGGREGATE_TYPE_P (type));
6279
6280  if (! AGGREGATE_TYPE_P (type) && type != error_mark_node)
6281    align = MAX (align, TYPE_ALIGN (type));
6282
6283  return align;
6284}
6285
6286/* Return 1 for an operand in small memory on V.4/eabi.  */
6287
6288int
6289small_data_operand (rtx op ATTRIBUTE_UNUSED,
6290		    machine_mode mode ATTRIBUTE_UNUSED)
6291{
6292#if TARGET_ELF
6293  rtx sym_ref;
6294
6295  if (rs6000_sdata == SDATA_NONE || rs6000_sdata == SDATA_DATA)
6296    return 0;
6297
6298  if (DEFAULT_ABI != ABI_V4)
6299    return 0;
6300
6301  /* Vector and float memory instructions have a limited offset on the
6302     SPE, so using a vector or float variable directly as an operand is
6303     not useful.  */
6304  if (TARGET_SPE
6305      && (SPE_VECTOR_MODE (mode) || FLOAT_MODE_P (mode)))
6306    return 0;
6307
6308  if (GET_CODE (op) == SYMBOL_REF)
6309    sym_ref = op;
6310
6311  else if (GET_CODE (op) != CONST
6312	   || GET_CODE (XEXP (op, 0)) != PLUS
6313	   || GET_CODE (XEXP (XEXP (op, 0), 0)) != SYMBOL_REF
6314	   || GET_CODE (XEXP (XEXP (op, 0), 1)) != CONST_INT)
6315    return 0;
6316
6317  else
6318    {
6319      rtx sum = XEXP (op, 0);
6320      HOST_WIDE_INT summand;
6321
6322      /* We have to be careful here, because it is the referenced address
6323	 that must be 32k from _SDA_BASE_, not just the symbol.  */
6324      summand = INTVAL (XEXP (sum, 1));
6325      if (summand < 0 || summand > g_switch_value)
6326	return 0;
6327
6328      sym_ref = XEXP (sum, 0);
6329    }
6330
6331  return SYMBOL_REF_SMALL_P (sym_ref);
6332#else
6333  return 0;
6334#endif
6335}
6336
6337/* Return true if either operand is a general purpose register.  */
6338
6339bool
6340gpr_or_gpr_p (rtx op0, rtx op1)
6341{
6342  return ((REG_P (op0) && INT_REGNO_P (REGNO (op0)))
6343	  || (REG_P (op1) && INT_REGNO_P (REGNO (op1))));
6344}
6345
6346/* Return true if this is a move direct operation between GPR registers and
6347   floating point/VSX registers.  */
6348
6349bool
6350direct_move_p (rtx op0, rtx op1)
6351{
6352  int regno0, regno1;
6353
6354  if (!REG_P (op0) || !REG_P (op1))
6355    return false;
6356
6357  if (!TARGET_DIRECT_MOVE && !TARGET_MFPGPR)
6358    return false;
6359
6360  regno0 = REGNO (op0);
6361  regno1 = REGNO (op1);
6362  if (regno0 >= FIRST_PSEUDO_REGISTER || regno1 >= FIRST_PSEUDO_REGISTER)
6363    return false;
6364
6365  if (INT_REGNO_P (regno0))
6366    return (TARGET_DIRECT_MOVE) ? VSX_REGNO_P (regno1) : FP_REGNO_P (regno1);
6367
6368  else if (INT_REGNO_P (regno1))
6369    {
6370      if (TARGET_MFPGPR && FP_REGNO_P (regno0))
6371	return true;
6372
6373      else if (TARGET_DIRECT_MOVE && VSX_REGNO_P (regno0))
6374	return true;
6375    }
6376
6377  return false;
6378}
6379
6380/* Return true if this is a load or store quad operation.  This function does
6381   not handle the atomic quad memory instructions.  */
6382
6383bool
6384quad_load_store_p (rtx op0, rtx op1)
6385{
6386  bool ret;
6387
6388  if (!TARGET_QUAD_MEMORY)
6389    ret = false;
6390
6391  else if (REG_P (op0) && MEM_P (op1))
6392    ret = (quad_int_reg_operand (op0, GET_MODE (op0))
6393	   && quad_memory_operand (op1, GET_MODE (op1))
6394	   && !reg_overlap_mentioned_p (op0, op1));
6395
6396  else if (MEM_P (op0) && REG_P (op1))
6397    ret = (quad_memory_operand (op0, GET_MODE (op0))
6398	   && quad_int_reg_operand (op1, GET_MODE (op1)));
6399
6400  else
6401    ret = false;
6402
6403  if (TARGET_DEBUG_ADDR)
6404    {
6405      fprintf (stderr, "\n========== quad_load_store, return %s\n",
6406	       ret ? "true" : "false");
6407      debug_rtx (gen_rtx_SET (VOIDmode, op0, op1));
6408    }
6409
6410  return ret;
6411}
6412
6413/* Given an address, return a constant offset term if one exists.  */
6414
6415static rtx
6416address_offset (rtx op)
6417{
6418  if (GET_CODE (op) == PRE_INC
6419      || GET_CODE (op) == PRE_DEC)
6420    op = XEXP (op, 0);
6421  else if (GET_CODE (op) == PRE_MODIFY
6422	   || GET_CODE (op) == LO_SUM)
6423    op = XEXP (op, 1);
6424
6425  if (GET_CODE (op) == CONST)
6426    op = XEXP (op, 0);
6427
6428  if (GET_CODE (op) == PLUS)
6429    op = XEXP (op, 1);
6430
6431  if (CONST_INT_P (op))
6432    return op;
6433
6434  return NULL_RTX;
6435}
6436
6437/* Return true if the MEM operand is a memory operand suitable for use
6438   with a (full width, possibly multiple) gpr load/store.  On
6439   powerpc64 this means the offset must be divisible by 4.
6440   Implements 'Y' constraint.
6441
6442   Accept direct, indexed, offset, lo_sum and tocref.  Since this is
6443   a constraint function we know the operand has satisfied a suitable
6444   memory predicate.  Also accept some odd rtl generated by reload
6445   (see rs6000_legitimize_reload_address for various forms).  It is
6446   important that reload rtl be accepted by appropriate constraints
6447   but not by the operand predicate.
6448
6449   Offsetting a lo_sum should not be allowed, except where we know by
6450   alignment that a 32k boundary is not crossed, but see the ???
6451   comment in rs6000_legitimize_reload_address.  Note that by
6452   "offsetting" here we mean a further offset to access parts of the
6453   MEM.  It's fine to have a lo_sum where the inner address is offset
6454   from a sym, since the same sym+offset will appear in the high part
6455   of the address calculation.  */
6456
6457bool
6458mem_operand_gpr (rtx op, machine_mode mode)
6459{
6460  unsigned HOST_WIDE_INT offset;
6461  int extra;
6462  rtx addr = XEXP (op, 0);
6463
6464  op = address_offset (addr);
6465  if (op == NULL_RTX)
6466    return true;
6467
6468  offset = INTVAL (op);
6469  if (TARGET_POWERPC64 && (offset & 3) != 0)
6470    return false;
6471
6472  extra = GET_MODE_SIZE (mode) - UNITS_PER_WORD;
6473  if (extra < 0)
6474    extra = 0;
6475
6476  if (GET_CODE (addr) == LO_SUM)
6477    /* For lo_sum addresses, we must allow any offset except one that
6478       causes a wrap, so test only the low 16 bits.  */
6479    offset = ((offset & 0xffff) ^ 0x8000) - 0x8000;
6480
6481  return offset + 0x8000 < 0x10000u - extra;
6482}
6483
6484/* Subroutines of rs6000_legitimize_address and rs6000_legitimate_address_p.  */
6485
6486static bool
6487reg_offset_addressing_ok_p (machine_mode mode)
6488{
6489  switch (mode)
6490    {
6491    case V16QImode:
6492    case V8HImode:
6493    case V4SFmode:
6494    case V4SImode:
6495    case V2DFmode:
6496    case V2DImode:
6497    case V1TImode:
6498    case TImode:
6499      /* AltiVec/VSX vector modes.  Only reg+reg addressing is valid.  While
6500	 TImode is not a vector mode, if we want to use the VSX registers to
6501	 move it around, we need to restrict ourselves to reg+reg
6502	 addressing.  */
6503      if (VECTOR_MEM_ALTIVEC_OR_VSX_P (mode))
6504	return false;
6505      break;
6506
6507    case V4HImode:
6508    case V2SImode:
6509    case V1DImode:
6510    case V2SFmode:
6511       /* Paired vector modes.  Only reg+reg addressing is valid.  */
6512      if (TARGET_PAIRED_FLOAT)
6513        return false;
6514      break;
6515
6516    case SDmode:
6517      /* If we can do direct load/stores of SDmode, restrict it to reg+reg
6518	 addressing for the LFIWZX and STFIWX instructions.  */
6519      if (TARGET_NO_SDMODE_STACK)
6520	return false;
6521      break;
6522
6523    default:
6524      break;
6525    }
6526
6527  return true;
6528}
6529
6530static bool
6531virtual_stack_registers_memory_p (rtx op)
6532{
6533  int regnum;
6534
6535  if (GET_CODE (op) == REG)
6536    regnum = REGNO (op);
6537
6538  else if (GET_CODE (op) == PLUS
6539	   && GET_CODE (XEXP (op, 0)) == REG
6540	   && GET_CODE (XEXP (op, 1)) == CONST_INT)
6541    regnum = REGNO (XEXP (op, 0));
6542
6543  else
6544    return false;
6545
6546  return (regnum >= FIRST_VIRTUAL_REGISTER
6547	  && regnum <= LAST_VIRTUAL_POINTER_REGISTER);
6548}
6549
6550/* Return true if a MODE sized memory accesses to OP plus OFFSET
6551   is known to not straddle a 32k boundary.  */
6552
6553static bool
6554offsettable_ok_by_alignment (rtx op, HOST_WIDE_INT offset,
6555			     machine_mode mode)
6556{
6557  tree decl, type;
6558  unsigned HOST_WIDE_INT dsize, dalign, lsb, mask;
6559
6560  if (GET_CODE (op) != SYMBOL_REF)
6561    return false;
6562
6563  dsize = GET_MODE_SIZE (mode);
6564  decl = SYMBOL_REF_DECL (op);
6565  if (!decl)
6566    {
6567      if (dsize == 0)
6568	return false;
6569
6570      /* -fsection-anchors loses the original SYMBOL_REF_DECL when
6571	 replacing memory addresses with an anchor plus offset.  We
6572	 could find the decl by rummaging around in the block->objects
6573	 VEC for the given offset but that seems like too much work.  */
6574      dalign = BITS_PER_UNIT;
6575      if (SYMBOL_REF_HAS_BLOCK_INFO_P (op)
6576	  && SYMBOL_REF_ANCHOR_P (op)
6577	  && SYMBOL_REF_BLOCK (op) != NULL)
6578	{
6579	  struct object_block *block = SYMBOL_REF_BLOCK (op);
6580
6581	  dalign = block->alignment;
6582	  offset += SYMBOL_REF_BLOCK_OFFSET (op);
6583	}
6584      else if (CONSTANT_POOL_ADDRESS_P (op))
6585	{
6586	  /* It would be nice to have get_pool_align()..  */
6587	  machine_mode cmode = get_pool_mode (op);
6588
6589	  dalign = GET_MODE_ALIGNMENT (cmode);
6590	}
6591    }
6592  else if (DECL_P (decl))
6593    {
6594      dalign = DECL_ALIGN (decl);
6595
6596      if (dsize == 0)
6597	{
6598	  /* Allow BLKmode when the entire object is known to not
6599	     cross a 32k boundary.  */
6600	  if (!DECL_SIZE_UNIT (decl))
6601	    return false;
6602
6603	  if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (decl)))
6604	    return false;
6605
6606	  dsize = tree_to_uhwi (DECL_SIZE_UNIT (decl));
6607	  if (dsize > 32768)
6608	    return false;
6609
6610	  return dalign / BITS_PER_UNIT >= dsize;
6611	}
6612    }
6613  else
6614    {
6615      type = TREE_TYPE (decl);
6616
6617      dalign = TYPE_ALIGN (type);
6618      if (CONSTANT_CLASS_P (decl))
6619	dalign = CONSTANT_ALIGNMENT (decl, dalign);
6620      else
6621	dalign = DATA_ALIGNMENT (decl, dalign);
6622
6623      if (dsize == 0)
6624	{
6625	  /* BLKmode, check the entire object.  */
6626	  if (TREE_CODE (decl) == STRING_CST)
6627	    dsize = TREE_STRING_LENGTH (decl);
6628	  else if (TYPE_SIZE_UNIT (type)
6629		   && tree_fits_uhwi_p (TYPE_SIZE_UNIT (type)))
6630	    dsize = tree_to_uhwi (TYPE_SIZE_UNIT (type));
6631	  else
6632	    return false;
6633	  if (dsize > 32768)
6634	    return false;
6635
6636	  return dalign / BITS_PER_UNIT >= dsize;
6637	}
6638    }
6639
6640  /* Find how many bits of the alignment we know for this access.  */
6641  mask = dalign / BITS_PER_UNIT - 1;
6642  lsb = offset & -offset;
6643  mask &= lsb - 1;
6644  dalign = mask + 1;
6645
6646  return dalign >= dsize;
6647}
6648
6649static bool
6650constant_pool_expr_p (rtx op)
6651{
6652  rtx base, offset;
6653
6654  split_const (op, &base, &offset);
6655  return (GET_CODE (base) == SYMBOL_REF
6656	  && CONSTANT_POOL_ADDRESS_P (base)
6657	  && ASM_OUTPUT_SPECIAL_POOL_ENTRY_P (get_pool_constant (base), Pmode));
6658}
6659
6660static const_rtx tocrel_base, tocrel_offset;
6661
6662/* Return true if OP is a toc pointer relative address (the output
6663   of create_TOC_reference).  If STRICT, do not match high part or
6664   non-split -mcmodel=large/medium toc pointer relative addresses.  */
6665
6666bool
6667toc_relative_expr_p (const_rtx op, bool strict)
6668{
6669  if (!TARGET_TOC)
6670    return false;
6671
6672  if (TARGET_CMODEL != CMODEL_SMALL)
6673    {
6674      /* Only match the low part.  */
6675      if (GET_CODE (op) == LO_SUM
6676	  && REG_P (XEXP (op, 0))
6677	  && INT_REG_OK_FOR_BASE_P (XEXP (op, 0), strict))
6678	op = XEXP (op, 1);
6679      else if (strict)
6680	return false;
6681    }
6682
6683  tocrel_base = op;
6684  tocrel_offset = const0_rtx;
6685  if (GET_CODE (op) == PLUS && add_cint_operand (XEXP (op, 1), GET_MODE (op)))
6686    {
6687      tocrel_base = XEXP (op, 0);
6688      tocrel_offset = XEXP (op, 1);
6689    }
6690
6691  return (GET_CODE (tocrel_base) == UNSPEC
6692	  && XINT (tocrel_base, 1) == UNSPEC_TOCREL);
6693}
6694
6695/* Return true if X is a constant pool address, and also for cmodel=medium
6696   if X is a toc-relative address known to be offsettable within MODE.  */
6697
6698bool
6699legitimate_constant_pool_address_p (const_rtx x, machine_mode mode,
6700				    bool strict)
6701{
6702  return (toc_relative_expr_p (x, strict)
6703	  && (TARGET_CMODEL != CMODEL_MEDIUM
6704	      || constant_pool_expr_p (XVECEXP (tocrel_base, 0, 0))
6705	      || mode == QImode
6706	      || offsettable_ok_by_alignment (XVECEXP (tocrel_base, 0, 0),
6707					      INTVAL (tocrel_offset), mode)));
6708}
6709
6710static bool
6711legitimate_small_data_p (machine_mode mode, rtx x)
6712{
6713  return (DEFAULT_ABI == ABI_V4
6714	  && !flag_pic && !TARGET_TOC
6715	  && (GET_CODE (x) == SYMBOL_REF || GET_CODE (x) == CONST)
6716	  && small_data_operand (x, mode));
6717}
6718
6719/* SPE offset addressing is limited to 5-bits worth of double words.  */
6720#define SPE_CONST_OFFSET_OK(x) (((x) & ~0xf8) == 0)
6721
6722bool
6723rs6000_legitimate_offset_address_p (machine_mode mode, rtx x,
6724				    bool strict, bool worst_case)
6725{
6726  unsigned HOST_WIDE_INT offset;
6727  unsigned int extra;
6728
6729  if (GET_CODE (x) != PLUS)
6730    return false;
6731  if (!REG_P (XEXP (x, 0)))
6732    return false;
6733  if (!INT_REG_OK_FOR_BASE_P (XEXP (x, 0), strict))
6734    return false;
6735  if (!reg_offset_addressing_ok_p (mode))
6736    return virtual_stack_registers_memory_p (x);
6737  if (legitimate_constant_pool_address_p (x, mode, strict || lra_in_progress))
6738    return true;
6739  if (GET_CODE (XEXP (x, 1)) != CONST_INT)
6740    return false;
6741
6742  offset = INTVAL (XEXP (x, 1));
6743  extra = 0;
6744  switch (mode)
6745    {
6746    case V4HImode:
6747    case V2SImode:
6748    case V1DImode:
6749    case V2SFmode:
6750      /* SPE vector modes.  */
6751      return SPE_CONST_OFFSET_OK (offset);
6752
6753    case DFmode:
6754    case DDmode:
6755    case DImode:
6756      /* On e500v2, we may have:
6757
6758	   (subreg:DF (mem:DI (plus (reg) (const_int))) 0).
6759
6760         Which gets addressed with evldd instructions.  */
6761      if (TARGET_E500_DOUBLE)
6762	return SPE_CONST_OFFSET_OK (offset);
6763
6764      /* If we are using VSX scalar loads, restrict ourselves to reg+reg
6765	 addressing.  */
6766      if (VECTOR_MEM_VSX_P (mode))
6767	return false;
6768
6769      if (!worst_case)
6770	break;
6771      if (!TARGET_POWERPC64)
6772	extra = 4;
6773      else if (offset & 3)
6774	return false;
6775      break;
6776
6777    case TFmode:
6778      if (TARGET_E500_DOUBLE)
6779	return (SPE_CONST_OFFSET_OK (offset)
6780		&& SPE_CONST_OFFSET_OK (offset + 8));
6781      /* fall through */
6782
6783    case TDmode:
6784    case TImode:
6785    case PTImode:
6786      extra = 8;
6787      if (!worst_case)
6788	break;
6789      if (!TARGET_POWERPC64)
6790	extra = 12;
6791      else if (offset & 3)
6792	return false;
6793      break;
6794
6795    default:
6796      break;
6797    }
6798
6799  offset += 0x8000;
6800  return offset < 0x10000 - extra;
6801}
6802
6803bool
6804legitimate_indexed_address_p (rtx x, int strict)
6805{
6806  rtx op0, op1;
6807
6808  if (GET_CODE (x) != PLUS)
6809    return false;
6810
6811  op0 = XEXP (x, 0);
6812  op1 = XEXP (x, 1);
6813
6814  /* Recognize the rtl generated by reload which we know will later be
6815     replaced with proper base and index regs.  */
6816  if (!strict
6817      && reload_in_progress
6818      && (REG_P (op0) || GET_CODE (op0) == PLUS)
6819      && REG_P (op1))
6820    return true;
6821
6822  return (REG_P (op0) && REG_P (op1)
6823	  && ((INT_REG_OK_FOR_BASE_P (op0, strict)
6824	       && INT_REG_OK_FOR_INDEX_P (op1, strict))
6825	      || (INT_REG_OK_FOR_BASE_P (op1, strict)
6826		  && INT_REG_OK_FOR_INDEX_P (op0, strict))));
6827}
6828
6829bool
6830avoiding_indexed_address_p (machine_mode mode)
6831{
6832  /* Avoid indexed addressing for modes that have non-indexed
6833     load/store instruction forms.  */
6834  return (TARGET_AVOID_XFORM && VECTOR_MEM_NONE_P (mode));
6835}
6836
6837bool
6838legitimate_indirect_address_p (rtx x, int strict)
6839{
6840  return GET_CODE (x) == REG && INT_REG_OK_FOR_BASE_P (x, strict);
6841}
6842
6843bool
6844macho_lo_sum_memory_operand (rtx x, machine_mode mode)
6845{
6846  if (!TARGET_MACHO || !flag_pic
6847      || mode != SImode || GET_CODE (x) != MEM)
6848    return false;
6849  x = XEXP (x, 0);
6850
6851  if (GET_CODE (x) != LO_SUM)
6852    return false;
6853  if (GET_CODE (XEXP (x, 0)) != REG)
6854    return false;
6855  if (!INT_REG_OK_FOR_BASE_P (XEXP (x, 0), 0))
6856    return false;
6857  x = XEXP (x, 1);
6858
6859  return CONSTANT_P (x);
6860}
6861
6862static bool
6863legitimate_lo_sum_address_p (machine_mode mode, rtx x, int strict)
6864{
6865  if (GET_CODE (x) != LO_SUM)
6866    return false;
6867  if (GET_CODE (XEXP (x, 0)) != REG)
6868    return false;
6869  if (!INT_REG_OK_FOR_BASE_P (XEXP (x, 0), strict))
6870    return false;
6871  /* Restrict addressing for DI because of our SUBREG hackery.  */
6872  if (TARGET_E500_DOUBLE && GET_MODE_SIZE (mode) > UNITS_PER_WORD)
6873    return false;
6874  x = XEXP (x, 1);
6875
6876  if (TARGET_ELF || TARGET_MACHO)
6877    {
6878      bool large_toc_ok;
6879
6880      if (DEFAULT_ABI == ABI_V4 && flag_pic)
6881	return false;
6882      /* LRA don't use LEGITIMIZE_RELOAD_ADDRESS as it usually calls
6883	 push_reload from reload pass code.  LEGITIMIZE_RELOAD_ADDRESS
6884	 recognizes some LO_SUM addresses as valid although this
6885	 function says opposite.  In most cases, LRA through different
6886	 transformations can generate correct code for address reloads.
6887	 It can not manage only some LO_SUM cases.  So we need to add
6888	 code analogous to one in rs6000_legitimize_reload_address for
6889	 LOW_SUM here saying that some addresses are still valid.  */
6890      large_toc_ok = (lra_in_progress && TARGET_CMODEL != CMODEL_SMALL
6891		      && small_toc_ref (x, VOIDmode));
6892      if (TARGET_TOC && ! large_toc_ok)
6893	return false;
6894      if (GET_MODE_NUNITS (mode) != 1)
6895	return false;
6896      if (GET_MODE_SIZE (mode) > UNITS_PER_WORD
6897	  && !(/* ??? Assume floating point reg based on mode?  */
6898	       TARGET_HARD_FLOAT && TARGET_FPRS && TARGET_DOUBLE_FLOAT
6899	       && (mode == DFmode || mode == DDmode)))
6900	return false;
6901
6902      return CONSTANT_P (x) || large_toc_ok;
6903    }
6904
6905  return false;
6906}
6907
6908
6909/* Try machine-dependent ways of modifying an illegitimate address
6910   to be legitimate.  If we find one, return the new, valid address.
6911   This is used from only one place: `memory_address' in explow.c.
6912
6913   OLDX is the address as it was before break_out_memory_refs was
6914   called.  In some cases it is useful to look at this to decide what
6915   needs to be done.
6916
6917   It is always safe for this function to do nothing.  It exists to
6918   recognize opportunities to optimize the output.
6919
6920   On RS/6000, first check for the sum of a register with a constant
6921   integer that is out of range.  If so, generate code to add the
6922   constant with the low-order 16 bits masked to the register and force
6923   this result into another register (this can be done with `cau').
6924   Then generate an address of REG+(CONST&0xffff), allowing for the
6925   possibility of bit 16 being a one.
6926
6927   Then check for the sum of a register and something not constant, try to
6928   load the other things into a register and return the sum.  */
6929
6930static rtx
6931rs6000_legitimize_address (rtx x, rtx oldx ATTRIBUTE_UNUSED,
6932			   machine_mode mode)
6933{
6934  unsigned int extra;
6935
6936  if (!reg_offset_addressing_ok_p (mode))
6937    {
6938      if (virtual_stack_registers_memory_p (x))
6939	return x;
6940
6941      /* In theory we should not be seeing addresses of the form reg+0,
6942	 but just in case it is generated, optimize it away.  */
6943      if (GET_CODE (x) == PLUS && XEXP (x, 1) == const0_rtx)
6944	return force_reg (Pmode, XEXP (x, 0));
6945
6946      /* For TImode with load/store quad, restrict addresses to just a single
6947	 pointer, so it works with both GPRs and VSX registers.  */
6948      /* Make sure both operands are registers.  */
6949      else if (GET_CODE (x) == PLUS
6950	       && (mode != TImode || !TARGET_QUAD_MEMORY))
6951	return gen_rtx_PLUS (Pmode,
6952			     force_reg (Pmode, XEXP (x, 0)),
6953			     force_reg (Pmode, XEXP (x, 1)));
6954      else
6955	return force_reg (Pmode, x);
6956    }
6957  if (GET_CODE (x) == SYMBOL_REF)
6958    {
6959      enum tls_model model = SYMBOL_REF_TLS_MODEL (x);
6960      if (model != 0)
6961	return rs6000_legitimize_tls_address (x, model);
6962    }
6963
6964  extra = 0;
6965  switch (mode)
6966    {
6967    case TFmode:
6968    case TDmode:
6969    case TImode:
6970    case PTImode:
6971      /* As in legitimate_offset_address_p we do not assume
6972	 worst-case.  The mode here is just a hint as to the registers
6973	 used.  A TImode is usually in gprs, but may actually be in
6974	 fprs.  Leave worst-case scenario for reload to handle via
6975	 insn constraints.  PTImode is only GPRs.  */
6976      extra = 8;
6977      break;
6978    default:
6979      break;
6980    }
6981
6982  if (GET_CODE (x) == PLUS
6983      && GET_CODE (XEXP (x, 0)) == REG
6984      && GET_CODE (XEXP (x, 1)) == CONST_INT
6985      && ((unsigned HOST_WIDE_INT) (INTVAL (XEXP (x, 1)) + 0x8000)
6986	  >= 0x10000 - extra)
6987      && !(SPE_VECTOR_MODE (mode)
6988	   || (TARGET_E500_DOUBLE && GET_MODE_SIZE (mode) > UNITS_PER_WORD)))
6989    {
6990      HOST_WIDE_INT high_int, low_int;
6991      rtx sum;
6992      low_int = ((INTVAL (XEXP (x, 1)) & 0xffff) ^ 0x8000) - 0x8000;
6993      if (low_int >= 0x8000 - extra)
6994	low_int = 0;
6995      high_int = INTVAL (XEXP (x, 1)) - low_int;
6996      sum = force_operand (gen_rtx_PLUS (Pmode, XEXP (x, 0),
6997					 GEN_INT (high_int)), 0);
6998      return plus_constant (Pmode, sum, low_int);
6999    }
7000  else if (GET_CODE (x) == PLUS
7001	   && GET_CODE (XEXP (x, 0)) == REG
7002	   && GET_CODE (XEXP (x, 1)) != CONST_INT
7003	   && GET_MODE_NUNITS (mode) == 1
7004	   && (GET_MODE_SIZE (mode) <= UNITS_PER_WORD
7005	       || (/* ??? Assume floating point reg based on mode?  */
7006		   (TARGET_HARD_FLOAT && TARGET_FPRS && TARGET_DOUBLE_FLOAT)
7007		   && (mode == DFmode || mode == DDmode)))
7008	   && !avoiding_indexed_address_p (mode))
7009    {
7010      return gen_rtx_PLUS (Pmode, XEXP (x, 0),
7011			   force_reg (Pmode, force_operand (XEXP (x, 1), 0)));
7012    }
7013  else if (SPE_VECTOR_MODE (mode)
7014	   || (TARGET_E500_DOUBLE && GET_MODE_SIZE (mode) > UNITS_PER_WORD))
7015    {
7016      if (mode == DImode)
7017	return x;
7018      /* We accept [reg + reg] and [reg + OFFSET].  */
7019
7020      if (GET_CODE (x) == PLUS)
7021       {
7022         rtx op1 = XEXP (x, 0);
7023         rtx op2 = XEXP (x, 1);
7024         rtx y;
7025
7026         op1 = force_reg (Pmode, op1);
7027
7028         if (GET_CODE (op2) != REG
7029             && (GET_CODE (op2) != CONST_INT
7030                 || !SPE_CONST_OFFSET_OK (INTVAL (op2))
7031                 || (GET_MODE_SIZE (mode) > 8
7032                     && !SPE_CONST_OFFSET_OK (INTVAL (op2) + 8))))
7033           op2 = force_reg (Pmode, op2);
7034
7035         /* We can't always do [reg + reg] for these, because [reg +
7036            reg + offset] is not a legitimate addressing mode.  */
7037         y = gen_rtx_PLUS (Pmode, op1, op2);
7038
7039         if ((GET_MODE_SIZE (mode) > 8 || mode == DDmode) && REG_P (op2))
7040           return force_reg (Pmode, y);
7041         else
7042           return y;
7043       }
7044
7045      return force_reg (Pmode, x);
7046    }
7047  else if ((TARGET_ELF
7048#if TARGET_MACHO
7049	    || !MACHO_DYNAMIC_NO_PIC_P
7050#endif
7051	    )
7052	   && TARGET_32BIT
7053	   && TARGET_NO_TOC
7054	   && ! flag_pic
7055	   && GET_CODE (x) != CONST_INT
7056	   && GET_CODE (x) != CONST_WIDE_INT
7057	   && GET_CODE (x) != CONST_DOUBLE
7058	   && CONSTANT_P (x)
7059	   && GET_MODE_NUNITS (mode) == 1
7060	   && (GET_MODE_SIZE (mode) <= UNITS_PER_WORD
7061	       || (/* ??? Assume floating point reg based on mode?  */
7062		   (TARGET_HARD_FLOAT && TARGET_FPRS && TARGET_DOUBLE_FLOAT)
7063		   && (mode == DFmode || mode == DDmode))))
7064    {
7065      rtx reg = gen_reg_rtx (Pmode);
7066      if (TARGET_ELF)
7067	emit_insn (gen_elf_high (reg, x));
7068      else
7069	emit_insn (gen_macho_high (reg, x));
7070      return gen_rtx_LO_SUM (Pmode, reg, x);
7071    }
7072  else if (TARGET_TOC
7073	   && GET_CODE (x) == SYMBOL_REF
7074	   && constant_pool_expr_p (x)
7075	   && ASM_OUTPUT_SPECIAL_POOL_ENTRY_P (get_pool_constant (x), Pmode))
7076    return create_TOC_reference (x, NULL_RTX);
7077  else
7078    return x;
7079}
7080
7081/* Debug version of rs6000_legitimize_address.  */
7082static rtx
7083rs6000_debug_legitimize_address (rtx x, rtx oldx, machine_mode mode)
7084{
7085  rtx ret;
7086  rtx_insn *insns;
7087
7088  start_sequence ();
7089  ret = rs6000_legitimize_address (x, oldx, mode);
7090  insns = get_insns ();
7091  end_sequence ();
7092
7093  if (ret != x)
7094    {
7095      fprintf (stderr,
7096	       "\nrs6000_legitimize_address: mode %s, old code %s, "
7097	       "new code %s, modified\n",
7098	       GET_MODE_NAME (mode), GET_RTX_NAME (GET_CODE (x)),
7099	       GET_RTX_NAME (GET_CODE (ret)));
7100
7101      fprintf (stderr, "Original address:\n");
7102      debug_rtx (x);
7103
7104      fprintf (stderr, "oldx:\n");
7105      debug_rtx (oldx);
7106
7107      fprintf (stderr, "New address:\n");
7108      debug_rtx (ret);
7109
7110      if (insns)
7111	{
7112	  fprintf (stderr, "Insns added:\n");
7113	  debug_rtx_list (insns, 20);
7114	}
7115    }
7116  else
7117    {
7118      fprintf (stderr,
7119	       "\nrs6000_legitimize_address: mode %s, code %s, no change:\n",
7120	       GET_MODE_NAME (mode), GET_RTX_NAME (GET_CODE (x)));
7121
7122      debug_rtx (x);
7123    }
7124
7125  if (insns)
7126    emit_insn (insns);
7127
7128  return ret;
7129}
7130
7131/* This is called from dwarf2out.c via TARGET_ASM_OUTPUT_DWARF_DTPREL.
7132   We need to emit DTP-relative relocations.  */
7133
7134static void rs6000_output_dwarf_dtprel (FILE *, int, rtx) ATTRIBUTE_UNUSED;
7135static void
7136rs6000_output_dwarf_dtprel (FILE *file, int size, rtx x)
7137{
7138  switch (size)
7139    {
7140    case 4:
7141      fputs ("\t.long\t", file);
7142      break;
7143    case 8:
7144      fputs (DOUBLE_INT_ASM_OP, file);
7145      break;
7146    default:
7147      gcc_unreachable ();
7148    }
7149  output_addr_const (file, x);
7150  fputs ("@dtprel+0x8000", file);
7151}
7152
7153/* Return true if X is a symbol that refers to real (rather than emulated)
7154   TLS.  */
7155
7156static bool
7157rs6000_real_tls_symbol_ref_p (rtx x)
7158{
7159  return (GET_CODE (x) == SYMBOL_REF
7160	  && SYMBOL_REF_TLS_MODEL (x) >= TLS_MODEL_REAL);
7161}
7162
7163/* In the name of slightly smaller debug output, and to cater to
7164   general assembler lossage, recognize various UNSPEC sequences
7165   and turn them back into a direct symbol reference.  */
7166
7167static rtx
7168rs6000_delegitimize_address (rtx orig_x)
7169{
7170  rtx x, y, offset;
7171
7172  orig_x = delegitimize_mem_from_attrs (orig_x);
7173  x = orig_x;
7174  if (MEM_P (x))
7175    x = XEXP (x, 0);
7176
7177  y = x;
7178  if (TARGET_CMODEL != CMODEL_SMALL
7179      && GET_CODE (y) == LO_SUM)
7180    y = XEXP (y, 1);
7181
7182  offset = NULL_RTX;
7183  if (GET_CODE (y) == PLUS
7184      && GET_MODE (y) == Pmode
7185      && CONST_INT_P (XEXP (y, 1)))
7186    {
7187      offset = XEXP (y, 1);
7188      y = XEXP (y, 0);
7189    }
7190
7191  if (GET_CODE (y) == UNSPEC
7192      && XINT (y, 1) == UNSPEC_TOCREL)
7193    {
7194      y = XVECEXP (y, 0, 0);
7195
7196#ifdef HAVE_AS_TLS
7197      /* Do not associate thread-local symbols with the original
7198	 constant pool symbol.  */
7199      if (TARGET_XCOFF
7200	  && GET_CODE (y) == SYMBOL_REF
7201	  && CONSTANT_POOL_ADDRESS_P (y)
7202	  && rs6000_real_tls_symbol_ref_p (get_pool_constant (y)))
7203	return orig_x;
7204#endif
7205
7206      if (offset != NULL_RTX)
7207	y = gen_rtx_PLUS (Pmode, y, offset);
7208      if (!MEM_P (orig_x))
7209	return y;
7210      else
7211	return replace_equiv_address_nv (orig_x, y);
7212    }
7213
7214  if (TARGET_MACHO
7215      && GET_CODE (orig_x) == LO_SUM
7216      && GET_CODE (XEXP (orig_x, 1)) == CONST)
7217    {
7218      y = XEXP (XEXP (orig_x, 1), 0);
7219      if (GET_CODE (y) == UNSPEC
7220	  && XINT (y, 1) == UNSPEC_MACHOPIC_OFFSET)
7221	return XVECEXP (y, 0, 0);
7222    }
7223
7224  return orig_x;
7225}
7226
7227/* Return true if X shouldn't be emitted into the debug info.
7228   The linker doesn't like .toc section references from
7229   .debug_* sections, so reject .toc section symbols.  */
7230
7231static bool
7232rs6000_const_not_ok_for_debug_p (rtx x)
7233{
7234  if (GET_CODE (x) == SYMBOL_REF
7235      && CONSTANT_POOL_ADDRESS_P (x))
7236    {
7237      rtx c = get_pool_constant (x);
7238      machine_mode cmode = get_pool_mode (x);
7239      if (ASM_OUTPUT_SPECIAL_POOL_ENTRY_P (c, cmode))
7240	return true;
7241    }
7242
7243  return false;
7244}
7245
7246/* Construct the SYMBOL_REF for the tls_get_addr function.  */
7247
7248static GTY(()) rtx rs6000_tls_symbol;
7249static rtx
7250rs6000_tls_get_addr (void)
7251{
7252  if (!rs6000_tls_symbol)
7253    rs6000_tls_symbol = init_one_libfunc ("__tls_get_addr");
7254
7255  return rs6000_tls_symbol;
7256}
7257
7258/* Construct the SYMBOL_REF for TLS GOT references.  */
7259
7260static GTY(()) rtx rs6000_got_symbol;
7261static rtx
7262rs6000_got_sym (void)
7263{
7264  if (!rs6000_got_symbol)
7265    {
7266      rs6000_got_symbol = gen_rtx_SYMBOL_REF (Pmode, "_GLOBAL_OFFSET_TABLE_");
7267      SYMBOL_REF_FLAGS (rs6000_got_symbol) |= SYMBOL_FLAG_LOCAL;
7268      SYMBOL_REF_FLAGS (rs6000_got_symbol) |= SYMBOL_FLAG_EXTERNAL;
7269    }
7270
7271  return rs6000_got_symbol;
7272}
7273
7274/* AIX Thread-Local Address support.  */
7275
7276static rtx
7277rs6000_legitimize_tls_address_aix (rtx addr, enum tls_model model)
7278{
7279  rtx sym, mem, tocref, tlsreg, tmpreg, dest, tlsaddr;
7280  const char *name;
7281  char *tlsname;
7282
7283  name = XSTR (addr, 0);
7284  /* Append TLS CSECT qualifier, unless the symbol already is qualified
7285     or the symbol will be in TLS private data section.  */
7286  if (name[strlen (name) - 1] != ']'
7287      && (TREE_PUBLIC (SYMBOL_REF_DECL (addr))
7288	  || bss_initializer_p (SYMBOL_REF_DECL (addr))))
7289    {
7290      tlsname = XALLOCAVEC (char, strlen (name) + 4);
7291      strcpy (tlsname, name);
7292      strcat (tlsname,
7293	      bss_initializer_p (SYMBOL_REF_DECL (addr)) ? "[UL]" : "[TL]");
7294      tlsaddr = copy_rtx (addr);
7295      XSTR (tlsaddr, 0) = ggc_strdup (tlsname);
7296    }
7297  else
7298    tlsaddr = addr;
7299
7300  /* Place addr into TOC constant pool.  */
7301  sym = force_const_mem (GET_MODE (tlsaddr), tlsaddr);
7302
7303  /* Output the TOC entry and create the MEM referencing the value.  */
7304  if (constant_pool_expr_p (XEXP (sym, 0))
7305      && ASM_OUTPUT_SPECIAL_POOL_ENTRY_P (get_pool_constant (XEXP (sym, 0)), Pmode))
7306    {
7307      tocref = create_TOC_reference (XEXP (sym, 0), NULL_RTX);
7308      mem = gen_const_mem (Pmode, tocref);
7309      set_mem_alias_set (mem, get_TOC_alias_set ());
7310    }
7311  else
7312    return sym;
7313
7314  /* Use global-dynamic for local-dynamic.  */
7315  if (model == TLS_MODEL_GLOBAL_DYNAMIC
7316      || model == TLS_MODEL_LOCAL_DYNAMIC)
7317    {
7318      /* Create new TOC reference for @m symbol.  */
7319      name = XSTR (XVECEXP (XEXP (mem, 0), 0, 0), 0);
7320      tlsname = XALLOCAVEC (char, strlen (name) + 1);
7321      strcpy (tlsname, "*LCM");
7322      strcat (tlsname, name + 3);
7323      rtx modaddr = gen_rtx_SYMBOL_REF (Pmode, ggc_strdup (tlsname));
7324      SYMBOL_REF_FLAGS (modaddr) |= SYMBOL_FLAG_LOCAL;
7325      tocref = create_TOC_reference (modaddr, NULL_RTX);
7326      rtx modmem = gen_const_mem (Pmode, tocref);
7327      set_mem_alias_set (modmem, get_TOC_alias_set ());
7328
7329      rtx modreg = gen_reg_rtx (Pmode);
7330      emit_insn (gen_rtx_SET (VOIDmode, modreg, modmem));
7331
7332      tmpreg = gen_reg_rtx (Pmode);
7333      emit_insn (gen_rtx_SET (VOIDmode, tmpreg, mem));
7334
7335      dest = gen_reg_rtx (Pmode);
7336      if (TARGET_32BIT)
7337	emit_insn (gen_tls_get_addrsi (dest, modreg, tmpreg));
7338      else
7339	emit_insn (gen_tls_get_addrdi (dest, modreg, tmpreg));
7340      return dest;
7341    }
7342  /* Obtain TLS pointer: 32 bit call or 64 bit GPR 13.  */
7343  else if (TARGET_32BIT)
7344    {
7345      tlsreg = gen_reg_rtx (SImode);
7346      emit_insn (gen_tls_get_tpointer (tlsreg));
7347    }
7348  else
7349    tlsreg = gen_rtx_REG (DImode, 13);
7350
7351  /* Load the TOC value into temporary register.  */
7352  tmpreg = gen_reg_rtx (Pmode);
7353  emit_insn (gen_rtx_SET (VOIDmode, tmpreg, mem));
7354  set_unique_reg_note (get_last_insn (), REG_EQUAL,
7355		       gen_rtx_MINUS (Pmode, addr, tlsreg));
7356
7357  /* Add TOC symbol value to TLS pointer.  */
7358  dest = force_reg (Pmode, gen_rtx_PLUS (Pmode, tmpreg, tlsreg));
7359
7360  return dest;
7361}
7362
7363/* ADDR contains a thread-local SYMBOL_REF.  Generate code to compute
7364   this (thread-local) address.  */
7365
7366static rtx
7367rs6000_legitimize_tls_address (rtx addr, enum tls_model model)
7368{
7369  rtx dest, insn;
7370
7371  if (TARGET_XCOFF)
7372    return rs6000_legitimize_tls_address_aix (addr, model);
7373
7374  dest = gen_reg_rtx (Pmode);
7375  if (model == TLS_MODEL_LOCAL_EXEC && rs6000_tls_size == 16)
7376    {
7377      rtx tlsreg;
7378
7379      if (TARGET_64BIT)
7380	{
7381	  tlsreg = gen_rtx_REG (Pmode, 13);
7382	  insn = gen_tls_tprel_64 (dest, tlsreg, addr);
7383	}
7384      else
7385	{
7386	  tlsreg = gen_rtx_REG (Pmode, 2);
7387	  insn = gen_tls_tprel_32 (dest, tlsreg, addr);
7388	}
7389      emit_insn (insn);
7390    }
7391  else if (model == TLS_MODEL_LOCAL_EXEC && rs6000_tls_size == 32)
7392    {
7393      rtx tlsreg, tmp;
7394
7395      tmp = gen_reg_rtx (Pmode);
7396      if (TARGET_64BIT)
7397	{
7398	  tlsreg = gen_rtx_REG (Pmode, 13);
7399	  insn = gen_tls_tprel_ha_64 (tmp, tlsreg, addr);
7400	}
7401      else
7402	{
7403	  tlsreg = gen_rtx_REG (Pmode, 2);
7404	  insn = gen_tls_tprel_ha_32 (tmp, tlsreg, addr);
7405	}
7406      emit_insn (insn);
7407      if (TARGET_64BIT)
7408	insn = gen_tls_tprel_lo_64 (dest, tmp, addr);
7409      else
7410	insn = gen_tls_tprel_lo_32 (dest, tmp, addr);
7411      emit_insn (insn);
7412    }
7413  else
7414    {
7415      rtx r3, got, tga, tmp1, tmp2, call_insn;
7416
7417      /* We currently use relocations like @got@tlsgd for tls, which
7418	 means the linker will handle allocation of tls entries, placing
7419	 them in the .got section.  So use a pointer to the .got section,
7420	 not one to secondary TOC sections used by 64-bit -mminimal-toc,
7421	 or to secondary GOT sections used by 32-bit -fPIC.  */
7422      if (TARGET_64BIT)
7423	got = gen_rtx_REG (Pmode, 2);
7424      else
7425	{
7426	  if (flag_pic == 1)
7427	    got = gen_rtx_REG (Pmode, RS6000_PIC_OFFSET_TABLE_REGNUM);
7428	  else
7429	    {
7430	      rtx gsym = rs6000_got_sym ();
7431	      got = gen_reg_rtx (Pmode);
7432	      if (flag_pic == 0)
7433		rs6000_emit_move (got, gsym, Pmode);
7434	      else
7435		{
7436		  rtx mem, lab, last;
7437
7438		  tmp1 = gen_reg_rtx (Pmode);
7439		  tmp2 = gen_reg_rtx (Pmode);
7440		  mem = gen_const_mem (Pmode, tmp1);
7441		  lab = gen_label_rtx ();
7442		  emit_insn (gen_load_toc_v4_PIC_1b (gsym, lab));
7443		  emit_move_insn (tmp1, gen_rtx_REG (Pmode, LR_REGNO));
7444		  if (TARGET_LINK_STACK)
7445		    emit_insn (gen_addsi3 (tmp1, tmp1, GEN_INT (4)));
7446		  emit_move_insn (tmp2, mem);
7447		  last = emit_insn (gen_addsi3 (got, tmp1, tmp2));
7448		  set_unique_reg_note (last, REG_EQUAL, gsym);
7449		}
7450	    }
7451	}
7452
7453      if (model == TLS_MODEL_GLOBAL_DYNAMIC)
7454	{
7455	  tga = rs6000_tls_get_addr ();
7456	  emit_library_call_value (tga, dest, LCT_CONST, Pmode,
7457				   1, const0_rtx, Pmode);
7458
7459	  r3 = gen_rtx_REG (Pmode, 3);
7460	  if (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
7461	    {
7462	      if (TARGET_64BIT)
7463		insn = gen_tls_gd_aix64 (r3, got, addr, tga, const0_rtx);
7464	      else
7465		insn = gen_tls_gd_aix32 (r3, got, addr, tga, const0_rtx);
7466	    }
7467	  else if (DEFAULT_ABI == ABI_V4)
7468	    insn = gen_tls_gd_sysvsi (r3, got, addr, tga, const0_rtx);
7469	  else
7470	    gcc_unreachable ();
7471	  call_insn = last_call_insn ();
7472	  PATTERN (call_insn) = insn;
7473	  if (DEFAULT_ABI == ABI_V4 && TARGET_SECURE_PLT && flag_pic)
7474	    use_reg (&CALL_INSN_FUNCTION_USAGE (call_insn),
7475		     pic_offset_table_rtx);
7476	}
7477      else if (model == TLS_MODEL_LOCAL_DYNAMIC)
7478	{
7479	  tga = rs6000_tls_get_addr ();
7480	  tmp1 = gen_reg_rtx (Pmode);
7481	  emit_library_call_value (tga, tmp1, LCT_CONST, Pmode,
7482				   1, const0_rtx, Pmode);
7483
7484	  r3 = gen_rtx_REG (Pmode, 3);
7485	  if (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
7486	    {
7487	      if (TARGET_64BIT)
7488		insn = gen_tls_ld_aix64 (r3, got, tga, const0_rtx);
7489	      else
7490		insn = gen_tls_ld_aix32 (r3, got, tga, const0_rtx);
7491	    }
7492	  else if (DEFAULT_ABI == ABI_V4)
7493	    insn = gen_tls_ld_sysvsi (r3, got, tga, const0_rtx);
7494	  else
7495	    gcc_unreachable ();
7496	  call_insn = last_call_insn ();
7497	  PATTERN (call_insn) = insn;
7498	  if (DEFAULT_ABI == ABI_V4 && TARGET_SECURE_PLT && flag_pic)
7499	    use_reg (&CALL_INSN_FUNCTION_USAGE (call_insn),
7500		     pic_offset_table_rtx);
7501
7502	  if (rs6000_tls_size == 16)
7503	    {
7504	      if (TARGET_64BIT)
7505		insn = gen_tls_dtprel_64 (dest, tmp1, addr);
7506	      else
7507		insn = gen_tls_dtprel_32 (dest, tmp1, addr);
7508	    }
7509	  else if (rs6000_tls_size == 32)
7510	    {
7511	      tmp2 = gen_reg_rtx (Pmode);
7512	      if (TARGET_64BIT)
7513		insn = gen_tls_dtprel_ha_64 (tmp2, tmp1, addr);
7514	      else
7515		insn = gen_tls_dtprel_ha_32 (tmp2, tmp1, addr);
7516	      emit_insn (insn);
7517	      if (TARGET_64BIT)
7518		insn = gen_tls_dtprel_lo_64 (dest, tmp2, addr);
7519	      else
7520		insn = gen_tls_dtprel_lo_32 (dest, tmp2, addr);
7521	    }
7522	  else
7523	    {
7524	      tmp2 = gen_reg_rtx (Pmode);
7525	      if (TARGET_64BIT)
7526		insn = gen_tls_got_dtprel_64 (tmp2, got, addr);
7527	      else
7528		insn = gen_tls_got_dtprel_32 (tmp2, got, addr);
7529	      emit_insn (insn);
7530	      insn = gen_rtx_SET (Pmode, dest,
7531				  gen_rtx_PLUS (Pmode, tmp2, tmp1));
7532	    }
7533	  emit_insn (insn);
7534	}
7535      else
7536	{
7537	  /* IE, or 64-bit offset LE.  */
7538	  tmp2 = gen_reg_rtx (Pmode);
7539	  if (TARGET_64BIT)
7540	    insn = gen_tls_got_tprel_64 (tmp2, got, addr);
7541	  else
7542	    insn = gen_tls_got_tprel_32 (tmp2, got, addr);
7543	  emit_insn (insn);
7544	  if (TARGET_64BIT)
7545	    insn = gen_tls_tls_64 (dest, tmp2, addr);
7546	  else
7547	    insn = gen_tls_tls_32 (dest, tmp2, addr);
7548	  emit_insn (insn);
7549	}
7550    }
7551
7552  return dest;
7553}
7554
7555/* Implement TARGET_CANNOT_FORCE_CONST_MEM.  */
7556
7557static bool
7558rs6000_cannot_force_const_mem (machine_mode mode ATTRIBUTE_UNUSED, rtx x)
7559{
7560  if (GET_CODE (x) == HIGH
7561      && GET_CODE (XEXP (x, 0)) == UNSPEC)
7562    return true;
7563
7564  /* A TLS symbol in the TOC cannot contain a sum.  */
7565  if (GET_CODE (x) == CONST
7566      && GET_CODE (XEXP (x, 0)) == PLUS
7567      && GET_CODE (XEXP (XEXP (x, 0), 0)) == SYMBOL_REF
7568      && SYMBOL_REF_TLS_MODEL (XEXP (XEXP (x, 0), 0)) != 0)
7569    return true;
7570
7571  /* Do not place an ELF TLS symbol in the constant pool.  */
7572  return TARGET_ELF && tls_referenced_p (x);
7573}
7574
7575/* Return true iff the given SYMBOL_REF refers to a constant pool entry
7576   that we have put in the TOC, or for cmodel=medium, if the SYMBOL_REF
7577   can be addressed relative to the toc pointer.  */
7578
7579static bool
7580use_toc_relative_ref (rtx sym)
7581{
7582  return ((constant_pool_expr_p (sym)
7583	   && ASM_OUTPUT_SPECIAL_POOL_ENTRY_P (get_pool_constant (sym),
7584					       get_pool_mode (sym)))
7585	  || (TARGET_CMODEL == CMODEL_MEDIUM
7586	      && SYMBOL_REF_LOCAL_P (sym)));
7587}
7588
7589/* Our implementation of LEGITIMIZE_RELOAD_ADDRESS.  Returns a value to
7590   replace the input X, or the original X if no replacement is called for.
7591   The output parameter *WIN is 1 if the calling macro should goto WIN,
7592   0 if it should not.
7593
7594   For RS/6000, we wish to handle large displacements off a base
7595   register by splitting the addend across an addiu/addis and the mem insn.
7596   This cuts number of extra insns needed from 3 to 1.
7597
7598   On Darwin, we use this to generate code for floating point constants.
7599   A movsf_low is generated so we wind up with 2 instructions rather than 3.
7600   The Darwin code is inside #if TARGET_MACHO because only then are the
7601   machopic_* functions defined.  */
7602static rtx
7603rs6000_legitimize_reload_address (rtx x, machine_mode mode,
7604				  int opnum, int type,
7605				  int ind_levels ATTRIBUTE_UNUSED, int *win)
7606{
7607  bool reg_offset_p = reg_offset_addressing_ok_p (mode);
7608
7609  /* Nasty hack for vsx_splat_V2DF/V2DI load from mem, which takes a
7610     DFmode/DImode MEM.  */
7611  if (reg_offset_p
7612      && opnum == 1
7613      && ((mode == DFmode && recog_data.operand_mode[0] == V2DFmode)
7614	  || (mode == DImode && recog_data.operand_mode[0] == V2DImode)))
7615    reg_offset_p = false;
7616
7617  /* We must recognize output that we have already generated ourselves.  */
7618  if (GET_CODE (x) == PLUS
7619      && GET_CODE (XEXP (x, 0)) == PLUS
7620      && GET_CODE (XEXP (XEXP (x, 0), 0)) == REG
7621      && GET_CODE (XEXP (XEXP (x, 0), 1)) == CONST_INT
7622      && GET_CODE (XEXP (x, 1)) == CONST_INT)
7623    {
7624      push_reload (XEXP (x, 0), NULL_RTX, &XEXP (x, 0), NULL,
7625		   BASE_REG_CLASS, GET_MODE (x), VOIDmode, 0, 0,
7626		   opnum, (enum reload_type) type);
7627      *win = 1;
7628      return x;
7629    }
7630
7631  /* Likewise for (lo_sum (high ...) ...) output we have generated.  */
7632  if (GET_CODE (x) == LO_SUM
7633      && GET_CODE (XEXP (x, 0)) == HIGH)
7634    {
7635      push_reload (XEXP (x, 0), NULL_RTX, &XEXP (x, 0), NULL,
7636		   BASE_REG_CLASS, Pmode, VOIDmode, 0, 0,
7637		   opnum, (enum reload_type) type);
7638      *win = 1;
7639      return x;
7640    }
7641
7642#if TARGET_MACHO
7643  if (DEFAULT_ABI == ABI_DARWIN && flag_pic
7644      && GET_CODE (x) == LO_SUM
7645      && GET_CODE (XEXP (x, 0)) == PLUS
7646      && XEXP (XEXP (x, 0), 0) == pic_offset_table_rtx
7647      && GET_CODE (XEXP (XEXP (x, 0), 1)) == HIGH
7648      && XEXP (XEXP (XEXP (x, 0), 1), 0) == XEXP (x, 1)
7649      && machopic_operand_p (XEXP (x, 1)))
7650    {
7651      /* Result of previous invocation of this function on Darwin
7652	 floating point constant.  */
7653      push_reload (XEXP (x, 0), NULL_RTX, &XEXP (x, 0), NULL,
7654		   BASE_REG_CLASS, Pmode, VOIDmode, 0, 0,
7655		   opnum, (enum reload_type) type);
7656      *win = 1;
7657      return x;
7658    }
7659#endif
7660
7661  if (TARGET_CMODEL != CMODEL_SMALL
7662      && reg_offset_p
7663      && small_toc_ref (x, VOIDmode))
7664    {
7665      rtx hi = gen_rtx_HIGH (Pmode, copy_rtx (x));
7666      x = gen_rtx_LO_SUM (Pmode, hi, x);
7667      push_reload (XEXP (x, 0), NULL_RTX, &XEXP (x, 0), NULL,
7668		   BASE_REG_CLASS, Pmode, VOIDmode, 0, 0,
7669		   opnum, (enum reload_type) type);
7670      *win = 1;
7671      return x;
7672    }
7673
7674  if (GET_CODE (x) == PLUS
7675      && GET_CODE (XEXP (x, 0)) == REG
7676      && REGNO (XEXP (x, 0)) < FIRST_PSEUDO_REGISTER
7677      && INT_REG_OK_FOR_BASE_P (XEXP (x, 0), 1)
7678      && GET_CODE (XEXP (x, 1)) == CONST_INT
7679      && reg_offset_p
7680      && !SPE_VECTOR_MODE (mode)
7681      && !(TARGET_E500_DOUBLE && GET_MODE_SIZE (mode) > UNITS_PER_WORD)
7682      && (!VECTOR_MODE_P (mode) || VECTOR_MEM_NONE_P (mode)))
7683    {
7684      HOST_WIDE_INT val = INTVAL (XEXP (x, 1));
7685      HOST_WIDE_INT low = ((val & 0xffff) ^ 0x8000) - 0x8000;
7686      HOST_WIDE_INT high
7687	= (((val - low) & 0xffffffff) ^ 0x80000000) - 0x80000000;
7688
7689      /* Check for 32-bit overflow.  */
7690      if (high + low != val)
7691	{
7692	  *win = 0;
7693	  return x;
7694	}
7695
7696      /* Reload the high part into a base reg; leave the low part
7697	 in the mem directly.  */
7698
7699      x = gen_rtx_PLUS (GET_MODE (x),
7700			gen_rtx_PLUS (GET_MODE (x), XEXP (x, 0),
7701				      GEN_INT (high)),
7702			GEN_INT (low));
7703
7704      push_reload (XEXP (x, 0), NULL_RTX, &XEXP (x, 0), NULL,
7705		   BASE_REG_CLASS, GET_MODE (x), VOIDmode, 0, 0,
7706		   opnum, (enum reload_type) type);
7707      *win = 1;
7708      return x;
7709    }
7710
7711  if (GET_CODE (x) == SYMBOL_REF
7712      && reg_offset_p
7713      && (!VECTOR_MODE_P (mode) || VECTOR_MEM_NONE_P (mode))
7714      && !SPE_VECTOR_MODE (mode)
7715#if TARGET_MACHO
7716      && DEFAULT_ABI == ABI_DARWIN
7717      && (flag_pic || MACHO_DYNAMIC_NO_PIC_P)
7718      && machopic_symbol_defined_p (x)
7719#else
7720      && DEFAULT_ABI == ABI_V4
7721      && !flag_pic
7722#endif
7723      /* Don't do this for TFmode or TDmode, since the result isn't offsettable.
7724	 The same goes for DImode without 64-bit gprs and DFmode and DDmode
7725	 without fprs.
7726	 ??? Assume floating point reg based on mode?  This assumption is
7727	 violated by eg. powerpc-linux -m32 compile of gcc.dg/pr28796-2.c
7728	 where reload ends up doing a DFmode load of a constant from
7729	 mem using two gprs.  Unfortunately, at this point reload
7730	 hasn't yet selected regs so poking around in reload data
7731	 won't help and even if we could figure out the regs reliably,
7732	 we'd still want to allow this transformation when the mem is
7733	 naturally aligned.  Since we say the address is good here, we
7734	 can't disable offsets from LO_SUMs in mem_operand_gpr.
7735	 FIXME: Allow offset from lo_sum for other modes too, when
7736	 mem is sufficiently aligned.
7737
7738	 Also disallow this if the type can go in VMX/Altivec registers, since
7739	 those registers do not have d-form (reg+offset) address modes.  */
7740      && !reg_addr[mode].scalar_in_vmx_p
7741      && mode != TFmode
7742      && mode != TDmode
7743      && (mode != TImode || !TARGET_VSX_TIMODE)
7744      && mode != PTImode
7745      && (mode != DImode || TARGET_POWERPC64)
7746      && ((mode != DFmode && mode != DDmode) || TARGET_POWERPC64
7747	  || (TARGET_HARD_FLOAT && TARGET_FPRS && TARGET_DOUBLE_FLOAT)))
7748    {
7749#if TARGET_MACHO
7750      if (flag_pic)
7751	{
7752	  rtx offset = machopic_gen_offset (x);
7753	  x = gen_rtx_LO_SUM (GET_MODE (x),
7754		gen_rtx_PLUS (Pmode, pic_offset_table_rtx,
7755		  gen_rtx_HIGH (Pmode, offset)), offset);
7756	}
7757      else
7758#endif
7759	x = gen_rtx_LO_SUM (GET_MODE (x),
7760	      gen_rtx_HIGH (Pmode, x), x);
7761
7762      push_reload (XEXP (x, 0), NULL_RTX, &XEXP (x, 0), NULL,
7763		   BASE_REG_CLASS, Pmode, VOIDmode, 0, 0,
7764		   opnum, (enum reload_type) type);
7765      *win = 1;
7766      return x;
7767    }
7768
7769  /* Reload an offset address wrapped by an AND that represents the
7770     masking of the lower bits.  Strip the outer AND and let reload
7771     convert the offset address into an indirect address.  For VSX,
7772     force reload to create the address with an AND in a separate
7773     register, because we can't guarantee an altivec register will
7774     be used.  */
7775  if (VECTOR_MEM_ALTIVEC_P (mode)
7776      && GET_CODE (x) == AND
7777      && GET_CODE (XEXP (x, 0)) == PLUS
7778      && GET_CODE (XEXP (XEXP (x, 0), 0)) == REG
7779      && GET_CODE (XEXP (XEXP (x, 0), 1)) == CONST_INT
7780      && GET_CODE (XEXP (x, 1)) == CONST_INT
7781      && INTVAL (XEXP (x, 1)) == -16)
7782    {
7783      x = XEXP (x, 0);
7784      *win = 1;
7785      return x;
7786    }
7787
7788  if (TARGET_TOC
7789      && reg_offset_p
7790      && GET_CODE (x) == SYMBOL_REF
7791      && use_toc_relative_ref (x))
7792    {
7793      x = create_TOC_reference (x, NULL_RTX);
7794      if (TARGET_CMODEL != CMODEL_SMALL)
7795	push_reload (XEXP (x, 0), NULL_RTX, &XEXP (x, 0), NULL,
7796		     BASE_REG_CLASS, Pmode, VOIDmode, 0, 0,
7797		     opnum, (enum reload_type) type);
7798      *win = 1;
7799      return x;
7800    }
7801  *win = 0;
7802  return x;
7803}
7804
7805/* Debug version of rs6000_legitimize_reload_address.  */
7806static rtx
7807rs6000_debug_legitimize_reload_address (rtx x, machine_mode mode,
7808					int opnum, int type,
7809					int ind_levels, int *win)
7810{
7811  rtx ret = rs6000_legitimize_reload_address (x, mode, opnum, type,
7812					      ind_levels, win);
7813  fprintf (stderr,
7814	   "\nrs6000_legitimize_reload_address: mode = %s, opnum = %d, "
7815	   "type = %d, ind_levels = %d, win = %d, original addr:\n",
7816	   GET_MODE_NAME (mode), opnum, type, ind_levels, *win);
7817  debug_rtx (x);
7818
7819  if (x == ret)
7820    fprintf (stderr, "Same address returned\n");
7821  else if (!ret)
7822    fprintf (stderr, "NULL returned\n");
7823  else
7824    {
7825      fprintf (stderr, "New address:\n");
7826      debug_rtx (ret);
7827    }
7828
7829  return ret;
7830}
7831
7832/* TARGET_LEGITIMATE_ADDRESS_P recognizes an RTL expression
7833   that is a valid memory address for an instruction.
7834   The MODE argument is the machine mode for the MEM expression
7835   that wants to use this address.
7836
7837   On the RS/6000, there are four valid address: a SYMBOL_REF that
7838   refers to a constant pool entry of an address (or the sum of it
7839   plus a constant), a short (16-bit signed) constant plus a register,
7840   the sum of two registers, or a register indirect, possibly with an
7841   auto-increment.  For DFmode, DDmode and DImode with a constant plus
7842   register, we must ensure that both words are addressable or PowerPC64
7843   with offset word aligned.
7844
7845   For modes spanning multiple registers (DFmode and DDmode in 32-bit GPRs,
7846   32-bit DImode, TImode, TFmode, TDmode), indexed addressing cannot be used
7847   because adjacent memory cells are accessed by adding word-sized offsets
7848   during assembly output.  */
7849static bool
7850rs6000_legitimate_address_p (machine_mode mode, rtx x, bool reg_ok_strict)
7851{
7852  bool reg_offset_p = reg_offset_addressing_ok_p (mode);
7853
7854  /* If this is an unaligned stvx/ldvx type address, discard the outer AND.  */
7855  if (VECTOR_MEM_ALTIVEC_P (mode)
7856      && GET_CODE (x) == AND
7857      && GET_CODE (XEXP (x, 1)) == CONST_INT
7858      && INTVAL (XEXP (x, 1)) == -16)
7859    x = XEXP (x, 0);
7860
7861  if (TARGET_ELF && RS6000_SYMBOL_REF_TLS_P (x))
7862    return 0;
7863  if (legitimate_indirect_address_p (x, reg_ok_strict))
7864    return 1;
7865  if (TARGET_UPDATE
7866      && (GET_CODE (x) == PRE_INC || GET_CODE (x) == PRE_DEC)
7867      && mode_supports_pre_incdec_p (mode)
7868      && legitimate_indirect_address_p (XEXP (x, 0), reg_ok_strict))
7869    return 1;
7870  if (virtual_stack_registers_memory_p (x))
7871    return 1;
7872  if (reg_offset_p && legitimate_small_data_p (mode, x))
7873    return 1;
7874  if (reg_offset_p
7875      && legitimate_constant_pool_address_p (x, mode,
7876					     reg_ok_strict || lra_in_progress))
7877    return 1;
7878  /* For TImode, if we have load/store quad and TImode in VSX registers, only
7879     allow register indirect addresses.  This will allow the values to go in
7880     either GPRs or VSX registers without reloading.  The vector types would
7881     tend to go into VSX registers, so we allow REG+REG, while TImode seems
7882     somewhat split, in that some uses are GPR based, and some VSX based.  */
7883  if (mode == TImode && TARGET_QUAD_MEMORY && TARGET_VSX_TIMODE)
7884    return 0;
7885  /* If not REG_OK_STRICT (before reload) let pass any stack offset.  */
7886  if (! reg_ok_strict
7887      && reg_offset_p
7888      && GET_CODE (x) == PLUS
7889      && GET_CODE (XEXP (x, 0)) == REG
7890      && (XEXP (x, 0) == virtual_stack_vars_rtx
7891	  || XEXP (x, 0) == arg_pointer_rtx)
7892      && GET_CODE (XEXP (x, 1)) == CONST_INT)
7893    return 1;
7894  if (rs6000_legitimate_offset_address_p (mode, x, reg_ok_strict, false))
7895    return 1;
7896  if (mode != TFmode
7897      && mode != TDmode
7898      && ((TARGET_HARD_FLOAT && TARGET_FPRS && TARGET_DOUBLE_FLOAT)
7899	  || TARGET_POWERPC64
7900	  || (mode != DFmode && mode != DDmode)
7901	  || (TARGET_E500_DOUBLE && mode != DDmode))
7902      && (TARGET_POWERPC64 || mode != DImode)
7903      && (mode != TImode || VECTOR_MEM_VSX_P (TImode))
7904      && mode != PTImode
7905      && !avoiding_indexed_address_p (mode)
7906      && legitimate_indexed_address_p (x, reg_ok_strict))
7907    return 1;
7908  if (TARGET_UPDATE && GET_CODE (x) == PRE_MODIFY
7909      && mode_supports_pre_modify_p (mode)
7910      && legitimate_indirect_address_p (XEXP (x, 0), reg_ok_strict)
7911      && (rs6000_legitimate_offset_address_p (mode, XEXP (x, 1),
7912					      reg_ok_strict, false)
7913	  || (!avoiding_indexed_address_p (mode)
7914	      && legitimate_indexed_address_p (XEXP (x, 1), reg_ok_strict)))
7915      && rtx_equal_p (XEXP (XEXP (x, 1), 0), XEXP (x, 0)))
7916    return 1;
7917  if (reg_offset_p && legitimate_lo_sum_address_p (mode, x, reg_ok_strict))
7918    return 1;
7919  return 0;
7920}
7921
7922/* Debug version of rs6000_legitimate_address_p.  */
7923static bool
7924rs6000_debug_legitimate_address_p (machine_mode mode, rtx x,
7925				   bool reg_ok_strict)
7926{
7927  bool ret = rs6000_legitimate_address_p (mode, x, reg_ok_strict);
7928  fprintf (stderr,
7929	   "\nrs6000_legitimate_address_p: return = %s, mode = %s, "
7930	   "strict = %d, reload = %s, code = %s\n",
7931	   ret ? "true" : "false",
7932	   GET_MODE_NAME (mode),
7933	   reg_ok_strict,
7934	   (reload_completed
7935	    ? "after"
7936	    : (reload_in_progress ? "progress" : "before")),
7937	   GET_RTX_NAME (GET_CODE (x)));
7938  debug_rtx (x);
7939
7940  return ret;
7941}
7942
7943/* Implement TARGET_MODE_DEPENDENT_ADDRESS_P.  */
7944
7945static bool
7946rs6000_mode_dependent_address_p (const_rtx addr,
7947				 addr_space_t as ATTRIBUTE_UNUSED)
7948{
7949  return rs6000_mode_dependent_address_ptr (addr);
7950}
7951
7952/* Go to LABEL if ADDR (a legitimate address expression)
7953   has an effect that depends on the machine mode it is used for.
7954
7955   On the RS/6000 this is true of all integral offsets (since AltiVec
7956   and VSX modes don't allow them) or is a pre-increment or decrement.
7957
7958   ??? Except that due to conceptual problems in offsettable_address_p
7959   we can't really report the problems of integral offsets.  So leave
7960   this assuming that the adjustable offset must be valid for the
7961   sub-words of a TFmode operand, which is what we had before.  */
7962
7963static bool
7964rs6000_mode_dependent_address (const_rtx addr)
7965{
7966  switch (GET_CODE (addr))
7967    {
7968    case PLUS:
7969      /* Any offset from virtual_stack_vars_rtx and arg_pointer_rtx
7970	 is considered a legitimate address before reload, so there
7971	 are no offset restrictions in that case.  Note that this
7972	 condition is safe in strict mode because any address involving
7973	 virtual_stack_vars_rtx or arg_pointer_rtx would already have
7974	 been rejected as illegitimate.  */
7975      if (XEXP (addr, 0) != virtual_stack_vars_rtx
7976	  && XEXP (addr, 0) != arg_pointer_rtx
7977	  && GET_CODE (XEXP (addr, 1)) == CONST_INT)
7978	{
7979	  unsigned HOST_WIDE_INT val = INTVAL (XEXP (addr, 1));
7980	  return val + 0x8000 >= 0x10000 - (TARGET_POWERPC64 ? 8 : 12);
7981	}
7982      break;
7983
7984    case LO_SUM:
7985      /* Anything in the constant pool is sufficiently aligned that
7986	 all bytes have the same high part address.  */
7987      return !legitimate_constant_pool_address_p (addr, QImode, false);
7988
7989    /* Auto-increment cases are now treated generically in recog.c.  */
7990    case PRE_MODIFY:
7991      return TARGET_UPDATE;
7992
7993    /* AND is only allowed in Altivec loads.  */
7994    case AND:
7995      return true;
7996
7997    default:
7998      break;
7999    }
8000
8001  return false;
8002}
8003
8004/* Debug version of rs6000_mode_dependent_address.  */
8005static bool
8006rs6000_debug_mode_dependent_address (const_rtx addr)
8007{
8008  bool ret = rs6000_mode_dependent_address (addr);
8009
8010  fprintf (stderr, "\nrs6000_mode_dependent_address: ret = %s\n",
8011	   ret ? "true" : "false");
8012  debug_rtx (addr);
8013
8014  return ret;
8015}
8016
8017/* Implement FIND_BASE_TERM.  */
8018
8019rtx
8020rs6000_find_base_term (rtx op)
8021{
8022  rtx base;
8023
8024  base = op;
8025  if (GET_CODE (base) == CONST)
8026    base = XEXP (base, 0);
8027  if (GET_CODE (base) == PLUS)
8028    base = XEXP (base, 0);
8029  if (GET_CODE (base) == UNSPEC)
8030    switch (XINT (base, 1))
8031      {
8032      case UNSPEC_TOCREL:
8033      case UNSPEC_MACHOPIC_OFFSET:
8034	/* OP represents SYM [+ OFFSET] - ANCHOR.  SYM is the base term
8035	   for aliasing purposes.  */
8036	return XVECEXP (base, 0, 0);
8037      }
8038
8039  return op;
8040}
8041
8042/* More elaborate version of recog's offsettable_memref_p predicate
8043   that works around the ??? note of rs6000_mode_dependent_address.
8044   In particular it accepts
8045
8046     (mem:DI (plus:SI (reg/f:SI 31 31) (const_int 32760 [0x7ff8])))
8047
8048   in 32-bit mode, that the recog predicate rejects.  */
8049
8050static bool
8051rs6000_offsettable_memref_p (rtx op, machine_mode reg_mode)
8052{
8053  bool worst_case;
8054
8055  if (!MEM_P (op))
8056    return false;
8057
8058  /* First mimic offsettable_memref_p.  */
8059  if (offsettable_address_p (true, GET_MODE (op), XEXP (op, 0)))
8060    return true;
8061
8062  /* offsettable_address_p invokes rs6000_mode_dependent_address, but
8063     the latter predicate knows nothing about the mode of the memory
8064     reference and, therefore, assumes that it is the largest supported
8065     mode (TFmode).  As a consequence, legitimate offsettable memory
8066     references are rejected.  rs6000_legitimate_offset_address_p contains
8067     the correct logic for the PLUS case of rs6000_mode_dependent_address,
8068     at least with a little bit of help here given that we know the
8069     actual registers used.  */
8070  worst_case = ((TARGET_POWERPC64 && GET_MODE_CLASS (reg_mode) == MODE_INT)
8071		|| GET_MODE_SIZE (reg_mode) == 4);
8072  return rs6000_legitimate_offset_address_p (GET_MODE (op), XEXP (op, 0),
8073					     true, worst_case);
8074}
8075
8076/* Change register usage conditional on target flags.  */
8077static void
8078rs6000_conditional_register_usage (void)
8079{
8080  int i;
8081
8082  if (TARGET_DEBUG_TARGET)
8083    fprintf (stderr, "rs6000_conditional_register_usage called\n");
8084
8085  /* Set MQ register fixed (already call_used) so that it will not be
8086     allocated.  */
8087  fixed_regs[64] = 1;
8088
8089  /* 64-bit AIX and Linux reserve GPR13 for thread-private data.  */
8090  if (TARGET_64BIT)
8091    fixed_regs[13] = call_used_regs[13]
8092      = call_really_used_regs[13] = 1;
8093
8094  /* Conditionally disable FPRs.  */
8095  if (TARGET_SOFT_FLOAT || !TARGET_FPRS)
8096    for (i = 32; i < 64; i++)
8097      fixed_regs[i] = call_used_regs[i]
8098	= call_really_used_regs[i] = 1;
8099
8100  /* The TOC register is not killed across calls in a way that is
8101     visible to the compiler.  */
8102  if (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
8103    call_really_used_regs[2] = 0;
8104
8105  if (DEFAULT_ABI == ABI_V4
8106      && PIC_OFFSET_TABLE_REGNUM != INVALID_REGNUM
8107      && flag_pic == 2)
8108    fixed_regs[RS6000_PIC_OFFSET_TABLE_REGNUM] = 1;
8109
8110  if (DEFAULT_ABI == ABI_V4
8111      && PIC_OFFSET_TABLE_REGNUM != INVALID_REGNUM
8112      && flag_pic == 1)
8113    fixed_regs[RS6000_PIC_OFFSET_TABLE_REGNUM]
8114      = call_used_regs[RS6000_PIC_OFFSET_TABLE_REGNUM]
8115      = call_really_used_regs[RS6000_PIC_OFFSET_TABLE_REGNUM] = 1;
8116
8117  if (DEFAULT_ABI == ABI_DARWIN
8118      && PIC_OFFSET_TABLE_REGNUM != INVALID_REGNUM)
8119      fixed_regs[RS6000_PIC_OFFSET_TABLE_REGNUM]
8120      = call_used_regs[RS6000_PIC_OFFSET_TABLE_REGNUM]
8121      = call_really_used_regs[RS6000_PIC_OFFSET_TABLE_REGNUM] = 1;
8122
8123  if (TARGET_TOC && TARGET_MINIMAL_TOC)
8124    fixed_regs[RS6000_PIC_OFFSET_TABLE_REGNUM]
8125      = call_used_regs[RS6000_PIC_OFFSET_TABLE_REGNUM] = 1;
8126
8127  if (TARGET_SPE)
8128    {
8129      global_regs[SPEFSCR_REGNO] = 1;
8130      /* We used to use r14 as FIXED_SCRATCH to address SPE 64-bit
8131         registers in prologues and epilogues.  We no longer use r14
8132         for FIXED_SCRATCH, but we're keeping r14 out of the allocation
8133         pool for link-compatibility with older versions of GCC.  Once
8134         "old" code has died out, we can return r14 to the allocation
8135         pool.  */
8136      fixed_regs[14]
8137	= call_used_regs[14]
8138	= call_really_used_regs[14] = 1;
8139    }
8140
8141  if (!TARGET_ALTIVEC && !TARGET_VSX)
8142    {
8143      for (i = FIRST_ALTIVEC_REGNO; i <= LAST_ALTIVEC_REGNO; ++i)
8144	fixed_regs[i] = call_used_regs[i] = call_really_used_regs[i] = 1;
8145      call_really_used_regs[VRSAVE_REGNO] = 1;
8146    }
8147
8148  if (TARGET_ALTIVEC || TARGET_VSX)
8149    global_regs[VSCR_REGNO] = 1;
8150
8151  if (TARGET_ALTIVEC_ABI)
8152    {
8153      for (i = FIRST_ALTIVEC_REGNO; i < FIRST_ALTIVEC_REGNO + 20; ++i)
8154	call_used_regs[i] = call_really_used_regs[i] = 1;
8155
8156      /* AIX reserves VR20:31 in non-extended ABI mode.  */
8157      if (TARGET_XCOFF)
8158	for (i = FIRST_ALTIVEC_REGNO + 20; i < FIRST_ALTIVEC_REGNO + 32; ++i)
8159	  fixed_regs[i] = call_used_regs[i] = call_really_used_regs[i] = 1;
8160    }
8161}
8162
8163
8164/* Output insns to set DEST equal to the constant SOURCE as a series of
8165   lis, ori and shl instructions and return TRUE.  */
8166
8167bool
8168rs6000_emit_set_const (rtx dest, rtx source)
8169{
8170  machine_mode mode = GET_MODE (dest);
8171  rtx temp, set;
8172  rtx_insn *insn;
8173  HOST_WIDE_INT c;
8174
8175  gcc_checking_assert (CONST_INT_P (source));
8176  c = INTVAL (source);
8177  switch (mode)
8178    {
8179    case QImode:
8180    case HImode:
8181      emit_insn (gen_rtx_SET (VOIDmode, dest, source));
8182      return true;
8183
8184    case SImode:
8185      temp = !can_create_pseudo_p () ? dest : gen_reg_rtx (SImode);
8186
8187      emit_insn (gen_rtx_SET (VOIDmode, copy_rtx (temp),
8188			      GEN_INT (c & ~(HOST_WIDE_INT) 0xffff)));
8189      emit_insn (gen_rtx_SET (VOIDmode, dest,
8190			      gen_rtx_IOR (SImode, copy_rtx (temp),
8191					   GEN_INT (c & 0xffff))));
8192      break;
8193
8194    case DImode:
8195      if (!TARGET_POWERPC64)
8196	{
8197	  rtx hi, lo;
8198
8199	  hi = operand_subword_force (copy_rtx (dest), WORDS_BIG_ENDIAN == 0,
8200				      DImode);
8201	  lo = operand_subword_force (dest, WORDS_BIG_ENDIAN != 0,
8202				      DImode);
8203	  emit_move_insn (hi, GEN_INT (c >> 32));
8204	  c = ((c & 0xffffffff) ^ 0x80000000) - 0x80000000;
8205	  emit_move_insn (lo, GEN_INT (c));
8206	}
8207      else
8208	rs6000_emit_set_long_const (dest, c);
8209      break;
8210
8211    default:
8212      gcc_unreachable ();
8213    }
8214
8215  insn = get_last_insn ();
8216  set = single_set (insn);
8217  if (! CONSTANT_P (SET_SRC (set)))
8218    set_unique_reg_note (insn, REG_EQUAL, GEN_INT (c));
8219
8220  return true;
8221}
8222
8223/* Subroutine of rs6000_emit_set_const, handling PowerPC64 DImode.
8224   Output insns to set DEST equal to the constant C as a series of
8225   lis, ori and shl instructions.  */
8226
8227static void
8228rs6000_emit_set_long_const (rtx dest, HOST_WIDE_INT c)
8229{
8230  rtx temp;
8231  HOST_WIDE_INT ud1, ud2, ud3, ud4;
8232
8233  ud1 = c & 0xffff;
8234  c = c >> 16;
8235  ud2 = c & 0xffff;
8236  c = c >> 16;
8237  ud3 = c & 0xffff;
8238  c = c >> 16;
8239  ud4 = c & 0xffff;
8240
8241  if ((ud4 == 0xffff && ud3 == 0xffff && ud2 == 0xffff && (ud1 & 0x8000))
8242      || (ud4 == 0 && ud3 == 0 && ud2 == 0 && ! (ud1 & 0x8000)))
8243    emit_move_insn (dest, GEN_INT ((ud1 ^ 0x8000) - 0x8000));
8244
8245  else if ((ud4 == 0xffff && ud3 == 0xffff && (ud2 & 0x8000))
8246	   || (ud4 == 0 && ud3 == 0 && ! (ud2 & 0x8000)))
8247    {
8248      temp = !can_create_pseudo_p () ? dest : gen_reg_rtx (DImode);
8249
8250      emit_move_insn (ud1 != 0 ? copy_rtx (temp) : dest,
8251		      GEN_INT (((ud2 << 16) ^ 0x80000000) - 0x80000000));
8252      if (ud1 != 0)
8253	emit_move_insn (dest,
8254			gen_rtx_IOR (DImode, copy_rtx (temp),
8255				     GEN_INT (ud1)));
8256    }
8257  else if (ud3 == 0 && ud4 == 0)
8258    {
8259      temp = !can_create_pseudo_p () ? dest : gen_reg_rtx (DImode);
8260
8261      gcc_assert (ud2 & 0x8000);
8262      emit_move_insn (copy_rtx (temp),
8263		      GEN_INT (((ud2 << 16) ^ 0x80000000) - 0x80000000));
8264      if (ud1 != 0)
8265	emit_move_insn (copy_rtx (temp),
8266			gen_rtx_IOR (DImode, copy_rtx (temp),
8267				     GEN_INT (ud1)));
8268      emit_move_insn (dest,
8269		      gen_rtx_ZERO_EXTEND (DImode,
8270					   gen_lowpart (SImode,
8271							copy_rtx (temp))));
8272    }
8273  else if ((ud4 == 0xffff && (ud3 & 0x8000))
8274	   || (ud4 == 0 && ! (ud3 & 0x8000)))
8275    {
8276      temp = !can_create_pseudo_p () ? dest : gen_reg_rtx (DImode);
8277
8278      emit_move_insn (copy_rtx (temp),
8279		      GEN_INT (((ud3 << 16) ^ 0x80000000) - 0x80000000));
8280      if (ud2 != 0)
8281	emit_move_insn (copy_rtx (temp),
8282			gen_rtx_IOR (DImode, copy_rtx (temp),
8283				     GEN_INT (ud2)));
8284      emit_move_insn (ud1 != 0 ? copy_rtx (temp) : dest,
8285		      gen_rtx_ASHIFT (DImode, copy_rtx (temp),
8286				      GEN_INT (16)));
8287      if (ud1 != 0)
8288	emit_move_insn (dest,
8289			gen_rtx_IOR (DImode, copy_rtx (temp),
8290				     GEN_INT (ud1)));
8291    }
8292  else
8293    {
8294      temp = !can_create_pseudo_p () ? dest : gen_reg_rtx (DImode);
8295
8296      emit_move_insn (copy_rtx (temp),
8297		      GEN_INT (((ud4 << 16) ^ 0x80000000) - 0x80000000));
8298      if (ud3 != 0)
8299	emit_move_insn (copy_rtx (temp),
8300			gen_rtx_IOR (DImode, copy_rtx (temp),
8301				     GEN_INT (ud3)));
8302
8303      emit_move_insn (ud2 != 0 || ud1 != 0 ? copy_rtx (temp) : dest,
8304		      gen_rtx_ASHIFT (DImode, copy_rtx (temp),
8305				      GEN_INT (32)));
8306      if (ud2 != 0)
8307	emit_move_insn (ud1 != 0 ? copy_rtx (temp) : dest,
8308			gen_rtx_IOR (DImode, copy_rtx (temp),
8309				     GEN_INT (ud2 << 16)));
8310      if (ud1 != 0)
8311	emit_move_insn (dest,
8312			gen_rtx_IOR (DImode, copy_rtx (temp),
8313				     GEN_INT (ud1)));
8314    }
8315}
8316
8317/* Helper for the following.  Get rid of [r+r] memory refs
8318   in cases where it won't work (TImode, TFmode, TDmode, PTImode).  */
8319
8320static void
8321rs6000_eliminate_indexed_memrefs (rtx operands[2])
8322{
8323  if (reload_in_progress)
8324    return;
8325
8326  if (GET_CODE (operands[0]) == MEM
8327      && GET_CODE (XEXP (operands[0], 0)) != REG
8328      && ! legitimate_constant_pool_address_p (XEXP (operands[0], 0),
8329					       GET_MODE (operands[0]), false))
8330    operands[0]
8331      = replace_equiv_address (operands[0],
8332			       copy_addr_to_reg (XEXP (operands[0], 0)));
8333
8334  if (GET_CODE (operands[1]) == MEM
8335      && GET_CODE (XEXP (operands[1], 0)) != REG
8336      && ! legitimate_constant_pool_address_p (XEXP (operands[1], 0),
8337					       GET_MODE (operands[1]), false))
8338    operands[1]
8339      = replace_equiv_address (operands[1],
8340			       copy_addr_to_reg (XEXP (operands[1], 0)));
8341}
8342
8343/* Generate a vector of constants to permute MODE for a little-endian
8344   storage operation by swapping the two halves of a vector.  */
8345static rtvec
8346rs6000_const_vec (machine_mode mode)
8347{
8348  int i, subparts;
8349  rtvec v;
8350
8351  switch (mode)
8352    {
8353    case V1TImode:
8354      subparts = 1;
8355      break;
8356    case V2DFmode:
8357    case V2DImode:
8358      subparts = 2;
8359      break;
8360    case V4SFmode:
8361    case V4SImode:
8362      subparts = 4;
8363      break;
8364    case V8HImode:
8365      subparts = 8;
8366      break;
8367    case V16QImode:
8368      subparts = 16;
8369      break;
8370    default:
8371      gcc_unreachable();
8372    }
8373
8374  v = rtvec_alloc (subparts);
8375
8376  for (i = 0; i < subparts / 2; ++i)
8377    RTVEC_ELT (v, i) = gen_rtx_CONST_INT (DImode, i + subparts / 2);
8378  for (i = subparts / 2; i < subparts; ++i)
8379    RTVEC_ELT (v, i) = gen_rtx_CONST_INT (DImode, i - subparts / 2);
8380
8381  return v;
8382}
8383
8384/* Generate a permute rtx that represents an lxvd2x, stxvd2x, or xxpermdi
8385   for a VSX load or store operation.  */
8386rtx
8387rs6000_gen_le_vsx_permute (rtx source, machine_mode mode)
8388{
8389  rtx par = gen_rtx_PARALLEL (VOIDmode, rs6000_const_vec (mode));
8390  return gen_rtx_VEC_SELECT (mode, source, par);
8391}
8392
8393/* Emit a little-endian load from vector memory location SOURCE to VSX
8394   register DEST in mode MODE.  The load is done with two permuting
8395   insn's that represent an lxvd2x and xxpermdi.  */
8396void
8397rs6000_emit_le_vsx_load (rtx dest, rtx source, machine_mode mode)
8398{
8399  rtx tmp, permute_mem, permute_reg;
8400
8401  /* Use V2DImode to do swaps of types with 128-bit scalare parts (TImode,
8402     V1TImode).  */
8403  if (mode == TImode || mode == V1TImode)
8404    {
8405      mode = V2DImode;
8406      dest = gen_lowpart (V2DImode, dest);
8407      source = adjust_address (source, V2DImode, 0);
8408    }
8409
8410  tmp = can_create_pseudo_p () ? gen_reg_rtx_and_attrs (dest) : dest;
8411  permute_mem = rs6000_gen_le_vsx_permute (source, mode);
8412  permute_reg = rs6000_gen_le_vsx_permute (tmp, mode);
8413  emit_insn (gen_rtx_SET (VOIDmode, tmp, permute_mem));
8414  emit_insn (gen_rtx_SET (VOIDmode, dest, permute_reg));
8415}
8416
8417/* Emit a little-endian store to vector memory location DEST from VSX
8418   register SOURCE in mode MODE.  The store is done with two permuting
8419   insn's that represent an xxpermdi and an stxvd2x.  */
8420void
8421rs6000_emit_le_vsx_store (rtx dest, rtx source, machine_mode mode)
8422{
8423  rtx tmp, permute_src, permute_tmp;
8424
8425  /* This should never be called during or after reload, because it does
8426     not re-permute the source register.  It is intended only for use
8427     during expand.  */
8428  gcc_assert (!reload_in_progress && !lra_in_progress && !reload_completed);
8429
8430  /* Use V2DImode to do swaps of types with 128-bit scalare parts (TImode,
8431     V1TImode).  */
8432  if (mode == TImode || mode == V1TImode)
8433    {
8434      mode = V2DImode;
8435      dest = adjust_address (dest, V2DImode, 0);
8436      source = gen_lowpart (V2DImode, source);
8437    }
8438
8439  tmp = can_create_pseudo_p () ? gen_reg_rtx_and_attrs (source) : source;
8440  permute_src = rs6000_gen_le_vsx_permute (source, mode);
8441  permute_tmp = rs6000_gen_le_vsx_permute (tmp, mode);
8442  emit_insn (gen_rtx_SET (VOIDmode, tmp, permute_src));
8443  emit_insn (gen_rtx_SET (VOIDmode, dest, permute_tmp));
8444}
8445
8446/* Emit a sequence representing a little-endian VSX load or store,
8447   moving data from SOURCE to DEST in mode MODE.  This is done
8448   separately from rs6000_emit_move to ensure it is called only
8449   during expand.  LE VSX loads and stores introduced later are
8450   handled with a split.  The expand-time RTL generation allows
8451   us to optimize away redundant pairs of register-permutes.  */
8452void
8453rs6000_emit_le_vsx_move (rtx dest, rtx source, machine_mode mode)
8454{
8455  gcc_assert (!BYTES_BIG_ENDIAN
8456	      && VECTOR_MEM_VSX_P (mode)
8457	      && !gpr_or_gpr_p (dest, source)
8458	      && (MEM_P (source) ^ MEM_P (dest)));
8459
8460  if (MEM_P (source))
8461    {
8462      gcc_assert (REG_P (dest) || GET_CODE (dest) == SUBREG);
8463      rs6000_emit_le_vsx_load (dest, source, mode);
8464    }
8465  else
8466    {
8467      if (!REG_P (source))
8468	source = force_reg (mode, source);
8469      rs6000_emit_le_vsx_store (dest, source, mode);
8470    }
8471}
8472
8473/* Emit a move from SOURCE to DEST in mode MODE.  */
8474void
8475rs6000_emit_move (rtx dest, rtx source, machine_mode mode)
8476{
8477  rtx operands[2];
8478  operands[0] = dest;
8479  operands[1] = source;
8480
8481  if (TARGET_DEBUG_ADDR)
8482    {
8483      fprintf (stderr,
8484	       "\nrs6000_emit_move: mode = %s, reload_in_progress = %d, "
8485	       "reload_completed = %d, can_create_pseudos = %d.\ndest:\n",
8486	       GET_MODE_NAME (mode),
8487	       reload_in_progress,
8488	       reload_completed,
8489	       can_create_pseudo_p ());
8490      debug_rtx (dest);
8491      fprintf (stderr, "source:\n");
8492      debug_rtx (source);
8493    }
8494
8495  /* Sanity checks.  Check that we get CONST_DOUBLE only when we should.  */
8496  if (CONST_WIDE_INT_P (operands[1])
8497      && GET_MODE_BITSIZE (mode) <= HOST_BITS_PER_WIDE_INT)
8498    {
8499      /* This should be fixed with the introduction of CONST_WIDE_INT.  */
8500      gcc_unreachable ();
8501    }
8502
8503  /* Check if GCC is setting up a block move that will end up using FP
8504     registers as temporaries.  We must make sure this is acceptable.  */
8505  if (GET_CODE (operands[0]) == MEM
8506      && GET_CODE (operands[1]) == MEM
8507      && mode == DImode
8508      && (SLOW_UNALIGNED_ACCESS (DImode, MEM_ALIGN (operands[0]))
8509	  || SLOW_UNALIGNED_ACCESS (DImode, MEM_ALIGN (operands[1])))
8510      && ! (SLOW_UNALIGNED_ACCESS (SImode, (MEM_ALIGN (operands[0]) > 32
8511					    ? 32 : MEM_ALIGN (operands[0])))
8512	    || SLOW_UNALIGNED_ACCESS (SImode, (MEM_ALIGN (operands[1]) > 32
8513					       ? 32
8514					       : MEM_ALIGN (operands[1]))))
8515      && ! MEM_VOLATILE_P (operands [0])
8516      && ! MEM_VOLATILE_P (operands [1]))
8517    {
8518      emit_move_insn (adjust_address (operands[0], SImode, 0),
8519		      adjust_address (operands[1], SImode, 0));
8520      emit_move_insn (adjust_address (copy_rtx (operands[0]), SImode, 4),
8521		      adjust_address (copy_rtx (operands[1]), SImode, 4));
8522      return;
8523    }
8524
8525  if (can_create_pseudo_p () && GET_CODE (operands[0]) == MEM
8526      && !gpc_reg_operand (operands[1], mode))
8527    operands[1] = force_reg (mode, operands[1]);
8528
8529  /* Recognize the case where operand[1] is a reference to thread-local
8530     data and load its address to a register.  */
8531  if (tls_referenced_p (operands[1]))
8532    {
8533      enum tls_model model;
8534      rtx tmp = operands[1];
8535      rtx addend = NULL;
8536
8537      if (GET_CODE (tmp) == CONST && GET_CODE (XEXP (tmp, 0)) == PLUS)
8538	{
8539          addend = XEXP (XEXP (tmp, 0), 1);
8540	  tmp = XEXP (XEXP (tmp, 0), 0);
8541	}
8542
8543      gcc_assert (GET_CODE (tmp) == SYMBOL_REF);
8544      model = SYMBOL_REF_TLS_MODEL (tmp);
8545      gcc_assert (model != 0);
8546
8547      tmp = rs6000_legitimize_tls_address (tmp, model);
8548      if (addend)
8549	{
8550	  tmp = gen_rtx_PLUS (mode, tmp, addend);
8551	  tmp = force_operand (tmp, operands[0]);
8552	}
8553      operands[1] = tmp;
8554    }
8555
8556  /* Handle the case where reload calls us with an invalid address.  */
8557  if (reload_in_progress && mode == Pmode
8558      && (! general_operand (operands[1], mode)
8559	  || ! nonimmediate_operand (operands[0], mode)))
8560    goto emit_set;
8561
8562  /* 128-bit constant floating-point values on Darwin should really be loaded
8563     as two parts.  However, this premature splitting is a problem when DFmode
8564     values can go into Altivec registers.  */
8565  if (!TARGET_IEEEQUAD && TARGET_LONG_DOUBLE_128
8566      && !reg_addr[DFmode].scalar_in_vmx_p
8567      && mode == TFmode && GET_CODE (operands[1]) == CONST_DOUBLE)
8568    {
8569      rs6000_emit_move (simplify_gen_subreg (DFmode, operands[0], mode, 0),
8570			simplify_gen_subreg (DFmode, operands[1], mode, 0),
8571			DFmode);
8572      rs6000_emit_move (simplify_gen_subreg (DFmode, operands[0], mode,
8573					     GET_MODE_SIZE (DFmode)),
8574			simplify_gen_subreg (DFmode, operands[1], mode,
8575					     GET_MODE_SIZE (DFmode)),
8576			DFmode);
8577      return;
8578    }
8579
8580  if (reload_in_progress && cfun->machine->sdmode_stack_slot != NULL_RTX)
8581    cfun->machine->sdmode_stack_slot =
8582      eliminate_regs (cfun->machine->sdmode_stack_slot, VOIDmode, NULL_RTX);
8583
8584
8585  /* Transform (p0:DD, (SUBREG:DD p1:SD)) to ((SUBREG:SD p0:DD),
8586     p1:SD) if p1 is not of floating point class and p0 is spilled as
8587     we can have no analogous movsd_store for this.  */
8588  if (lra_in_progress && mode == DDmode
8589      && REG_P (operands[0]) && REGNO (operands[0]) >= FIRST_PSEUDO_REGISTER
8590      && reg_preferred_class (REGNO (operands[0])) == NO_REGS
8591      && GET_CODE (operands[1]) == SUBREG && REG_P (SUBREG_REG (operands[1]))
8592      && GET_MODE (SUBREG_REG (operands[1])) == SDmode)
8593    {
8594      enum reg_class cl;
8595      int regno = REGNO (SUBREG_REG (operands[1]));
8596
8597      if (regno >= FIRST_PSEUDO_REGISTER)
8598	{
8599	  cl = reg_preferred_class (regno);
8600	  regno = cl == NO_REGS ? -1 : ira_class_hard_regs[cl][1];
8601	}
8602      if (regno >= 0 && ! FP_REGNO_P (regno))
8603	{
8604	  mode = SDmode;
8605	  operands[0] = gen_lowpart_SUBREG (SDmode, operands[0]);
8606	  operands[1] = SUBREG_REG (operands[1]);
8607	}
8608    }
8609  if (lra_in_progress
8610      && mode == SDmode
8611      && REG_P (operands[0]) && REGNO (operands[0]) >= FIRST_PSEUDO_REGISTER
8612      && reg_preferred_class (REGNO (operands[0])) == NO_REGS
8613      && (REG_P (operands[1])
8614	  || (GET_CODE (operands[1]) == SUBREG
8615	      && REG_P (SUBREG_REG (operands[1])))))
8616    {
8617      int regno = REGNO (GET_CODE (operands[1]) == SUBREG
8618			 ? SUBREG_REG (operands[1]) : operands[1]);
8619      enum reg_class cl;
8620
8621      if (regno >= FIRST_PSEUDO_REGISTER)
8622	{
8623	  cl = reg_preferred_class (regno);
8624	  gcc_assert (cl != NO_REGS);
8625	  regno = ira_class_hard_regs[cl][0];
8626	}
8627      if (FP_REGNO_P (regno))
8628	{
8629	  if (GET_MODE (operands[0]) != DDmode)
8630	    operands[0] = gen_rtx_SUBREG (DDmode, operands[0], 0);
8631	  emit_insn (gen_movsd_store (operands[0], operands[1]));
8632	}
8633      else if (INT_REGNO_P (regno))
8634	emit_insn (gen_movsd_hardfloat (operands[0], operands[1]));
8635      else
8636	gcc_unreachable();
8637      return;
8638    }
8639  /* Transform ((SUBREG:DD p0:SD), p1:DD) to (p0:SD, (SUBREG:SD
8640     p:DD)) if p0 is not of floating point class and p1 is spilled as
8641     we can have no analogous movsd_load for this.  */
8642  if (lra_in_progress && mode == DDmode
8643      && GET_CODE (operands[0]) == SUBREG && REG_P (SUBREG_REG (operands[0]))
8644      && GET_MODE (SUBREG_REG (operands[0])) == SDmode
8645      && REG_P (operands[1]) && REGNO (operands[1]) >= FIRST_PSEUDO_REGISTER
8646      && reg_preferred_class (REGNO (operands[1])) == NO_REGS)
8647    {
8648      enum reg_class cl;
8649      int regno = REGNO (SUBREG_REG (operands[0]));
8650
8651      if (regno >= FIRST_PSEUDO_REGISTER)
8652	{
8653	  cl = reg_preferred_class (regno);
8654	  regno = cl == NO_REGS ? -1 : ira_class_hard_regs[cl][0];
8655	}
8656      if (regno >= 0 && ! FP_REGNO_P (regno))
8657	{
8658	  mode = SDmode;
8659	  operands[0] = SUBREG_REG (operands[0]);
8660	  operands[1] = gen_lowpart_SUBREG (SDmode, operands[1]);
8661	}
8662    }
8663  if (lra_in_progress
8664      && mode == SDmode
8665      && (REG_P (operands[0])
8666	  || (GET_CODE (operands[0]) == SUBREG
8667	      && REG_P (SUBREG_REG (operands[0]))))
8668      && REG_P (operands[1]) && REGNO (operands[1]) >= FIRST_PSEUDO_REGISTER
8669      && reg_preferred_class (REGNO (operands[1])) == NO_REGS)
8670    {
8671      int regno = REGNO (GET_CODE (operands[0]) == SUBREG
8672			 ? SUBREG_REG (operands[0]) : operands[0]);
8673      enum reg_class cl;
8674
8675      if (regno >= FIRST_PSEUDO_REGISTER)
8676	{
8677	  cl = reg_preferred_class (regno);
8678	  gcc_assert (cl != NO_REGS);
8679	  regno = ira_class_hard_regs[cl][0];
8680	}
8681      if (FP_REGNO_P (regno))
8682	{
8683	  if (GET_MODE (operands[1]) != DDmode)
8684	    operands[1] = gen_rtx_SUBREG (DDmode, operands[1], 0);
8685	  emit_insn (gen_movsd_load (operands[0], operands[1]));
8686	}
8687      else if (INT_REGNO_P (regno))
8688	emit_insn (gen_movsd_hardfloat (operands[0], operands[1]));
8689      else
8690	gcc_unreachable();
8691      return;
8692    }
8693
8694  if (reload_in_progress
8695      && mode == SDmode
8696      && cfun->machine->sdmode_stack_slot != NULL_RTX
8697      && MEM_P (operands[0])
8698      && rtx_equal_p (operands[0], cfun->machine->sdmode_stack_slot)
8699      && REG_P (operands[1]))
8700    {
8701      if (FP_REGNO_P (REGNO (operands[1])))
8702	{
8703	  rtx mem = adjust_address_nv (operands[0], DDmode, 0);
8704	  mem = eliminate_regs (mem, VOIDmode, NULL_RTX);
8705	  emit_insn (gen_movsd_store (mem, operands[1]));
8706	}
8707      else if (INT_REGNO_P (REGNO (operands[1])))
8708	{
8709	  rtx mem = operands[0];
8710	  if (BYTES_BIG_ENDIAN)
8711	    mem = adjust_address_nv (mem, mode, 4);
8712	  mem = eliminate_regs (mem, VOIDmode, NULL_RTX);
8713	  emit_insn (gen_movsd_hardfloat (mem, operands[1]));
8714	}
8715      else
8716	gcc_unreachable();
8717      return;
8718    }
8719  if (reload_in_progress
8720      && mode == SDmode
8721      && REG_P (operands[0])
8722      && MEM_P (operands[1])
8723      && cfun->machine->sdmode_stack_slot != NULL_RTX
8724      && rtx_equal_p (operands[1], cfun->machine->sdmode_stack_slot))
8725    {
8726      if (FP_REGNO_P (REGNO (operands[0])))
8727	{
8728	  rtx mem = adjust_address_nv (operands[1], DDmode, 0);
8729	  mem = eliminate_regs (mem, VOIDmode, NULL_RTX);
8730	  emit_insn (gen_movsd_load (operands[0], mem));
8731	}
8732      else if (INT_REGNO_P (REGNO (operands[0])))
8733	{
8734	  rtx mem = operands[1];
8735	  if (BYTES_BIG_ENDIAN)
8736	    mem = adjust_address_nv (mem, mode, 4);
8737	  mem = eliminate_regs (mem, VOIDmode, NULL_RTX);
8738	  emit_insn (gen_movsd_hardfloat (operands[0], mem));
8739	}
8740      else
8741	gcc_unreachable();
8742      return;
8743    }
8744
8745  /* FIXME:  In the long term, this switch statement should go away
8746     and be replaced by a sequence of tests based on things like
8747     mode == Pmode.  */
8748  switch (mode)
8749    {
8750    case HImode:
8751    case QImode:
8752      if (CONSTANT_P (operands[1])
8753	  && GET_CODE (operands[1]) != CONST_INT)
8754	operands[1] = force_const_mem (mode, operands[1]);
8755      break;
8756
8757    case TFmode:
8758    case TDmode:
8759      rs6000_eliminate_indexed_memrefs (operands);
8760      /* fall through */
8761
8762    case DFmode:
8763    case DDmode:
8764    case SFmode:
8765    case SDmode:
8766      if (CONSTANT_P (operands[1])
8767	  && ! easy_fp_constant (operands[1], mode))
8768	operands[1] = force_const_mem (mode, operands[1]);
8769      break;
8770
8771    case V16QImode:
8772    case V8HImode:
8773    case V4SFmode:
8774    case V4SImode:
8775    case V4HImode:
8776    case V2SFmode:
8777    case V2SImode:
8778    case V1DImode:
8779    case V2DFmode:
8780    case V2DImode:
8781    case V1TImode:
8782      if (CONSTANT_P (operands[1])
8783	  && !easy_vector_constant (operands[1], mode))
8784	operands[1] = force_const_mem (mode, operands[1]);
8785      break;
8786
8787    case SImode:
8788    case DImode:
8789      /* Use default pattern for address of ELF small data */
8790      if (TARGET_ELF
8791	  && mode == Pmode
8792	  && DEFAULT_ABI == ABI_V4
8793	  && (GET_CODE (operands[1]) == SYMBOL_REF
8794	      || GET_CODE (operands[1]) == CONST)
8795	  && small_data_operand (operands[1], mode))
8796	{
8797	  emit_insn (gen_rtx_SET (VOIDmode, operands[0], operands[1]));
8798	  return;
8799	}
8800
8801      if (DEFAULT_ABI == ABI_V4
8802	  && mode == Pmode && mode == SImode
8803	  && flag_pic == 1 && got_operand (operands[1], mode))
8804	{
8805	  emit_insn (gen_movsi_got (operands[0], operands[1]));
8806	  return;
8807	}
8808
8809      if ((TARGET_ELF || DEFAULT_ABI == ABI_DARWIN)
8810	  && TARGET_NO_TOC
8811	  && ! flag_pic
8812	  && mode == Pmode
8813	  && CONSTANT_P (operands[1])
8814	  && GET_CODE (operands[1]) != HIGH
8815	  && GET_CODE (operands[1]) != CONST_INT)
8816	{
8817	  rtx target = (!can_create_pseudo_p ()
8818			? operands[0]
8819			: gen_reg_rtx (mode));
8820
8821	  /* If this is a function address on -mcall-aixdesc,
8822	     convert it to the address of the descriptor.  */
8823	  if (DEFAULT_ABI == ABI_AIX
8824	      && GET_CODE (operands[1]) == SYMBOL_REF
8825	      && XSTR (operands[1], 0)[0] == '.')
8826	    {
8827	      const char *name = XSTR (operands[1], 0);
8828	      rtx new_ref;
8829	      while (*name == '.')
8830		name++;
8831	      new_ref = gen_rtx_SYMBOL_REF (Pmode, name);
8832	      CONSTANT_POOL_ADDRESS_P (new_ref)
8833		= CONSTANT_POOL_ADDRESS_P (operands[1]);
8834	      SYMBOL_REF_FLAGS (new_ref) = SYMBOL_REF_FLAGS (operands[1]);
8835	      SYMBOL_REF_USED (new_ref) = SYMBOL_REF_USED (operands[1]);
8836	      SYMBOL_REF_DATA (new_ref) = SYMBOL_REF_DATA (operands[1]);
8837	      operands[1] = new_ref;
8838	    }
8839
8840	  if (DEFAULT_ABI == ABI_DARWIN)
8841	    {
8842#if TARGET_MACHO
8843	      if (MACHO_DYNAMIC_NO_PIC_P)
8844		{
8845		  /* Take care of any required data indirection.  */
8846		  operands[1] = rs6000_machopic_legitimize_pic_address (
8847				  operands[1], mode, operands[0]);
8848		  if (operands[0] != operands[1])
8849		    emit_insn (gen_rtx_SET (VOIDmode,
8850					    operands[0], operands[1]));
8851		  return;
8852		}
8853#endif
8854	      emit_insn (gen_macho_high (target, operands[1]));
8855	      emit_insn (gen_macho_low (operands[0], target, operands[1]));
8856	      return;
8857	    }
8858
8859	  emit_insn (gen_elf_high (target, operands[1]));
8860	  emit_insn (gen_elf_low (operands[0], target, operands[1]));
8861	  return;
8862	}
8863
8864      /* If this is a SYMBOL_REF that refers to a constant pool entry,
8865	 and we have put it in the TOC, we just need to make a TOC-relative
8866	 reference to it.  */
8867      if (TARGET_TOC
8868	  && GET_CODE (operands[1]) == SYMBOL_REF
8869	  && use_toc_relative_ref (operands[1]))
8870	operands[1] = create_TOC_reference (operands[1], operands[0]);
8871      else if (mode == Pmode
8872	       && CONSTANT_P (operands[1])
8873	       && GET_CODE (operands[1]) != HIGH
8874	       && ((GET_CODE (operands[1]) != CONST_INT
8875		    && ! easy_fp_constant (operands[1], mode))
8876		   || (GET_CODE (operands[1]) == CONST_INT
8877		       && (num_insns_constant (operands[1], mode)
8878			   > (TARGET_CMODEL != CMODEL_SMALL ? 3 : 2)))
8879		   || (GET_CODE (operands[0]) == REG
8880		       && FP_REGNO_P (REGNO (operands[0]))))
8881	       && !toc_relative_expr_p (operands[1], false)
8882	       && (TARGET_CMODEL == CMODEL_SMALL
8883		   || can_create_pseudo_p ()
8884		   || (REG_P (operands[0])
8885		       && INT_REG_OK_FOR_BASE_P (operands[0], true))))
8886	{
8887
8888#if TARGET_MACHO
8889	  /* Darwin uses a special PIC legitimizer.  */
8890	  if (DEFAULT_ABI == ABI_DARWIN && MACHOPIC_INDIRECT)
8891	    {
8892	      operands[1] =
8893		rs6000_machopic_legitimize_pic_address (operands[1], mode,
8894							operands[0]);
8895	      if (operands[0] != operands[1])
8896		emit_insn (gen_rtx_SET (VOIDmode, operands[0], operands[1]));
8897	      return;
8898	    }
8899#endif
8900
8901	  /* If we are to limit the number of things we put in the TOC and
8902	     this is a symbol plus a constant we can add in one insn,
8903	     just put the symbol in the TOC and add the constant.  Don't do
8904	     this if reload is in progress.  */
8905	  if (GET_CODE (operands[1]) == CONST
8906	      && TARGET_NO_SUM_IN_TOC && ! reload_in_progress
8907	      && GET_CODE (XEXP (operands[1], 0)) == PLUS
8908	      && add_operand (XEXP (XEXP (operands[1], 0), 1), mode)
8909	      && (GET_CODE (XEXP (XEXP (operands[1], 0), 0)) == LABEL_REF
8910		  || GET_CODE (XEXP (XEXP (operands[1], 0), 0)) == SYMBOL_REF)
8911	      && ! side_effects_p (operands[0]))
8912	    {
8913	      rtx sym =
8914		force_const_mem (mode, XEXP (XEXP (operands[1], 0), 0));
8915	      rtx other = XEXP (XEXP (operands[1], 0), 1);
8916
8917	      sym = force_reg (mode, sym);
8918	      emit_insn (gen_add3_insn (operands[0], sym, other));
8919	      return;
8920	    }
8921
8922	  operands[1] = force_const_mem (mode, operands[1]);
8923
8924	  if (TARGET_TOC
8925	      && GET_CODE (XEXP (operands[1], 0)) == SYMBOL_REF
8926	      && constant_pool_expr_p (XEXP (operands[1], 0))
8927	      && ASM_OUTPUT_SPECIAL_POOL_ENTRY_P (
8928			get_pool_constant (XEXP (operands[1], 0)),
8929			get_pool_mode (XEXP (operands[1], 0))))
8930	    {
8931	      rtx tocref = create_TOC_reference (XEXP (operands[1], 0),
8932						 operands[0]);
8933	      operands[1] = gen_const_mem (mode, tocref);
8934	      set_mem_alias_set (operands[1], get_TOC_alias_set ());
8935	    }
8936	}
8937      break;
8938
8939    case TImode:
8940      if (!VECTOR_MEM_VSX_P (TImode))
8941	rs6000_eliminate_indexed_memrefs (operands);
8942      break;
8943
8944    case PTImode:
8945      rs6000_eliminate_indexed_memrefs (operands);
8946      break;
8947
8948    default:
8949      fatal_insn ("bad move", gen_rtx_SET (VOIDmode, dest, source));
8950    }
8951
8952  /* Above, we may have called force_const_mem which may have returned
8953     an invalid address.  If we can, fix this up; otherwise, reload will
8954     have to deal with it.  */
8955  if (GET_CODE (operands[1]) == MEM && ! reload_in_progress)
8956    operands[1] = validize_mem (operands[1]);
8957
8958 emit_set:
8959  emit_insn (gen_rtx_SET (VOIDmode, operands[0], operands[1]));
8960}
8961
8962/* Return true if a structure, union or array containing FIELD should be
8963   accessed using `BLKMODE'.
8964
8965   For the SPE, simd types are V2SI, and gcc can be tempted to put the
8966   entire thing in a DI and use subregs to access the internals.
8967   store_bit_field() will force (subreg:DI (reg:V2SI x))'s to the
8968   back-end.  Because a single GPR can hold a V2SI, but not a DI, the
8969   best thing to do is set structs to BLKmode and avoid Severe Tire
8970   Damage.
8971
8972   On e500 v2, DF and DI modes suffer from the same anomaly.  DF can
8973   fit into 1, whereas DI still needs two.  */
8974
8975static bool
8976rs6000_member_type_forces_blk (const_tree field, machine_mode mode)
8977{
8978  return ((TARGET_SPE && TREE_CODE (TREE_TYPE (field)) == VECTOR_TYPE)
8979	  || (TARGET_E500_DOUBLE && mode == DFmode));
8980}
8981
8982/* Nonzero if we can use a floating-point register to pass this arg.  */
8983#define USE_FP_FOR_ARG_P(CUM,MODE)		\
8984  (SCALAR_FLOAT_MODE_P (MODE)			\
8985   && (CUM)->fregno <= FP_ARG_MAX_REG		\
8986   && TARGET_HARD_FLOAT && TARGET_FPRS)
8987
8988/* Nonzero if we can use an AltiVec register to pass this arg.  */
8989#define USE_ALTIVEC_FOR_ARG_P(CUM,MODE,NAMED)			\
8990  (ALTIVEC_OR_VSX_VECTOR_MODE (MODE)				\
8991   && (CUM)->vregno <= ALTIVEC_ARG_MAX_REG			\
8992   && TARGET_ALTIVEC_ABI					\
8993   && (NAMED))
8994
8995/* Walk down the type tree of TYPE counting consecutive base elements.
8996   If *MODEP is VOIDmode, then set it to the first valid floating point
8997   or vector type.  If a non-floating point or vector type is found, or
8998   if a floating point or vector type that doesn't match a non-VOIDmode
8999   *MODEP is found, then return -1, otherwise return the count in the
9000   sub-tree.  */
9001
9002static int
9003rs6000_aggregate_candidate (const_tree type, machine_mode *modep)
9004{
9005  machine_mode mode;
9006  HOST_WIDE_INT size;
9007
9008  switch (TREE_CODE (type))
9009    {
9010    case REAL_TYPE:
9011      mode = TYPE_MODE (type);
9012      if (!SCALAR_FLOAT_MODE_P (mode))
9013	return -1;
9014
9015      if (*modep == VOIDmode)
9016	*modep = mode;
9017
9018      if (*modep == mode)
9019	return 1;
9020
9021      break;
9022
9023    case COMPLEX_TYPE:
9024      mode = TYPE_MODE (TREE_TYPE (type));
9025      if (!SCALAR_FLOAT_MODE_P (mode))
9026	return -1;
9027
9028      if (*modep == VOIDmode)
9029	*modep = mode;
9030
9031      if (*modep == mode)
9032	return 2;
9033
9034      break;
9035
9036    case VECTOR_TYPE:
9037      if (!TARGET_ALTIVEC_ABI || !TARGET_ALTIVEC)
9038	return -1;
9039
9040      /* Use V4SImode as representative of all 128-bit vector types.  */
9041      size = int_size_in_bytes (type);
9042      switch (size)
9043	{
9044	case 16:
9045	  mode = V4SImode;
9046	  break;
9047	default:
9048	  return -1;
9049	}
9050
9051      if (*modep == VOIDmode)
9052	*modep = mode;
9053
9054      /* Vector modes are considered to be opaque: two vectors are
9055	 equivalent for the purposes of being homogeneous aggregates
9056	 if they are the same size.  */
9057      if (*modep == mode)
9058	return 1;
9059
9060      break;
9061
9062    case ARRAY_TYPE:
9063      {
9064	int count;
9065	tree index = TYPE_DOMAIN (type);
9066
9067	/* Can't handle incomplete types nor sizes that are not
9068	   fixed.  */
9069	if (!COMPLETE_TYPE_P (type)
9070	    || TREE_CODE (TYPE_SIZE (type)) != INTEGER_CST)
9071	  return -1;
9072
9073	count = rs6000_aggregate_candidate (TREE_TYPE (type), modep);
9074	if (count == -1
9075	    || !index
9076	    || !TYPE_MAX_VALUE (index)
9077	    || !tree_fits_uhwi_p (TYPE_MAX_VALUE (index))
9078	    || !TYPE_MIN_VALUE (index)
9079	    || !tree_fits_uhwi_p (TYPE_MIN_VALUE (index))
9080	    || count < 0)
9081	  return -1;
9082
9083	count *= (1 + tree_to_uhwi (TYPE_MAX_VALUE (index))
9084		      - tree_to_uhwi (TYPE_MIN_VALUE (index)));
9085
9086	/* There must be no padding.  */
9087	if (wi::ne_p (TYPE_SIZE (type), count * GET_MODE_BITSIZE (*modep)))
9088	  return -1;
9089
9090	return count;
9091      }
9092
9093    case RECORD_TYPE:
9094      {
9095	int count = 0;
9096	int sub_count;
9097	tree field;
9098
9099	/* Can't handle incomplete types nor sizes that are not
9100	   fixed.  */
9101	if (!COMPLETE_TYPE_P (type)
9102	    || TREE_CODE (TYPE_SIZE (type)) != INTEGER_CST)
9103	  return -1;
9104
9105	for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
9106	  {
9107	    if (TREE_CODE (field) != FIELD_DECL)
9108	      continue;
9109
9110	    sub_count = rs6000_aggregate_candidate (TREE_TYPE (field), modep);
9111	    if (sub_count < 0)
9112	      return -1;
9113	    count += sub_count;
9114	  }
9115
9116	/* There must be no padding.  */
9117	if (wi::ne_p (TYPE_SIZE (type), count * GET_MODE_BITSIZE (*modep)))
9118	  return -1;
9119
9120	return count;
9121      }
9122
9123    case UNION_TYPE:
9124    case QUAL_UNION_TYPE:
9125      {
9126	/* These aren't very interesting except in a degenerate case.  */
9127	int count = 0;
9128	int sub_count;
9129	tree field;
9130
9131	/* Can't handle incomplete types nor sizes that are not
9132	   fixed.  */
9133	if (!COMPLETE_TYPE_P (type)
9134	    || TREE_CODE (TYPE_SIZE (type)) != INTEGER_CST)
9135	  return -1;
9136
9137	for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
9138	  {
9139	    if (TREE_CODE (field) != FIELD_DECL)
9140	      continue;
9141
9142	    sub_count = rs6000_aggregate_candidate (TREE_TYPE (field), modep);
9143	    if (sub_count < 0)
9144	      return -1;
9145	    count = count > sub_count ? count : sub_count;
9146	  }
9147
9148	/* There must be no padding.  */
9149	if (wi::ne_p (TYPE_SIZE (type), count * GET_MODE_BITSIZE (*modep)))
9150	  return -1;
9151
9152	return count;
9153      }
9154
9155    default:
9156      break;
9157    }
9158
9159  return -1;
9160}
9161
9162/* If an argument, whose type is described by TYPE and MODE, is a homogeneous
9163   float or vector aggregate that shall be passed in FP/vector registers
9164   according to the ELFv2 ABI, return the homogeneous element mode in
9165   *ELT_MODE and the number of elements in *N_ELTS, and return TRUE.
9166
9167   Otherwise, set *ELT_MODE to MODE and *N_ELTS to 1, and return FALSE.  */
9168
9169static bool
9170rs6000_discover_homogeneous_aggregate (machine_mode mode, const_tree type,
9171				       machine_mode *elt_mode,
9172				       int *n_elts)
9173{
9174  /* Note that we do not accept complex types at the top level as
9175     homogeneous aggregates; these types are handled via the
9176     targetm.calls.split_complex_arg mechanism.  Complex types
9177     can be elements of homogeneous aggregates, however.  */
9178  if (DEFAULT_ABI == ABI_ELFv2 && type && AGGREGATE_TYPE_P (type))
9179    {
9180      machine_mode field_mode = VOIDmode;
9181      int field_count = rs6000_aggregate_candidate (type, &field_mode);
9182
9183      if (field_count > 0)
9184	{
9185	  int n_regs = (SCALAR_FLOAT_MODE_P (field_mode)?
9186			(GET_MODE_SIZE (field_mode) + 7) >> 3 : 1);
9187
9188	  /* The ELFv2 ABI allows homogeneous aggregates to occupy
9189	     up to AGGR_ARG_NUM_REG registers.  */
9190	  if (field_count * n_regs <= AGGR_ARG_NUM_REG)
9191	    {
9192	      if (elt_mode)
9193		*elt_mode = field_mode;
9194	      if (n_elts)
9195		*n_elts = field_count;
9196	      return true;
9197	    }
9198	}
9199    }
9200
9201  if (elt_mode)
9202    *elt_mode = mode;
9203  if (n_elts)
9204    *n_elts = 1;
9205  return false;
9206}
9207
9208/* Return a nonzero value to say to return the function value in
9209   memory, just as large structures are always returned.  TYPE will be
9210   the data type of the value, and FNTYPE will be the type of the
9211   function doing the returning, or @code{NULL} for libcalls.
9212
9213   The AIX ABI for the RS/6000 specifies that all structures are
9214   returned in memory.  The Darwin ABI does the same.
9215
9216   For the Darwin 64 Bit ABI, a function result can be returned in
9217   registers or in memory, depending on the size of the return data
9218   type.  If it is returned in registers, the value occupies the same
9219   registers as it would if it were the first and only function
9220   argument.  Otherwise, the function places its result in memory at
9221   the location pointed to by GPR3.
9222
9223   The SVR4 ABI specifies that structures <= 8 bytes are returned in r3/r4,
9224   but a draft put them in memory, and GCC used to implement the draft
9225   instead of the final standard.  Therefore, aix_struct_return
9226   controls this instead of DEFAULT_ABI; V.4 targets needing backward
9227   compatibility can change DRAFT_V4_STRUCT_RET to override the
9228   default, and -m switches get the final word.  See
9229   rs6000_option_override_internal for more details.
9230
9231   The PPC32 SVR4 ABI uses IEEE double extended for long double, if 128-bit
9232   long double support is enabled.  These values are returned in memory.
9233
9234   int_size_in_bytes returns -1 for variable size objects, which go in
9235   memory always.  The cast to unsigned makes -1 > 8.  */
9236
9237static bool
9238rs6000_return_in_memory (const_tree type, const_tree fntype ATTRIBUTE_UNUSED)
9239{
9240  /* For the Darwin64 ABI, test if we can fit the return value in regs.  */
9241  if (TARGET_MACHO
9242      && rs6000_darwin64_abi
9243      && TREE_CODE (type) == RECORD_TYPE
9244      && int_size_in_bytes (type) > 0)
9245    {
9246      CUMULATIVE_ARGS valcum;
9247      rtx valret;
9248
9249      valcum.words = 0;
9250      valcum.fregno = FP_ARG_MIN_REG;
9251      valcum.vregno = ALTIVEC_ARG_MIN_REG;
9252      /* Do a trial code generation as if this were going to be passed
9253	 as an argument; if any part goes in memory, we return NULL.  */
9254      valret = rs6000_darwin64_record_arg (&valcum, type, true, true);
9255      if (valret)
9256	return false;
9257      /* Otherwise fall through to more conventional ABI rules.  */
9258    }
9259
9260  /* The ELFv2 ABI returns homogeneous VFP aggregates in registers */
9261  if (rs6000_discover_homogeneous_aggregate (TYPE_MODE (type), type,
9262					     NULL, NULL))
9263    return false;
9264
9265  /* The ELFv2 ABI returns aggregates up to 16B in registers */
9266  if (DEFAULT_ABI == ABI_ELFv2 && AGGREGATE_TYPE_P (type)
9267      && (unsigned HOST_WIDE_INT) int_size_in_bytes (type) <= 16)
9268    return false;
9269
9270  if (AGGREGATE_TYPE_P (type)
9271      && (aix_struct_return
9272	  || (unsigned HOST_WIDE_INT) int_size_in_bytes (type) > 8))
9273    return true;
9274
9275  /* Allow -maltivec -mabi=no-altivec without warning.  Altivec vector
9276     modes only exist for GCC vector types if -maltivec.  */
9277  if (TARGET_32BIT && !TARGET_ALTIVEC_ABI
9278      && ALTIVEC_VECTOR_MODE (TYPE_MODE (type)))
9279    return false;
9280
9281  /* Return synthetic vectors in memory.  */
9282  if (TREE_CODE (type) == VECTOR_TYPE
9283      && int_size_in_bytes (type) > (TARGET_ALTIVEC_ABI ? 16 : 8))
9284    {
9285      static bool warned_for_return_big_vectors = false;
9286      if (!warned_for_return_big_vectors)
9287	{
9288	  warning (0, "GCC vector returned by reference: "
9289		   "non-standard ABI extension with no compatibility guarantee");
9290	  warned_for_return_big_vectors = true;
9291	}
9292      return true;
9293    }
9294
9295  if (DEFAULT_ABI == ABI_V4 && TARGET_IEEEQUAD && TYPE_MODE (type) == TFmode)
9296    return true;
9297
9298  return false;
9299}
9300
9301/* Specify whether values returned in registers should be at the most
9302   significant end of a register.  We want aggregates returned by
9303   value to match the way aggregates are passed to functions.  */
9304
9305static bool
9306rs6000_return_in_msb (const_tree valtype)
9307{
9308  return (DEFAULT_ABI == ABI_ELFv2
9309	  && BYTES_BIG_ENDIAN
9310	  && AGGREGATE_TYPE_P (valtype)
9311	  && FUNCTION_ARG_PADDING (TYPE_MODE (valtype), valtype) == upward);
9312}
9313
9314#ifdef HAVE_AS_GNU_ATTRIBUTE
9315/* Return TRUE if a call to function FNDECL may be one that
9316   potentially affects the function calling ABI of the object file.  */
9317
9318static bool
9319call_ABI_of_interest (tree fndecl)
9320{
9321  if (symtab->state == EXPANSION)
9322    {
9323      struct cgraph_node *c_node;
9324
9325      /* Libcalls are always interesting.  */
9326      if (fndecl == NULL_TREE)
9327	return true;
9328
9329      /* Any call to an external function is interesting.  */
9330      if (DECL_EXTERNAL (fndecl))
9331	return true;
9332
9333      /* Interesting functions that we are emitting in this object file.  */
9334      c_node = cgraph_node::get (fndecl);
9335      c_node = c_node->ultimate_alias_target ();
9336      return !c_node->only_called_directly_p ();
9337    }
9338  return false;
9339}
9340#endif
9341
9342/* Initialize a variable CUM of type CUMULATIVE_ARGS
9343   for a call to a function whose data type is FNTYPE.
9344   For a library call, FNTYPE is 0 and RETURN_MODE the return value mode.
9345
9346   For incoming args we set the number of arguments in the prototype large
9347   so we never return a PARALLEL.  */
9348
9349void
9350init_cumulative_args (CUMULATIVE_ARGS *cum, tree fntype,
9351		      rtx libname ATTRIBUTE_UNUSED, int incoming,
9352		      int libcall, int n_named_args,
9353		      tree fndecl ATTRIBUTE_UNUSED,
9354		      machine_mode return_mode ATTRIBUTE_UNUSED)
9355{
9356  static CUMULATIVE_ARGS zero_cumulative;
9357
9358  *cum = zero_cumulative;
9359  cum->words = 0;
9360  cum->fregno = FP_ARG_MIN_REG;
9361  cum->vregno = ALTIVEC_ARG_MIN_REG;
9362  cum->prototype = (fntype && prototype_p (fntype));
9363  cum->call_cookie = ((DEFAULT_ABI == ABI_V4 && libcall)
9364		      ? CALL_LIBCALL : CALL_NORMAL);
9365  cum->sysv_gregno = GP_ARG_MIN_REG;
9366  cum->stdarg = stdarg_p (fntype);
9367
9368  cum->nargs_prototype = 0;
9369  if (incoming || cum->prototype)
9370    cum->nargs_prototype = n_named_args;
9371
9372  /* Check for a longcall attribute.  */
9373  if ((!fntype && rs6000_default_long_calls)
9374      || (fntype
9375	  && lookup_attribute ("longcall", TYPE_ATTRIBUTES (fntype))
9376	  && !lookup_attribute ("shortcall", TYPE_ATTRIBUTES (fntype))))
9377    cum->call_cookie |= CALL_LONG;
9378
9379  if (TARGET_DEBUG_ARG)
9380    {
9381      fprintf (stderr, "\ninit_cumulative_args:");
9382      if (fntype)
9383	{
9384	  tree ret_type = TREE_TYPE (fntype);
9385	  fprintf (stderr, " ret code = %s,",
9386		   get_tree_code_name (TREE_CODE (ret_type)));
9387	}
9388
9389      if (cum->call_cookie & CALL_LONG)
9390	fprintf (stderr, " longcall,");
9391
9392      fprintf (stderr, " proto = %d, nargs = %d\n",
9393	       cum->prototype, cum->nargs_prototype);
9394    }
9395
9396#ifdef HAVE_AS_GNU_ATTRIBUTE
9397  if (DEFAULT_ABI == ABI_V4)
9398    {
9399      cum->escapes = call_ABI_of_interest (fndecl);
9400      if (cum->escapes)
9401	{
9402	  tree return_type;
9403
9404	  if (fntype)
9405	    {
9406	      return_type = TREE_TYPE (fntype);
9407	      return_mode = TYPE_MODE (return_type);
9408	    }
9409	  else
9410	    return_type = lang_hooks.types.type_for_mode (return_mode, 0);
9411
9412	  if (return_type != NULL)
9413	    {
9414	      if (TREE_CODE (return_type) == RECORD_TYPE
9415		  && TYPE_TRANSPARENT_AGGR (return_type))
9416		{
9417		  return_type = TREE_TYPE (first_field (return_type));
9418		  return_mode = TYPE_MODE (return_type);
9419		}
9420	      if (AGGREGATE_TYPE_P (return_type)
9421		  && ((unsigned HOST_WIDE_INT) int_size_in_bytes (return_type)
9422		      <= 8))
9423		rs6000_returns_struct = true;
9424	    }
9425	  if (SCALAR_FLOAT_MODE_P (return_mode))
9426	    rs6000_passes_float = true;
9427	  else if (ALTIVEC_OR_VSX_VECTOR_MODE (return_mode)
9428		   || SPE_VECTOR_MODE (return_mode))
9429	    rs6000_passes_vector = true;
9430	}
9431    }
9432#endif
9433
9434  if (fntype
9435      && !TARGET_ALTIVEC
9436      && TARGET_ALTIVEC_ABI
9437      && ALTIVEC_VECTOR_MODE (TYPE_MODE (TREE_TYPE (fntype))))
9438    {
9439      error ("cannot return value in vector register because"
9440	     " altivec instructions are disabled, use -maltivec"
9441	     " to enable them");
9442    }
9443}
9444
9445/* The mode the ABI uses for a word.  This is not the same as word_mode
9446   for -m32 -mpowerpc64.  This is used to implement various target hooks.  */
9447
9448static machine_mode
9449rs6000_abi_word_mode (void)
9450{
9451  return TARGET_32BIT ? SImode : DImode;
9452}
9453
9454/* On rs6000, function arguments are promoted, as are function return
9455   values.  */
9456
9457static machine_mode
9458rs6000_promote_function_mode (const_tree type ATTRIBUTE_UNUSED,
9459			      machine_mode mode,
9460			      int *punsignedp ATTRIBUTE_UNUSED,
9461			      const_tree, int)
9462{
9463  PROMOTE_MODE (mode, *punsignedp, type);
9464
9465  return mode;
9466}
9467
9468/* Return true if TYPE must be passed on the stack and not in registers.  */
9469
9470static bool
9471rs6000_must_pass_in_stack (machine_mode mode, const_tree type)
9472{
9473  if (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2 || TARGET_64BIT)
9474    return must_pass_in_stack_var_size (mode, type);
9475  else
9476    return must_pass_in_stack_var_size_or_pad (mode, type);
9477}
9478
9479/* If defined, a C expression which determines whether, and in which
9480   direction, to pad out an argument with extra space.  The value
9481   should be of type `enum direction': either `upward' to pad above
9482   the argument, `downward' to pad below, or `none' to inhibit
9483   padding.
9484
9485   For the AIX ABI structs are always stored left shifted in their
9486   argument slot.  */
9487
9488enum direction
9489function_arg_padding (machine_mode mode, const_tree type)
9490{
9491#ifndef AGGREGATE_PADDING_FIXED
9492#define AGGREGATE_PADDING_FIXED 0
9493#endif
9494#ifndef AGGREGATES_PAD_UPWARD_ALWAYS
9495#define AGGREGATES_PAD_UPWARD_ALWAYS 0
9496#endif
9497
9498  if (!AGGREGATE_PADDING_FIXED)
9499    {
9500      /* GCC used to pass structures of the same size as integer types as
9501	 if they were in fact integers, ignoring FUNCTION_ARG_PADDING.
9502	 i.e. Structures of size 1 or 2 (or 4 when TARGET_64BIT) were
9503	 passed padded downward, except that -mstrict-align further
9504	 muddied the water in that multi-component structures of 2 and 4
9505	 bytes in size were passed padded upward.
9506
9507	 The following arranges for best compatibility with previous
9508	 versions of gcc, but removes the -mstrict-align dependency.  */
9509      if (BYTES_BIG_ENDIAN)
9510	{
9511	  HOST_WIDE_INT size = 0;
9512
9513	  if (mode == BLKmode)
9514	    {
9515	      if (type && TREE_CODE (TYPE_SIZE (type)) == INTEGER_CST)
9516		size = int_size_in_bytes (type);
9517	    }
9518	  else
9519	    size = GET_MODE_SIZE (mode);
9520
9521	  if (size == 1 || size == 2 || size == 4)
9522	    return downward;
9523	}
9524      return upward;
9525    }
9526
9527  if (AGGREGATES_PAD_UPWARD_ALWAYS)
9528    {
9529      if (type != 0 && AGGREGATE_TYPE_P (type))
9530	return upward;
9531    }
9532
9533  /* Fall back to the default.  */
9534  return DEFAULT_FUNCTION_ARG_PADDING (mode, type);
9535}
9536
9537/* If defined, a C expression that gives the alignment boundary, in bits,
9538   of an argument with the specified mode and type.  If it is not defined,
9539   PARM_BOUNDARY is used for all arguments.
9540
9541   V.4 wants long longs and doubles to be double word aligned.  Just
9542   testing the mode size is a boneheaded way to do this as it means
9543   that other types such as complex int are also double word aligned.
9544   However, we're stuck with this because changing the ABI might break
9545   existing library interfaces.
9546
9547   Doubleword align SPE vectors.
9548   Quadword align Altivec/VSX vectors.
9549   Quadword align large synthetic vector types.   */
9550
9551static unsigned int
9552rs6000_function_arg_boundary (machine_mode mode, const_tree type)
9553{
9554  machine_mode elt_mode;
9555  int n_elts;
9556
9557  rs6000_discover_homogeneous_aggregate (mode, type, &elt_mode, &n_elts);
9558
9559  if (DEFAULT_ABI == ABI_V4
9560      && (GET_MODE_SIZE (mode) == 8
9561	  || (TARGET_HARD_FLOAT
9562	      && TARGET_FPRS
9563	      && (mode == TFmode || mode == TDmode))))
9564    return 64;
9565  else if (SPE_VECTOR_MODE (mode)
9566	   || (type && TREE_CODE (type) == VECTOR_TYPE
9567	       && int_size_in_bytes (type) >= 8
9568	       && int_size_in_bytes (type) < 16))
9569    return 64;
9570  else if (ALTIVEC_OR_VSX_VECTOR_MODE (elt_mode)
9571	   || (type && TREE_CODE (type) == VECTOR_TYPE
9572	       && int_size_in_bytes (type) >= 16))
9573    return 128;
9574
9575  /* Aggregate types that need > 8 byte alignment are quadword-aligned
9576     in the parameter area in the ELFv2 ABI, and in the AIX ABI unless
9577     -mcompat-align-parm is used.  */
9578  if (((DEFAULT_ABI == ABI_AIX && !rs6000_compat_align_parm)
9579       || DEFAULT_ABI == ABI_ELFv2)
9580      && type && TYPE_ALIGN (type) > 64)
9581    {
9582      /* "Aggregate" means any AGGREGATE_TYPE except for single-element
9583         or homogeneous float/vector aggregates here.  We already handled
9584         vector aggregates above, but still need to check for float here. */
9585      bool aggregate_p = (AGGREGATE_TYPE_P (type)
9586			  && !SCALAR_FLOAT_MODE_P (elt_mode));
9587
9588      /* We used to check for BLKmode instead of the above aggregate type
9589	 check.  Warn when this results in any difference to the ABI.  */
9590      if (aggregate_p != (mode == BLKmode))
9591	{
9592	  static bool warned;
9593	  if (!warned && warn_psabi)
9594	    {
9595	      warned = true;
9596	      inform (input_location,
9597		      "the ABI of passing aggregates with %d-byte alignment"
9598		      " has changed in GCC 5",
9599		      (int) TYPE_ALIGN (type) / BITS_PER_UNIT);
9600	    }
9601	}
9602
9603      if (aggregate_p)
9604	return 128;
9605    }
9606
9607  /* Similar for the Darwin64 ABI.  Note that for historical reasons we
9608     implement the "aggregate type" check as a BLKmode check here; this
9609     means certain aggregate types are in fact not aligned.  */
9610  if (TARGET_MACHO && rs6000_darwin64_abi
9611      && mode == BLKmode
9612      && type && TYPE_ALIGN (type) > 64)
9613    return 128;
9614
9615  return PARM_BOUNDARY;
9616}
9617
9618/* The offset in words to the start of the parameter save area.  */
9619
9620static unsigned int
9621rs6000_parm_offset (void)
9622{
9623  return (DEFAULT_ABI == ABI_V4 ? 2
9624	  : DEFAULT_ABI == ABI_ELFv2 ? 4
9625	  : 6);
9626}
9627
9628/* For a function parm of MODE and TYPE, return the starting word in
9629   the parameter area.  NWORDS of the parameter area are already used.  */
9630
9631static unsigned int
9632rs6000_parm_start (machine_mode mode, const_tree type,
9633		   unsigned int nwords)
9634{
9635  unsigned int align;
9636
9637  align = rs6000_function_arg_boundary (mode, type) / PARM_BOUNDARY - 1;
9638  return nwords + (-(rs6000_parm_offset () + nwords) & align);
9639}
9640
9641/* Compute the size (in words) of a function argument.  */
9642
9643static unsigned long
9644rs6000_arg_size (machine_mode mode, const_tree type)
9645{
9646  unsigned long size;
9647
9648  if (mode != BLKmode)
9649    size = GET_MODE_SIZE (mode);
9650  else
9651    size = int_size_in_bytes (type);
9652
9653  if (TARGET_32BIT)
9654    return (size + 3) >> 2;
9655  else
9656    return (size + 7) >> 3;
9657}
9658
9659/* Use this to flush pending int fields.  */
9660
9661static void
9662rs6000_darwin64_record_arg_advance_flush (CUMULATIVE_ARGS *cum,
9663					  HOST_WIDE_INT bitpos, int final)
9664{
9665  unsigned int startbit, endbit;
9666  int intregs, intoffset;
9667  machine_mode mode;
9668
9669  /* Handle the situations where a float is taking up the first half
9670     of the GPR, and the other half is empty (typically due to
9671     alignment restrictions). We can detect this by a 8-byte-aligned
9672     int field, or by seeing that this is the final flush for this
9673     argument. Count the word and continue on.  */
9674  if (cum->floats_in_gpr == 1
9675      && (cum->intoffset % 64 == 0
9676	  || (cum->intoffset == -1 && final)))
9677    {
9678      cum->words++;
9679      cum->floats_in_gpr = 0;
9680    }
9681
9682  if (cum->intoffset == -1)
9683    return;
9684
9685  intoffset = cum->intoffset;
9686  cum->intoffset = -1;
9687  cum->floats_in_gpr = 0;
9688
9689  if (intoffset % BITS_PER_WORD != 0)
9690    {
9691      mode = mode_for_size (BITS_PER_WORD - intoffset % BITS_PER_WORD,
9692			    MODE_INT, 0);
9693      if (mode == BLKmode)
9694	{
9695	  /* We couldn't find an appropriate mode, which happens,
9696	     e.g., in packed structs when there are 3 bytes to load.
9697	     Back intoffset back to the beginning of the word in this
9698	     case.  */
9699	  intoffset = intoffset & -BITS_PER_WORD;
9700	}
9701    }
9702
9703  startbit = intoffset & -BITS_PER_WORD;
9704  endbit = (bitpos + BITS_PER_WORD - 1) & -BITS_PER_WORD;
9705  intregs = (endbit - startbit) / BITS_PER_WORD;
9706  cum->words += intregs;
9707  /* words should be unsigned. */
9708  if ((unsigned)cum->words < (endbit/BITS_PER_WORD))
9709    {
9710      int pad = (endbit/BITS_PER_WORD) - cum->words;
9711      cum->words += pad;
9712    }
9713}
9714
9715/* The darwin64 ABI calls for us to recurse down through structs,
9716   looking for elements passed in registers.  Unfortunately, we have
9717   to track int register count here also because of misalignments
9718   in powerpc alignment mode.  */
9719
9720static void
9721rs6000_darwin64_record_arg_advance_recurse (CUMULATIVE_ARGS *cum,
9722					    const_tree type,
9723					    HOST_WIDE_INT startbitpos)
9724{
9725  tree f;
9726
9727  for (f = TYPE_FIELDS (type); f ; f = DECL_CHAIN (f))
9728    if (TREE_CODE (f) == FIELD_DECL)
9729      {
9730	HOST_WIDE_INT bitpos = startbitpos;
9731	tree ftype = TREE_TYPE (f);
9732	machine_mode mode;
9733	if (ftype == error_mark_node)
9734	  continue;
9735	mode = TYPE_MODE (ftype);
9736
9737	if (DECL_SIZE (f) != 0
9738	    && tree_fits_uhwi_p (bit_position (f)))
9739	  bitpos += int_bit_position (f);
9740
9741	/* ??? FIXME: else assume zero offset.  */
9742
9743	if (TREE_CODE (ftype) == RECORD_TYPE)
9744	  rs6000_darwin64_record_arg_advance_recurse (cum, ftype, bitpos);
9745	else if (USE_FP_FOR_ARG_P (cum, mode))
9746	  {
9747	    unsigned n_fpregs = (GET_MODE_SIZE (mode) + 7) >> 3;
9748	    rs6000_darwin64_record_arg_advance_flush (cum, bitpos, 0);
9749	    cum->fregno += n_fpregs;
9750	    /* Single-precision floats present a special problem for
9751	       us, because they are smaller than an 8-byte GPR, and so
9752	       the structure-packing rules combined with the standard
9753	       varargs behavior mean that we want to pack float/float
9754	       and float/int combinations into a single register's
9755	       space. This is complicated by the arg advance flushing,
9756	       which works on arbitrarily large groups of int-type
9757	       fields.  */
9758	    if (mode == SFmode)
9759	      {
9760		if (cum->floats_in_gpr == 1)
9761		  {
9762		    /* Two floats in a word; count the word and reset
9763		       the float count.  */
9764		    cum->words++;
9765		    cum->floats_in_gpr = 0;
9766		  }
9767		else if (bitpos % 64 == 0)
9768		  {
9769		    /* A float at the beginning of an 8-byte word;
9770		       count it and put off adjusting cum->words until
9771		       we see if a arg advance flush is going to do it
9772		       for us.  */
9773		    cum->floats_in_gpr++;
9774		  }
9775		else
9776		  {
9777		    /* The float is at the end of a word, preceded
9778		       by integer fields, so the arg advance flush
9779		       just above has already set cum->words and
9780		       everything is taken care of.  */
9781		  }
9782	      }
9783	    else
9784	      cum->words += n_fpregs;
9785	  }
9786	else if (USE_ALTIVEC_FOR_ARG_P (cum, mode, 1))
9787	  {
9788	    rs6000_darwin64_record_arg_advance_flush (cum, bitpos, 0);
9789	    cum->vregno++;
9790	    cum->words += 2;
9791	  }
9792	else if (cum->intoffset == -1)
9793	  cum->intoffset = bitpos;
9794      }
9795}
9796
9797/* Check for an item that needs to be considered specially under the darwin 64
9798   bit ABI.  These are record types where the mode is BLK or the structure is
9799   8 bytes in size.  */
9800static int
9801rs6000_darwin64_struct_check_p (machine_mode mode, const_tree type)
9802{
9803  return rs6000_darwin64_abi
9804	 && ((mode == BLKmode
9805	      && TREE_CODE (type) == RECORD_TYPE
9806	      && int_size_in_bytes (type) > 0)
9807	  || (type && TREE_CODE (type) == RECORD_TYPE
9808	      && int_size_in_bytes (type) == 8)) ? 1 : 0;
9809}
9810
9811/* Update the data in CUM to advance over an argument
9812   of mode MODE and data type TYPE.
9813   (TYPE is null for libcalls where that information may not be available.)
9814
9815   Note that for args passed by reference, function_arg will be called
9816   with MODE and TYPE set to that of the pointer to the arg, not the arg
9817   itself.  */
9818
9819static void
9820rs6000_function_arg_advance_1 (CUMULATIVE_ARGS *cum, machine_mode mode,
9821			       const_tree type, bool named, int depth)
9822{
9823  machine_mode elt_mode;
9824  int n_elts;
9825
9826  rs6000_discover_homogeneous_aggregate (mode, type, &elt_mode, &n_elts);
9827
9828  /* Only tick off an argument if we're not recursing.  */
9829  if (depth == 0)
9830    cum->nargs_prototype--;
9831
9832#ifdef HAVE_AS_GNU_ATTRIBUTE
9833  if (DEFAULT_ABI == ABI_V4
9834      && cum->escapes)
9835    {
9836      if (SCALAR_FLOAT_MODE_P (mode))
9837	rs6000_passes_float = true;
9838      else if (named && ALTIVEC_OR_VSX_VECTOR_MODE (mode))
9839	rs6000_passes_vector = true;
9840      else if (SPE_VECTOR_MODE (mode)
9841	       && !cum->stdarg
9842	       && cum->sysv_gregno <= GP_ARG_MAX_REG)
9843	rs6000_passes_vector = true;
9844    }
9845#endif
9846
9847  if (TARGET_ALTIVEC_ABI
9848      && (ALTIVEC_OR_VSX_VECTOR_MODE (elt_mode)
9849	  || (type && TREE_CODE (type) == VECTOR_TYPE
9850	      && int_size_in_bytes (type) == 16)))
9851    {
9852      bool stack = false;
9853
9854      if (USE_ALTIVEC_FOR_ARG_P (cum, elt_mode, named))
9855	{
9856	  cum->vregno += n_elts;
9857
9858	  if (!TARGET_ALTIVEC)
9859	    error ("cannot pass argument in vector register because"
9860		   " altivec instructions are disabled, use -maltivec"
9861		   " to enable them");
9862
9863	  /* PowerPC64 Linux and AIX allocate GPRs for a vector argument
9864	     even if it is going to be passed in a vector register.
9865	     Darwin does the same for variable-argument functions.  */
9866	  if (((DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
9867	       && TARGET_64BIT)
9868	      || (cum->stdarg && DEFAULT_ABI != ABI_V4))
9869	    stack = true;
9870	}
9871      else
9872	stack = true;
9873
9874      if (stack)
9875	{
9876	  int align;
9877
9878	  /* Vector parameters must be 16-byte aligned.  In 32-bit
9879	     mode this means we need to take into account the offset
9880	     to the parameter save area.  In 64-bit mode, they just
9881	     have to start on an even word, since the parameter save
9882	     area is 16-byte aligned.  */
9883	  if (TARGET_32BIT)
9884	    align = -(rs6000_parm_offset () + cum->words) & 3;
9885	  else
9886	    align = cum->words & 1;
9887	  cum->words += align + rs6000_arg_size (mode, type);
9888
9889	  if (TARGET_DEBUG_ARG)
9890	    {
9891	      fprintf (stderr, "function_adv: words = %2d, align=%d, ",
9892		       cum->words, align);
9893	      fprintf (stderr, "nargs = %4d, proto = %d, mode = %4s\n",
9894		       cum->nargs_prototype, cum->prototype,
9895		       GET_MODE_NAME (mode));
9896	    }
9897	}
9898    }
9899  else if (TARGET_SPE_ABI && TARGET_SPE && SPE_VECTOR_MODE (mode)
9900	   && !cum->stdarg
9901	   && cum->sysv_gregno <= GP_ARG_MAX_REG)
9902    cum->sysv_gregno++;
9903
9904  else if (TARGET_MACHO && rs6000_darwin64_struct_check_p (mode, type))
9905    {
9906      int size = int_size_in_bytes (type);
9907      /* Variable sized types have size == -1 and are
9908	 treated as if consisting entirely of ints.
9909	 Pad to 16 byte boundary if needed.  */
9910      if (TYPE_ALIGN (type) >= 2 * BITS_PER_WORD
9911	  && (cum->words % 2) != 0)
9912	cum->words++;
9913      /* For varargs, we can just go up by the size of the struct. */
9914      if (!named)
9915	cum->words += (size + 7) / 8;
9916      else
9917	{
9918	  /* It is tempting to say int register count just goes up by
9919	     sizeof(type)/8, but this is wrong in a case such as
9920	     { int; double; int; } [powerpc alignment].  We have to
9921	     grovel through the fields for these too.  */
9922	  cum->intoffset = 0;
9923	  cum->floats_in_gpr = 0;
9924	  rs6000_darwin64_record_arg_advance_recurse (cum, type, 0);
9925	  rs6000_darwin64_record_arg_advance_flush (cum,
9926						    size * BITS_PER_UNIT, 1);
9927	}
9928	  if (TARGET_DEBUG_ARG)
9929	    {
9930	      fprintf (stderr, "function_adv: words = %2d, align=%d, size=%d",
9931		       cum->words, TYPE_ALIGN (type), size);
9932	      fprintf (stderr,
9933	           "nargs = %4d, proto = %d, mode = %4s (darwin64 abi)\n",
9934		       cum->nargs_prototype, cum->prototype,
9935		       GET_MODE_NAME (mode));
9936	    }
9937    }
9938  else if (DEFAULT_ABI == ABI_V4)
9939    {
9940      if (TARGET_HARD_FLOAT && TARGET_FPRS
9941	  && ((TARGET_SINGLE_FLOAT && mode == SFmode)
9942	      || (TARGET_DOUBLE_FLOAT && mode == DFmode)
9943	      || (mode == TFmode && !TARGET_IEEEQUAD)
9944	      || mode == SDmode || mode == DDmode || mode == TDmode))
9945	{
9946	  /* _Decimal128 must use an even/odd register pair.  This assumes
9947	     that the register number is odd when fregno is odd.  */
9948	  if (mode == TDmode && (cum->fregno % 2) == 1)
9949	    cum->fregno++;
9950
9951	  if (cum->fregno + (mode == TFmode || mode == TDmode ? 1 : 0)
9952	      <= FP_ARG_V4_MAX_REG)
9953	    cum->fregno += (GET_MODE_SIZE (mode) + 7) >> 3;
9954	  else
9955	    {
9956	      cum->fregno = FP_ARG_V4_MAX_REG + 1;
9957	      if (mode == DFmode || mode == TFmode
9958		  || mode == DDmode || mode == TDmode)
9959		cum->words += cum->words & 1;
9960	      cum->words += rs6000_arg_size (mode, type);
9961	    }
9962	}
9963      else
9964	{
9965	  int n_words = rs6000_arg_size (mode, type);
9966	  int gregno = cum->sysv_gregno;
9967
9968	  /* Long long and SPE vectors are put in (r3,r4), (r5,r6),
9969	     (r7,r8) or (r9,r10).  As does any other 2 word item such
9970	     as complex int due to a historical mistake.  */
9971	  if (n_words == 2)
9972	    gregno += (1 - gregno) & 1;
9973
9974	  /* Multi-reg args are not split between registers and stack.  */
9975	  if (gregno + n_words - 1 > GP_ARG_MAX_REG)
9976	    {
9977	      /* Long long and SPE vectors are aligned on the stack.
9978		 So are other 2 word items such as complex int due to
9979		 a historical mistake.  */
9980	      if (n_words == 2)
9981		cum->words += cum->words & 1;
9982	      cum->words += n_words;
9983	    }
9984
9985	  /* Note: continuing to accumulate gregno past when we've started
9986	     spilling to the stack indicates the fact that we've started
9987	     spilling to the stack to expand_builtin_saveregs.  */
9988	  cum->sysv_gregno = gregno + n_words;
9989	}
9990
9991      if (TARGET_DEBUG_ARG)
9992	{
9993	  fprintf (stderr, "function_adv: words = %2d, fregno = %2d, ",
9994		   cum->words, cum->fregno);
9995	  fprintf (stderr, "gregno = %2d, nargs = %4d, proto = %d, ",
9996		   cum->sysv_gregno, cum->nargs_prototype, cum->prototype);
9997	  fprintf (stderr, "mode = %4s, named = %d\n",
9998		   GET_MODE_NAME (mode), named);
9999	}
10000    }
10001  else
10002    {
10003      int n_words = rs6000_arg_size (mode, type);
10004      int start_words = cum->words;
10005      int align_words = rs6000_parm_start (mode, type, start_words);
10006
10007      cum->words = align_words + n_words;
10008
10009      if (SCALAR_FLOAT_MODE_P (elt_mode)
10010	  && TARGET_HARD_FLOAT && TARGET_FPRS)
10011	{
10012	  /* _Decimal128 must be passed in an even/odd float register pair.
10013	     This assumes that the register number is odd when fregno is
10014	     odd.  */
10015	  if (elt_mode == TDmode && (cum->fregno % 2) == 1)
10016	    cum->fregno++;
10017	  cum->fregno += n_elts * ((GET_MODE_SIZE (elt_mode) + 7) >> 3);
10018	}
10019
10020      if (TARGET_DEBUG_ARG)
10021	{
10022	  fprintf (stderr, "function_adv: words = %2d, fregno = %2d, ",
10023		   cum->words, cum->fregno);
10024	  fprintf (stderr, "nargs = %4d, proto = %d, mode = %4s, ",
10025		   cum->nargs_prototype, cum->prototype, GET_MODE_NAME (mode));
10026	  fprintf (stderr, "named = %d, align = %d, depth = %d\n",
10027		   named, align_words - start_words, depth);
10028	}
10029    }
10030}
10031
10032static void
10033rs6000_function_arg_advance (cumulative_args_t cum, machine_mode mode,
10034			     const_tree type, bool named)
10035{
10036  rs6000_function_arg_advance_1 (get_cumulative_args (cum), mode, type, named,
10037				 0);
10038}
10039
10040static rtx
10041spe_build_register_parallel (machine_mode mode, int gregno)
10042{
10043  rtx r1, r3, r5, r7;
10044
10045  switch (mode)
10046    {
10047    case DFmode:
10048      r1 = gen_rtx_REG (DImode, gregno);
10049      r1 = gen_rtx_EXPR_LIST (VOIDmode, r1, const0_rtx);
10050      return gen_rtx_PARALLEL (mode, gen_rtvec (1, r1));
10051
10052    case DCmode:
10053    case TFmode:
10054      r1 = gen_rtx_REG (DImode, gregno);
10055      r1 = gen_rtx_EXPR_LIST (VOIDmode, r1, const0_rtx);
10056      r3 = gen_rtx_REG (DImode, gregno + 2);
10057      r3 = gen_rtx_EXPR_LIST (VOIDmode, r3, GEN_INT (8));
10058      return gen_rtx_PARALLEL (mode, gen_rtvec (2, r1, r3));
10059
10060    case TCmode:
10061      r1 = gen_rtx_REG (DImode, gregno);
10062      r1 = gen_rtx_EXPR_LIST (VOIDmode, r1, const0_rtx);
10063      r3 = gen_rtx_REG (DImode, gregno + 2);
10064      r3 = gen_rtx_EXPR_LIST (VOIDmode, r3, GEN_INT (8));
10065      r5 = gen_rtx_REG (DImode, gregno + 4);
10066      r5 = gen_rtx_EXPR_LIST (VOIDmode, r5, GEN_INT (16));
10067      r7 = gen_rtx_REG (DImode, gregno + 6);
10068      r7 = gen_rtx_EXPR_LIST (VOIDmode, r7, GEN_INT (24));
10069      return gen_rtx_PARALLEL (mode, gen_rtvec (4, r1, r3, r5, r7));
10070
10071    default:
10072      gcc_unreachable ();
10073    }
10074}
10075
10076/* Determine where to put a SIMD argument on the SPE.  */
10077static rtx
10078rs6000_spe_function_arg (const CUMULATIVE_ARGS *cum, machine_mode mode,
10079			 const_tree type)
10080{
10081  int gregno = cum->sysv_gregno;
10082
10083  /* On E500 v2, double arithmetic is done on the full 64-bit GPR, but
10084     are passed and returned in a pair of GPRs for ABI compatibility.  */
10085  if (TARGET_E500_DOUBLE && (mode == DFmode || mode == TFmode
10086			     || mode == DCmode || mode == TCmode))
10087    {
10088      int n_words = rs6000_arg_size (mode, type);
10089
10090      /* Doubles go in an odd/even register pair (r5/r6, etc).  */
10091      if (mode == DFmode)
10092	gregno += (1 - gregno) & 1;
10093
10094      /* Multi-reg args are not split between registers and stack.  */
10095      if (gregno + n_words - 1 > GP_ARG_MAX_REG)
10096	return NULL_RTX;
10097
10098      return spe_build_register_parallel (mode, gregno);
10099    }
10100  if (cum->stdarg)
10101    {
10102      int n_words = rs6000_arg_size (mode, type);
10103
10104      /* SPE vectors are put in odd registers.  */
10105      if (n_words == 2 && (gregno & 1) == 0)
10106	gregno += 1;
10107
10108      if (gregno + n_words - 1 <= GP_ARG_MAX_REG)
10109	{
10110	  rtx r1, r2;
10111	  machine_mode m = SImode;
10112
10113	  r1 = gen_rtx_REG (m, gregno);
10114	  r1 = gen_rtx_EXPR_LIST (m, r1, const0_rtx);
10115	  r2 = gen_rtx_REG (m, gregno + 1);
10116	  r2 = gen_rtx_EXPR_LIST (m, r2, GEN_INT (4));
10117	  return gen_rtx_PARALLEL (mode, gen_rtvec (2, r1, r2));
10118	}
10119      else
10120	return NULL_RTX;
10121    }
10122  else
10123    {
10124      if (gregno <= GP_ARG_MAX_REG)
10125	return gen_rtx_REG (mode, gregno);
10126      else
10127	return NULL_RTX;
10128    }
10129}
10130
10131/* A subroutine of rs6000_darwin64_record_arg.  Assign the bits of the
10132   structure between cum->intoffset and bitpos to integer registers.  */
10133
10134static void
10135rs6000_darwin64_record_arg_flush (CUMULATIVE_ARGS *cum,
10136				  HOST_WIDE_INT bitpos, rtx rvec[], int *k)
10137{
10138  machine_mode mode;
10139  unsigned int regno;
10140  unsigned int startbit, endbit;
10141  int this_regno, intregs, intoffset;
10142  rtx reg;
10143
10144  if (cum->intoffset == -1)
10145    return;
10146
10147  intoffset = cum->intoffset;
10148  cum->intoffset = -1;
10149
10150  /* If this is the trailing part of a word, try to only load that
10151     much into the register.  Otherwise load the whole register.  Note
10152     that in the latter case we may pick up unwanted bits.  It's not a
10153     problem at the moment but may wish to revisit.  */
10154
10155  if (intoffset % BITS_PER_WORD != 0)
10156    {
10157      mode = mode_for_size (BITS_PER_WORD - intoffset % BITS_PER_WORD,
10158			  MODE_INT, 0);
10159      if (mode == BLKmode)
10160	{
10161	  /* We couldn't find an appropriate mode, which happens,
10162	     e.g., in packed structs when there are 3 bytes to load.
10163	     Back intoffset back to the beginning of the word in this
10164	     case.  */
10165	 intoffset = intoffset & -BITS_PER_WORD;
10166	 mode = word_mode;
10167	}
10168    }
10169  else
10170    mode = word_mode;
10171
10172  startbit = intoffset & -BITS_PER_WORD;
10173  endbit = (bitpos + BITS_PER_WORD - 1) & -BITS_PER_WORD;
10174  intregs = (endbit - startbit) / BITS_PER_WORD;
10175  this_regno = cum->words + intoffset / BITS_PER_WORD;
10176
10177  if (intregs > 0 && intregs > GP_ARG_NUM_REG - this_regno)
10178    cum->use_stack = 1;
10179
10180  intregs = MIN (intregs, GP_ARG_NUM_REG - this_regno);
10181  if (intregs <= 0)
10182    return;
10183
10184  intoffset /= BITS_PER_UNIT;
10185  do
10186    {
10187      regno = GP_ARG_MIN_REG + this_regno;
10188      reg = gen_rtx_REG (mode, regno);
10189      rvec[(*k)++] =
10190	gen_rtx_EXPR_LIST (VOIDmode, reg, GEN_INT (intoffset));
10191
10192      this_regno += 1;
10193      intoffset = (intoffset | (UNITS_PER_WORD-1)) + 1;
10194      mode = word_mode;
10195      intregs -= 1;
10196    }
10197  while (intregs > 0);
10198}
10199
10200/* Recursive workhorse for the following.  */
10201
10202static void
10203rs6000_darwin64_record_arg_recurse (CUMULATIVE_ARGS *cum, const_tree type,
10204				    HOST_WIDE_INT startbitpos, rtx rvec[],
10205				    int *k)
10206{
10207  tree f;
10208
10209  for (f = TYPE_FIELDS (type); f ; f = DECL_CHAIN (f))
10210    if (TREE_CODE (f) == FIELD_DECL)
10211      {
10212	HOST_WIDE_INT bitpos = startbitpos;
10213	tree ftype = TREE_TYPE (f);
10214	machine_mode mode;
10215	if (ftype == error_mark_node)
10216	  continue;
10217	mode = TYPE_MODE (ftype);
10218
10219	if (DECL_SIZE (f) != 0
10220	    && tree_fits_uhwi_p (bit_position (f)))
10221	  bitpos += int_bit_position (f);
10222
10223	/* ??? FIXME: else assume zero offset.  */
10224
10225	if (TREE_CODE (ftype) == RECORD_TYPE)
10226	  rs6000_darwin64_record_arg_recurse (cum, ftype, bitpos, rvec, k);
10227	else if (cum->named && USE_FP_FOR_ARG_P (cum, mode))
10228	  {
10229	    unsigned n_fpreg = (GET_MODE_SIZE (mode) + 7) >> 3;
10230#if 0
10231	    switch (mode)
10232	      {
10233	      case SCmode: mode = SFmode; break;
10234	      case DCmode: mode = DFmode; break;
10235	      case TCmode: mode = TFmode; break;
10236	      default: break;
10237	      }
10238#endif
10239	    rs6000_darwin64_record_arg_flush (cum, bitpos, rvec, k);
10240	    if (cum->fregno + n_fpreg > FP_ARG_MAX_REG + 1)
10241	      {
10242		gcc_assert (cum->fregno == FP_ARG_MAX_REG
10243			    && (mode == TFmode || mode == TDmode));
10244		/* Long double or _Decimal128 split over regs and memory.  */
10245		mode = DECIMAL_FLOAT_MODE_P (mode) ? DDmode : DFmode;
10246		cum->use_stack=1;
10247	      }
10248	    rvec[(*k)++]
10249	      = gen_rtx_EXPR_LIST (VOIDmode,
10250				   gen_rtx_REG (mode, cum->fregno++),
10251				   GEN_INT (bitpos / BITS_PER_UNIT));
10252	    if (mode == TFmode || mode == TDmode)
10253	      cum->fregno++;
10254	  }
10255	else if (cum->named && USE_ALTIVEC_FOR_ARG_P (cum, mode, 1))
10256	  {
10257	    rs6000_darwin64_record_arg_flush (cum, bitpos, rvec, k);
10258	    rvec[(*k)++]
10259	      = gen_rtx_EXPR_LIST (VOIDmode,
10260				   gen_rtx_REG (mode, cum->vregno++),
10261				   GEN_INT (bitpos / BITS_PER_UNIT));
10262	  }
10263	else if (cum->intoffset == -1)
10264	  cum->intoffset = bitpos;
10265      }
10266}
10267
10268/* For the darwin64 ABI, we want to construct a PARALLEL consisting of
10269   the register(s) to be used for each field and subfield of a struct
10270   being passed by value, along with the offset of where the
10271   register's value may be found in the block.  FP fields go in FP
10272   register, vector fields go in vector registers, and everything
10273   else goes in int registers, packed as in memory.
10274
10275   This code is also used for function return values.  RETVAL indicates
10276   whether this is the case.
10277
10278   Much of this is taken from the SPARC V9 port, which has a similar
10279   calling convention.  */
10280
10281static rtx
10282rs6000_darwin64_record_arg (CUMULATIVE_ARGS *orig_cum, const_tree type,
10283			    bool named, bool retval)
10284{
10285  rtx rvec[FIRST_PSEUDO_REGISTER];
10286  int k = 1, kbase = 1;
10287  HOST_WIDE_INT typesize = int_size_in_bytes (type);
10288  /* This is a copy; modifications are not visible to our caller.  */
10289  CUMULATIVE_ARGS copy_cum = *orig_cum;
10290  CUMULATIVE_ARGS *cum = &copy_cum;
10291
10292  /* Pad to 16 byte boundary if needed.  */
10293  if (!retval && TYPE_ALIGN (type) >= 2 * BITS_PER_WORD
10294      && (cum->words % 2) != 0)
10295    cum->words++;
10296
10297  cum->intoffset = 0;
10298  cum->use_stack = 0;
10299  cum->named = named;
10300
10301  /* Put entries into rvec[] for individual FP and vector fields, and
10302     for the chunks of memory that go in int regs.  Note we start at
10303     element 1; 0 is reserved for an indication of using memory, and
10304     may or may not be filled in below. */
10305  rs6000_darwin64_record_arg_recurse (cum, type, /* startbit pos= */ 0, rvec, &k);
10306  rs6000_darwin64_record_arg_flush (cum, typesize * BITS_PER_UNIT, rvec, &k);
10307
10308  /* If any part of the struct went on the stack put all of it there.
10309     This hack is because the generic code for
10310     FUNCTION_ARG_PARTIAL_NREGS cannot handle cases where the register
10311     parts of the struct are not at the beginning.  */
10312  if (cum->use_stack)
10313    {
10314      if (retval)
10315	return NULL_RTX;    /* doesn't go in registers at all */
10316      kbase = 0;
10317      rvec[0] = gen_rtx_EXPR_LIST (VOIDmode, NULL_RTX, const0_rtx);
10318    }
10319  if (k > 1 || cum->use_stack)
10320    return gen_rtx_PARALLEL (BLKmode, gen_rtvec_v (k - kbase, &rvec[kbase]));
10321  else
10322    return NULL_RTX;
10323}
10324
10325/* Determine where to place an argument in 64-bit mode with 32-bit ABI.  */
10326
10327static rtx
10328rs6000_mixed_function_arg (machine_mode mode, const_tree type,
10329			   int align_words)
10330{
10331  int n_units;
10332  int i, k;
10333  rtx rvec[GP_ARG_NUM_REG + 1];
10334
10335  if (align_words >= GP_ARG_NUM_REG)
10336    return NULL_RTX;
10337
10338  n_units = rs6000_arg_size (mode, type);
10339
10340  /* Optimize the simple case where the arg fits in one gpr, except in
10341     the case of BLKmode due to assign_parms assuming that registers are
10342     BITS_PER_WORD wide.  */
10343  if (n_units == 0
10344      || (n_units == 1 && mode != BLKmode))
10345    return gen_rtx_REG (mode, GP_ARG_MIN_REG + align_words);
10346
10347  k = 0;
10348  if (align_words + n_units > GP_ARG_NUM_REG)
10349    /* Not all of the arg fits in gprs.  Say that it goes in memory too,
10350       using a magic NULL_RTX component.
10351       This is not strictly correct.  Only some of the arg belongs in
10352       memory, not all of it.  However, the normal scheme using
10353       function_arg_partial_nregs can result in unusual subregs, eg.
10354       (subreg:SI (reg:DF) 4), which are not handled well.  The code to
10355       store the whole arg to memory is often more efficient than code
10356       to store pieces, and we know that space is available in the right
10357       place for the whole arg.  */
10358    rvec[k++] = gen_rtx_EXPR_LIST (VOIDmode, NULL_RTX, const0_rtx);
10359
10360  i = 0;
10361  do
10362    {
10363      rtx r = gen_rtx_REG (SImode, GP_ARG_MIN_REG + align_words);
10364      rtx off = GEN_INT (i++ * 4);
10365      rvec[k++] = gen_rtx_EXPR_LIST (VOIDmode, r, off);
10366    }
10367  while (++align_words < GP_ARG_NUM_REG && --n_units != 0);
10368
10369  return gen_rtx_PARALLEL (mode, gen_rtvec_v (k, rvec));
10370}
10371
10372/* We have an argument of MODE and TYPE that goes into FPRs or VRs,
10373   but must also be copied into the parameter save area starting at
10374   offset ALIGN_WORDS.  Fill in RVEC with the elements corresponding
10375   to the GPRs and/or memory.  Return the number of elements used.  */
10376
10377static int
10378rs6000_psave_function_arg (machine_mode mode, const_tree type,
10379			   int align_words, rtx *rvec)
10380{
10381  int k = 0;
10382
10383  if (align_words < GP_ARG_NUM_REG)
10384    {
10385      int n_words = rs6000_arg_size (mode, type);
10386
10387      if (align_words + n_words > GP_ARG_NUM_REG
10388	  || mode == BLKmode
10389	  || (TARGET_32BIT && TARGET_POWERPC64))
10390	{
10391	  /* If this is partially on the stack, then we only
10392	     include the portion actually in registers here.  */
10393	  machine_mode rmode = TARGET_32BIT ? SImode : DImode;
10394	  int i = 0;
10395
10396	  if (align_words + n_words > GP_ARG_NUM_REG)
10397	    {
10398	      /* Not all of the arg fits in gprs.  Say that it goes in memory
10399		 too, using a magic NULL_RTX component.  Also see comment in
10400		 rs6000_mixed_function_arg for why the normal
10401		 function_arg_partial_nregs scheme doesn't work in this case. */
10402	      rvec[k++] = gen_rtx_EXPR_LIST (VOIDmode, NULL_RTX, const0_rtx);
10403	    }
10404
10405	  do
10406	    {
10407	      rtx r = gen_rtx_REG (rmode, GP_ARG_MIN_REG + align_words);
10408	      rtx off = GEN_INT (i++ * GET_MODE_SIZE (rmode));
10409	      rvec[k++] = gen_rtx_EXPR_LIST (VOIDmode, r, off);
10410	    }
10411	  while (++align_words < GP_ARG_NUM_REG && --n_words != 0);
10412	}
10413      else
10414	{
10415	  /* The whole arg fits in gprs.  */
10416	  rtx r = gen_rtx_REG (mode, GP_ARG_MIN_REG + align_words);
10417	  rvec[k++] = gen_rtx_EXPR_LIST (VOIDmode, r, const0_rtx);
10418	}
10419    }
10420  else
10421    {
10422      /* It's entirely in memory.  */
10423      rvec[k++] = gen_rtx_EXPR_LIST (VOIDmode, NULL_RTX, const0_rtx);
10424    }
10425
10426  return k;
10427}
10428
10429/* RVEC is a vector of K components of an argument of mode MODE.
10430   Construct the final function_arg return value from it.  */
10431
10432static rtx
10433rs6000_finish_function_arg (machine_mode mode, rtx *rvec, int k)
10434{
10435  gcc_assert (k >= 1);
10436
10437  /* Avoid returning a PARALLEL in the trivial cases.  */
10438  if (k == 1)
10439    {
10440      if (XEXP (rvec[0], 0) == NULL_RTX)
10441	return NULL_RTX;
10442
10443      if (GET_MODE (XEXP (rvec[0], 0)) == mode)
10444	return XEXP (rvec[0], 0);
10445    }
10446
10447  return gen_rtx_PARALLEL (mode, gen_rtvec_v (k, rvec));
10448}
10449
10450/* Determine where to put an argument to a function.
10451   Value is zero to push the argument on the stack,
10452   or a hard register in which to store the argument.
10453
10454   MODE is the argument's machine mode.
10455   TYPE is the data type of the argument (as a tree).
10456    This is null for libcalls where that information may
10457    not be available.
10458   CUM is a variable of type CUMULATIVE_ARGS which gives info about
10459    the preceding args and about the function being called.  It is
10460    not modified in this routine.
10461   NAMED is nonzero if this argument is a named parameter
10462    (otherwise it is an extra parameter matching an ellipsis).
10463
10464   On RS/6000 the first eight words of non-FP are normally in registers
10465   and the rest are pushed.  Under AIX, the first 13 FP args are in registers.
10466   Under V.4, the first 8 FP args are in registers.
10467
10468   If this is floating-point and no prototype is specified, we use
10469   both an FP and integer register (or possibly FP reg and stack).  Library
10470   functions (when CALL_LIBCALL is set) always have the proper types for args,
10471   so we can pass the FP value just in one register.  emit_library_function
10472   doesn't support PARALLEL anyway.
10473
10474   Note that for args passed by reference, function_arg will be called
10475   with MODE and TYPE set to that of the pointer to the arg, not the arg
10476   itself.  */
10477
10478static rtx
10479rs6000_function_arg (cumulative_args_t cum_v, machine_mode mode,
10480		     const_tree type, bool named)
10481{
10482  CUMULATIVE_ARGS *cum = get_cumulative_args (cum_v);
10483  enum rs6000_abi abi = DEFAULT_ABI;
10484  machine_mode elt_mode;
10485  int n_elts;
10486
10487  /* Return a marker to indicate whether CR1 needs to set or clear the
10488     bit that V.4 uses to say fp args were passed in registers.
10489     Assume that we don't need the marker for software floating point,
10490     or compiler generated library calls.  */
10491  if (mode == VOIDmode)
10492    {
10493      if (abi == ABI_V4
10494	  && (cum->call_cookie & CALL_LIBCALL) == 0
10495	  && (cum->stdarg
10496	      || (cum->nargs_prototype < 0
10497		  && (cum->prototype || TARGET_NO_PROTOTYPE))))
10498	{
10499	  /* For the SPE, we need to crxor CR6 always.  */
10500	  if (TARGET_SPE_ABI)
10501	    return GEN_INT (cum->call_cookie | CALL_V4_SET_FP_ARGS);
10502	  else if (TARGET_HARD_FLOAT && TARGET_FPRS)
10503	    return GEN_INT (cum->call_cookie
10504			    | ((cum->fregno == FP_ARG_MIN_REG)
10505			       ? CALL_V4_SET_FP_ARGS
10506			       : CALL_V4_CLEAR_FP_ARGS));
10507	}
10508
10509      return GEN_INT (cum->call_cookie & ~CALL_LIBCALL);
10510    }
10511
10512  rs6000_discover_homogeneous_aggregate (mode, type, &elt_mode, &n_elts);
10513
10514  if (TARGET_MACHO && rs6000_darwin64_struct_check_p (mode, type))
10515    {
10516      rtx rslt = rs6000_darwin64_record_arg (cum, type, named, /*retval= */false);
10517      if (rslt != NULL_RTX)
10518	return rslt;
10519      /* Else fall through to usual handling.  */
10520    }
10521
10522  if (USE_ALTIVEC_FOR_ARG_P (cum, elt_mode, named))
10523    {
10524      rtx rvec[GP_ARG_NUM_REG + AGGR_ARG_NUM_REG + 1];
10525      rtx r, off;
10526      int i, k = 0;
10527
10528      /* Do we also need to pass this argument in the parameter
10529	 save area?  */
10530      if (TARGET_64BIT && ! cum->prototype)
10531	{
10532	  int align_words = (cum->words + 1) & ~1;
10533	  k = rs6000_psave_function_arg (mode, type, align_words, rvec);
10534	}
10535
10536      /* Describe where this argument goes in the vector registers.  */
10537      for (i = 0; i < n_elts && cum->vregno + i <= ALTIVEC_ARG_MAX_REG; i++)
10538	{
10539	  r = gen_rtx_REG (elt_mode, cum->vregno + i);
10540	  off = GEN_INT (i * GET_MODE_SIZE (elt_mode));
10541	  rvec[k++] =  gen_rtx_EXPR_LIST (VOIDmode, r, off);
10542	}
10543
10544      return rs6000_finish_function_arg (mode, rvec, k);
10545    }
10546  else if (TARGET_ALTIVEC_ABI
10547	   && (ALTIVEC_OR_VSX_VECTOR_MODE (mode)
10548	       || (type && TREE_CODE (type) == VECTOR_TYPE
10549		   && int_size_in_bytes (type) == 16)))
10550    {
10551      if (named || abi == ABI_V4)
10552	return NULL_RTX;
10553      else
10554	{
10555	  /* Vector parameters to varargs functions under AIX or Darwin
10556	     get passed in memory and possibly also in GPRs.  */
10557	  int align, align_words, n_words;
10558	  machine_mode part_mode;
10559
10560	  /* Vector parameters must be 16-byte aligned.  In 32-bit
10561	     mode this means we need to take into account the offset
10562	     to the parameter save area.  In 64-bit mode, they just
10563	     have to start on an even word, since the parameter save
10564	     area is 16-byte aligned.  */
10565	  if (TARGET_32BIT)
10566	    align = -(rs6000_parm_offset () + cum->words) & 3;
10567	  else
10568	    align = cum->words & 1;
10569	  align_words = cum->words + align;
10570
10571	  /* Out of registers?  Memory, then.  */
10572	  if (align_words >= GP_ARG_NUM_REG)
10573	    return NULL_RTX;
10574
10575	  if (TARGET_32BIT && TARGET_POWERPC64)
10576	    return rs6000_mixed_function_arg (mode, type, align_words);
10577
10578	  /* The vector value goes in GPRs.  Only the part of the
10579	     value in GPRs is reported here.  */
10580	  part_mode = mode;
10581	  n_words = rs6000_arg_size (mode, type);
10582	  if (align_words + n_words > GP_ARG_NUM_REG)
10583	    /* Fortunately, there are only two possibilities, the value
10584	       is either wholly in GPRs or half in GPRs and half not.  */
10585	    part_mode = DImode;
10586
10587	  return gen_rtx_REG (part_mode, GP_ARG_MIN_REG + align_words);
10588	}
10589    }
10590  else if (TARGET_SPE_ABI && TARGET_SPE
10591	   && (SPE_VECTOR_MODE (mode)
10592	       || (TARGET_E500_DOUBLE && (mode == DFmode
10593					  || mode == DCmode
10594					  || mode == TFmode
10595					  || mode == TCmode))))
10596    return rs6000_spe_function_arg (cum, mode, type);
10597
10598  else if (abi == ABI_V4)
10599    {
10600      if (TARGET_HARD_FLOAT && TARGET_FPRS
10601	  && ((TARGET_SINGLE_FLOAT && mode == SFmode)
10602	      || (TARGET_DOUBLE_FLOAT && mode == DFmode)
10603	      || (mode == TFmode && !TARGET_IEEEQUAD)
10604	      || mode == SDmode || mode == DDmode || mode == TDmode))
10605	{
10606	  /* _Decimal128 must use an even/odd register pair.  This assumes
10607	     that the register number is odd when fregno is odd.  */
10608	  if (mode == TDmode && (cum->fregno % 2) == 1)
10609	    cum->fregno++;
10610
10611	  if (cum->fregno + (mode == TFmode || mode == TDmode ? 1 : 0)
10612	      <= FP_ARG_V4_MAX_REG)
10613	    return gen_rtx_REG (mode, cum->fregno);
10614	  else
10615	    return NULL_RTX;
10616	}
10617      else
10618	{
10619	  int n_words = rs6000_arg_size (mode, type);
10620	  int gregno = cum->sysv_gregno;
10621
10622	  /* Long long and SPE vectors are put in (r3,r4), (r5,r6),
10623	     (r7,r8) or (r9,r10).  As does any other 2 word item such
10624	     as complex int due to a historical mistake.  */
10625	  if (n_words == 2)
10626	    gregno += (1 - gregno) & 1;
10627
10628	  /* Multi-reg args are not split between registers and stack.  */
10629	  if (gregno + n_words - 1 > GP_ARG_MAX_REG)
10630	    return NULL_RTX;
10631
10632	  if (TARGET_32BIT && TARGET_POWERPC64)
10633	    return rs6000_mixed_function_arg (mode, type,
10634					      gregno - GP_ARG_MIN_REG);
10635	  return gen_rtx_REG (mode, gregno);
10636	}
10637    }
10638  else
10639    {
10640      int align_words = rs6000_parm_start (mode, type, cum->words);
10641
10642      /* _Decimal128 must be passed in an even/odd float register pair.
10643	 This assumes that the register number is odd when fregno is odd.  */
10644      if (elt_mode == TDmode && (cum->fregno % 2) == 1)
10645	cum->fregno++;
10646
10647      if (USE_FP_FOR_ARG_P (cum, elt_mode))
10648	{
10649	  rtx rvec[GP_ARG_NUM_REG + AGGR_ARG_NUM_REG + 1];
10650	  rtx r, off;
10651	  int i, k = 0;
10652	  unsigned long n_fpreg = (GET_MODE_SIZE (elt_mode) + 7) >> 3;
10653	  int fpr_words;
10654
10655	  /* Do we also need to pass this argument in the parameter
10656	     save area?  */
10657	  if (type && (cum->nargs_prototype <= 0
10658		       || ((DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
10659			   && TARGET_XL_COMPAT
10660			   && align_words >= GP_ARG_NUM_REG)))
10661	    k = rs6000_psave_function_arg (mode, type, align_words, rvec);
10662
10663	  /* Describe where this argument goes in the fprs.  */
10664	  for (i = 0; i < n_elts
10665		      && cum->fregno + i * n_fpreg <= FP_ARG_MAX_REG; i++)
10666	    {
10667	      /* Check if the argument is split over registers and memory.
10668		 This can only ever happen for long double or _Decimal128;
10669		 complex types are handled via split_complex_arg.  */
10670	      machine_mode fmode = elt_mode;
10671	      if (cum->fregno + (i + 1) * n_fpreg > FP_ARG_MAX_REG + 1)
10672		{
10673		  gcc_assert (fmode == TFmode || fmode == TDmode);
10674		  fmode = DECIMAL_FLOAT_MODE_P (fmode) ? DDmode : DFmode;
10675		}
10676
10677	      r = gen_rtx_REG (fmode, cum->fregno + i * n_fpreg);
10678	      off = GEN_INT (i * GET_MODE_SIZE (elt_mode));
10679	      rvec[k++] = gen_rtx_EXPR_LIST (VOIDmode, r, off);
10680	    }
10681
10682	  /* If there were not enough FPRs to hold the argument, the rest
10683	     usually goes into memory.  However, if the current position
10684	     is still within the register parameter area, a portion may
10685	     actually have to go into GPRs.
10686
10687	     Note that it may happen that the portion of the argument
10688	     passed in the first "half" of the first GPR was already
10689	     passed in the last FPR as well.
10690
10691	     For unnamed arguments, we already set up GPRs to cover the
10692	     whole argument in rs6000_psave_function_arg, so there is
10693	     nothing further to do at this point.  */
10694	  fpr_words = (i * GET_MODE_SIZE (elt_mode)) / (TARGET_32BIT ? 4 : 8);
10695	  if (i < n_elts && align_words + fpr_words < GP_ARG_NUM_REG
10696	      && cum->nargs_prototype > 0)
10697            {
10698	      static bool warned;
10699
10700	      machine_mode rmode = TARGET_32BIT ? SImode : DImode;
10701	      int n_words = rs6000_arg_size (mode, type);
10702
10703	      align_words += fpr_words;
10704	      n_words -= fpr_words;
10705
10706	      do
10707		{
10708		  r = gen_rtx_REG (rmode, GP_ARG_MIN_REG + align_words);
10709		  off = GEN_INT (fpr_words++ * GET_MODE_SIZE (rmode));
10710		  rvec[k++] = gen_rtx_EXPR_LIST (VOIDmode, r, off);
10711		}
10712	      while (++align_words < GP_ARG_NUM_REG && --n_words != 0);
10713
10714	      if (!warned && warn_psabi)
10715		{
10716		  warned = true;
10717		  inform (input_location,
10718			  "the ABI of passing homogeneous float aggregates"
10719			  " has changed in GCC 5");
10720		}
10721	    }
10722
10723	  return rs6000_finish_function_arg (mode, rvec, k);
10724	}
10725      else if (align_words < GP_ARG_NUM_REG)
10726	{
10727	  if (TARGET_32BIT && TARGET_POWERPC64)
10728	    return rs6000_mixed_function_arg (mode, type, align_words);
10729
10730	  return gen_rtx_REG (mode, GP_ARG_MIN_REG + align_words);
10731	}
10732      else
10733	return NULL_RTX;
10734    }
10735}
10736
10737/* For an arg passed partly in registers and partly in memory, this is
10738   the number of bytes passed in registers.  For args passed entirely in
10739   registers or entirely in memory, zero.  When an arg is described by a
10740   PARALLEL, perhaps using more than one register type, this function
10741   returns the number of bytes used by the first element of the PARALLEL.  */
10742
10743static int
10744rs6000_arg_partial_bytes (cumulative_args_t cum_v, machine_mode mode,
10745			  tree type, bool named)
10746{
10747  CUMULATIVE_ARGS *cum = get_cumulative_args (cum_v);
10748  bool passed_in_gprs = true;
10749  int ret = 0;
10750  int align_words;
10751  machine_mode elt_mode;
10752  int n_elts;
10753
10754  rs6000_discover_homogeneous_aggregate (mode, type, &elt_mode, &n_elts);
10755
10756  if (DEFAULT_ABI == ABI_V4)
10757    return 0;
10758
10759  if (USE_ALTIVEC_FOR_ARG_P (cum, elt_mode, named))
10760    {
10761      /* If we are passing this arg in the fixed parameter save area
10762         (gprs or memory) as well as VRs, we do not use the partial
10763	 bytes mechanism; instead, rs6000_function_arg will return a
10764	 PARALLEL including a memory element as necessary.  */
10765      if (TARGET_64BIT && ! cum->prototype)
10766	return 0;
10767
10768      /* Otherwise, we pass in VRs only.  Check for partial copies.  */
10769      passed_in_gprs = false;
10770      if (cum->vregno + n_elts > ALTIVEC_ARG_MAX_REG + 1)
10771	ret = (ALTIVEC_ARG_MAX_REG + 1 - cum->vregno) * 16;
10772    }
10773
10774  /* In this complicated case we just disable the partial_nregs code.  */
10775  if (TARGET_MACHO && rs6000_darwin64_struct_check_p (mode, type))
10776    return 0;
10777
10778  align_words = rs6000_parm_start (mode, type, cum->words);
10779
10780  if (USE_FP_FOR_ARG_P (cum, elt_mode))
10781    {
10782      unsigned long n_fpreg = (GET_MODE_SIZE (elt_mode) + 7) >> 3;
10783
10784      /* If we are passing this arg in the fixed parameter save area
10785         (gprs or memory) as well as FPRs, we do not use the partial
10786	 bytes mechanism; instead, rs6000_function_arg will return a
10787	 PARALLEL including a memory element as necessary.  */
10788      if (type
10789	  && (cum->nargs_prototype <= 0
10790	      || ((DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
10791		  && TARGET_XL_COMPAT
10792		  && align_words >= GP_ARG_NUM_REG)))
10793	return 0;
10794
10795      /* Otherwise, we pass in FPRs only.  Check for partial copies.  */
10796      passed_in_gprs = false;
10797      if (cum->fregno + n_elts * n_fpreg > FP_ARG_MAX_REG + 1)
10798	{
10799	  /* Compute number of bytes / words passed in FPRs.  If there
10800	     is still space available in the register parameter area
10801	     *after* that amount, a part of the argument will be passed
10802	     in GPRs.  In that case, the total amount passed in any
10803	     registers is equal to the amount that would have been passed
10804	     in GPRs if everything were passed there, so we fall back to
10805	     the GPR code below to compute the appropriate value.  */
10806	  int fpr = ((FP_ARG_MAX_REG + 1 - cum->fregno)
10807		     * MIN (8, GET_MODE_SIZE (elt_mode)));
10808	  int fpr_words = fpr / (TARGET_32BIT ? 4 : 8);
10809
10810	  if (align_words + fpr_words < GP_ARG_NUM_REG)
10811	    passed_in_gprs = true;
10812	  else
10813	    ret = fpr;
10814	}
10815    }
10816
10817  if (passed_in_gprs
10818      && align_words < GP_ARG_NUM_REG
10819      && GP_ARG_NUM_REG < align_words + rs6000_arg_size (mode, type))
10820    ret = (GP_ARG_NUM_REG - align_words) * (TARGET_32BIT ? 4 : 8);
10821
10822  if (ret != 0 && TARGET_DEBUG_ARG)
10823    fprintf (stderr, "rs6000_arg_partial_bytes: %d\n", ret);
10824
10825  return ret;
10826}
10827
10828/* A C expression that indicates when an argument must be passed by
10829   reference.  If nonzero for an argument, a copy of that argument is
10830   made in memory and a pointer to the argument is passed instead of
10831   the argument itself.  The pointer is passed in whatever way is
10832   appropriate for passing a pointer to that type.
10833
10834   Under V.4, aggregates and long double are passed by reference.
10835
10836   As an extension to all 32-bit ABIs, AltiVec vectors are passed by
10837   reference unless the AltiVec vector extension ABI is in force.
10838
10839   As an extension to all ABIs, variable sized types are passed by
10840   reference.  */
10841
10842static bool
10843rs6000_pass_by_reference (cumulative_args_t cum ATTRIBUTE_UNUSED,
10844			  machine_mode mode, const_tree type,
10845			  bool named ATTRIBUTE_UNUSED)
10846{
10847  if (DEFAULT_ABI == ABI_V4 && TARGET_IEEEQUAD && mode == TFmode)
10848    {
10849      if (TARGET_DEBUG_ARG)
10850	fprintf (stderr, "function_arg_pass_by_reference: V4 long double\n");
10851      return 1;
10852    }
10853
10854  if (!type)
10855    return 0;
10856
10857  if (DEFAULT_ABI == ABI_V4 && AGGREGATE_TYPE_P (type))
10858    {
10859      if (TARGET_DEBUG_ARG)
10860	fprintf (stderr, "function_arg_pass_by_reference: V4 aggregate\n");
10861      return 1;
10862    }
10863
10864  if (int_size_in_bytes (type) < 0)
10865    {
10866      if (TARGET_DEBUG_ARG)
10867	fprintf (stderr, "function_arg_pass_by_reference: variable size\n");
10868      return 1;
10869    }
10870
10871  /* Allow -maltivec -mabi=no-altivec without warning.  Altivec vector
10872     modes only exist for GCC vector types if -maltivec.  */
10873  if (TARGET_32BIT && !TARGET_ALTIVEC_ABI && ALTIVEC_VECTOR_MODE (mode))
10874    {
10875      if (TARGET_DEBUG_ARG)
10876	fprintf (stderr, "function_arg_pass_by_reference: AltiVec\n");
10877      return 1;
10878    }
10879
10880  /* Pass synthetic vectors in memory.  */
10881  if (TREE_CODE (type) == VECTOR_TYPE
10882      && int_size_in_bytes (type) > (TARGET_ALTIVEC_ABI ? 16 : 8))
10883    {
10884      static bool warned_for_pass_big_vectors = false;
10885      if (TARGET_DEBUG_ARG)
10886	fprintf (stderr, "function_arg_pass_by_reference: synthetic vector\n");
10887      if (!warned_for_pass_big_vectors)
10888	{
10889	  warning (0, "GCC vector passed by reference: "
10890		   "non-standard ABI extension with no compatibility guarantee");
10891	  warned_for_pass_big_vectors = true;
10892	}
10893      return 1;
10894    }
10895
10896  return 0;
10897}
10898
10899/* Process parameter of type TYPE after ARGS_SO_FAR parameters were
10900   already processes.  Return true if the parameter must be passed
10901   (fully or partially) on the stack.  */
10902
10903static bool
10904rs6000_parm_needs_stack (cumulative_args_t args_so_far, tree type)
10905{
10906  machine_mode mode;
10907  int unsignedp;
10908  rtx entry_parm;
10909
10910  /* Catch errors.  */
10911  if (type == NULL || type == error_mark_node)
10912    return true;
10913
10914  /* Handle types with no storage requirement.  */
10915  if (TYPE_MODE (type) == VOIDmode)
10916    return false;
10917
10918  /* Handle complex types.  */
10919  if (TREE_CODE (type) == COMPLEX_TYPE)
10920    return (rs6000_parm_needs_stack (args_so_far, TREE_TYPE (type))
10921	    || rs6000_parm_needs_stack (args_so_far, TREE_TYPE (type)));
10922
10923  /* Handle transparent aggregates.  */
10924  if ((TREE_CODE (type) == UNION_TYPE || TREE_CODE (type) == RECORD_TYPE)
10925      && TYPE_TRANSPARENT_AGGR (type))
10926    type = TREE_TYPE (first_field (type));
10927
10928  /* See if this arg was passed by invisible reference.  */
10929  if (pass_by_reference (get_cumulative_args (args_so_far),
10930			 TYPE_MODE (type), type, true))
10931    type = build_pointer_type (type);
10932
10933  /* Find mode as it is passed by the ABI.  */
10934  unsignedp = TYPE_UNSIGNED (type);
10935  mode = promote_mode (type, TYPE_MODE (type), &unsignedp);
10936
10937  /* If we must pass in stack, we need a stack.  */
10938  if (rs6000_must_pass_in_stack (mode, type))
10939    return true;
10940
10941  /* If there is no incoming register, we need a stack.  */
10942  entry_parm = rs6000_function_arg (args_so_far, mode, type, true);
10943  if (entry_parm == NULL)
10944    return true;
10945
10946  /* Likewise if we need to pass both in registers and on the stack.  */
10947  if (GET_CODE (entry_parm) == PARALLEL
10948      && XEXP (XVECEXP (entry_parm, 0, 0), 0) == NULL_RTX)
10949    return true;
10950
10951  /* Also true if we're partially in registers and partially not.  */
10952  if (rs6000_arg_partial_bytes (args_so_far, mode, type, true) != 0)
10953    return true;
10954
10955  /* Update info on where next arg arrives in registers.  */
10956  rs6000_function_arg_advance (args_so_far, mode, type, true);
10957  return false;
10958}
10959
10960/* Return true if FUN has no prototype, has a variable argument
10961   list, or passes any parameter in memory.  */
10962
10963static bool
10964rs6000_function_parms_need_stack (tree fun, bool incoming)
10965{
10966  tree fntype, result;
10967  CUMULATIVE_ARGS args_so_far_v;
10968  cumulative_args_t args_so_far;
10969
10970  if (!fun)
10971    /* Must be a libcall, all of which only use reg parms.  */
10972    return false;
10973
10974  fntype = fun;
10975  if (!TYPE_P (fun))
10976    fntype = TREE_TYPE (fun);
10977
10978  /* Varargs functions need the parameter save area.  */
10979  if ((!incoming && !prototype_p (fntype)) || stdarg_p (fntype))
10980    return true;
10981
10982  INIT_CUMULATIVE_INCOMING_ARGS (args_so_far_v, fntype, NULL_RTX);
10983  args_so_far = pack_cumulative_args (&args_so_far_v);
10984
10985  /* When incoming, we will have been passed the function decl.
10986     It is necessary to use the decl to handle K&R style functions,
10987     where TYPE_ARG_TYPES may not be available.  */
10988  if (incoming)
10989    {
10990      gcc_assert (DECL_P (fun));
10991      result = DECL_RESULT (fun);
10992    }
10993  else
10994    result = TREE_TYPE (fntype);
10995
10996  if (result && aggregate_value_p (result, fntype))
10997    {
10998      if (!TYPE_P (result))
10999	result = TREE_TYPE (result);
11000      result = build_pointer_type (result);
11001      rs6000_parm_needs_stack (args_so_far, result);
11002    }
11003
11004  if (incoming)
11005    {
11006      tree parm;
11007
11008      for (parm = DECL_ARGUMENTS (fun);
11009	   parm && parm != void_list_node;
11010	   parm = TREE_CHAIN (parm))
11011	if (rs6000_parm_needs_stack (args_so_far, TREE_TYPE (parm)))
11012	  return true;
11013    }
11014  else
11015    {
11016      function_args_iterator args_iter;
11017      tree arg_type;
11018
11019      FOREACH_FUNCTION_ARGS (fntype, arg_type, args_iter)
11020	if (rs6000_parm_needs_stack (args_so_far, arg_type))
11021	  return true;
11022    }
11023
11024  return false;
11025}
11026
11027/* Return the size of the REG_PARM_STACK_SPACE are for FUN.  This is
11028   usually a constant depending on the ABI.  However, in the ELFv2 ABI
11029   the register parameter area is optional when calling a function that
11030   has a prototype is scope, has no variable argument list, and passes
11031   all parameters in registers.  */
11032
11033int
11034rs6000_reg_parm_stack_space (tree fun, bool incoming)
11035{
11036  int reg_parm_stack_space;
11037
11038  switch (DEFAULT_ABI)
11039    {
11040    default:
11041      reg_parm_stack_space = 0;
11042      break;
11043
11044    case ABI_AIX:
11045    case ABI_DARWIN:
11046      reg_parm_stack_space = TARGET_64BIT ? 64 : 32;
11047      break;
11048
11049    case ABI_ELFv2:
11050      /* ??? Recomputing this every time is a bit expensive.  Is there
11051	 a place to cache this information?  */
11052      if (rs6000_function_parms_need_stack (fun, incoming))
11053	reg_parm_stack_space = TARGET_64BIT ? 64 : 32;
11054      else
11055	reg_parm_stack_space = 0;
11056      break;
11057    }
11058
11059  return reg_parm_stack_space;
11060}
11061
11062static void
11063rs6000_move_block_from_reg (int regno, rtx x, int nregs)
11064{
11065  int i;
11066  machine_mode reg_mode = TARGET_32BIT ? SImode : DImode;
11067
11068  if (nregs == 0)
11069    return;
11070
11071  for (i = 0; i < nregs; i++)
11072    {
11073      rtx tem = adjust_address_nv (x, reg_mode, i * GET_MODE_SIZE (reg_mode));
11074      if (reload_completed)
11075	{
11076	  if (! strict_memory_address_p (reg_mode, XEXP (tem, 0)))
11077	    tem = NULL_RTX;
11078	  else
11079	    tem = simplify_gen_subreg (reg_mode, x, BLKmode,
11080				       i * GET_MODE_SIZE (reg_mode));
11081	}
11082      else
11083	tem = replace_equiv_address (tem, XEXP (tem, 0));
11084
11085      gcc_assert (tem);
11086
11087      emit_move_insn (tem, gen_rtx_REG (reg_mode, regno + i));
11088    }
11089}
11090
11091/* Perform any needed actions needed for a function that is receiving a
11092   variable number of arguments.
11093
11094   CUM is as above.
11095
11096   MODE and TYPE are the mode and type of the current parameter.
11097
11098   PRETEND_SIZE is a variable that should be set to the amount of stack
11099   that must be pushed by the prolog to pretend that our caller pushed
11100   it.
11101
11102   Normally, this macro will push all remaining incoming registers on the
11103   stack and set PRETEND_SIZE to the length of the registers pushed.  */
11104
11105static void
11106setup_incoming_varargs (cumulative_args_t cum, machine_mode mode,
11107			tree type, int *pretend_size ATTRIBUTE_UNUSED,
11108			int no_rtl)
11109{
11110  CUMULATIVE_ARGS next_cum;
11111  int reg_size = TARGET_32BIT ? 4 : 8;
11112  rtx save_area = NULL_RTX, mem;
11113  int first_reg_offset;
11114  alias_set_type set;
11115
11116  /* Skip the last named argument.  */
11117  next_cum = *get_cumulative_args (cum);
11118  rs6000_function_arg_advance_1 (&next_cum, mode, type, true, 0);
11119
11120  if (DEFAULT_ABI == ABI_V4)
11121    {
11122      first_reg_offset = next_cum.sysv_gregno - GP_ARG_MIN_REG;
11123
11124      if (! no_rtl)
11125	{
11126	  int gpr_reg_num = 0, gpr_size = 0, fpr_size = 0;
11127	  HOST_WIDE_INT offset = 0;
11128
11129	  /* Try to optimize the size of the varargs save area.
11130	     The ABI requires that ap.reg_save_area is doubleword
11131	     aligned, but we don't need to allocate space for all
11132	     the bytes, only those to which we actually will save
11133	     anything.  */
11134	  if (cfun->va_list_gpr_size && first_reg_offset < GP_ARG_NUM_REG)
11135	    gpr_reg_num = GP_ARG_NUM_REG - first_reg_offset;
11136	  if (TARGET_HARD_FLOAT && TARGET_FPRS
11137	      && next_cum.fregno <= FP_ARG_V4_MAX_REG
11138	      && cfun->va_list_fpr_size)
11139	    {
11140	      if (gpr_reg_num)
11141		fpr_size = (next_cum.fregno - FP_ARG_MIN_REG)
11142			   * UNITS_PER_FP_WORD;
11143	      if (cfun->va_list_fpr_size
11144		  < FP_ARG_V4_MAX_REG + 1 - next_cum.fregno)
11145		fpr_size += cfun->va_list_fpr_size * UNITS_PER_FP_WORD;
11146	      else
11147		fpr_size += (FP_ARG_V4_MAX_REG + 1 - next_cum.fregno)
11148			    * UNITS_PER_FP_WORD;
11149	    }
11150	  if (gpr_reg_num)
11151	    {
11152	      offset = -((first_reg_offset * reg_size) & ~7);
11153	      if (!fpr_size && gpr_reg_num > cfun->va_list_gpr_size)
11154		{
11155		  gpr_reg_num = cfun->va_list_gpr_size;
11156		  if (reg_size == 4 && (first_reg_offset & 1))
11157		    gpr_reg_num++;
11158		}
11159	      gpr_size = (gpr_reg_num * reg_size + 7) & ~7;
11160	    }
11161	  else if (fpr_size)
11162	    offset = - (int) (next_cum.fregno - FP_ARG_MIN_REG)
11163		       * UNITS_PER_FP_WORD
11164		     - (int) (GP_ARG_NUM_REG * reg_size);
11165
11166	  if (gpr_size + fpr_size)
11167	    {
11168	      rtx reg_save_area
11169		= assign_stack_local (BLKmode, gpr_size + fpr_size, 64);
11170	      gcc_assert (GET_CODE (reg_save_area) == MEM);
11171	      reg_save_area = XEXP (reg_save_area, 0);
11172	      if (GET_CODE (reg_save_area) == PLUS)
11173		{
11174		  gcc_assert (XEXP (reg_save_area, 0)
11175			      == virtual_stack_vars_rtx);
11176		  gcc_assert (GET_CODE (XEXP (reg_save_area, 1)) == CONST_INT);
11177		  offset += INTVAL (XEXP (reg_save_area, 1));
11178		}
11179	      else
11180		gcc_assert (reg_save_area == virtual_stack_vars_rtx);
11181	    }
11182
11183	  cfun->machine->varargs_save_offset = offset;
11184	  save_area = plus_constant (Pmode, virtual_stack_vars_rtx, offset);
11185	}
11186    }
11187  else
11188    {
11189      first_reg_offset = next_cum.words;
11190      save_area = virtual_incoming_args_rtx;
11191
11192      if (targetm.calls.must_pass_in_stack (mode, type))
11193	first_reg_offset += rs6000_arg_size (TYPE_MODE (type), type);
11194    }
11195
11196  set = get_varargs_alias_set ();
11197  if (! no_rtl && first_reg_offset < GP_ARG_NUM_REG
11198      && cfun->va_list_gpr_size)
11199    {
11200      int n_gpr, nregs = GP_ARG_NUM_REG - first_reg_offset;
11201
11202      if (va_list_gpr_counter_field)
11203	/* V4 va_list_gpr_size counts number of registers needed.  */
11204	n_gpr = cfun->va_list_gpr_size;
11205      else
11206	/* char * va_list instead counts number of bytes needed.  */
11207	n_gpr = (cfun->va_list_gpr_size + reg_size - 1) / reg_size;
11208
11209      if (nregs > n_gpr)
11210	nregs = n_gpr;
11211
11212      mem = gen_rtx_MEM (BLKmode,
11213			 plus_constant (Pmode, save_area,
11214					first_reg_offset * reg_size));
11215      MEM_NOTRAP_P (mem) = 1;
11216      set_mem_alias_set (mem, set);
11217      set_mem_align (mem, BITS_PER_WORD);
11218
11219      rs6000_move_block_from_reg (GP_ARG_MIN_REG + first_reg_offset, mem,
11220				  nregs);
11221    }
11222
11223  /* Save FP registers if needed.  */
11224  if (DEFAULT_ABI == ABI_V4
11225      && TARGET_HARD_FLOAT && TARGET_FPRS
11226      && ! no_rtl
11227      && next_cum.fregno <= FP_ARG_V4_MAX_REG
11228      && cfun->va_list_fpr_size)
11229    {
11230      int fregno = next_cum.fregno, nregs;
11231      rtx cr1 = gen_rtx_REG (CCmode, CR1_REGNO);
11232      rtx lab = gen_label_rtx ();
11233      int off = (GP_ARG_NUM_REG * reg_size) + ((fregno - FP_ARG_MIN_REG)
11234					       * UNITS_PER_FP_WORD);
11235
11236      emit_jump_insn
11237	(gen_rtx_SET (VOIDmode,
11238		      pc_rtx,
11239		      gen_rtx_IF_THEN_ELSE (VOIDmode,
11240					    gen_rtx_NE (VOIDmode, cr1,
11241							const0_rtx),
11242					    gen_rtx_LABEL_REF (VOIDmode, lab),
11243					    pc_rtx)));
11244
11245      for (nregs = 0;
11246	   fregno <= FP_ARG_V4_MAX_REG && nregs < cfun->va_list_fpr_size;
11247	   fregno++, off += UNITS_PER_FP_WORD, nregs++)
11248	{
11249	  mem = gen_rtx_MEM ((TARGET_HARD_FLOAT && TARGET_DOUBLE_FLOAT)
11250			      ? DFmode : SFmode,
11251                             plus_constant (Pmode, save_area, off));
11252  	  MEM_NOTRAP_P (mem) = 1;
11253  	  set_mem_alias_set (mem, set);
11254	  set_mem_align (mem, GET_MODE_ALIGNMENT (
11255			 (TARGET_HARD_FLOAT && TARGET_DOUBLE_FLOAT)
11256			  ? DFmode : SFmode));
11257	  emit_move_insn (mem, gen_rtx_REG (
11258                          (TARGET_HARD_FLOAT && TARGET_DOUBLE_FLOAT)
11259			   ? DFmode : SFmode, fregno));
11260	}
11261
11262      emit_label (lab);
11263    }
11264}
11265
11266/* Create the va_list data type.  */
11267
11268static tree
11269rs6000_build_builtin_va_list (void)
11270{
11271  tree f_gpr, f_fpr, f_res, f_ovf, f_sav, record, type_decl;
11272
11273  /* For AIX, prefer 'char *' because that's what the system
11274     header files like.  */
11275  if (DEFAULT_ABI != ABI_V4)
11276    return build_pointer_type (char_type_node);
11277
11278  record = (*lang_hooks.types.make_type) (RECORD_TYPE);
11279  type_decl = build_decl (BUILTINS_LOCATION, TYPE_DECL,
11280      			  get_identifier ("__va_list_tag"), record);
11281
11282  f_gpr = build_decl (BUILTINS_LOCATION, FIELD_DECL, get_identifier ("gpr"),
11283		      unsigned_char_type_node);
11284  f_fpr = build_decl (BUILTINS_LOCATION, FIELD_DECL, get_identifier ("fpr"),
11285		      unsigned_char_type_node);
11286  /* Give the two bytes of padding a name, so that -Wpadded won't warn on
11287     every user file.  */
11288  f_res = build_decl (BUILTINS_LOCATION, FIELD_DECL,
11289      		      get_identifier ("reserved"), short_unsigned_type_node);
11290  f_ovf = build_decl (BUILTINS_LOCATION, FIELD_DECL,
11291      		      get_identifier ("overflow_arg_area"),
11292		      ptr_type_node);
11293  f_sav = build_decl (BUILTINS_LOCATION, FIELD_DECL,
11294      		      get_identifier ("reg_save_area"),
11295		      ptr_type_node);
11296
11297  va_list_gpr_counter_field = f_gpr;
11298  va_list_fpr_counter_field = f_fpr;
11299
11300  DECL_FIELD_CONTEXT (f_gpr) = record;
11301  DECL_FIELD_CONTEXT (f_fpr) = record;
11302  DECL_FIELD_CONTEXT (f_res) = record;
11303  DECL_FIELD_CONTEXT (f_ovf) = record;
11304  DECL_FIELD_CONTEXT (f_sav) = record;
11305
11306  TYPE_STUB_DECL (record) = type_decl;
11307  TYPE_NAME (record) = type_decl;
11308  TYPE_FIELDS (record) = f_gpr;
11309  DECL_CHAIN (f_gpr) = f_fpr;
11310  DECL_CHAIN (f_fpr) = f_res;
11311  DECL_CHAIN (f_res) = f_ovf;
11312  DECL_CHAIN (f_ovf) = f_sav;
11313
11314  layout_type (record);
11315
11316  /* The correct type is an array type of one element.  */
11317  return build_array_type (record, build_index_type (size_zero_node));
11318}
11319
11320/* Implement va_start.  */
11321
11322static void
11323rs6000_va_start (tree valist, rtx nextarg)
11324{
11325  HOST_WIDE_INT words, n_gpr, n_fpr;
11326  tree f_gpr, f_fpr, f_res, f_ovf, f_sav;
11327  tree gpr, fpr, ovf, sav, t;
11328
11329  /* Only SVR4 needs something special.  */
11330  if (DEFAULT_ABI != ABI_V4)
11331    {
11332      std_expand_builtin_va_start (valist, nextarg);
11333      return;
11334    }
11335
11336  f_gpr = TYPE_FIELDS (TREE_TYPE (va_list_type_node));
11337  f_fpr = DECL_CHAIN (f_gpr);
11338  f_res = DECL_CHAIN (f_fpr);
11339  f_ovf = DECL_CHAIN (f_res);
11340  f_sav = DECL_CHAIN (f_ovf);
11341
11342  valist = build_simple_mem_ref (valist);
11343  gpr = build3 (COMPONENT_REF, TREE_TYPE (f_gpr), valist, f_gpr, NULL_TREE);
11344  fpr = build3 (COMPONENT_REF, TREE_TYPE (f_fpr), unshare_expr (valist),
11345		f_fpr, NULL_TREE);
11346  ovf = build3 (COMPONENT_REF, TREE_TYPE (f_ovf), unshare_expr (valist),
11347		f_ovf, NULL_TREE);
11348  sav = build3 (COMPONENT_REF, TREE_TYPE (f_sav), unshare_expr (valist),
11349		f_sav, NULL_TREE);
11350
11351  /* Count number of gp and fp argument registers used.  */
11352  words = crtl->args.info.words;
11353  n_gpr = MIN (crtl->args.info.sysv_gregno - GP_ARG_MIN_REG,
11354	       GP_ARG_NUM_REG);
11355  n_fpr = MIN (crtl->args.info.fregno - FP_ARG_MIN_REG,
11356	       FP_ARG_NUM_REG);
11357
11358  if (TARGET_DEBUG_ARG)
11359    fprintf (stderr, "va_start: words = "HOST_WIDE_INT_PRINT_DEC", n_gpr = "
11360	     HOST_WIDE_INT_PRINT_DEC", n_fpr = "HOST_WIDE_INT_PRINT_DEC"\n",
11361	     words, n_gpr, n_fpr);
11362
11363  if (cfun->va_list_gpr_size)
11364    {
11365      t = build2 (MODIFY_EXPR, TREE_TYPE (gpr), gpr,
11366		  build_int_cst (NULL_TREE, n_gpr));
11367      TREE_SIDE_EFFECTS (t) = 1;
11368      expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
11369    }
11370
11371  if (cfun->va_list_fpr_size)
11372    {
11373      t = build2 (MODIFY_EXPR, TREE_TYPE (fpr), fpr,
11374		  build_int_cst (NULL_TREE, n_fpr));
11375      TREE_SIDE_EFFECTS (t) = 1;
11376      expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
11377
11378#ifdef HAVE_AS_GNU_ATTRIBUTE
11379      if (call_ABI_of_interest (cfun->decl))
11380	rs6000_passes_float = true;
11381#endif
11382    }
11383
11384  /* Find the overflow area.  */
11385  t = make_tree (TREE_TYPE (ovf), virtual_incoming_args_rtx);
11386  if (words != 0)
11387    t = fold_build_pointer_plus_hwi (t, words * MIN_UNITS_PER_WORD);
11388  t = build2 (MODIFY_EXPR, TREE_TYPE (ovf), ovf, t);
11389  TREE_SIDE_EFFECTS (t) = 1;
11390  expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
11391
11392  /* If there were no va_arg invocations, don't set up the register
11393     save area.  */
11394  if (!cfun->va_list_gpr_size
11395      && !cfun->va_list_fpr_size
11396      && n_gpr < GP_ARG_NUM_REG
11397      && n_fpr < FP_ARG_V4_MAX_REG)
11398    return;
11399
11400  /* Find the register save area.  */
11401  t = make_tree (TREE_TYPE (sav), virtual_stack_vars_rtx);
11402  if (cfun->machine->varargs_save_offset)
11403    t = fold_build_pointer_plus_hwi (t, cfun->machine->varargs_save_offset);
11404  t = build2 (MODIFY_EXPR, TREE_TYPE (sav), sav, t);
11405  TREE_SIDE_EFFECTS (t) = 1;
11406  expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
11407}
11408
11409/* Implement va_arg.  */
11410
11411static tree
11412rs6000_gimplify_va_arg (tree valist, tree type, gimple_seq *pre_p,
11413			gimple_seq *post_p)
11414{
11415  tree f_gpr, f_fpr, f_res, f_ovf, f_sav;
11416  tree gpr, fpr, ovf, sav, reg, t, u;
11417  int size, rsize, n_reg, sav_ofs, sav_scale;
11418  tree lab_false, lab_over, addr;
11419  int align;
11420  tree ptrtype = build_pointer_type_for_mode (type, ptr_mode, true);
11421  int regalign = 0;
11422  gimple stmt;
11423
11424  if (pass_by_reference (NULL, TYPE_MODE (type), type, false))
11425    {
11426      t = rs6000_gimplify_va_arg (valist, ptrtype, pre_p, post_p);
11427      return build_va_arg_indirect_ref (t);
11428    }
11429
11430  /* We need to deal with the fact that the darwin ppc64 ABI is defined by an
11431     earlier version of gcc, with the property that it always applied alignment
11432     adjustments to the va-args (even for zero-sized types).  The cheapest way
11433     to deal with this is to replicate the effect of the part of
11434     std_gimplify_va_arg_expr that carries out the align adjust, for the case
11435     of relevance.
11436     We don't need to check for pass-by-reference because of the test above.
11437     We can return a simplifed answer, since we know there's no offset to add.  */
11438
11439  if (((TARGET_MACHO
11440        && rs6000_darwin64_abi)
11441       || DEFAULT_ABI == ABI_ELFv2
11442       || (DEFAULT_ABI == ABI_AIX && !rs6000_compat_align_parm))
11443      && integer_zerop (TYPE_SIZE (type)))
11444    {
11445      unsigned HOST_WIDE_INT align, boundary;
11446      tree valist_tmp = get_initialized_tmp_var (valist, pre_p, NULL);
11447      align = PARM_BOUNDARY / BITS_PER_UNIT;
11448      boundary = rs6000_function_arg_boundary (TYPE_MODE (type), type);
11449      if (boundary > MAX_SUPPORTED_STACK_ALIGNMENT)
11450	boundary = MAX_SUPPORTED_STACK_ALIGNMENT;
11451      boundary /= BITS_PER_UNIT;
11452      if (boundary > align)
11453	{
11454	  tree t ;
11455	  /* This updates arg ptr by the amount that would be necessary
11456	     to align the zero-sized (but not zero-alignment) item.  */
11457	  t = build2 (MODIFY_EXPR, TREE_TYPE (valist), valist_tmp,
11458		      fold_build_pointer_plus_hwi (valist_tmp, boundary - 1));
11459	  gimplify_and_add (t, pre_p);
11460
11461	  t = fold_convert (sizetype, valist_tmp);
11462	  t = build2 (MODIFY_EXPR, TREE_TYPE (valist), valist_tmp,
11463		  fold_convert (TREE_TYPE (valist),
11464				fold_build2 (BIT_AND_EXPR, sizetype, t,
11465					     size_int (-boundary))));
11466	  t = build2 (MODIFY_EXPR, TREE_TYPE (valist), valist, t);
11467	  gimplify_and_add (t, pre_p);
11468	}
11469      /* Since it is zero-sized there's no increment for the item itself. */
11470      valist_tmp = fold_convert (build_pointer_type (type), valist_tmp);
11471      return build_va_arg_indirect_ref (valist_tmp);
11472    }
11473
11474  if (DEFAULT_ABI != ABI_V4)
11475    {
11476      if (targetm.calls.split_complex_arg && TREE_CODE (type) == COMPLEX_TYPE)
11477	{
11478	  tree elem_type = TREE_TYPE (type);
11479	  machine_mode elem_mode = TYPE_MODE (elem_type);
11480	  int elem_size = GET_MODE_SIZE (elem_mode);
11481
11482	  if (elem_size < UNITS_PER_WORD)
11483	    {
11484	      tree real_part, imag_part;
11485	      gimple_seq post = NULL;
11486
11487	      real_part = rs6000_gimplify_va_arg (valist, elem_type, pre_p,
11488						  &post);
11489	      /* Copy the value into a temporary, lest the formal temporary
11490		 be reused out from under us.  */
11491	      real_part = get_initialized_tmp_var (real_part, pre_p, &post);
11492	      gimple_seq_add_seq (pre_p, post);
11493
11494	      imag_part = rs6000_gimplify_va_arg (valist, elem_type, pre_p,
11495						  post_p);
11496
11497	      return build2 (COMPLEX_EXPR, type, real_part, imag_part);
11498	    }
11499	}
11500
11501      return std_gimplify_va_arg_expr (valist, type, pre_p, post_p);
11502    }
11503
11504  f_gpr = TYPE_FIELDS (TREE_TYPE (va_list_type_node));
11505  f_fpr = DECL_CHAIN (f_gpr);
11506  f_res = DECL_CHAIN (f_fpr);
11507  f_ovf = DECL_CHAIN (f_res);
11508  f_sav = DECL_CHAIN (f_ovf);
11509
11510  valist = build_va_arg_indirect_ref (valist);
11511  gpr = build3 (COMPONENT_REF, TREE_TYPE (f_gpr), valist, f_gpr, NULL_TREE);
11512  fpr = build3 (COMPONENT_REF, TREE_TYPE (f_fpr), unshare_expr (valist),
11513		f_fpr, NULL_TREE);
11514  ovf = build3 (COMPONENT_REF, TREE_TYPE (f_ovf), unshare_expr (valist),
11515		f_ovf, NULL_TREE);
11516  sav = build3 (COMPONENT_REF, TREE_TYPE (f_sav), unshare_expr (valist),
11517		f_sav, NULL_TREE);
11518
11519  size = int_size_in_bytes (type);
11520  rsize = (size + 3) / 4;
11521  align = 1;
11522
11523  if (TARGET_HARD_FLOAT && TARGET_FPRS
11524      && ((TARGET_SINGLE_FLOAT && TYPE_MODE (type) == SFmode)
11525          || (TARGET_DOUBLE_FLOAT
11526              && (TYPE_MODE (type) == DFmode
11527 	          || TYPE_MODE (type) == TFmode
11528	          || TYPE_MODE (type) == SDmode
11529	          || TYPE_MODE (type) == DDmode
11530	          || TYPE_MODE (type) == TDmode))))
11531    {
11532      /* FP args go in FP registers, if present.  */
11533      reg = fpr;
11534      n_reg = (size + 7) / 8;
11535      sav_ofs = ((TARGET_HARD_FLOAT && TARGET_DOUBLE_FLOAT) ? 8 : 4) * 4;
11536      sav_scale = ((TARGET_HARD_FLOAT && TARGET_DOUBLE_FLOAT) ? 8 : 4);
11537      if (TYPE_MODE (type) != SFmode && TYPE_MODE (type) != SDmode)
11538	align = 8;
11539    }
11540  else
11541    {
11542      /* Otherwise into GP registers.  */
11543      reg = gpr;
11544      n_reg = rsize;
11545      sav_ofs = 0;
11546      sav_scale = 4;
11547      if (n_reg == 2)
11548	align = 8;
11549    }
11550
11551  /* Pull the value out of the saved registers....  */
11552
11553  lab_over = NULL;
11554  addr = create_tmp_var (ptr_type_node, "addr");
11555
11556  /*  AltiVec vectors never go in registers when -mabi=altivec.  */
11557  if (TARGET_ALTIVEC_ABI && ALTIVEC_VECTOR_MODE (TYPE_MODE (type)))
11558    align = 16;
11559  else
11560    {
11561      lab_false = create_artificial_label (input_location);
11562      lab_over = create_artificial_label (input_location);
11563
11564      /* Long long and SPE vectors are aligned in the registers.
11565	 As are any other 2 gpr item such as complex int due to a
11566	 historical mistake.  */
11567      u = reg;
11568      if (n_reg == 2 && reg == gpr)
11569	{
11570	  regalign = 1;
11571	  u = build2 (BIT_AND_EXPR, TREE_TYPE (reg), unshare_expr (reg),
11572		     build_int_cst (TREE_TYPE (reg), n_reg - 1));
11573	  u = build2 (POSTINCREMENT_EXPR, TREE_TYPE (reg),
11574		      unshare_expr (reg), u);
11575	}
11576      /* _Decimal128 is passed in even/odd fpr pairs; the stored
11577	 reg number is 0 for f1, so we want to make it odd.  */
11578      else if (reg == fpr && TYPE_MODE (type) == TDmode)
11579	{
11580	  t = build2 (BIT_IOR_EXPR, TREE_TYPE (reg), unshare_expr (reg),
11581		      build_int_cst (TREE_TYPE (reg), 1));
11582	  u = build2 (MODIFY_EXPR, void_type_node, unshare_expr (reg), t);
11583	}
11584
11585      t = fold_convert (TREE_TYPE (reg), size_int (8 - n_reg + 1));
11586      t = build2 (GE_EXPR, boolean_type_node, u, t);
11587      u = build1 (GOTO_EXPR, void_type_node, lab_false);
11588      t = build3 (COND_EXPR, void_type_node, t, u, NULL_TREE);
11589      gimplify_and_add (t, pre_p);
11590
11591      t = sav;
11592      if (sav_ofs)
11593	t = fold_build_pointer_plus_hwi (sav, sav_ofs);
11594
11595      u = build2 (POSTINCREMENT_EXPR, TREE_TYPE (reg), unshare_expr (reg),
11596		  build_int_cst (TREE_TYPE (reg), n_reg));
11597      u = fold_convert (sizetype, u);
11598      u = build2 (MULT_EXPR, sizetype, u, size_int (sav_scale));
11599      t = fold_build_pointer_plus (t, u);
11600
11601      /* _Decimal32 varargs are located in the second word of the 64-bit
11602	 FP register for 32-bit binaries.  */
11603      if (TARGET_32BIT
11604	  && TARGET_HARD_FLOAT && TARGET_FPRS
11605	  && TYPE_MODE (type) == SDmode)
11606	t = fold_build_pointer_plus_hwi (t, size);
11607
11608      gimplify_assign (addr, t, pre_p);
11609
11610      gimple_seq_add_stmt (pre_p, gimple_build_goto (lab_over));
11611
11612      stmt = gimple_build_label (lab_false);
11613      gimple_seq_add_stmt (pre_p, stmt);
11614
11615      if ((n_reg == 2 && !regalign) || n_reg > 2)
11616	{
11617	  /* Ensure that we don't find any more args in regs.
11618	     Alignment has taken care of for special cases.  */
11619	  gimplify_assign (reg, build_int_cst (TREE_TYPE (reg), 8), pre_p);
11620	}
11621    }
11622
11623  /* ... otherwise out of the overflow area.  */
11624
11625  /* Care for on-stack alignment if needed.  */
11626  t = ovf;
11627  if (align != 1)
11628    {
11629      t = fold_build_pointer_plus_hwi (t, align - 1);
11630      t = build2 (BIT_AND_EXPR, TREE_TYPE (t), t,
11631		  build_int_cst (TREE_TYPE (t), -align));
11632    }
11633  gimplify_expr (&t, pre_p, NULL, is_gimple_val, fb_rvalue);
11634
11635  gimplify_assign (unshare_expr (addr), t, pre_p);
11636
11637  t = fold_build_pointer_plus_hwi (t, size);
11638  gimplify_assign (unshare_expr (ovf), t, pre_p);
11639
11640  if (lab_over)
11641    {
11642      stmt = gimple_build_label (lab_over);
11643      gimple_seq_add_stmt (pre_p, stmt);
11644    }
11645
11646  if (STRICT_ALIGNMENT
11647      && (TYPE_ALIGN (type)
11648	  > (unsigned) BITS_PER_UNIT * (align < 4 ? 4 : align)))
11649    {
11650      /* The value (of type complex double, for example) may not be
11651	 aligned in memory in the saved registers, so copy via a
11652	 temporary.  (This is the same code as used for SPARC.)  */
11653      tree tmp = create_tmp_var (type, "va_arg_tmp");
11654      tree dest_addr = build_fold_addr_expr (tmp);
11655
11656      tree copy = build_call_expr (builtin_decl_implicit (BUILT_IN_MEMCPY),
11657				   3, dest_addr, addr, size_int (rsize * 4));
11658
11659      gimplify_and_add (copy, pre_p);
11660      addr = dest_addr;
11661    }
11662
11663  addr = fold_convert (ptrtype, addr);
11664  return build_va_arg_indirect_ref (addr);
11665}
11666
11667/* Builtins.  */
11668
11669static void
11670def_builtin (const char *name, tree type, enum rs6000_builtins code)
11671{
11672  tree t;
11673  unsigned classify = rs6000_builtin_info[(int)code].attr;
11674  const char *attr_string = "";
11675
11676  gcc_assert (name != NULL);
11677  gcc_assert (IN_RANGE ((int)code, 0, (int)RS6000_BUILTIN_COUNT));
11678
11679  if (rs6000_builtin_decls[(int)code])
11680    fatal_error (input_location,
11681		 "internal error: builtin function %s already processed", name);
11682
11683  rs6000_builtin_decls[(int)code] = t =
11684    add_builtin_function (name, type, (int)code, BUILT_IN_MD, NULL, NULL_TREE);
11685
11686  /* Set any special attributes.  */
11687  if ((classify & RS6000_BTC_CONST) != 0)
11688    {
11689      /* const function, function only depends on the inputs.  */
11690      TREE_READONLY (t) = 1;
11691      TREE_NOTHROW (t) = 1;
11692      attr_string = ", pure";
11693    }
11694  else if ((classify & RS6000_BTC_PURE) != 0)
11695    {
11696      /* pure function, function can read global memory, but does not set any
11697	 external state.  */
11698      DECL_PURE_P (t) = 1;
11699      TREE_NOTHROW (t) = 1;
11700      attr_string = ", const";
11701    }
11702  else if ((classify & RS6000_BTC_FP) != 0)
11703    {
11704      /* Function is a math function.  If rounding mode is on, then treat the
11705	 function as not reading global memory, but it can have arbitrary side
11706	 effects.  If it is off, then assume the function is a const function.
11707	 This mimics the ATTR_MATHFN_FPROUNDING attribute in
11708	 builtin-attribute.def that is used for the math functions. */
11709      TREE_NOTHROW (t) = 1;
11710      if (flag_rounding_math)
11711	{
11712	  DECL_PURE_P (t) = 1;
11713	  DECL_IS_NOVOPS (t) = 1;
11714	  attr_string = ", fp, pure";
11715	}
11716      else
11717	{
11718	  TREE_READONLY (t) = 1;
11719	  attr_string = ", fp, const";
11720	}
11721    }
11722  else if ((classify & RS6000_BTC_ATTR_MASK) != 0)
11723    gcc_unreachable ();
11724
11725  if (TARGET_DEBUG_BUILTIN)
11726    fprintf (stderr, "rs6000_builtin, code = %4d, %s%s\n",
11727	     (int)code, name, attr_string);
11728}
11729
11730/* Simple ternary operations: VECd = foo (VECa, VECb, VECc).  */
11731
11732#undef RS6000_BUILTIN_1
11733#undef RS6000_BUILTIN_2
11734#undef RS6000_BUILTIN_3
11735#undef RS6000_BUILTIN_A
11736#undef RS6000_BUILTIN_D
11737#undef RS6000_BUILTIN_E
11738#undef RS6000_BUILTIN_H
11739#undef RS6000_BUILTIN_P
11740#undef RS6000_BUILTIN_Q
11741#undef RS6000_BUILTIN_S
11742#undef RS6000_BUILTIN_X
11743
11744#define RS6000_BUILTIN_1(ENUM, NAME, MASK, ATTR, ICODE)
11745#define RS6000_BUILTIN_2(ENUM, NAME, MASK, ATTR, ICODE)
11746#define RS6000_BUILTIN_3(ENUM, NAME, MASK, ATTR, ICODE) \
11747  { MASK, ICODE, NAME, ENUM },
11748
11749#define RS6000_BUILTIN_A(ENUM, NAME, MASK, ATTR, ICODE)
11750#define RS6000_BUILTIN_D(ENUM, NAME, MASK, ATTR, ICODE)
11751#define RS6000_BUILTIN_E(ENUM, NAME, MASK, ATTR, ICODE)
11752#define RS6000_BUILTIN_H(ENUM, NAME, MASK, ATTR, ICODE)
11753#define RS6000_BUILTIN_P(ENUM, NAME, MASK, ATTR, ICODE)
11754#define RS6000_BUILTIN_Q(ENUM, NAME, MASK, ATTR, ICODE)
11755#define RS6000_BUILTIN_S(ENUM, NAME, MASK, ATTR, ICODE)
11756#define RS6000_BUILTIN_X(ENUM, NAME, MASK, ATTR, ICODE)
11757
11758static const struct builtin_description bdesc_3arg[] =
11759{
11760#include "rs6000-builtin.def"
11761};
11762
11763/* DST operations: void foo (void *, const int, const char).  */
11764
11765#undef RS6000_BUILTIN_1
11766#undef RS6000_BUILTIN_2
11767#undef RS6000_BUILTIN_3
11768#undef RS6000_BUILTIN_A
11769#undef RS6000_BUILTIN_D
11770#undef RS6000_BUILTIN_E
11771#undef RS6000_BUILTIN_H
11772#undef RS6000_BUILTIN_P
11773#undef RS6000_BUILTIN_Q
11774#undef RS6000_BUILTIN_S
11775#undef RS6000_BUILTIN_X
11776
11777#define RS6000_BUILTIN_1(ENUM, NAME, MASK, ATTR, ICODE)
11778#define RS6000_BUILTIN_2(ENUM, NAME, MASK, ATTR, ICODE)
11779#define RS6000_BUILTIN_3(ENUM, NAME, MASK, ATTR, ICODE)
11780#define RS6000_BUILTIN_A(ENUM, NAME, MASK, ATTR, ICODE)
11781#define RS6000_BUILTIN_D(ENUM, NAME, MASK, ATTR, ICODE) \
11782  { MASK, ICODE, NAME, ENUM },
11783
11784#define RS6000_BUILTIN_E(ENUM, NAME, MASK, ATTR, ICODE)
11785#define RS6000_BUILTIN_H(ENUM, NAME, MASK, ATTR, ICODE)
11786#define RS6000_BUILTIN_P(ENUM, NAME, MASK, ATTR, ICODE)
11787#define RS6000_BUILTIN_Q(ENUM, NAME, MASK, ATTR, ICODE)
11788#define RS6000_BUILTIN_S(ENUM, NAME, MASK, ATTR, ICODE)
11789#define RS6000_BUILTIN_X(ENUM, NAME, MASK, ATTR, ICODE)
11790
11791static const struct builtin_description bdesc_dst[] =
11792{
11793#include "rs6000-builtin.def"
11794};
11795
11796/* Simple binary operations: VECc = foo (VECa, VECb).  */
11797
11798#undef RS6000_BUILTIN_1
11799#undef RS6000_BUILTIN_2
11800#undef RS6000_BUILTIN_3
11801#undef RS6000_BUILTIN_A
11802#undef RS6000_BUILTIN_D
11803#undef RS6000_BUILTIN_E
11804#undef RS6000_BUILTIN_H
11805#undef RS6000_BUILTIN_P
11806#undef RS6000_BUILTIN_Q
11807#undef RS6000_BUILTIN_S
11808#undef RS6000_BUILTIN_X
11809
11810#define RS6000_BUILTIN_1(ENUM, NAME, MASK, ATTR, ICODE)
11811#define RS6000_BUILTIN_2(ENUM, NAME, MASK, ATTR, ICODE) \
11812  { MASK, ICODE, NAME, ENUM },
11813
11814#define RS6000_BUILTIN_3(ENUM, NAME, MASK, ATTR, ICODE)
11815#define RS6000_BUILTIN_A(ENUM, NAME, MASK, ATTR, ICODE)
11816#define RS6000_BUILTIN_D(ENUM, NAME, MASK, ATTR, ICODE)
11817#define RS6000_BUILTIN_E(ENUM, NAME, MASK, ATTR, ICODE)
11818#define RS6000_BUILTIN_H(ENUM, NAME, MASK, ATTR, ICODE)
11819#define RS6000_BUILTIN_P(ENUM, NAME, MASK, ATTR, ICODE)
11820#define RS6000_BUILTIN_Q(ENUM, NAME, MASK, ATTR, ICODE)
11821#define RS6000_BUILTIN_S(ENUM, NAME, MASK, ATTR, ICODE)
11822#define RS6000_BUILTIN_X(ENUM, NAME, MASK, ATTR, ICODE)
11823
11824static const struct builtin_description bdesc_2arg[] =
11825{
11826#include "rs6000-builtin.def"
11827};
11828
11829#undef RS6000_BUILTIN_1
11830#undef RS6000_BUILTIN_2
11831#undef RS6000_BUILTIN_3
11832#undef RS6000_BUILTIN_A
11833#undef RS6000_BUILTIN_D
11834#undef RS6000_BUILTIN_E
11835#undef RS6000_BUILTIN_H
11836#undef RS6000_BUILTIN_P
11837#undef RS6000_BUILTIN_Q
11838#undef RS6000_BUILTIN_S
11839#undef RS6000_BUILTIN_X
11840
11841#define RS6000_BUILTIN_1(ENUM, NAME, MASK, ATTR, ICODE)
11842#define RS6000_BUILTIN_2(ENUM, NAME, MASK, ATTR, ICODE)
11843#define RS6000_BUILTIN_3(ENUM, NAME, MASK, ATTR, ICODE)
11844#define RS6000_BUILTIN_A(ENUM, NAME, MASK, ATTR, ICODE)
11845#define RS6000_BUILTIN_D(ENUM, NAME, MASK, ATTR, ICODE)
11846#define RS6000_BUILTIN_E(ENUM, NAME, MASK, ATTR, ICODE)
11847#define RS6000_BUILTIN_H(ENUM, NAME, MASK, ATTR, ICODE)
11848#define RS6000_BUILTIN_P(ENUM, NAME, MASK, ATTR, ICODE) \
11849  { MASK, ICODE, NAME, ENUM },
11850
11851#define RS6000_BUILTIN_Q(ENUM, NAME, MASK, ATTR, ICODE)
11852#define RS6000_BUILTIN_S(ENUM, NAME, MASK, ATTR, ICODE)
11853#define RS6000_BUILTIN_X(ENUM, NAME, MASK, ATTR, ICODE)
11854
11855/* AltiVec predicates.  */
11856
11857static const struct builtin_description bdesc_altivec_preds[] =
11858{
11859#include "rs6000-builtin.def"
11860};
11861
11862/* SPE predicates.  */
11863#undef RS6000_BUILTIN_1
11864#undef RS6000_BUILTIN_2
11865#undef RS6000_BUILTIN_3
11866#undef RS6000_BUILTIN_A
11867#undef RS6000_BUILTIN_D
11868#undef RS6000_BUILTIN_E
11869#undef RS6000_BUILTIN_H
11870#undef RS6000_BUILTIN_P
11871#undef RS6000_BUILTIN_Q
11872#undef RS6000_BUILTIN_S
11873#undef RS6000_BUILTIN_X
11874
11875#define RS6000_BUILTIN_1(ENUM, NAME, MASK, ATTR, ICODE)
11876#define RS6000_BUILTIN_2(ENUM, NAME, MASK, ATTR, ICODE)
11877#define RS6000_BUILTIN_3(ENUM, NAME, MASK, ATTR, ICODE)
11878#define RS6000_BUILTIN_A(ENUM, NAME, MASK, ATTR, ICODE)
11879#define RS6000_BUILTIN_D(ENUM, NAME, MASK, ATTR, ICODE)
11880#define RS6000_BUILTIN_E(ENUM, NAME, MASK, ATTR, ICODE)
11881#define RS6000_BUILTIN_H(ENUM, NAME, MASK, ATTR, ICODE)
11882#define RS6000_BUILTIN_P(ENUM, NAME, MASK, ATTR, ICODE)
11883#define RS6000_BUILTIN_Q(ENUM, NAME, MASK, ATTR, ICODE)
11884#define RS6000_BUILTIN_S(ENUM, NAME, MASK, ATTR, ICODE) \
11885  { MASK, ICODE, NAME, ENUM },
11886
11887#define RS6000_BUILTIN_X(ENUM, NAME, MASK, ATTR, ICODE)
11888
11889static const struct builtin_description bdesc_spe_predicates[] =
11890{
11891#include "rs6000-builtin.def"
11892};
11893
11894/* SPE evsel predicates.  */
11895#undef RS6000_BUILTIN_1
11896#undef RS6000_BUILTIN_2
11897#undef RS6000_BUILTIN_3
11898#undef RS6000_BUILTIN_A
11899#undef RS6000_BUILTIN_D
11900#undef RS6000_BUILTIN_E
11901#undef RS6000_BUILTIN_H
11902#undef RS6000_BUILTIN_P
11903#undef RS6000_BUILTIN_Q
11904#undef RS6000_BUILTIN_S
11905#undef RS6000_BUILTIN_X
11906
11907#define RS6000_BUILTIN_1(ENUM, NAME, MASK, ATTR, ICODE)
11908#define RS6000_BUILTIN_2(ENUM, NAME, MASK, ATTR, ICODE)
11909#define RS6000_BUILTIN_3(ENUM, NAME, MASK, ATTR, ICODE)
11910#define RS6000_BUILTIN_A(ENUM, NAME, MASK, ATTR, ICODE)
11911#define RS6000_BUILTIN_D(ENUM, NAME, MASK, ATTR, ICODE)
11912#define RS6000_BUILTIN_E(ENUM, NAME, MASK, ATTR, ICODE) \
11913  { MASK, ICODE, NAME, ENUM },
11914
11915#define RS6000_BUILTIN_H(ENUM, NAME, MASK, ATTR, ICODE)
11916#define RS6000_BUILTIN_P(ENUM, NAME, MASK, ATTR, ICODE)
11917#define RS6000_BUILTIN_Q(ENUM, NAME, MASK, ATTR, ICODE)
11918#define RS6000_BUILTIN_S(ENUM, NAME, MASK, ATTR, ICODE)
11919#define RS6000_BUILTIN_X(ENUM, NAME, MASK, ATTR, ICODE)
11920
11921static const struct builtin_description bdesc_spe_evsel[] =
11922{
11923#include "rs6000-builtin.def"
11924};
11925
11926/* PAIRED predicates.  */
11927#undef RS6000_BUILTIN_1
11928#undef RS6000_BUILTIN_2
11929#undef RS6000_BUILTIN_3
11930#undef RS6000_BUILTIN_A
11931#undef RS6000_BUILTIN_D
11932#undef RS6000_BUILTIN_E
11933#undef RS6000_BUILTIN_H
11934#undef RS6000_BUILTIN_P
11935#undef RS6000_BUILTIN_Q
11936#undef RS6000_BUILTIN_S
11937#undef RS6000_BUILTIN_X
11938
11939#define RS6000_BUILTIN_1(ENUM, NAME, MASK, ATTR, ICODE)
11940#define RS6000_BUILTIN_2(ENUM, NAME, MASK, ATTR, ICODE)
11941#define RS6000_BUILTIN_3(ENUM, NAME, MASK, ATTR, ICODE)
11942#define RS6000_BUILTIN_A(ENUM, NAME, MASK, ATTR, ICODE)
11943#define RS6000_BUILTIN_D(ENUM, NAME, MASK, ATTR, ICODE)
11944#define RS6000_BUILTIN_E(ENUM, NAME, MASK, ATTR, ICODE)
11945#define RS6000_BUILTIN_H(ENUM, NAME, MASK, ATTR, ICODE)
11946#define RS6000_BUILTIN_P(ENUM, NAME, MASK, ATTR, ICODE)
11947#define RS6000_BUILTIN_Q(ENUM, NAME, MASK, ATTR, ICODE) \
11948  { MASK, ICODE, NAME, ENUM },
11949
11950#define RS6000_BUILTIN_S(ENUM, NAME, MASK, ATTR, ICODE)
11951#define RS6000_BUILTIN_X(ENUM, NAME, MASK, ATTR, ICODE)
11952
11953static const struct builtin_description bdesc_paired_preds[] =
11954{
11955#include "rs6000-builtin.def"
11956};
11957
11958/* ABS* operations.  */
11959
11960#undef RS6000_BUILTIN_1
11961#undef RS6000_BUILTIN_2
11962#undef RS6000_BUILTIN_3
11963#undef RS6000_BUILTIN_A
11964#undef RS6000_BUILTIN_D
11965#undef RS6000_BUILTIN_E
11966#undef RS6000_BUILTIN_H
11967#undef RS6000_BUILTIN_P
11968#undef RS6000_BUILTIN_Q
11969#undef RS6000_BUILTIN_S
11970#undef RS6000_BUILTIN_X
11971
11972#define RS6000_BUILTIN_1(ENUM, NAME, MASK, ATTR, ICODE)
11973#define RS6000_BUILTIN_2(ENUM, NAME, MASK, ATTR, ICODE)
11974#define RS6000_BUILTIN_3(ENUM, NAME, MASK, ATTR, ICODE)
11975#define RS6000_BUILTIN_A(ENUM, NAME, MASK, ATTR, ICODE) \
11976  { MASK, ICODE, NAME, ENUM },
11977
11978#define RS6000_BUILTIN_D(ENUM, NAME, MASK, ATTR, ICODE)
11979#define RS6000_BUILTIN_E(ENUM, NAME, MASK, ATTR, ICODE)
11980#define RS6000_BUILTIN_H(ENUM, NAME, MASK, ATTR, ICODE)
11981#define RS6000_BUILTIN_P(ENUM, NAME, MASK, ATTR, ICODE)
11982#define RS6000_BUILTIN_Q(ENUM, NAME, MASK, ATTR, ICODE)
11983#define RS6000_BUILTIN_S(ENUM, NAME, MASK, ATTR, ICODE)
11984#define RS6000_BUILTIN_X(ENUM, NAME, MASK, ATTR, ICODE)
11985
11986static const struct builtin_description bdesc_abs[] =
11987{
11988#include "rs6000-builtin.def"
11989};
11990
11991/* Simple unary operations: VECb = foo (unsigned literal) or VECb =
11992   foo (VECa).  */
11993
11994#undef RS6000_BUILTIN_1
11995#undef RS6000_BUILTIN_2
11996#undef RS6000_BUILTIN_3
11997#undef RS6000_BUILTIN_A
11998#undef RS6000_BUILTIN_D
11999#undef RS6000_BUILTIN_E
12000#undef RS6000_BUILTIN_H
12001#undef RS6000_BUILTIN_P
12002#undef RS6000_BUILTIN_Q
12003#undef RS6000_BUILTIN_S
12004#undef RS6000_BUILTIN_X
12005
12006#define RS6000_BUILTIN_1(ENUM, NAME, MASK, ATTR, ICODE) \
12007  { MASK, ICODE, NAME, ENUM },
12008
12009#define RS6000_BUILTIN_2(ENUM, NAME, MASK, ATTR, ICODE)
12010#define RS6000_BUILTIN_3(ENUM, NAME, MASK, ATTR, ICODE)
12011#define RS6000_BUILTIN_A(ENUM, NAME, MASK, ATTR, ICODE)
12012#define RS6000_BUILTIN_D(ENUM, NAME, MASK, ATTR, ICODE)
12013#define RS6000_BUILTIN_E(ENUM, NAME, MASK, ATTR, ICODE)
12014#define RS6000_BUILTIN_H(ENUM, NAME, MASK, ATTR, ICODE)
12015#define RS6000_BUILTIN_P(ENUM, NAME, MASK, ATTR, ICODE)
12016#define RS6000_BUILTIN_Q(ENUM, NAME, MASK, ATTR, ICODE)
12017#define RS6000_BUILTIN_S(ENUM, NAME, MASK, ATTR, ICODE)
12018#define RS6000_BUILTIN_X(ENUM, NAME, MASK, ATTR, ICODE)
12019
12020static const struct builtin_description bdesc_1arg[] =
12021{
12022#include "rs6000-builtin.def"
12023};
12024
12025/* HTM builtins.  */
12026#undef RS6000_BUILTIN_1
12027#undef RS6000_BUILTIN_2
12028#undef RS6000_BUILTIN_3
12029#undef RS6000_BUILTIN_A
12030#undef RS6000_BUILTIN_D
12031#undef RS6000_BUILTIN_E
12032#undef RS6000_BUILTIN_H
12033#undef RS6000_BUILTIN_P
12034#undef RS6000_BUILTIN_Q
12035#undef RS6000_BUILTIN_S
12036#undef RS6000_BUILTIN_X
12037
12038#define RS6000_BUILTIN_1(ENUM, NAME, MASK, ATTR, ICODE)
12039#define RS6000_BUILTIN_2(ENUM, NAME, MASK, ATTR, ICODE)
12040#define RS6000_BUILTIN_3(ENUM, NAME, MASK, ATTR, ICODE)
12041#define RS6000_BUILTIN_A(ENUM, NAME, MASK, ATTR, ICODE)
12042#define RS6000_BUILTIN_D(ENUM, NAME, MASK, ATTR, ICODE)
12043#define RS6000_BUILTIN_E(ENUM, NAME, MASK, ATTR, ICODE)
12044#define RS6000_BUILTIN_H(ENUM, NAME, MASK, ATTR, ICODE) \
12045  { MASK, ICODE, NAME, ENUM },
12046
12047#define RS6000_BUILTIN_P(ENUM, NAME, MASK, ATTR, ICODE)
12048#define RS6000_BUILTIN_Q(ENUM, NAME, MASK, ATTR, ICODE)
12049#define RS6000_BUILTIN_S(ENUM, NAME, MASK, ATTR, ICODE)
12050#define RS6000_BUILTIN_X(ENUM, NAME, MASK, ATTR, ICODE)
12051
12052static const struct builtin_description bdesc_htm[] =
12053{
12054#include "rs6000-builtin.def"
12055};
12056
12057#undef RS6000_BUILTIN_1
12058#undef RS6000_BUILTIN_2
12059#undef RS6000_BUILTIN_3
12060#undef RS6000_BUILTIN_A
12061#undef RS6000_BUILTIN_D
12062#undef RS6000_BUILTIN_E
12063#undef RS6000_BUILTIN_H
12064#undef RS6000_BUILTIN_P
12065#undef RS6000_BUILTIN_Q
12066#undef RS6000_BUILTIN_S
12067
12068/* Return true if a builtin function is overloaded.  */
12069bool
12070rs6000_overloaded_builtin_p (enum rs6000_builtins fncode)
12071{
12072  return (rs6000_builtin_info[(int)fncode].attr & RS6000_BTC_OVERLOADED) != 0;
12073}
12074
12075/* Expand an expression EXP that calls a builtin without arguments.  */
12076static rtx
12077rs6000_expand_zeroop_builtin (enum insn_code icode, rtx target)
12078{
12079  rtx pat;
12080  machine_mode tmode = insn_data[icode].operand[0].mode;
12081
12082  if (icode == CODE_FOR_nothing)
12083    /* Builtin not supported on this processor.  */
12084    return 0;
12085
12086  if (target == 0
12087      || GET_MODE (target) != tmode
12088      || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
12089    target = gen_reg_rtx (tmode);
12090
12091  pat = GEN_FCN (icode) (target);
12092  if (! pat)
12093    return 0;
12094  emit_insn (pat);
12095
12096  return target;
12097}
12098
12099
12100static rtx
12101rs6000_expand_mtfsf_builtin (enum insn_code icode, tree exp)
12102{
12103  rtx pat;
12104  tree arg0 = CALL_EXPR_ARG (exp, 0);
12105  tree arg1 = CALL_EXPR_ARG (exp, 1);
12106  rtx op0 = expand_normal (arg0);
12107  rtx op1 = expand_normal (arg1);
12108  machine_mode mode0 = insn_data[icode].operand[0].mode;
12109  machine_mode mode1 = insn_data[icode].operand[1].mode;
12110
12111  if (icode == CODE_FOR_nothing)
12112    /* Builtin not supported on this processor.  */
12113    return 0;
12114
12115  /* If we got invalid arguments bail out before generating bad rtl.  */
12116  if (arg0 == error_mark_node || arg1 == error_mark_node)
12117    return const0_rtx;
12118
12119  if (GET_CODE (op0) != CONST_INT
12120      || INTVAL (op0) > 255
12121      || INTVAL (op0) < 0)
12122    {
12123      error ("argument 1 must be an 8-bit field value");
12124      return const0_rtx;
12125    }
12126
12127  if (! (*insn_data[icode].operand[0].predicate) (op0, mode0))
12128    op0 = copy_to_mode_reg (mode0, op0);
12129
12130  if (! (*insn_data[icode].operand[1].predicate) (op1, mode1))
12131    op1 = copy_to_mode_reg (mode1, op1);
12132
12133  pat = GEN_FCN (icode) (op0, op1);
12134  if (! pat)
12135    return const0_rtx;
12136  emit_insn (pat);
12137
12138  return NULL_RTX;
12139}
12140
12141
12142static rtx
12143rs6000_expand_unop_builtin (enum insn_code icode, tree exp, rtx target)
12144{
12145  rtx pat;
12146  tree arg0 = CALL_EXPR_ARG (exp, 0);
12147  rtx op0 = expand_normal (arg0);
12148  machine_mode tmode = insn_data[icode].operand[0].mode;
12149  machine_mode mode0 = insn_data[icode].operand[1].mode;
12150
12151  if (icode == CODE_FOR_nothing)
12152    /* Builtin not supported on this processor.  */
12153    return 0;
12154
12155  /* If we got invalid arguments bail out before generating bad rtl.  */
12156  if (arg0 == error_mark_node)
12157    return const0_rtx;
12158
12159  if (icode == CODE_FOR_altivec_vspltisb
12160      || icode == CODE_FOR_altivec_vspltish
12161      || icode == CODE_FOR_altivec_vspltisw
12162      || icode == CODE_FOR_spe_evsplatfi
12163      || icode == CODE_FOR_spe_evsplati)
12164    {
12165      /* Only allow 5-bit *signed* literals.  */
12166      if (GET_CODE (op0) != CONST_INT
12167	  || INTVAL (op0) > 15
12168	  || INTVAL (op0) < -16)
12169	{
12170	  error ("argument 1 must be a 5-bit signed literal");
12171	  return const0_rtx;
12172	}
12173    }
12174
12175  if (target == 0
12176      || GET_MODE (target) != tmode
12177      || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
12178    target = gen_reg_rtx (tmode);
12179
12180  if (! (*insn_data[icode].operand[1].predicate) (op0, mode0))
12181    op0 = copy_to_mode_reg (mode0, op0);
12182
12183  pat = GEN_FCN (icode) (target, op0);
12184  if (! pat)
12185    return 0;
12186  emit_insn (pat);
12187
12188  return target;
12189}
12190
12191static rtx
12192altivec_expand_abs_builtin (enum insn_code icode, tree exp, rtx target)
12193{
12194  rtx pat, scratch1, scratch2;
12195  tree arg0 = CALL_EXPR_ARG (exp, 0);
12196  rtx op0 = expand_normal (arg0);
12197  machine_mode tmode = insn_data[icode].operand[0].mode;
12198  machine_mode mode0 = insn_data[icode].operand[1].mode;
12199
12200  /* If we have invalid arguments, bail out before generating bad rtl.  */
12201  if (arg0 == error_mark_node)
12202    return const0_rtx;
12203
12204  if (target == 0
12205      || GET_MODE (target) != tmode
12206      || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
12207    target = gen_reg_rtx (tmode);
12208
12209  if (! (*insn_data[icode].operand[1].predicate) (op0, mode0))
12210    op0 = copy_to_mode_reg (mode0, op0);
12211
12212  scratch1 = gen_reg_rtx (mode0);
12213  scratch2 = gen_reg_rtx (mode0);
12214
12215  pat = GEN_FCN (icode) (target, op0, scratch1, scratch2);
12216  if (! pat)
12217    return 0;
12218  emit_insn (pat);
12219
12220  return target;
12221}
12222
12223static rtx
12224rs6000_expand_binop_builtin (enum insn_code icode, tree exp, rtx target)
12225{
12226  rtx pat;
12227  tree arg0 = CALL_EXPR_ARG (exp, 0);
12228  tree arg1 = CALL_EXPR_ARG (exp, 1);
12229  rtx op0 = expand_normal (arg0);
12230  rtx op1 = expand_normal (arg1);
12231  machine_mode tmode = insn_data[icode].operand[0].mode;
12232  machine_mode mode0 = insn_data[icode].operand[1].mode;
12233  machine_mode mode1 = insn_data[icode].operand[2].mode;
12234
12235  if (icode == CODE_FOR_nothing)
12236    /* Builtin not supported on this processor.  */
12237    return 0;
12238
12239  /* If we got invalid arguments bail out before generating bad rtl.  */
12240  if (arg0 == error_mark_node || arg1 == error_mark_node)
12241    return const0_rtx;
12242
12243  if (icode == CODE_FOR_altivec_vcfux
12244      || icode == CODE_FOR_altivec_vcfsx
12245      || icode == CODE_FOR_altivec_vctsxs
12246      || icode == CODE_FOR_altivec_vctuxs
12247      || icode == CODE_FOR_altivec_vspltb
12248      || icode == CODE_FOR_altivec_vsplth
12249      || icode == CODE_FOR_altivec_vspltw
12250      || icode == CODE_FOR_spe_evaddiw
12251      || icode == CODE_FOR_spe_evldd
12252      || icode == CODE_FOR_spe_evldh
12253      || icode == CODE_FOR_spe_evldw
12254      || icode == CODE_FOR_spe_evlhhesplat
12255      || icode == CODE_FOR_spe_evlhhossplat
12256      || icode == CODE_FOR_spe_evlhhousplat
12257      || icode == CODE_FOR_spe_evlwhe
12258      || icode == CODE_FOR_spe_evlwhos
12259      || icode == CODE_FOR_spe_evlwhou
12260      || icode == CODE_FOR_spe_evlwhsplat
12261      || icode == CODE_FOR_spe_evlwwsplat
12262      || icode == CODE_FOR_spe_evrlwi
12263      || icode == CODE_FOR_spe_evslwi
12264      || icode == CODE_FOR_spe_evsrwis
12265      || icode == CODE_FOR_spe_evsubifw
12266      || icode == CODE_FOR_spe_evsrwiu)
12267    {
12268      /* Only allow 5-bit unsigned literals.  */
12269      STRIP_NOPS (arg1);
12270      if (TREE_CODE (arg1) != INTEGER_CST
12271	  || TREE_INT_CST_LOW (arg1) & ~0x1f)
12272	{
12273	  error ("argument 2 must be a 5-bit unsigned literal");
12274	  return const0_rtx;
12275	}
12276    }
12277
12278  if (target == 0
12279      || GET_MODE (target) != tmode
12280      || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
12281    target = gen_reg_rtx (tmode);
12282
12283  if (! (*insn_data[icode].operand[1].predicate) (op0, mode0))
12284    op0 = copy_to_mode_reg (mode0, op0);
12285  if (! (*insn_data[icode].operand[2].predicate) (op1, mode1))
12286    op1 = copy_to_mode_reg (mode1, op1);
12287
12288  pat = GEN_FCN (icode) (target, op0, op1);
12289  if (! pat)
12290    return 0;
12291  emit_insn (pat);
12292
12293  return target;
12294}
12295
12296static rtx
12297altivec_expand_predicate_builtin (enum insn_code icode, tree exp, rtx target)
12298{
12299  rtx pat, scratch;
12300  tree cr6_form = CALL_EXPR_ARG (exp, 0);
12301  tree arg0 = CALL_EXPR_ARG (exp, 1);
12302  tree arg1 = CALL_EXPR_ARG (exp, 2);
12303  rtx op0 = expand_normal (arg0);
12304  rtx op1 = expand_normal (arg1);
12305  machine_mode tmode = SImode;
12306  machine_mode mode0 = insn_data[icode].operand[1].mode;
12307  machine_mode mode1 = insn_data[icode].operand[2].mode;
12308  int cr6_form_int;
12309
12310  if (TREE_CODE (cr6_form) != INTEGER_CST)
12311    {
12312      error ("argument 1 of __builtin_altivec_predicate must be a constant");
12313      return const0_rtx;
12314    }
12315  else
12316    cr6_form_int = TREE_INT_CST_LOW (cr6_form);
12317
12318  gcc_assert (mode0 == mode1);
12319
12320  /* If we have invalid arguments, bail out before generating bad rtl.  */
12321  if (arg0 == error_mark_node || arg1 == error_mark_node)
12322    return const0_rtx;
12323
12324  if (target == 0
12325      || GET_MODE (target) != tmode
12326      || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
12327    target = gen_reg_rtx (tmode);
12328
12329  if (! (*insn_data[icode].operand[1].predicate) (op0, mode0))
12330    op0 = copy_to_mode_reg (mode0, op0);
12331  if (! (*insn_data[icode].operand[2].predicate) (op1, mode1))
12332    op1 = copy_to_mode_reg (mode1, op1);
12333
12334  scratch = gen_reg_rtx (mode0);
12335
12336  pat = GEN_FCN (icode) (scratch, op0, op1);
12337  if (! pat)
12338    return 0;
12339  emit_insn (pat);
12340
12341  /* The vec_any* and vec_all* predicates use the same opcodes for two
12342     different operations, but the bits in CR6 will be different
12343     depending on what information we want.  So we have to play tricks
12344     with CR6 to get the right bits out.
12345
12346     If you think this is disgusting, look at the specs for the
12347     AltiVec predicates.  */
12348
12349  switch (cr6_form_int)
12350    {
12351    case 0:
12352      emit_insn (gen_cr6_test_for_zero (target));
12353      break;
12354    case 1:
12355      emit_insn (gen_cr6_test_for_zero_reverse (target));
12356      break;
12357    case 2:
12358      emit_insn (gen_cr6_test_for_lt (target));
12359      break;
12360    case 3:
12361      emit_insn (gen_cr6_test_for_lt_reverse (target));
12362      break;
12363    default:
12364      error ("argument 1 of __builtin_altivec_predicate is out of range");
12365      break;
12366    }
12367
12368  return target;
12369}
12370
12371static rtx
12372paired_expand_lv_builtin (enum insn_code icode, tree exp, rtx target)
12373{
12374  rtx pat, addr;
12375  tree arg0 = CALL_EXPR_ARG (exp, 0);
12376  tree arg1 = CALL_EXPR_ARG (exp, 1);
12377  machine_mode tmode = insn_data[icode].operand[0].mode;
12378  machine_mode mode0 = Pmode;
12379  machine_mode mode1 = Pmode;
12380  rtx op0 = expand_normal (arg0);
12381  rtx op1 = expand_normal (arg1);
12382
12383  if (icode == CODE_FOR_nothing)
12384    /* Builtin not supported on this processor.  */
12385    return 0;
12386
12387  /* If we got invalid arguments bail out before generating bad rtl.  */
12388  if (arg0 == error_mark_node || arg1 == error_mark_node)
12389    return const0_rtx;
12390
12391  if (target == 0
12392      || GET_MODE (target) != tmode
12393      || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
12394    target = gen_reg_rtx (tmode);
12395
12396  op1 = copy_to_mode_reg (mode1, op1);
12397
12398  if (op0 == const0_rtx)
12399    {
12400      addr = gen_rtx_MEM (tmode, op1);
12401    }
12402  else
12403    {
12404      op0 = copy_to_mode_reg (mode0, op0);
12405      addr = gen_rtx_MEM (tmode, gen_rtx_PLUS (Pmode, op0, op1));
12406    }
12407
12408  pat = GEN_FCN (icode) (target, addr);
12409
12410  if (! pat)
12411    return 0;
12412  emit_insn (pat);
12413
12414  return target;
12415}
12416
12417/* Return a constant vector for use as a little-endian permute control vector
12418   to reverse the order of elements of the given vector mode.  */
12419static rtx
12420swap_selector_for_mode (machine_mode mode)
12421{
12422  /* These are little endian vectors, so their elements are reversed
12423     from what you would normally expect for a permute control vector.  */
12424  unsigned int swap2[16] = {7,6,5,4,3,2,1,0,15,14,13,12,11,10,9,8};
12425  unsigned int swap4[16] = {3,2,1,0,7,6,5,4,11,10,9,8,15,14,13,12};
12426  unsigned int swap8[16] = {1,0,3,2,5,4,7,6,9,8,11,10,13,12,15,14};
12427  unsigned int swap16[16] = {0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15};
12428  unsigned int *swaparray, i;
12429  rtx perm[16];
12430
12431  switch (mode)
12432    {
12433    case V2DFmode:
12434    case V2DImode:
12435      swaparray = swap2;
12436      break;
12437    case V4SFmode:
12438    case V4SImode:
12439      swaparray = swap4;
12440      break;
12441    case V8HImode:
12442      swaparray = swap8;
12443      break;
12444    case V16QImode:
12445      swaparray = swap16;
12446      break;
12447    default:
12448      gcc_unreachable ();
12449    }
12450
12451  for (i = 0; i < 16; ++i)
12452    perm[i] = GEN_INT (swaparray[i]);
12453
12454  return force_reg (V16QImode, gen_rtx_CONST_VECTOR (V16QImode, gen_rtvec_v (16, perm)));
12455}
12456
12457/* Generate code for an "lvx", "lvxl", or "lve*x" built-in for a little endian target
12458   with -maltivec=be specified.  Issue the load followed by an element-reversing
12459   permute.  */
12460void
12461altivec_expand_lvx_be (rtx op0, rtx op1, machine_mode mode, unsigned unspec)
12462{
12463  rtx tmp = gen_reg_rtx (mode);
12464  rtx load = gen_rtx_SET (VOIDmode, tmp, op1);
12465  rtx lvx = gen_rtx_UNSPEC (mode, gen_rtvec (1, const0_rtx), unspec);
12466  rtx par = gen_rtx_PARALLEL (mode, gen_rtvec (2, load, lvx));
12467  rtx sel = swap_selector_for_mode (mode);
12468  rtx vperm = gen_rtx_UNSPEC (mode, gen_rtvec (3, tmp, tmp, sel), UNSPEC_VPERM);
12469
12470  gcc_assert (REG_P (op0));
12471  emit_insn (par);
12472  emit_insn (gen_rtx_SET (VOIDmode, op0, vperm));
12473}
12474
12475/* Generate code for a "stvx" or "stvxl" built-in for a little endian target
12476   with -maltivec=be specified.  Issue the store preceded by an element-reversing
12477   permute.  */
12478void
12479altivec_expand_stvx_be (rtx op0, rtx op1, machine_mode mode, unsigned unspec)
12480{
12481  rtx tmp = gen_reg_rtx (mode);
12482  rtx store = gen_rtx_SET (VOIDmode, op0, tmp);
12483  rtx stvx = gen_rtx_UNSPEC (mode, gen_rtvec (1, const0_rtx), unspec);
12484  rtx par = gen_rtx_PARALLEL (mode, gen_rtvec (2, store, stvx));
12485  rtx sel = swap_selector_for_mode (mode);
12486  rtx vperm;
12487
12488  gcc_assert (REG_P (op1));
12489  vperm = gen_rtx_UNSPEC (mode, gen_rtvec (3, op1, op1, sel), UNSPEC_VPERM);
12490  emit_insn (gen_rtx_SET (VOIDmode, tmp, vperm));
12491  emit_insn (par);
12492}
12493
12494/* Generate code for a "stve*x" built-in for a little endian target with -maltivec=be
12495   specified.  Issue the store preceded by an element-reversing permute.  */
12496void
12497altivec_expand_stvex_be (rtx op0, rtx op1, machine_mode mode, unsigned unspec)
12498{
12499  machine_mode inner_mode = GET_MODE_INNER (mode);
12500  rtx tmp = gen_reg_rtx (mode);
12501  rtx stvx = gen_rtx_UNSPEC (inner_mode, gen_rtvec (1, tmp), unspec);
12502  rtx sel = swap_selector_for_mode (mode);
12503  rtx vperm;
12504
12505  gcc_assert (REG_P (op1));
12506  vperm = gen_rtx_UNSPEC (mode, gen_rtvec (3, op1, op1, sel), UNSPEC_VPERM);
12507  emit_insn (gen_rtx_SET (VOIDmode, tmp, vperm));
12508  emit_insn (gen_rtx_SET (VOIDmode, op0, stvx));
12509}
12510
12511static rtx
12512altivec_expand_lv_builtin (enum insn_code icode, tree exp, rtx target, bool blk)
12513{
12514  rtx pat, addr;
12515  tree arg0 = CALL_EXPR_ARG (exp, 0);
12516  tree arg1 = CALL_EXPR_ARG (exp, 1);
12517  machine_mode tmode = insn_data[icode].operand[0].mode;
12518  machine_mode mode0 = Pmode;
12519  machine_mode mode1 = Pmode;
12520  rtx op0 = expand_normal (arg0);
12521  rtx op1 = expand_normal (arg1);
12522
12523  if (icode == CODE_FOR_nothing)
12524    /* Builtin not supported on this processor.  */
12525    return 0;
12526
12527  /* If we got invalid arguments bail out before generating bad rtl.  */
12528  if (arg0 == error_mark_node || arg1 == error_mark_node)
12529    return const0_rtx;
12530
12531  if (target == 0
12532      || GET_MODE (target) != tmode
12533      || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
12534    target = gen_reg_rtx (tmode);
12535
12536  op1 = copy_to_mode_reg (mode1, op1);
12537
12538  if (op0 == const0_rtx)
12539    {
12540      addr = gen_rtx_MEM (blk ? BLKmode : tmode, op1);
12541    }
12542  else
12543    {
12544      op0 = copy_to_mode_reg (mode0, op0);
12545      addr = gen_rtx_MEM (blk ? BLKmode : tmode, gen_rtx_PLUS (Pmode, op0, op1));
12546    }
12547
12548  pat = GEN_FCN (icode) (target, addr);
12549
12550  if (! pat)
12551    return 0;
12552  emit_insn (pat);
12553
12554  return target;
12555}
12556
12557static rtx
12558spe_expand_stv_builtin (enum insn_code icode, tree exp)
12559{
12560  tree arg0 = CALL_EXPR_ARG (exp, 0);
12561  tree arg1 = CALL_EXPR_ARG (exp, 1);
12562  tree arg2 = CALL_EXPR_ARG (exp, 2);
12563  rtx op0 = expand_normal (arg0);
12564  rtx op1 = expand_normal (arg1);
12565  rtx op2 = expand_normal (arg2);
12566  rtx pat;
12567  machine_mode mode0 = insn_data[icode].operand[0].mode;
12568  machine_mode mode1 = insn_data[icode].operand[1].mode;
12569  machine_mode mode2 = insn_data[icode].operand[2].mode;
12570
12571  /* Invalid arguments.  Bail before doing anything stoopid!  */
12572  if (arg0 == error_mark_node
12573      || arg1 == error_mark_node
12574      || arg2 == error_mark_node)
12575    return const0_rtx;
12576
12577  if (! (*insn_data[icode].operand[2].predicate) (op0, mode2))
12578    op0 = copy_to_mode_reg (mode2, op0);
12579  if (! (*insn_data[icode].operand[0].predicate) (op1, mode0))
12580    op1 = copy_to_mode_reg (mode0, op1);
12581  if (! (*insn_data[icode].operand[1].predicate) (op2, mode1))
12582    op2 = copy_to_mode_reg (mode1, op2);
12583
12584  pat = GEN_FCN (icode) (op1, op2, op0);
12585  if (pat)
12586    emit_insn (pat);
12587  return NULL_RTX;
12588}
12589
12590static rtx
12591paired_expand_stv_builtin (enum insn_code icode, tree exp)
12592{
12593  tree arg0 = CALL_EXPR_ARG (exp, 0);
12594  tree arg1 = CALL_EXPR_ARG (exp, 1);
12595  tree arg2 = CALL_EXPR_ARG (exp, 2);
12596  rtx op0 = expand_normal (arg0);
12597  rtx op1 = expand_normal (arg1);
12598  rtx op2 = expand_normal (arg2);
12599  rtx pat, addr;
12600  machine_mode tmode = insn_data[icode].operand[0].mode;
12601  machine_mode mode1 = Pmode;
12602  machine_mode mode2 = Pmode;
12603
12604  /* Invalid arguments.  Bail before doing anything stoopid!  */
12605  if (arg0 == error_mark_node
12606      || arg1 == error_mark_node
12607      || arg2 == error_mark_node)
12608    return const0_rtx;
12609
12610  if (! (*insn_data[icode].operand[1].predicate) (op0, tmode))
12611    op0 = copy_to_mode_reg (tmode, op0);
12612
12613  op2 = copy_to_mode_reg (mode2, op2);
12614
12615  if (op1 == const0_rtx)
12616    {
12617      addr = gen_rtx_MEM (tmode, op2);
12618    }
12619  else
12620    {
12621      op1 = copy_to_mode_reg (mode1, op1);
12622      addr = gen_rtx_MEM (tmode, gen_rtx_PLUS (Pmode, op1, op2));
12623    }
12624
12625  pat = GEN_FCN (icode) (addr, op0);
12626  if (pat)
12627    emit_insn (pat);
12628  return NULL_RTX;
12629}
12630
12631static rtx
12632altivec_expand_stv_builtin (enum insn_code icode, tree exp)
12633{
12634  tree arg0 = CALL_EXPR_ARG (exp, 0);
12635  tree arg1 = CALL_EXPR_ARG (exp, 1);
12636  tree arg2 = CALL_EXPR_ARG (exp, 2);
12637  rtx op0 = expand_normal (arg0);
12638  rtx op1 = expand_normal (arg1);
12639  rtx op2 = expand_normal (arg2);
12640  rtx pat, addr;
12641  machine_mode tmode = insn_data[icode].operand[0].mode;
12642  machine_mode smode = insn_data[icode].operand[1].mode;
12643  machine_mode mode1 = Pmode;
12644  machine_mode mode2 = Pmode;
12645
12646  /* Invalid arguments.  Bail before doing anything stoopid!  */
12647  if (arg0 == error_mark_node
12648      || arg1 == error_mark_node
12649      || arg2 == error_mark_node)
12650    return const0_rtx;
12651
12652  if (! (*insn_data[icode].operand[1].predicate) (op0, smode))
12653    op0 = copy_to_mode_reg (smode, op0);
12654
12655  op2 = copy_to_mode_reg (mode2, op2);
12656
12657  if (op1 == const0_rtx)
12658    {
12659      addr = gen_rtx_MEM (tmode, op2);
12660    }
12661  else
12662    {
12663      op1 = copy_to_mode_reg (mode1, op1);
12664      addr = gen_rtx_MEM (tmode, gen_rtx_PLUS (Pmode, op1, op2));
12665    }
12666
12667  pat = GEN_FCN (icode) (addr, op0);
12668  if (pat)
12669    emit_insn (pat);
12670  return NULL_RTX;
12671}
12672
12673/* Return the appropriate SPR number associated with the given builtin.  */
12674static inline HOST_WIDE_INT
12675htm_spr_num (enum rs6000_builtins code)
12676{
12677  if (code == HTM_BUILTIN_GET_TFHAR
12678      || code == HTM_BUILTIN_SET_TFHAR)
12679    return TFHAR_SPR;
12680  else if (code == HTM_BUILTIN_GET_TFIAR
12681	   || code == HTM_BUILTIN_SET_TFIAR)
12682    return TFIAR_SPR;
12683  else if (code == HTM_BUILTIN_GET_TEXASR
12684	   || code == HTM_BUILTIN_SET_TEXASR)
12685    return TEXASR_SPR;
12686  gcc_assert (code == HTM_BUILTIN_GET_TEXASRU
12687	      || code == HTM_BUILTIN_SET_TEXASRU);
12688  return TEXASRU_SPR;
12689}
12690
12691/* Return the appropriate SPR regno associated with the given builtin.  */
12692static inline HOST_WIDE_INT
12693htm_spr_regno (enum rs6000_builtins code)
12694{
12695  if (code == HTM_BUILTIN_GET_TFHAR
12696      || code == HTM_BUILTIN_SET_TFHAR)
12697    return TFHAR_REGNO;
12698  else if (code == HTM_BUILTIN_GET_TFIAR
12699	   || code == HTM_BUILTIN_SET_TFIAR)
12700    return TFIAR_REGNO;
12701  gcc_assert (code == HTM_BUILTIN_GET_TEXASR
12702	      || code == HTM_BUILTIN_SET_TEXASR
12703	      || code == HTM_BUILTIN_GET_TEXASRU
12704	      || code == HTM_BUILTIN_SET_TEXASRU);
12705  return TEXASR_REGNO;
12706}
12707
12708/* Return the correct ICODE value depending on whether we are
12709   setting or reading the HTM SPRs.  */
12710static inline enum insn_code
12711rs6000_htm_spr_icode (bool nonvoid)
12712{
12713  if (nonvoid)
12714    return (TARGET_POWERPC64) ? CODE_FOR_htm_mfspr_di : CODE_FOR_htm_mfspr_si;
12715  else
12716    return (TARGET_POWERPC64) ? CODE_FOR_htm_mtspr_di : CODE_FOR_htm_mtspr_si;
12717}
12718
12719/* Expand the HTM builtin in EXP and store the result in TARGET.
12720   Store true in *EXPANDEDP if we found a builtin to expand.  */
12721static rtx
12722htm_expand_builtin (tree exp, rtx target, bool * expandedp)
12723{
12724  tree fndecl = TREE_OPERAND (CALL_EXPR_FN (exp), 0);
12725  bool nonvoid = TREE_TYPE (TREE_TYPE (fndecl)) != void_type_node;
12726  enum rs6000_builtins fcode = (enum rs6000_builtins) DECL_FUNCTION_CODE (fndecl);
12727  const struct builtin_description *d;
12728  size_t i;
12729
12730  *expandedp = true;
12731
12732  if (!TARGET_POWERPC64
12733      && (fcode == HTM_BUILTIN_TABORTDC
12734	  || fcode == HTM_BUILTIN_TABORTDCI))
12735    {
12736      size_t uns_fcode = (size_t)fcode;
12737      const char *name = rs6000_builtin_info[uns_fcode].name;
12738      error ("builtin %s is only valid in 64-bit mode", name);
12739      return const0_rtx;
12740    }
12741
12742  /* Expand the HTM builtins.  */
12743  d = bdesc_htm;
12744  for (i = 0; i < ARRAY_SIZE (bdesc_htm); i++, d++)
12745    if (d->code == fcode)
12746      {
12747	rtx op[MAX_HTM_OPERANDS], pat;
12748	int nopnds = 0;
12749	tree arg;
12750	call_expr_arg_iterator iter;
12751	unsigned attr = rs6000_builtin_info[fcode].attr;
12752	enum insn_code icode = d->icode;
12753	const struct insn_operand_data *insn_op;
12754	bool uses_spr = (attr & RS6000_BTC_SPR);
12755	rtx cr = NULL_RTX;
12756
12757	if (uses_spr)
12758	  icode = rs6000_htm_spr_icode (nonvoid);
12759	insn_op = &insn_data[icode].operand[0];
12760
12761	if (nonvoid)
12762	  {
12763	    machine_mode tmode = (uses_spr) ? insn_op->mode : SImode;
12764	    if (!target
12765		|| GET_MODE (target) != tmode
12766		|| (uses_spr && !(*insn_op->predicate) (target, tmode)))
12767	      target = gen_reg_rtx (tmode);
12768	    if (uses_spr)
12769	      op[nopnds++] = target;
12770	  }
12771
12772	FOR_EACH_CALL_EXPR_ARG (arg, iter, exp)
12773	{
12774	  if (arg == error_mark_node || nopnds >= MAX_HTM_OPERANDS)
12775	    return const0_rtx;
12776
12777	  insn_op = &insn_data[icode].operand[nopnds];
12778
12779	  op[nopnds] = expand_normal (arg);
12780
12781	  if (!(*insn_op->predicate) (op[nopnds], insn_op->mode))
12782	    {
12783	      if (!strcmp (insn_op->constraint, "n"))
12784		{
12785		  int arg_num = (nonvoid) ? nopnds : nopnds + 1;
12786		  if (!CONST_INT_P (op[nopnds]))
12787		    error ("argument %d must be an unsigned literal", arg_num);
12788		  else
12789		    error ("argument %d is an unsigned literal that is "
12790			   "out of range", arg_num);
12791		  return const0_rtx;
12792		}
12793	      op[nopnds] = copy_to_mode_reg (insn_op->mode, op[nopnds]);
12794	    }
12795
12796	  nopnds++;
12797	}
12798
12799	/* Handle the builtins for extended mnemonics.  These accept
12800	   no arguments, but map to builtins that take arguments.  */
12801	switch (fcode)
12802	  {
12803	  case HTM_BUILTIN_TENDALL:  /* Alias for: tend. 1  */
12804	  case HTM_BUILTIN_TRESUME:  /* Alias for: tsr. 1  */
12805	    op[nopnds++] = GEN_INT (1);
12806#ifdef ENABLE_CHECKING
12807	    attr |= RS6000_BTC_UNARY;
12808#endif
12809	    break;
12810	  case HTM_BUILTIN_TSUSPEND: /* Alias for: tsr. 0  */
12811	    op[nopnds++] = GEN_INT (0);
12812#ifdef ENABLE_CHECKING
12813	    attr |= RS6000_BTC_UNARY;
12814#endif
12815	    break;
12816	  default:
12817	    break;
12818	  }
12819
12820	/* If this builtin accesses SPRs, then pass in the appropriate
12821	   SPR number and SPR regno as the last two operands.  */
12822	if (uses_spr)
12823	  {
12824	    machine_mode mode = (TARGET_POWERPC64) ? DImode : SImode;
12825	    op[nopnds++] = gen_rtx_CONST_INT (mode, htm_spr_num (fcode));
12826	    op[nopnds++] = gen_rtx_REG (mode, htm_spr_regno (fcode));
12827	  }
12828	/* If this builtin accesses a CR, then pass in a scratch
12829	   CR as the last operand.  */
12830	else if (attr & RS6000_BTC_CR)
12831	  { cr = gen_reg_rtx (CCmode);
12832	    op[nopnds++] = cr;
12833	  }
12834
12835#ifdef ENABLE_CHECKING
12836	int expected_nopnds = 0;
12837	if ((attr & RS6000_BTC_TYPE_MASK) == RS6000_BTC_UNARY)
12838	  expected_nopnds = 1;
12839	else if ((attr & RS6000_BTC_TYPE_MASK) == RS6000_BTC_BINARY)
12840	  expected_nopnds = 2;
12841	else if ((attr & RS6000_BTC_TYPE_MASK) == RS6000_BTC_TERNARY)
12842	  expected_nopnds = 3;
12843	if (!(attr & RS6000_BTC_VOID))
12844	  expected_nopnds += 1;
12845	if (uses_spr)
12846	  expected_nopnds += 2;
12847
12848	gcc_assert (nopnds == expected_nopnds && nopnds <= MAX_HTM_OPERANDS);
12849#endif
12850
12851	switch (nopnds)
12852	  {
12853	  case 1:
12854	    pat = GEN_FCN (icode) (op[0]);
12855	    break;
12856	  case 2:
12857	    pat = GEN_FCN (icode) (op[0], op[1]);
12858	    break;
12859	  case 3:
12860	    pat = GEN_FCN (icode) (op[0], op[1], op[2]);
12861	    break;
12862	  case 4:
12863	    pat = GEN_FCN (icode) (op[0], op[1], op[2], op[3]);
12864	    break;
12865	  default:
12866	    gcc_unreachable ();
12867	  }
12868	if (!pat)
12869	  return NULL_RTX;
12870	emit_insn (pat);
12871
12872	if (attr & RS6000_BTC_CR)
12873	  {
12874	    if (fcode == HTM_BUILTIN_TBEGIN)
12875	      {
12876		/* Emit code to set TARGET to true or false depending on
12877		   whether the tbegin. instruction successfully or failed
12878		   to start a transaction.  We do this by placing the 1's
12879		   complement of CR's EQ bit into TARGET.  */
12880		rtx scratch = gen_reg_rtx (SImode);
12881		emit_insn (gen_rtx_SET (VOIDmode, scratch,
12882					gen_rtx_EQ (SImode, cr,
12883						     const0_rtx)));
12884		emit_insn (gen_rtx_SET (VOIDmode, target,
12885					gen_rtx_XOR (SImode, scratch,
12886						     GEN_INT (1))));
12887	      }
12888	    else
12889	      {
12890		/* Emit code to copy the 4-bit condition register field
12891		   CR into the least significant end of register TARGET.  */
12892		rtx scratch1 = gen_reg_rtx (SImode);
12893		rtx scratch2 = gen_reg_rtx (SImode);
12894		rtx subreg = simplify_gen_subreg (CCmode, scratch1, SImode, 0);
12895		emit_insn (gen_movcc (subreg, cr));
12896		emit_insn (gen_lshrsi3 (scratch2, scratch1, GEN_INT (28)));
12897		emit_insn (gen_andsi3 (target, scratch2, GEN_INT (0xf)));
12898	      }
12899	  }
12900
12901	if (nonvoid)
12902	  return target;
12903	return const0_rtx;
12904      }
12905
12906  *expandedp = false;
12907  return NULL_RTX;
12908}
12909
12910static rtx
12911rs6000_expand_ternop_builtin (enum insn_code icode, tree exp, rtx target)
12912{
12913  rtx pat;
12914  tree arg0 = CALL_EXPR_ARG (exp, 0);
12915  tree arg1 = CALL_EXPR_ARG (exp, 1);
12916  tree arg2 = CALL_EXPR_ARG (exp, 2);
12917  rtx op0 = expand_normal (arg0);
12918  rtx op1 = expand_normal (arg1);
12919  rtx op2 = expand_normal (arg2);
12920  machine_mode tmode = insn_data[icode].operand[0].mode;
12921  machine_mode mode0 = insn_data[icode].operand[1].mode;
12922  machine_mode mode1 = insn_data[icode].operand[2].mode;
12923  machine_mode mode2 = insn_data[icode].operand[3].mode;
12924
12925  if (icode == CODE_FOR_nothing)
12926    /* Builtin not supported on this processor.  */
12927    return 0;
12928
12929  /* If we got invalid arguments bail out before generating bad rtl.  */
12930  if (arg0 == error_mark_node
12931      || arg1 == error_mark_node
12932      || arg2 == error_mark_node)
12933    return const0_rtx;
12934
12935  /* Check and prepare argument depending on the instruction code.
12936
12937     Note that a switch statement instead of the sequence of tests
12938     would be incorrect as many of the CODE_FOR values could be
12939     CODE_FOR_nothing and that would yield multiple alternatives
12940     with identical values.  We'd never reach here at runtime in
12941     this case.  */
12942  if (icode == CODE_FOR_altivec_vsldoi_v4sf
12943      || icode == CODE_FOR_altivec_vsldoi_v4si
12944      || icode == CODE_FOR_altivec_vsldoi_v8hi
12945      || icode == CODE_FOR_altivec_vsldoi_v16qi)
12946    {
12947      /* Only allow 4-bit unsigned literals.  */
12948      STRIP_NOPS (arg2);
12949      if (TREE_CODE (arg2) != INTEGER_CST
12950	  || TREE_INT_CST_LOW (arg2) & ~0xf)
12951	{
12952	  error ("argument 3 must be a 4-bit unsigned literal");
12953	  return const0_rtx;
12954	}
12955    }
12956  else if (icode == CODE_FOR_vsx_xxpermdi_v2df
12957           || icode == CODE_FOR_vsx_xxpermdi_v2di
12958           || icode == CODE_FOR_vsx_xxsldwi_v16qi
12959           || icode == CODE_FOR_vsx_xxsldwi_v8hi
12960           || icode == CODE_FOR_vsx_xxsldwi_v4si
12961           || icode == CODE_FOR_vsx_xxsldwi_v4sf
12962           || icode == CODE_FOR_vsx_xxsldwi_v2di
12963           || icode == CODE_FOR_vsx_xxsldwi_v2df)
12964    {
12965      /* Only allow 2-bit unsigned literals.  */
12966      STRIP_NOPS (arg2);
12967      if (TREE_CODE (arg2) != INTEGER_CST
12968	  || TREE_INT_CST_LOW (arg2) & ~0x3)
12969	{
12970	  error ("argument 3 must be a 2-bit unsigned literal");
12971	  return const0_rtx;
12972	}
12973    }
12974  else if (icode == CODE_FOR_vsx_set_v2df
12975           || icode == CODE_FOR_vsx_set_v2di
12976	   || icode == CODE_FOR_bcdadd
12977	   || icode == CODE_FOR_bcdadd_lt
12978	   || icode == CODE_FOR_bcdadd_eq
12979	   || icode == CODE_FOR_bcdadd_gt
12980	   || icode == CODE_FOR_bcdsub
12981	   || icode == CODE_FOR_bcdsub_lt
12982	   || icode == CODE_FOR_bcdsub_eq
12983	   || icode == CODE_FOR_bcdsub_gt)
12984    {
12985      /* Only allow 1-bit unsigned literals.  */
12986      STRIP_NOPS (arg2);
12987      if (TREE_CODE (arg2) != INTEGER_CST
12988	  || TREE_INT_CST_LOW (arg2) & ~0x1)
12989	{
12990	  error ("argument 3 must be a 1-bit unsigned literal");
12991	  return const0_rtx;
12992	}
12993    }
12994  else if (icode == CODE_FOR_dfp_ddedpd_dd
12995           || icode == CODE_FOR_dfp_ddedpd_td)
12996    {
12997      /* Only allow 2-bit unsigned literals where the value is 0 or 2.  */
12998      STRIP_NOPS (arg0);
12999      if (TREE_CODE (arg0) != INTEGER_CST
13000	  || TREE_INT_CST_LOW (arg2) & ~0x3)
13001	{
13002	  error ("argument 1 must be 0 or 2");
13003	  return const0_rtx;
13004	}
13005    }
13006  else if (icode == CODE_FOR_dfp_denbcd_dd
13007	   || icode == CODE_FOR_dfp_denbcd_td)
13008    {
13009      /* Only allow 1-bit unsigned literals.  */
13010      STRIP_NOPS (arg0);
13011      if (TREE_CODE (arg0) != INTEGER_CST
13012	  || TREE_INT_CST_LOW (arg0) & ~0x1)
13013	{
13014	  error ("argument 1 must be a 1-bit unsigned literal");
13015	  return const0_rtx;
13016	}
13017    }
13018  else if (icode == CODE_FOR_dfp_dscli_dd
13019           || icode == CODE_FOR_dfp_dscli_td
13020	   || icode == CODE_FOR_dfp_dscri_dd
13021	   || icode == CODE_FOR_dfp_dscri_td)
13022    {
13023      /* Only allow 6-bit unsigned literals.  */
13024      STRIP_NOPS (arg1);
13025      if (TREE_CODE (arg1) != INTEGER_CST
13026	  || TREE_INT_CST_LOW (arg1) & ~0x3f)
13027	{
13028	  error ("argument 2 must be a 6-bit unsigned literal");
13029	  return const0_rtx;
13030	}
13031    }
13032  else if (icode == CODE_FOR_crypto_vshasigmaw
13033	   || icode == CODE_FOR_crypto_vshasigmad)
13034    {
13035      /* Check whether the 2nd and 3rd arguments are integer constants and in
13036	 range and prepare arguments.  */
13037      STRIP_NOPS (arg1);
13038      if (TREE_CODE (arg1) != INTEGER_CST || wi::geu_p (arg1, 2))
13039	{
13040	  error ("argument 2 must be 0 or 1");
13041	  return const0_rtx;
13042	}
13043
13044      STRIP_NOPS (arg2);
13045      if (TREE_CODE (arg2) != INTEGER_CST || wi::geu_p (arg1, 16))
13046	{
13047	  error ("argument 3 must be in the range 0..15");
13048	  return const0_rtx;
13049	}
13050    }
13051
13052  if (target == 0
13053      || GET_MODE (target) != tmode
13054      || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
13055    target = gen_reg_rtx (tmode);
13056
13057  if (! (*insn_data[icode].operand[1].predicate) (op0, mode0))
13058    op0 = copy_to_mode_reg (mode0, op0);
13059  if (! (*insn_data[icode].operand[2].predicate) (op1, mode1))
13060    op1 = copy_to_mode_reg (mode1, op1);
13061  if (! (*insn_data[icode].operand[3].predicate) (op2, mode2))
13062    op2 = copy_to_mode_reg (mode2, op2);
13063
13064  if (TARGET_PAIRED_FLOAT && icode == CODE_FOR_selv2sf4)
13065    pat = GEN_FCN (icode) (target, op0, op1, op2, CONST0_RTX (SFmode));
13066  else
13067    pat = GEN_FCN (icode) (target, op0, op1, op2);
13068  if (! pat)
13069    return 0;
13070  emit_insn (pat);
13071
13072  return target;
13073}
13074
13075/* Expand the lvx builtins.  */
13076static rtx
13077altivec_expand_ld_builtin (tree exp, rtx target, bool *expandedp)
13078{
13079  tree fndecl = TREE_OPERAND (CALL_EXPR_FN (exp), 0);
13080  unsigned int fcode = DECL_FUNCTION_CODE (fndecl);
13081  tree arg0;
13082  machine_mode tmode, mode0;
13083  rtx pat, op0;
13084  enum insn_code icode;
13085
13086  switch (fcode)
13087    {
13088    case ALTIVEC_BUILTIN_LD_INTERNAL_16qi:
13089      icode = CODE_FOR_vector_altivec_load_v16qi;
13090      break;
13091    case ALTIVEC_BUILTIN_LD_INTERNAL_8hi:
13092      icode = CODE_FOR_vector_altivec_load_v8hi;
13093      break;
13094    case ALTIVEC_BUILTIN_LD_INTERNAL_4si:
13095      icode = CODE_FOR_vector_altivec_load_v4si;
13096      break;
13097    case ALTIVEC_BUILTIN_LD_INTERNAL_4sf:
13098      icode = CODE_FOR_vector_altivec_load_v4sf;
13099      break;
13100    case ALTIVEC_BUILTIN_LD_INTERNAL_2df:
13101      icode = CODE_FOR_vector_altivec_load_v2df;
13102      break;
13103    case ALTIVEC_BUILTIN_LD_INTERNAL_2di:
13104      icode = CODE_FOR_vector_altivec_load_v2di;
13105    case ALTIVEC_BUILTIN_LD_INTERNAL_1ti:
13106      icode = CODE_FOR_vector_altivec_load_v1ti;
13107      break;
13108    default:
13109      *expandedp = false;
13110      return NULL_RTX;
13111    }
13112
13113  *expandedp = true;
13114
13115  arg0 = CALL_EXPR_ARG (exp, 0);
13116  op0 = expand_normal (arg0);
13117  tmode = insn_data[icode].operand[0].mode;
13118  mode0 = insn_data[icode].operand[1].mode;
13119
13120  if (target == 0
13121      || GET_MODE (target) != tmode
13122      || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
13123    target = gen_reg_rtx (tmode);
13124
13125  if (! (*insn_data[icode].operand[1].predicate) (op0, mode0))
13126    op0 = gen_rtx_MEM (mode0, copy_to_mode_reg (Pmode, op0));
13127
13128  pat = GEN_FCN (icode) (target, op0);
13129  if (! pat)
13130    return 0;
13131  emit_insn (pat);
13132  return target;
13133}
13134
13135/* Expand the stvx builtins.  */
13136static rtx
13137altivec_expand_st_builtin (tree exp, rtx target ATTRIBUTE_UNUSED,
13138			   bool *expandedp)
13139{
13140  tree fndecl = TREE_OPERAND (CALL_EXPR_FN (exp), 0);
13141  unsigned int fcode = DECL_FUNCTION_CODE (fndecl);
13142  tree arg0, arg1;
13143  machine_mode mode0, mode1;
13144  rtx pat, op0, op1;
13145  enum insn_code icode;
13146
13147  switch (fcode)
13148    {
13149    case ALTIVEC_BUILTIN_ST_INTERNAL_16qi:
13150      icode = CODE_FOR_vector_altivec_store_v16qi;
13151      break;
13152    case ALTIVEC_BUILTIN_ST_INTERNAL_8hi:
13153      icode = CODE_FOR_vector_altivec_store_v8hi;
13154      break;
13155    case ALTIVEC_BUILTIN_ST_INTERNAL_4si:
13156      icode = CODE_FOR_vector_altivec_store_v4si;
13157      break;
13158    case ALTIVEC_BUILTIN_ST_INTERNAL_4sf:
13159      icode = CODE_FOR_vector_altivec_store_v4sf;
13160      break;
13161    case ALTIVEC_BUILTIN_ST_INTERNAL_2df:
13162      icode = CODE_FOR_vector_altivec_store_v2df;
13163      break;
13164    case ALTIVEC_BUILTIN_ST_INTERNAL_2di:
13165      icode = CODE_FOR_vector_altivec_store_v2di;
13166    case ALTIVEC_BUILTIN_ST_INTERNAL_1ti:
13167      icode = CODE_FOR_vector_altivec_store_v1ti;
13168      break;
13169    default:
13170      *expandedp = false;
13171      return NULL_RTX;
13172    }
13173
13174  arg0 = CALL_EXPR_ARG (exp, 0);
13175  arg1 = CALL_EXPR_ARG (exp, 1);
13176  op0 = expand_normal (arg0);
13177  op1 = expand_normal (arg1);
13178  mode0 = insn_data[icode].operand[0].mode;
13179  mode1 = insn_data[icode].operand[1].mode;
13180
13181  if (! (*insn_data[icode].operand[0].predicate) (op0, mode0))
13182    op0 = gen_rtx_MEM (mode0, copy_to_mode_reg (Pmode, op0));
13183  if (! (*insn_data[icode].operand[1].predicate) (op1, mode1))
13184    op1 = copy_to_mode_reg (mode1, op1);
13185
13186  pat = GEN_FCN (icode) (op0, op1);
13187  if (pat)
13188    emit_insn (pat);
13189
13190  *expandedp = true;
13191  return NULL_RTX;
13192}
13193
13194/* Expand the dst builtins.  */
13195static rtx
13196altivec_expand_dst_builtin (tree exp, rtx target ATTRIBUTE_UNUSED,
13197			    bool *expandedp)
13198{
13199  tree fndecl = TREE_OPERAND (CALL_EXPR_FN (exp), 0);
13200  enum rs6000_builtins fcode = (enum rs6000_builtins) DECL_FUNCTION_CODE (fndecl);
13201  tree arg0, arg1, arg2;
13202  machine_mode mode0, mode1;
13203  rtx pat, op0, op1, op2;
13204  const struct builtin_description *d;
13205  size_t i;
13206
13207  *expandedp = false;
13208
13209  /* Handle DST variants.  */
13210  d = bdesc_dst;
13211  for (i = 0; i < ARRAY_SIZE (bdesc_dst); i++, d++)
13212    if (d->code == fcode)
13213      {
13214	arg0 = CALL_EXPR_ARG (exp, 0);
13215	arg1 = CALL_EXPR_ARG (exp, 1);
13216	arg2 = CALL_EXPR_ARG (exp, 2);
13217	op0 = expand_normal (arg0);
13218	op1 = expand_normal (arg1);
13219	op2 = expand_normal (arg2);
13220	mode0 = insn_data[d->icode].operand[0].mode;
13221	mode1 = insn_data[d->icode].operand[1].mode;
13222
13223	/* Invalid arguments, bail out before generating bad rtl.  */
13224	if (arg0 == error_mark_node
13225	    || arg1 == error_mark_node
13226	    || arg2 == error_mark_node)
13227	  return const0_rtx;
13228
13229	*expandedp = true;
13230	STRIP_NOPS (arg2);
13231	if (TREE_CODE (arg2) != INTEGER_CST
13232	    || TREE_INT_CST_LOW (arg2) & ~0x3)
13233	  {
13234	    error ("argument to %qs must be a 2-bit unsigned literal", d->name);
13235	    return const0_rtx;
13236	  }
13237
13238	if (! (*insn_data[d->icode].operand[0].predicate) (op0, mode0))
13239	  op0 = copy_to_mode_reg (Pmode, op0);
13240	if (! (*insn_data[d->icode].operand[1].predicate) (op1, mode1))
13241	  op1 = copy_to_mode_reg (mode1, op1);
13242
13243	pat = GEN_FCN (d->icode) (op0, op1, op2);
13244	if (pat != 0)
13245	  emit_insn (pat);
13246
13247	return NULL_RTX;
13248      }
13249
13250  return NULL_RTX;
13251}
13252
13253/* Expand vec_init builtin.  */
13254static rtx
13255altivec_expand_vec_init_builtin (tree type, tree exp, rtx target)
13256{
13257  machine_mode tmode = TYPE_MODE (type);
13258  machine_mode inner_mode = GET_MODE_INNER (tmode);
13259  int i, n_elt = GET_MODE_NUNITS (tmode);
13260
13261  gcc_assert (VECTOR_MODE_P (tmode));
13262  gcc_assert (n_elt == call_expr_nargs (exp));
13263
13264  if (!target || !register_operand (target, tmode))
13265    target = gen_reg_rtx (tmode);
13266
13267  /* If we have a vector compromised of a single element, such as V1TImode, do
13268     the initialization directly.  */
13269  if (n_elt == 1 && GET_MODE_SIZE (tmode) == GET_MODE_SIZE (inner_mode))
13270    {
13271      rtx x = expand_normal (CALL_EXPR_ARG (exp, 0));
13272      emit_move_insn (target, gen_lowpart (tmode, x));
13273    }
13274  else
13275    {
13276      rtvec v = rtvec_alloc (n_elt);
13277
13278      for (i = 0; i < n_elt; ++i)
13279	{
13280	  rtx x = expand_normal (CALL_EXPR_ARG (exp, i));
13281	  RTVEC_ELT (v, i) = gen_lowpart (inner_mode, x);
13282	}
13283
13284      rs6000_expand_vector_init (target, gen_rtx_PARALLEL (tmode, v));
13285    }
13286
13287  return target;
13288}
13289
13290/* Return the integer constant in ARG.  Constrain it to be in the range
13291   of the subparts of VEC_TYPE; issue an error if not.  */
13292
13293static int
13294get_element_number (tree vec_type, tree arg)
13295{
13296  unsigned HOST_WIDE_INT elt, max = TYPE_VECTOR_SUBPARTS (vec_type) - 1;
13297
13298  if (!tree_fits_uhwi_p (arg)
13299      || (elt = tree_to_uhwi (arg), elt > max))
13300    {
13301      error ("selector must be an integer constant in the range 0..%wi", max);
13302      return 0;
13303    }
13304
13305  return elt;
13306}
13307
13308/* Expand vec_set builtin.  */
13309static rtx
13310altivec_expand_vec_set_builtin (tree exp)
13311{
13312  machine_mode tmode, mode1;
13313  tree arg0, arg1, arg2;
13314  int elt;
13315  rtx op0, op1;
13316
13317  arg0 = CALL_EXPR_ARG (exp, 0);
13318  arg1 = CALL_EXPR_ARG (exp, 1);
13319  arg2 = CALL_EXPR_ARG (exp, 2);
13320
13321  tmode = TYPE_MODE (TREE_TYPE (arg0));
13322  mode1 = TYPE_MODE (TREE_TYPE (TREE_TYPE (arg0)));
13323  gcc_assert (VECTOR_MODE_P (tmode));
13324
13325  op0 = expand_expr (arg0, NULL_RTX, tmode, EXPAND_NORMAL);
13326  op1 = expand_expr (arg1, NULL_RTX, mode1, EXPAND_NORMAL);
13327  elt = get_element_number (TREE_TYPE (arg0), arg2);
13328
13329  if (GET_MODE (op1) != mode1 && GET_MODE (op1) != VOIDmode)
13330    op1 = convert_modes (mode1, GET_MODE (op1), op1, true);
13331
13332  op0 = force_reg (tmode, op0);
13333  op1 = force_reg (mode1, op1);
13334
13335  rs6000_expand_vector_set (op0, op1, elt);
13336
13337  return op0;
13338}
13339
13340/* Expand vec_ext builtin.  */
13341static rtx
13342altivec_expand_vec_ext_builtin (tree exp, rtx target)
13343{
13344  machine_mode tmode, mode0;
13345  tree arg0, arg1;
13346  int elt;
13347  rtx op0;
13348
13349  arg0 = CALL_EXPR_ARG (exp, 0);
13350  arg1 = CALL_EXPR_ARG (exp, 1);
13351
13352  op0 = expand_normal (arg0);
13353  elt = get_element_number (TREE_TYPE (arg0), arg1);
13354
13355  tmode = TYPE_MODE (TREE_TYPE (TREE_TYPE (arg0)));
13356  mode0 = TYPE_MODE (TREE_TYPE (arg0));
13357  gcc_assert (VECTOR_MODE_P (mode0));
13358
13359  op0 = force_reg (mode0, op0);
13360
13361  if (optimize || !target || !register_operand (target, tmode))
13362    target = gen_reg_rtx (tmode);
13363
13364  rs6000_expand_vector_extract (target, op0, elt);
13365
13366  return target;
13367}
13368
13369/* Expand the builtin in EXP and store the result in TARGET.  Store
13370   true in *EXPANDEDP if we found a builtin to expand.  */
13371static rtx
13372altivec_expand_builtin (tree exp, rtx target, bool *expandedp)
13373{
13374  const struct builtin_description *d;
13375  size_t i;
13376  enum insn_code icode;
13377  tree fndecl = TREE_OPERAND (CALL_EXPR_FN (exp), 0);
13378  tree arg0;
13379  rtx op0, pat;
13380  machine_mode tmode, mode0;
13381  enum rs6000_builtins fcode
13382    = (enum rs6000_builtins) DECL_FUNCTION_CODE (fndecl);
13383
13384  if (rs6000_overloaded_builtin_p (fcode))
13385    {
13386      *expandedp = true;
13387      error ("unresolved overload for Altivec builtin %qF", fndecl);
13388
13389      /* Given it is invalid, just generate a normal call.  */
13390      return expand_call (exp, target, false);
13391    }
13392
13393  target = altivec_expand_ld_builtin (exp, target, expandedp);
13394  if (*expandedp)
13395    return target;
13396
13397  target = altivec_expand_st_builtin (exp, target, expandedp);
13398  if (*expandedp)
13399    return target;
13400
13401  target = altivec_expand_dst_builtin (exp, target, expandedp);
13402  if (*expandedp)
13403    return target;
13404
13405  *expandedp = true;
13406
13407  switch (fcode)
13408    {
13409    case ALTIVEC_BUILTIN_STVX_V2DF:
13410      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvx_v2df, exp);
13411    case ALTIVEC_BUILTIN_STVX_V2DI:
13412      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvx_v2di, exp);
13413    case ALTIVEC_BUILTIN_STVX_V4SF:
13414      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvx_v4sf, exp);
13415    case ALTIVEC_BUILTIN_STVX:
13416    case ALTIVEC_BUILTIN_STVX_V4SI:
13417      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvx_v4si, exp);
13418    case ALTIVEC_BUILTIN_STVX_V8HI:
13419      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvx_v8hi, exp);
13420    case ALTIVEC_BUILTIN_STVX_V16QI:
13421      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvx_v16qi, exp);
13422    case ALTIVEC_BUILTIN_STVEBX:
13423      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvebx, exp);
13424    case ALTIVEC_BUILTIN_STVEHX:
13425      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvehx, exp);
13426    case ALTIVEC_BUILTIN_STVEWX:
13427      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvewx, exp);
13428    case ALTIVEC_BUILTIN_STVXL_V2DF:
13429      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvxl_v2df, exp);
13430    case ALTIVEC_BUILTIN_STVXL_V2DI:
13431      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvxl_v2di, exp);
13432    case ALTIVEC_BUILTIN_STVXL_V4SF:
13433      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvxl_v4sf, exp);
13434    case ALTIVEC_BUILTIN_STVXL:
13435    case ALTIVEC_BUILTIN_STVXL_V4SI:
13436      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvxl_v4si, exp);
13437    case ALTIVEC_BUILTIN_STVXL_V8HI:
13438      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvxl_v8hi, exp);
13439    case ALTIVEC_BUILTIN_STVXL_V16QI:
13440      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvxl_v16qi, exp);
13441
13442    case ALTIVEC_BUILTIN_STVLX:
13443      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvlx, exp);
13444    case ALTIVEC_BUILTIN_STVLXL:
13445      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvlxl, exp);
13446    case ALTIVEC_BUILTIN_STVRX:
13447      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvrx, exp);
13448    case ALTIVEC_BUILTIN_STVRXL:
13449      return altivec_expand_stv_builtin (CODE_FOR_altivec_stvrxl, exp);
13450
13451    case VSX_BUILTIN_STXVD2X_V1TI:
13452      return altivec_expand_stv_builtin (CODE_FOR_vsx_store_v1ti, exp);
13453    case VSX_BUILTIN_STXVD2X_V2DF:
13454      return altivec_expand_stv_builtin (CODE_FOR_vsx_store_v2df, exp);
13455    case VSX_BUILTIN_STXVD2X_V2DI:
13456      return altivec_expand_stv_builtin (CODE_FOR_vsx_store_v2di, exp);
13457    case VSX_BUILTIN_STXVW4X_V4SF:
13458      return altivec_expand_stv_builtin (CODE_FOR_vsx_store_v4sf, exp);
13459    case VSX_BUILTIN_STXVW4X_V4SI:
13460      return altivec_expand_stv_builtin (CODE_FOR_vsx_store_v4si, exp);
13461    case VSX_BUILTIN_STXVW4X_V8HI:
13462      return altivec_expand_stv_builtin (CODE_FOR_vsx_store_v8hi, exp);
13463    case VSX_BUILTIN_STXVW4X_V16QI:
13464      return altivec_expand_stv_builtin (CODE_FOR_vsx_store_v16qi, exp);
13465
13466    case ALTIVEC_BUILTIN_MFVSCR:
13467      icode = CODE_FOR_altivec_mfvscr;
13468      tmode = insn_data[icode].operand[0].mode;
13469
13470      if (target == 0
13471	  || GET_MODE (target) != tmode
13472	  || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
13473	target = gen_reg_rtx (tmode);
13474
13475      pat = GEN_FCN (icode) (target);
13476      if (! pat)
13477	return 0;
13478      emit_insn (pat);
13479      return target;
13480
13481    case ALTIVEC_BUILTIN_MTVSCR:
13482      icode = CODE_FOR_altivec_mtvscr;
13483      arg0 = CALL_EXPR_ARG (exp, 0);
13484      op0 = expand_normal (arg0);
13485      mode0 = insn_data[icode].operand[0].mode;
13486
13487      /* If we got invalid arguments bail out before generating bad rtl.  */
13488      if (arg0 == error_mark_node)
13489	return const0_rtx;
13490
13491      if (! (*insn_data[icode].operand[0].predicate) (op0, mode0))
13492	op0 = copy_to_mode_reg (mode0, op0);
13493
13494      pat = GEN_FCN (icode) (op0);
13495      if (pat)
13496	emit_insn (pat);
13497      return NULL_RTX;
13498
13499    case ALTIVEC_BUILTIN_DSSALL:
13500      emit_insn (gen_altivec_dssall ());
13501      return NULL_RTX;
13502
13503    case ALTIVEC_BUILTIN_DSS:
13504      icode = CODE_FOR_altivec_dss;
13505      arg0 = CALL_EXPR_ARG (exp, 0);
13506      STRIP_NOPS (arg0);
13507      op0 = expand_normal (arg0);
13508      mode0 = insn_data[icode].operand[0].mode;
13509
13510      /* If we got invalid arguments bail out before generating bad rtl.  */
13511      if (arg0 == error_mark_node)
13512	return const0_rtx;
13513
13514      if (TREE_CODE (arg0) != INTEGER_CST
13515	  || TREE_INT_CST_LOW (arg0) & ~0x3)
13516	{
13517	  error ("argument to dss must be a 2-bit unsigned literal");
13518	  return const0_rtx;
13519	}
13520
13521      if (! (*insn_data[icode].operand[0].predicate) (op0, mode0))
13522	op0 = copy_to_mode_reg (mode0, op0);
13523
13524      emit_insn (gen_altivec_dss (op0));
13525      return NULL_RTX;
13526
13527    case ALTIVEC_BUILTIN_VEC_INIT_V4SI:
13528    case ALTIVEC_BUILTIN_VEC_INIT_V8HI:
13529    case ALTIVEC_BUILTIN_VEC_INIT_V16QI:
13530    case ALTIVEC_BUILTIN_VEC_INIT_V4SF:
13531    case VSX_BUILTIN_VEC_INIT_V2DF:
13532    case VSX_BUILTIN_VEC_INIT_V2DI:
13533    case VSX_BUILTIN_VEC_INIT_V1TI:
13534      return altivec_expand_vec_init_builtin (TREE_TYPE (exp), exp, target);
13535
13536    case ALTIVEC_BUILTIN_VEC_SET_V4SI:
13537    case ALTIVEC_BUILTIN_VEC_SET_V8HI:
13538    case ALTIVEC_BUILTIN_VEC_SET_V16QI:
13539    case ALTIVEC_BUILTIN_VEC_SET_V4SF:
13540    case VSX_BUILTIN_VEC_SET_V2DF:
13541    case VSX_BUILTIN_VEC_SET_V2DI:
13542    case VSX_BUILTIN_VEC_SET_V1TI:
13543      return altivec_expand_vec_set_builtin (exp);
13544
13545    case ALTIVEC_BUILTIN_VEC_EXT_V4SI:
13546    case ALTIVEC_BUILTIN_VEC_EXT_V8HI:
13547    case ALTIVEC_BUILTIN_VEC_EXT_V16QI:
13548    case ALTIVEC_BUILTIN_VEC_EXT_V4SF:
13549    case VSX_BUILTIN_VEC_EXT_V2DF:
13550    case VSX_BUILTIN_VEC_EXT_V2DI:
13551    case VSX_BUILTIN_VEC_EXT_V1TI:
13552      return altivec_expand_vec_ext_builtin (exp, target);
13553
13554    default:
13555      break;
13556      /* Fall through.  */
13557    }
13558
13559  /* Expand abs* operations.  */
13560  d = bdesc_abs;
13561  for (i = 0; i < ARRAY_SIZE (bdesc_abs); i++, d++)
13562    if (d->code == fcode)
13563      return altivec_expand_abs_builtin (d->icode, exp, target);
13564
13565  /* Expand the AltiVec predicates.  */
13566  d = bdesc_altivec_preds;
13567  for (i = 0; i < ARRAY_SIZE (bdesc_altivec_preds); i++, d++)
13568    if (d->code == fcode)
13569      return altivec_expand_predicate_builtin (d->icode, exp, target);
13570
13571  /* LV* are funky.  We initialized them differently.  */
13572  switch (fcode)
13573    {
13574    case ALTIVEC_BUILTIN_LVSL:
13575      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvsl,
13576					exp, target, false);
13577    case ALTIVEC_BUILTIN_LVSR:
13578      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvsr,
13579					exp, target, false);
13580    case ALTIVEC_BUILTIN_LVEBX:
13581      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvebx,
13582					exp, target, false);
13583    case ALTIVEC_BUILTIN_LVEHX:
13584      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvehx,
13585					exp, target, false);
13586    case ALTIVEC_BUILTIN_LVEWX:
13587      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvewx,
13588					exp, target, false);
13589    case ALTIVEC_BUILTIN_LVXL_V2DF:
13590      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvxl_v2df,
13591					exp, target, false);
13592    case ALTIVEC_BUILTIN_LVXL_V2DI:
13593      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvxl_v2di,
13594					exp, target, false);
13595    case ALTIVEC_BUILTIN_LVXL_V4SF:
13596      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvxl_v4sf,
13597					exp, target, false);
13598    case ALTIVEC_BUILTIN_LVXL:
13599    case ALTIVEC_BUILTIN_LVXL_V4SI:
13600      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvxl_v4si,
13601					exp, target, false);
13602    case ALTIVEC_BUILTIN_LVXL_V8HI:
13603      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvxl_v8hi,
13604					exp, target, false);
13605    case ALTIVEC_BUILTIN_LVXL_V16QI:
13606      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvxl_v16qi,
13607					exp, target, false);
13608    case ALTIVEC_BUILTIN_LVX_V2DF:
13609      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvx_v2df,
13610					exp, target, false);
13611    case ALTIVEC_BUILTIN_LVX_V2DI:
13612      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvx_v2di,
13613					exp, target, false);
13614    case ALTIVEC_BUILTIN_LVX_V4SF:
13615      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvx_v4sf,
13616					exp, target, false);
13617    case ALTIVEC_BUILTIN_LVX:
13618    case ALTIVEC_BUILTIN_LVX_V4SI:
13619      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvx_v4si,
13620					exp, target, false);
13621    case ALTIVEC_BUILTIN_LVX_V8HI:
13622      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvx_v8hi,
13623					exp, target, false);
13624    case ALTIVEC_BUILTIN_LVX_V16QI:
13625      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvx_v16qi,
13626					exp, target, false);
13627    case ALTIVEC_BUILTIN_LVLX:
13628      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvlx,
13629					exp, target, true);
13630    case ALTIVEC_BUILTIN_LVLXL:
13631      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvlxl,
13632					exp, target, true);
13633    case ALTIVEC_BUILTIN_LVRX:
13634      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvrx,
13635					exp, target, true);
13636    case ALTIVEC_BUILTIN_LVRXL:
13637      return altivec_expand_lv_builtin (CODE_FOR_altivec_lvrxl,
13638					exp, target, true);
13639    case VSX_BUILTIN_LXVD2X_V1TI:
13640      return altivec_expand_lv_builtin (CODE_FOR_vsx_load_v1ti,
13641					exp, target, false);
13642    case VSX_BUILTIN_LXVD2X_V2DF:
13643      return altivec_expand_lv_builtin (CODE_FOR_vsx_load_v2df,
13644					exp, target, false);
13645    case VSX_BUILTIN_LXVD2X_V2DI:
13646      return altivec_expand_lv_builtin (CODE_FOR_vsx_load_v2di,
13647					exp, target, false);
13648    case VSX_BUILTIN_LXVW4X_V4SF:
13649      return altivec_expand_lv_builtin (CODE_FOR_vsx_load_v4sf,
13650					exp, target, false);
13651    case VSX_BUILTIN_LXVW4X_V4SI:
13652      return altivec_expand_lv_builtin (CODE_FOR_vsx_load_v4si,
13653					exp, target, false);
13654    case VSX_BUILTIN_LXVW4X_V8HI:
13655      return altivec_expand_lv_builtin (CODE_FOR_vsx_load_v8hi,
13656					exp, target, false);
13657    case VSX_BUILTIN_LXVW4X_V16QI:
13658      return altivec_expand_lv_builtin (CODE_FOR_vsx_load_v16qi,
13659					exp, target, false);
13660      break;
13661    default:
13662      break;
13663      /* Fall through.  */
13664    }
13665
13666  *expandedp = false;
13667  return NULL_RTX;
13668}
13669
13670/* Expand the builtin in EXP and store the result in TARGET.  Store
13671   true in *EXPANDEDP if we found a builtin to expand.  */
13672static rtx
13673paired_expand_builtin (tree exp, rtx target, bool * expandedp)
13674{
13675  tree fndecl = TREE_OPERAND (CALL_EXPR_FN (exp), 0);
13676  enum rs6000_builtins fcode = (enum rs6000_builtins) DECL_FUNCTION_CODE (fndecl);
13677  const struct builtin_description *d;
13678  size_t i;
13679
13680  *expandedp = true;
13681
13682  switch (fcode)
13683    {
13684    case PAIRED_BUILTIN_STX:
13685      return paired_expand_stv_builtin (CODE_FOR_paired_stx, exp);
13686    case PAIRED_BUILTIN_LX:
13687      return paired_expand_lv_builtin (CODE_FOR_paired_lx, exp, target);
13688    default:
13689      break;
13690      /* Fall through.  */
13691    }
13692
13693  /* Expand the paired predicates.  */
13694  d = bdesc_paired_preds;
13695  for (i = 0; i < ARRAY_SIZE (bdesc_paired_preds); i++, d++)
13696    if (d->code == fcode)
13697      return paired_expand_predicate_builtin (d->icode, exp, target);
13698
13699  *expandedp = false;
13700  return NULL_RTX;
13701}
13702
13703/* Binops that need to be initialized manually, but can be expanded
13704   automagically by rs6000_expand_binop_builtin.  */
13705static const struct builtin_description bdesc_2arg_spe[] =
13706{
13707  { RS6000_BTM_SPE, CODE_FOR_spe_evlddx, "__builtin_spe_evlddx", SPE_BUILTIN_EVLDDX },
13708  { RS6000_BTM_SPE, CODE_FOR_spe_evldwx, "__builtin_spe_evldwx", SPE_BUILTIN_EVLDWX },
13709  { RS6000_BTM_SPE, CODE_FOR_spe_evldhx, "__builtin_spe_evldhx", SPE_BUILTIN_EVLDHX },
13710  { RS6000_BTM_SPE, CODE_FOR_spe_evlwhex, "__builtin_spe_evlwhex", SPE_BUILTIN_EVLWHEX },
13711  { RS6000_BTM_SPE, CODE_FOR_spe_evlwhoux, "__builtin_spe_evlwhoux", SPE_BUILTIN_EVLWHOUX },
13712  { RS6000_BTM_SPE, CODE_FOR_spe_evlwhosx, "__builtin_spe_evlwhosx", SPE_BUILTIN_EVLWHOSX },
13713  { RS6000_BTM_SPE, CODE_FOR_spe_evlwwsplatx, "__builtin_spe_evlwwsplatx", SPE_BUILTIN_EVLWWSPLATX },
13714  { RS6000_BTM_SPE, CODE_FOR_spe_evlwhsplatx, "__builtin_spe_evlwhsplatx", SPE_BUILTIN_EVLWHSPLATX },
13715  { RS6000_BTM_SPE, CODE_FOR_spe_evlhhesplatx, "__builtin_spe_evlhhesplatx", SPE_BUILTIN_EVLHHESPLATX },
13716  { RS6000_BTM_SPE, CODE_FOR_spe_evlhhousplatx, "__builtin_spe_evlhhousplatx", SPE_BUILTIN_EVLHHOUSPLATX },
13717  { RS6000_BTM_SPE, CODE_FOR_spe_evlhhossplatx, "__builtin_spe_evlhhossplatx", SPE_BUILTIN_EVLHHOSSPLATX },
13718  { RS6000_BTM_SPE, CODE_FOR_spe_evldd, "__builtin_spe_evldd", SPE_BUILTIN_EVLDD },
13719  { RS6000_BTM_SPE, CODE_FOR_spe_evldw, "__builtin_spe_evldw", SPE_BUILTIN_EVLDW },
13720  { RS6000_BTM_SPE, CODE_FOR_spe_evldh, "__builtin_spe_evldh", SPE_BUILTIN_EVLDH },
13721  { RS6000_BTM_SPE, CODE_FOR_spe_evlwhe, "__builtin_spe_evlwhe", SPE_BUILTIN_EVLWHE },
13722  { RS6000_BTM_SPE, CODE_FOR_spe_evlwhou, "__builtin_spe_evlwhou", SPE_BUILTIN_EVLWHOU },
13723  { RS6000_BTM_SPE, CODE_FOR_spe_evlwhos, "__builtin_spe_evlwhos", SPE_BUILTIN_EVLWHOS },
13724  { RS6000_BTM_SPE, CODE_FOR_spe_evlwwsplat, "__builtin_spe_evlwwsplat", SPE_BUILTIN_EVLWWSPLAT },
13725  { RS6000_BTM_SPE, CODE_FOR_spe_evlwhsplat, "__builtin_spe_evlwhsplat", SPE_BUILTIN_EVLWHSPLAT },
13726  { RS6000_BTM_SPE, CODE_FOR_spe_evlhhesplat, "__builtin_spe_evlhhesplat", SPE_BUILTIN_EVLHHESPLAT },
13727  { RS6000_BTM_SPE, CODE_FOR_spe_evlhhousplat, "__builtin_spe_evlhhousplat", SPE_BUILTIN_EVLHHOUSPLAT },
13728  { RS6000_BTM_SPE, CODE_FOR_spe_evlhhossplat, "__builtin_spe_evlhhossplat", SPE_BUILTIN_EVLHHOSSPLAT }
13729};
13730
13731/* Expand the builtin in EXP and store the result in TARGET.  Store
13732   true in *EXPANDEDP if we found a builtin to expand.
13733
13734   This expands the SPE builtins that are not simple unary and binary
13735   operations.  */
13736static rtx
13737spe_expand_builtin (tree exp, rtx target, bool *expandedp)
13738{
13739  tree fndecl = TREE_OPERAND (CALL_EXPR_FN (exp), 0);
13740  tree arg1, arg0;
13741  enum rs6000_builtins fcode = (enum rs6000_builtins) DECL_FUNCTION_CODE (fndecl);
13742  enum insn_code icode;
13743  machine_mode tmode, mode0;
13744  rtx pat, op0;
13745  const struct builtin_description *d;
13746  size_t i;
13747
13748  *expandedp = true;
13749
13750  /* Syntax check for a 5-bit unsigned immediate.  */
13751  switch (fcode)
13752    {
13753    case SPE_BUILTIN_EVSTDD:
13754    case SPE_BUILTIN_EVSTDH:
13755    case SPE_BUILTIN_EVSTDW:
13756    case SPE_BUILTIN_EVSTWHE:
13757    case SPE_BUILTIN_EVSTWHO:
13758    case SPE_BUILTIN_EVSTWWE:
13759    case SPE_BUILTIN_EVSTWWO:
13760      arg1 = CALL_EXPR_ARG (exp, 2);
13761      if (TREE_CODE (arg1) != INTEGER_CST
13762	  || TREE_INT_CST_LOW (arg1) & ~0x1f)
13763	{
13764	  error ("argument 2 must be a 5-bit unsigned literal");
13765	  return const0_rtx;
13766	}
13767      break;
13768    default:
13769      break;
13770    }
13771
13772  /* The evsplat*i instructions are not quite generic.  */
13773  switch (fcode)
13774    {
13775    case SPE_BUILTIN_EVSPLATFI:
13776      return rs6000_expand_unop_builtin (CODE_FOR_spe_evsplatfi,
13777					 exp, target);
13778    case SPE_BUILTIN_EVSPLATI:
13779      return rs6000_expand_unop_builtin (CODE_FOR_spe_evsplati,
13780					 exp, target);
13781    default:
13782      break;
13783    }
13784
13785  d = bdesc_2arg_spe;
13786  for (i = 0; i < ARRAY_SIZE (bdesc_2arg_spe); ++i, ++d)
13787    if (d->code == fcode)
13788      return rs6000_expand_binop_builtin (d->icode, exp, target);
13789
13790  d = bdesc_spe_predicates;
13791  for (i = 0; i < ARRAY_SIZE (bdesc_spe_predicates); ++i, ++d)
13792    if (d->code == fcode)
13793      return spe_expand_predicate_builtin (d->icode, exp, target);
13794
13795  d = bdesc_spe_evsel;
13796  for (i = 0; i < ARRAY_SIZE (bdesc_spe_evsel); ++i, ++d)
13797    if (d->code == fcode)
13798      return spe_expand_evsel_builtin (d->icode, exp, target);
13799
13800  switch (fcode)
13801    {
13802    case SPE_BUILTIN_EVSTDDX:
13803      return spe_expand_stv_builtin (CODE_FOR_spe_evstddx, exp);
13804    case SPE_BUILTIN_EVSTDHX:
13805      return spe_expand_stv_builtin (CODE_FOR_spe_evstdhx, exp);
13806    case SPE_BUILTIN_EVSTDWX:
13807      return spe_expand_stv_builtin (CODE_FOR_spe_evstdwx, exp);
13808    case SPE_BUILTIN_EVSTWHEX:
13809      return spe_expand_stv_builtin (CODE_FOR_spe_evstwhex, exp);
13810    case SPE_BUILTIN_EVSTWHOX:
13811      return spe_expand_stv_builtin (CODE_FOR_spe_evstwhox, exp);
13812    case SPE_BUILTIN_EVSTWWEX:
13813      return spe_expand_stv_builtin (CODE_FOR_spe_evstwwex, exp);
13814    case SPE_BUILTIN_EVSTWWOX:
13815      return spe_expand_stv_builtin (CODE_FOR_spe_evstwwox, exp);
13816    case SPE_BUILTIN_EVSTDD:
13817      return spe_expand_stv_builtin (CODE_FOR_spe_evstdd, exp);
13818    case SPE_BUILTIN_EVSTDH:
13819      return spe_expand_stv_builtin (CODE_FOR_spe_evstdh, exp);
13820    case SPE_BUILTIN_EVSTDW:
13821      return spe_expand_stv_builtin (CODE_FOR_spe_evstdw, exp);
13822    case SPE_BUILTIN_EVSTWHE:
13823      return spe_expand_stv_builtin (CODE_FOR_spe_evstwhe, exp);
13824    case SPE_BUILTIN_EVSTWHO:
13825      return spe_expand_stv_builtin (CODE_FOR_spe_evstwho, exp);
13826    case SPE_BUILTIN_EVSTWWE:
13827      return spe_expand_stv_builtin (CODE_FOR_spe_evstwwe, exp);
13828    case SPE_BUILTIN_EVSTWWO:
13829      return spe_expand_stv_builtin (CODE_FOR_spe_evstwwo, exp);
13830    case SPE_BUILTIN_MFSPEFSCR:
13831      icode = CODE_FOR_spe_mfspefscr;
13832      tmode = insn_data[icode].operand[0].mode;
13833
13834      if (target == 0
13835	  || GET_MODE (target) != tmode
13836	  || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
13837	target = gen_reg_rtx (tmode);
13838
13839      pat = GEN_FCN (icode) (target);
13840      if (! pat)
13841	return 0;
13842      emit_insn (pat);
13843      return target;
13844    case SPE_BUILTIN_MTSPEFSCR:
13845      icode = CODE_FOR_spe_mtspefscr;
13846      arg0 = CALL_EXPR_ARG (exp, 0);
13847      op0 = expand_normal (arg0);
13848      mode0 = insn_data[icode].operand[0].mode;
13849
13850      if (arg0 == error_mark_node)
13851	return const0_rtx;
13852
13853      if (! (*insn_data[icode].operand[0].predicate) (op0, mode0))
13854	op0 = copy_to_mode_reg (mode0, op0);
13855
13856      pat = GEN_FCN (icode) (op0);
13857      if (pat)
13858	emit_insn (pat);
13859      return NULL_RTX;
13860    default:
13861      break;
13862    }
13863
13864  *expandedp = false;
13865  return NULL_RTX;
13866}
13867
13868static rtx
13869paired_expand_predicate_builtin (enum insn_code icode, tree exp, rtx target)
13870{
13871  rtx pat, scratch, tmp;
13872  tree form = CALL_EXPR_ARG (exp, 0);
13873  tree arg0 = CALL_EXPR_ARG (exp, 1);
13874  tree arg1 = CALL_EXPR_ARG (exp, 2);
13875  rtx op0 = expand_normal (arg0);
13876  rtx op1 = expand_normal (arg1);
13877  machine_mode mode0 = insn_data[icode].operand[1].mode;
13878  machine_mode mode1 = insn_data[icode].operand[2].mode;
13879  int form_int;
13880  enum rtx_code code;
13881
13882  if (TREE_CODE (form) != INTEGER_CST)
13883    {
13884      error ("argument 1 of __builtin_paired_predicate must be a constant");
13885      return const0_rtx;
13886    }
13887  else
13888    form_int = TREE_INT_CST_LOW (form);
13889
13890  gcc_assert (mode0 == mode1);
13891
13892  if (arg0 == error_mark_node || arg1 == error_mark_node)
13893    return const0_rtx;
13894
13895  if (target == 0
13896      || GET_MODE (target) != SImode
13897      || !(*insn_data[icode].operand[0].predicate) (target, SImode))
13898    target = gen_reg_rtx (SImode);
13899  if (!(*insn_data[icode].operand[1].predicate) (op0, mode0))
13900    op0 = copy_to_mode_reg (mode0, op0);
13901  if (!(*insn_data[icode].operand[2].predicate) (op1, mode1))
13902    op1 = copy_to_mode_reg (mode1, op1);
13903
13904  scratch = gen_reg_rtx (CCFPmode);
13905
13906  pat = GEN_FCN (icode) (scratch, op0, op1);
13907  if (!pat)
13908    return const0_rtx;
13909
13910  emit_insn (pat);
13911
13912  switch (form_int)
13913    {
13914      /* LT bit.  */
13915    case 0:
13916      code = LT;
13917      break;
13918      /* GT bit.  */
13919    case 1:
13920      code = GT;
13921      break;
13922      /* EQ bit.  */
13923    case 2:
13924      code = EQ;
13925      break;
13926      /* UN bit.  */
13927    case 3:
13928      emit_insn (gen_move_from_CR_ov_bit (target, scratch));
13929      return target;
13930    default:
13931      error ("argument 1 of __builtin_paired_predicate is out of range");
13932      return const0_rtx;
13933    }
13934
13935  tmp = gen_rtx_fmt_ee (code, SImode, scratch, const0_rtx);
13936  emit_move_insn (target, tmp);
13937  return target;
13938}
13939
13940static rtx
13941spe_expand_predicate_builtin (enum insn_code icode, tree exp, rtx target)
13942{
13943  rtx pat, scratch, tmp;
13944  tree form = CALL_EXPR_ARG (exp, 0);
13945  tree arg0 = CALL_EXPR_ARG (exp, 1);
13946  tree arg1 = CALL_EXPR_ARG (exp, 2);
13947  rtx op0 = expand_normal (arg0);
13948  rtx op1 = expand_normal (arg1);
13949  machine_mode mode0 = insn_data[icode].operand[1].mode;
13950  machine_mode mode1 = insn_data[icode].operand[2].mode;
13951  int form_int;
13952  enum rtx_code code;
13953
13954  if (TREE_CODE (form) != INTEGER_CST)
13955    {
13956      error ("argument 1 of __builtin_spe_predicate must be a constant");
13957      return const0_rtx;
13958    }
13959  else
13960    form_int = TREE_INT_CST_LOW (form);
13961
13962  gcc_assert (mode0 == mode1);
13963
13964  if (arg0 == error_mark_node || arg1 == error_mark_node)
13965    return const0_rtx;
13966
13967  if (target == 0
13968      || GET_MODE (target) != SImode
13969      || ! (*insn_data[icode].operand[0].predicate) (target, SImode))
13970    target = gen_reg_rtx (SImode);
13971
13972  if (! (*insn_data[icode].operand[1].predicate) (op0, mode0))
13973    op0 = copy_to_mode_reg (mode0, op0);
13974  if (! (*insn_data[icode].operand[2].predicate) (op1, mode1))
13975    op1 = copy_to_mode_reg (mode1, op1);
13976
13977  scratch = gen_reg_rtx (CCmode);
13978
13979  pat = GEN_FCN (icode) (scratch, op0, op1);
13980  if (! pat)
13981    return const0_rtx;
13982  emit_insn (pat);
13983
13984  /* There are 4 variants for each predicate: _any_, _all_, _upper_,
13985     _lower_.  We use one compare, but look in different bits of the
13986     CR for each variant.
13987
13988     There are 2 elements in each SPE simd type (upper/lower).  The CR
13989     bits are set as follows:
13990
13991     BIT0  | BIT 1  | BIT 2   | BIT 3
13992     U     |   L    | (U | L) | (U & L)
13993
13994     So, for an "all" relationship, BIT 3 would be set.
13995     For an "any" relationship, BIT 2 would be set.  Etc.
13996
13997     Following traditional nomenclature, these bits map to:
13998
13999     BIT0  | BIT 1  | BIT 2   | BIT 3
14000     LT    | GT     | EQ      | OV
14001
14002     Later, we will generate rtl to look in the LT/EQ/EQ/OV bits.
14003  */
14004
14005  switch (form_int)
14006    {
14007      /* All variant.  OV bit.  */
14008    case 0:
14009      /* We need to get to the OV bit, which is the ORDERED bit.  We
14010	 could generate (ordered:SI (reg:CC xx) (const_int 0)), but
14011	 that's ugly and will make validate_condition_mode die.
14012	 So let's just use another pattern.  */
14013      emit_insn (gen_move_from_CR_ov_bit (target, scratch));
14014      return target;
14015      /* Any variant.  EQ bit.  */
14016    case 1:
14017      code = EQ;
14018      break;
14019      /* Upper variant.  LT bit.  */
14020    case 2:
14021      code = LT;
14022      break;
14023      /* Lower variant.  GT bit.  */
14024    case 3:
14025      code = GT;
14026      break;
14027    default:
14028      error ("argument 1 of __builtin_spe_predicate is out of range");
14029      return const0_rtx;
14030    }
14031
14032  tmp = gen_rtx_fmt_ee (code, SImode, scratch, const0_rtx);
14033  emit_move_insn (target, tmp);
14034
14035  return target;
14036}
14037
14038/* The evsel builtins look like this:
14039
14040     e = __builtin_spe_evsel_OP (a, b, c, d);
14041
14042   and work like this:
14043
14044     e[upper] = a[upper] *OP* b[upper] ? c[upper] : d[upper];
14045     e[lower] = a[lower] *OP* b[lower] ? c[lower] : d[lower];
14046*/
14047
14048static rtx
14049spe_expand_evsel_builtin (enum insn_code icode, tree exp, rtx target)
14050{
14051  rtx pat, scratch;
14052  tree arg0 = CALL_EXPR_ARG (exp, 0);
14053  tree arg1 = CALL_EXPR_ARG (exp, 1);
14054  tree arg2 = CALL_EXPR_ARG (exp, 2);
14055  tree arg3 = CALL_EXPR_ARG (exp, 3);
14056  rtx op0 = expand_normal (arg0);
14057  rtx op1 = expand_normal (arg1);
14058  rtx op2 = expand_normal (arg2);
14059  rtx op3 = expand_normal (arg3);
14060  machine_mode mode0 = insn_data[icode].operand[1].mode;
14061  machine_mode mode1 = insn_data[icode].operand[2].mode;
14062
14063  gcc_assert (mode0 == mode1);
14064
14065  if (arg0 == error_mark_node || arg1 == error_mark_node
14066      || arg2 == error_mark_node || arg3 == error_mark_node)
14067    return const0_rtx;
14068
14069  if (target == 0
14070      || GET_MODE (target) != mode0
14071      || ! (*insn_data[icode].operand[0].predicate) (target, mode0))
14072    target = gen_reg_rtx (mode0);
14073
14074  if (! (*insn_data[icode].operand[1].predicate) (op0, mode0))
14075    op0 = copy_to_mode_reg (mode0, op0);
14076  if (! (*insn_data[icode].operand[1].predicate) (op1, mode1))
14077    op1 = copy_to_mode_reg (mode0, op1);
14078  if (! (*insn_data[icode].operand[1].predicate) (op2, mode1))
14079    op2 = copy_to_mode_reg (mode0, op2);
14080  if (! (*insn_data[icode].operand[1].predicate) (op3, mode1))
14081    op3 = copy_to_mode_reg (mode0, op3);
14082
14083  /* Generate the compare.  */
14084  scratch = gen_reg_rtx (CCmode);
14085  pat = GEN_FCN (icode) (scratch, op0, op1);
14086  if (! pat)
14087    return const0_rtx;
14088  emit_insn (pat);
14089
14090  if (mode0 == V2SImode)
14091    emit_insn (gen_spe_evsel (target, op2, op3, scratch));
14092  else
14093    emit_insn (gen_spe_evsel_fs (target, op2, op3, scratch));
14094
14095  return target;
14096}
14097
14098/* Raise an error message for a builtin function that is called without the
14099   appropriate target options being set.  */
14100
14101static void
14102rs6000_invalid_builtin (enum rs6000_builtins fncode)
14103{
14104  size_t uns_fncode = (size_t)fncode;
14105  const char *name = rs6000_builtin_info[uns_fncode].name;
14106  HOST_WIDE_INT fnmask = rs6000_builtin_info[uns_fncode].mask;
14107
14108  gcc_assert (name != NULL);
14109  if ((fnmask & RS6000_BTM_CELL) != 0)
14110    error ("Builtin function %s is only valid for the cell processor", name);
14111  else if ((fnmask & RS6000_BTM_VSX) != 0)
14112    error ("Builtin function %s requires the -mvsx option", name);
14113  else if ((fnmask & RS6000_BTM_HTM) != 0)
14114    error ("Builtin function %s requires the -mhtm option", name);
14115  else if ((fnmask & RS6000_BTM_ALTIVEC) != 0)
14116    error ("Builtin function %s requires the -maltivec option", name);
14117  else if ((fnmask & RS6000_BTM_PAIRED) != 0)
14118    error ("Builtin function %s requires the -mpaired option", name);
14119  else if ((fnmask & RS6000_BTM_SPE) != 0)
14120    error ("Builtin function %s requires the -mspe option", name);
14121  else if ((fnmask & (RS6000_BTM_DFP | RS6000_BTM_P8_VECTOR))
14122	   == (RS6000_BTM_DFP | RS6000_BTM_P8_VECTOR))
14123    error ("Builtin function %s requires the -mhard-dfp and"
14124	   " -mpower8-vector options", name);
14125  else if ((fnmask & RS6000_BTM_DFP) != 0)
14126    error ("Builtin function %s requires the -mhard-dfp option", name);
14127  else if ((fnmask & RS6000_BTM_P8_VECTOR) != 0)
14128    error ("Builtin function %s requires the -mpower8-vector option", name);
14129  else if ((fnmask & (RS6000_BTM_HARD_FLOAT | RS6000_BTM_LDBL128))
14130	   == (RS6000_BTM_HARD_FLOAT | RS6000_BTM_LDBL128))
14131    error ("Builtin function %s requires the -mhard-float and"
14132	   " -mlong-double-128 options", name);
14133  else if ((fnmask & RS6000_BTM_HARD_FLOAT) != 0)
14134    error ("Builtin function %s requires the -mhard-float option", name);
14135  else
14136    error ("Builtin function %s is not supported with the current options",
14137	   name);
14138}
14139
14140/* Expand an expression EXP that calls a built-in function,
14141   with result going to TARGET if that's convenient
14142   (and in mode MODE if that's convenient).
14143   SUBTARGET may be used as the target for computing one of EXP's operands.
14144   IGNORE is nonzero if the value is to be ignored.  */
14145
14146static rtx
14147rs6000_expand_builtin (tree exp, rtx target, rtx subtarget ATTRIBUTE_UNUSED,
14148		       machine_mode mode ATTRIBUTE_UNUSED,
14149		       int ignore ATTRIBUTE_UNUSED)
14150{
14151  tree fndecl = TREE_OPERAND (CALL_EXPR_FN (exp), 0);
14152  enum rs6000_builtins fcode
14153    = (enum rs6000_builtins)DECL_FUNCTION_CODE (fndecl);
14154  size_t uns_fcode = (size_t)fcode;
14155  const struct builtin_description *d;
14156  size_t i;
14157  rtx ret;
14158  bool success;
14159  HOST_WIDE_INT mask = rs6000_builtin_info[uns_fcode].mask;
14160  bool func_valid_p = ((rs6000_builtin_mask & mask) == mask);
14161
14162  if (TARGET_DEBUG_BUILTIN)
14163    {
14164      enum insn_code icode = rs6000_builtin_info[uns_fcode].icode;
14165      const char *name1 = rs6000_builtin_info[uns_fcode].name;
14166      const char *name2 = ((icode != CODE_FOR_nothing)
14167			   ? get_insn_name ((int)icode)
14168			   : "nothing");
14169      const char *name3;
14170
14171      switch (rs6000_builtin_info[uns_fcode].attr & RS6000_BTC_TYPE_MASK)
14172	{
14173	default:		   name3 = "unknown";	break;
14174	case RS6000_BTC_SPECIAL:   name3 = "special";	break;
14175	case RS6000_BTC_UNARY:	   name3 = "unary";	break;
14176	case RS6000_BTC_BINARY:	   name3 = "binary";	break;
14177	case RS6000_BTC_TERNARY:   name3 = "ternary";	break;
14178	case RS6000_BTC_PREDICATE: name3 = "predicate";	break;
14179	case RS6000_BTC_ABS:	   name3 = "abs";	break;
14180	case RS6000_BTC_EVSEL:	   name3 = "evsel";	break;
14181	case RS6000_BTC_DST:	   name3 = "dst";	break;
14182	}
14183
14184
14185      fprintf (stderr,
14186	       "rs6000_expand_builtin, %s (%d), insn = %s (%d), type=%s%s\n",
14187	       (name1) ? name1 : "---", fcode,
14188	       (name2) ? name2 : "---", (int)icode,
14189	       name3,
14190	       func_valid_p ? "" : ", not valid");
14191    }
14192
14193  if (!func_valid_p)
14194    {
14195      rs6000_invalid_builtin (fcode);
14196
14197      /* Given it is invalid, just generate a normal call.  */
14198      return expand_call (exp, target, ignore);
14199    }
14200
14201  switch (fcode)
14202    {
14203    case RS6000_BUILTIN_RECIP:
14204      return rs6000_expand_binop_builtin (CODE_FOR_recipdf3, exp, target);
14205
14206    case RS6000_BUILTIN_RECIPF:
14207      return rs6000_expand_binop_builtin (CODE_FOR_recipsf3, exp, target);
14208
14209    case RS6000_BUILTIN_RSQRTF:
14210      return rs6000_expand_unop_builtin (CODE_FOR_rsqrtsf2, exp, target);
14211
14212    case RS6000_BUILTIN_RSQRT:
14213      return rs6000_expand_unop_builtin (CODE_FOR_rsqrtdf2, exp, target);
14214
14215    case POWER7_BUILTIN_BPERMD:
14216      return rs6000_expand_binop_builtin (((TARGET_64BIT)
14217					   ? CODE_FOR_bpermd_di
14218					   : CODE_FOR_bpermd_si), exp, target);
14219
14220    case RS6000_BUILTIN_GET_TB:
14221      return rs6000_expand_zeroop_builtin (CODE_FOR_rs6000_get_timebase,
14222					   target);
14223
14224    case RS6000_BUILTIN_MFTB:
14225      return rs6000_expand_zeroop_builtin (((TARGET_64BIT)
14226					    ? CODE_FOR_rs6000_mftb_di
14227					    : CODE_FOR_rs6000_mftb_si),
14228					   target);
14229
14230    case RS6000_BUILTIN_MFFS:
14231      return rs6000_expand_zeroop_builtin (CODE_FOR_rs6000_mffs, target);
14232
14233    case RS6000_BUILTIN_MTFSF:
14234      return rs6000_expand_mtfsf_builtin (CODE_FOR_rs6000_mtfsf, exp);
14235
14236    case ALTIVEC_BUILTIN_MASK_FOR_LOAD:
14237    case ALTIVEC_BUILTIN_MASK_FOR_STORE:
14238      {
14239	int icode = (BYTES_BIG_ENDIAN ? (int) CODE_FOR_altivec_lvsr_direct
14240		     : (int) CODE_FOR_altivec_lvsl_direct);
14241	machine_mode tmode = insn_data[icode].operand[0].mode;
14242	machine_mode mode = insn_data[icode].operand[1].mode;
14243	tree arg;
14244	rtx op, addr, pat;
14245
14246	gcc_assert (TARGET_ALTIVEC);
14247
14248	arg = CALL_EXPR_ARG (exp, 0);
14249	gcc_assert (POINTER_TYPE_P (TREE_TYPE (arg)));
14250	op = expand_expr (arg, NULL_RTX, Pmode, EXPAND_NORMAL);
14251	addr = memory_address (mode, op);
14252	if (fcode == ALTIVEC_BUILTIN_MASK_FOR_STORE)
14253	  op = addr;
14254	else
14255	  {
14256	    /* For the load case need to negate the address.  */
14257	    op = gen_reg_rtx (GET_MODE (addr));
14258	    emit_insn (gen_rtx_SET (VOIDmode, op,
14259				    gen_rtx_NEG (GET_MODE (addr), addr)));
14260	  }
14261	op = gen_rtx_MEM (mode, op);
14262
14263	if (target == 0
14264	    || GET_MODE (target) != tmode
14265	    || ! (*insn_data[icode].operand[0].predicate) (target, tmode))
14266	  target = gen_reg_rtx (tmode);
14267
14268	pat = GEN_FCN (icode) (target, op);
14269	if (!pat)
14270	  return 0;
14271	emit_insn (pat);
14272
14273	return target;
14274      }
14275
14276    case ALTIVEC_BUILTIN_VCFUX:
14277    case ALTIVEC_BUILTIN_VCFSX:
14278    case ALTIVEC_BUILTIN_VCTUXS:
14279    case ALTIVEC_BUILTIN_VCTSXS:
14280  /* FIXME: There's got to be a nicer way to handle this case than
14281     constructing a new CALL_EXPR.  */
14282      if (call_expr_nargs (exp) == 1)
14283	{
14284	  exp = build_call_nary (TREE_TYPE (exp), CALL_EXPR_FN (exp),
14285				 2, CALL_EXPR_ARG (exp, 0), integer_zero_node);
14286	}
14287      break;
14288
14289    default:
14290      break;
14291    }
14292
14293  if (TARGET_ALTIVEC)
14294    {
14295      ret = altivec_expand_builtin (exp, target, &success);
14296
14297      if (success)
14298	return ret;
14299    }
14300  if (TARGET_SPE)
14301    {
14302      ret = spe_expand_builtin (exp, target, &success);
14303
14304      if (success)
14305	return ret;
14306    }
14307  if (TARGET_PAIRED_FLOAT)
14308    {
14309      ret = paired_expand_builtin (exp, target, &success);
14310
14311      if (success)
14312	return ret;
14313    }
14314  if (TARGET_HTM)
14315    {
14316      ret = htm_expand_builtin (exp, target, &success);
14317
14318      if (success)
14319	return ret;
14320    }
14321
14322  unsigned attr = rs6000_builtin_info[uns_fcode].attr & RS6000_BTC_TYPE_MASK;
14323  gcc_assert (attr == RS6000_BTC_UNARY
14324	      || attr == RS6000_BTC_BINARY
14325	      || attr == RS6000_BTC_TERNARY);
14326
14327  /* Handle simple unary operations.  */
14328  d = bdesc_1arg;
14329  for (i = 0; i < ARRAY_SIZE (bdesc_1arg); i++, d++)
14330    if (d->code == fcode)
14331      return rs6000_expand_unop_builtin (d->icode, exp, target);
14332
14333  /* Handle simple binary operations.  */
14334  d = bdesc_2arg;
14335  for (i = 0; i < ARRAY_SIZE (bdesc_2arg); i++, d++)
14336    if (d->code == fcode)
14337      return rs6000_expand_binop_builtin (d->icode, exp, target);
14338
14339  /* Handle simple ternary operations.  */
14340  d = bdesc_3arg;
14341  for (i = 0; i < ARRAY_SIZE  (bdesc_3arg); i++, d++)
14342    if (d->code == fcode)
14343      return rs6000_expand_ternop_builtin (d->icode, exp, target);
14344
14345  gcc_unreachable ();
14346}
14347
14348static void
14349rs6000_init_builtins (void)
14350{
14351  tree tdecl;
14352  tree ftype;
14353  machine_mode mode;
14354
14355  if (TARGET_DEBUG_BUILTIN)
14356    fprintf (stderr, "rs6000_init_builtins%s%s%s%s\n",
14357	     (TARGET_PAIRED_FLOAT) ? ", paired"	 : "",
14358	     (TARGET_SPE)	   ? ", spe"	 : "",
14359	     (TARGET_ALTIVEC)	   ? ", altivec" : "",
14360	     (TARGET_VSX)	   ? ", vsx"	 : "");
14361
14362  V2SI_type_node = build_vector_type (intSI_type_node, 2);
14363  V2SF_type_node = build_vector_type (float_type_node, 2);
14364  V2DI_type_node = build_vector_type (intDI_type_node, 2);
14365  V2DF_type_node = build_vector_type (double_type_node, 2);
14366  V4HI_type_node = build_vector_type (intHI_type_node, 4);
14367  V4SI_type_node = build_vector_type (intSI_type_node, 4);
14368  V4SF_type_node = build_vector_type (float_type_node, 4);
14369  V8HI_type_node = build_vector_type (intHI_type_node, 8);
14370  V16QI_type_node = build_vector_type (intQI_type_node, 16);
14371
14372  unsigned_V16QI_type_node = build_vector_type (unsigned_intQI_type_node, 16);
14373  unsigned_V8HI_type_node = build_vector_type (unsigned_intHI_type_node, 8);
14374  unsigned_V4SI_type_node = build_vector_type (unsigned_intSI_type_node, 4);
14375  unsigned_V2DI_type_node = build_vector_type (unsigned_intDI_type_node, 2);
14376
14377  opaque_V2SF_type_node = build_opaque_vector_type (float_type_node, 2);
14378  opaque_V2SI_type_node = build_opaque_vector_type (intSI_type_node, 2);
14379  opaque_p_V2SI_type_node = build_pointer_type (opaque_V2SI_type_node);
14380  opaque_V4SI_type_node = build_opaque_vector_type (intSI_type_node, 4);
14381
14382  /* We use V1TI mode as a special container to hold __int128_t items that
14383     must live in VSX registers.  */
14384  if (intTI_type_node)
14385    {
14386      V1TI_type_node = build_vector_type (intTI_type_node, 1);
14387      unsigned_V1TI_type_node = build_vector_type (unsigned_intTI_type_node, 1);
14388    }
14389
14390  /* The 'vector bool ...' types must be kept distinct from 'vector unsigned ...'
14391     types, especially in C++ land.  Similarly, 'vector pixel' is distinct from
14392     'vector unsigned short'.  */
14393
14394  bool_char_type_node = build_distinct_type_copy (unsigned_intQI_type_node);
14395  bool_short_type_node = build_distinct_type_copy (unsigned_intHI_type_node);
14396  bool_int_type_node = build_distinct_type_copy (unsigned_intSI_type_node);
14397  bool_long_type_node = build_distinct_type_copy (unsigned_intDI_type_node);
14398  pixel_type_node = build_distinct_type_copy (unsigned_intHI_type_node);
14399
14400  long_integer_type_internal_node = long_integer_type_node;
14401  long_unsigned_type_internal_node = long_unsigned_type_node;
14402  long_long_integer_type_internal_node = long_long_integer_type_node;
14403  long_long_unsigned_type_internal_node = long_long_unsigned_type_node;
14404  intQI_type_internal_node = intQI_type_node;
14405  uintQI_type_internal_node = unsigned_intQI_type_node;
14406  intHI_type_internal_node = intHI_type_node;
14407  uintHI_type_internal_node = unsigned_intHI_type_node;
14408  intSI_type_internal_node = intSI_type_node;
14409  uintSI_type_internal_node = unsigned_intSI_type_node;
14410  intDI_type_internal_node = intDI_type_node;
14411  uintDI_type_internal_node = unsigned_intDI_type_node;
14412  intTI_type_internal_node = intTI_type_node;
14413  uintTI_type_internal_node = unsigned_intTI_type_node;
14414  float_type_internal_node = float_type_node;
14415  double_type_internal_node = double_type_node;
14416  long_double_type_internal_node = long_double_type_node;
14417  dfloat64_type_internal_node = dfloat64_type_node;
14418  dfloat128_type_internal_node = dfloat128_type_node;
14419  void_type_internal_node = void_type_node;
14420
14421  /* Initialize the modes for builtin_function_type, mapping a machine mode to
14422     tree type node.  */
14423  builtin_mode_to_type[QImode][0] = integer_type_node;
14424  builtin_mode_to_type[HImode][0] = integer_type_node;
14425  builtin_mode_to_type[SImode][0] = intSI_type_node;
14426  builtin_mode_to_type[SImode][1] = unsigned_intSI_type_node;
14427  builtin_mode_to_type[DImode][0] = intDI_type_node;
14428  builtin_mode_to_type[DImode][1] = unsigned_intDI_type_node;
14429  builtin_mode_to_type[TImode][0] = intTI_type_node;
14430  builtin_mode_to_type[TImode][1] = unsigned_intTI_type_node;
14431  builtin_mode_to_type[SFmode][0] = float_type_node;
14432  builtin_mode_to_type[DFmode][0] = double_type_node;
14433  builtin_mode_to_type[TFmode][0] = long_double_type_node;
14434  builtin_mode_to_type[DDmode][0] = dfloat64_type_node;
14435  builtin_mode_to_type[TDmode][0] = dfloat128_type_node;
14436  builtin_mode_to_type[V1TImode][0] = V1TI_type_node;
14437  builtin_mode_to_type[V1TImode][1] = unsigned_V1TI_type_node;
14438  builtin_mode_to_type[V2SImode][0] = V2SI_type_node;
14439  builtin_mode_to_type[V2SFmode][0] = V2SF_type_node;
14440  builtin_mode_to_type[V2DImode][0] = V2DI_type_node;
14441  builtin_mode_to_type[V2DImode][1] = unsigned_V2DI_type_node;
14442  builtin_mode_to_type[V2DFmode][0] = V2DF_type_node;
14443  builtin_mode_to_type[V4HImode][0] = V4HI_type_node;
14444  builtin_mode_to_type[V4SImode][0] = V4SI_type_node;
14445  builtin_mode_to_type[V4SImode][1] = unsigned_V4SI_type_node;
14446  builtin_mode_to_type[V4SFmode][0] = V4SF_type_node;
14447  builtin_mode_to_type[V8HImode][0] = V8HI_type_node;
14448  builtin_mode_to_type[V8HImode][1] = unsigned_V8HI_type_node;
14449  builtin_mode_to_type[V16QImode][0] = V16QI_type_node;
14450  builtin_mode_to_type[V16QImode][1] = unsigned_V16QI_type_node;
14451
14452  tdecl = add_builtin_type ("__bool char", bool_char_type_node);
14453  TYPE_NAME (bool_char_type_node) = tdecl;
14454
14455  tdecl = add_builtin_type ("__bool short", bool_short_type_node);
14456  TYPE_NAME (bool_short_type_node) = tdecl;
14457
14458  tdecl = add_builtin_type ("__bool int", bool_int_type_node);
14459  TYPE_NAME (bool_int_type_node) = tdecl;
14460
14461  tdecl = add_builtin_type ("__pixel", pixel_type_node);
14462  TYPE_NAME (pixel_type_node) = tdecl;
14463
14464  bool_V16QI_type_node = build_vector_type (bool_char_type_node, 16);
14465  bool_V8HI_type_node = build_vector_type (bool_short_type_node, 8);
14466  bool_V4SI_type_node = build_vector_type (bool_int_type_node, 4);
14467  bool_V2DI_type_node = build_vector_type (bool_long_type_node, 2);
14468  pixel_V8HI_type_node = build_vector_type (pixel_type_node, 8);
14469
14470  tdecl = add_builtin_type ("__vector unsigned char", unsigned_V16QI_type_node);
14471  TYPE_NAME (unsigned_V16QI_type_node) = tdecl;
14472
14473  tdecl = add_builtin_type ("__vector signed char", V16QI_type_node);
14474  TYPE_NAME (V16QI_type_node) = tdecl;
14475
14476  tdecl = add_builtin_type ("__vector __bool char", bool_V16QI_type_node);
14477  TYPE_NAME ( bool_V16QI_type_node) = tdecl;
14478
14479  tdecl = add_builtin_type ("__vector unsigned short", unsigned_V8HI_type_node);
14480  TYPE_NAME (unsigned_V8HI_type_node) = tdecl;
14481
14482  tdecl = add_builtin_type ("__vector signed short", V8HI_type_node);
14483  TYPE_NAME (V8HI_type_node) = tdecl;
14484
14485  tdecl = add_builtin_type ("__vector __bool short", bool_V8HI_type_node);
14486  TYPE_NAME (bool_V8HI_type_node) = tdecl;
14487
14488  tdecl = add_builtin_type ("__vector unsigned int", unsigned_V4SI_type_node);
14489  TYPE_NAME (unsigned_V4SI_type_node) = tdecl;
14490
14491  tdecl = add_builtin_type ("__vector signed int", V4SI_type_node);
14492  TYPE_NAME (V4SI_type_node) = tdecl;
14493
14494  tdecl = add_builtin_type ("__vector __bool int", bool_V4SI_type_node);
14495  TYPE_NAME (bool_V4SI_type_node) = tdecl;
14496
14497  tdecl = add_builtin_type ("__vector float", V4SF_type_node);
14498  TYPE_NAME (V4SF_type_node) = tdecl;
14499
14500  tdecl = add_builtin_type ("__vector __pixel", pixel_V8HI_type_node);
14501  TYPE_NAME (pixel_V8HI_type_node) = tdecl;
14502
14503  tdecl = add_builtin_type ("__vector double", V2DF_type_node);
14504  TYPE_NAME (V2DF_type_node) = tdecl;
14505
14506  if (TARGET_POWERPC64)
14507    {
14508      tdecl = add_builtin_type ("__vector long", V2DI_type_node);
14509      TYPE_NAME (V2DI_type_node) = tdecl;
14510
14511      tdecl = add_builtin_type ("__vector unsigned long",
14512				unsigned_V2DI_type_node);
14513      TYPE_NAME (unsigned_V2DI_type_node) = tdecl;
14514
14515      tdecl = add_builtin_type ("__vector __bool long", bool_V2DI_type_node);
14516      TYPE_NAME (bool_V2DI_type_node) = tdecl;
14517    }
14518  else
14519    {
14520      tdecl = add_builtin_type ("__vector long long", V2DI_type_node);
14521      TYPE_NAME (V2DI_type_node) = tdecl;
14522
14523      tdecl = add_builtin_type ("__vector unsigned long long",
14524				unsigned_V2DI_type_node);
14525      TYPE_NAME (unsigned_V2DI_type_node) = tdecl;
14526
14527      tdecl = add_builtin_type ("__vector __bool long long",
14528				bool_V2DI_type_node);
14529      TYPE_NAME (bool_V2DI_type_node) = tdecl;
14530    }
14531
14532  if (V1TI_type_node)
14533    {
14534      tdecl = add_builtin_type ("__vector __int128", V1TI_type_node);
14535      TYPE_NAME (V1TI_type_node) = tdecl;
14536
14537      tdecl = add_builtin_type ("__vector unsigned __int128",
14538				unsigned_V1TI_type_node);
14539      TYPE_NAME (unsigned_V1TI_type_node) = tdecl;
14540    }
14541
14542  /* Paired and SPE builtins are only available if you build a compiler with
14543     the appropriate options, so only create those builtins with the
14544     appropriate compiler option.  Create Altivec and VSX builtins on machines
14545     with at least the general purpose extensions (970 and newer) to allow the
14546     use of the target attribute.  */
14547  if (TARGET_PAIRED_FLOAT)
14548    paired_init_builtins ();
14549  if (TARGET_SPE)
14550    spe_init_builtins ();
14551  if (TARGET_EXTRA_BUILTINS)
14552    altivec_init_builtins ();
14553  if (TARGET_HTM)
14554    htm_init_builtins ();
14555
14556  if (TARGET_EXTRA_BUILTINS || TARGET_SPE || TARGET_PAIRED_FLOAT)
14557    rs6000_common_init_builtins ();
14558
14559  ftype = builtin_function_type (DFmode, DFmode, DFmode, VOIDmode,
14560				 RS6000_BUILTIN_RECIP, "__builtin_recipdiv");
14561  def_builtin ("__builtin_recipdiv", ftype, RS6000_BUILTIN_RECIP);
14562
14563  ftype = builtin_function_type (SFmode, SFmode, SFmode, VOIDmode,
14564				 RS6000_BUILTIN_RECIPF, "__builtin_recipdivf");
14565  def_builtin ("__builtin_recipdivf", ftype, RS6000_BUILTIN_RECIPF);
14566
14567  ftype = builtin_function_type (DFmode, DFmode, VOIDmode, VOIDmode,
14568				 RS6000_BUILTIN_RSQRT, "__builtin_rsqrt");
14569  def_builtin ("__builtin_rsqrt", ftype, RS6000_BUILTIN_RSQRT);
14570
14571  ftype = builtin_function_type (SFmode, SFmode, VOIDmode, VOIDmode,
14572				 RS6000_BUILTIN_RSQRTF, "__builtin_rsqrtf");
14573  def_builtin ("__builtin_rsqrtf", ftype, RS6000_BUILTIN_RSQRTF);
14574
14575  mode = (TARGET_64BIT) ? DImode : SImode;
14576  ftype = builtin_function_type (mode, mode, mode, VOIDmode,
14577				 POWER7_BUILTIN_BPERMD, "__builtin_bpermd");
14578  def_builtin ("__builtin_bpermd", ftype, POWER7_BUILTIN_BPERMD);
14579
14580  ftype = build_function_type_list (unsigned_intDI_type_node,
14581				    NULL_TREE);
14582  def_builtin ("__builtin_ppc_get_timebase", ftype, RS6000_BUILTIN_GET_TB);
14583
14584  if (TARGET_64BIT)
14585    ftype = build_function_type_list (unsigned_intDI_type_node,
14586				      NULL_TREE);
14587  else
14588    ftype = build_function_type_list (unsigned_intSI_type_node,
14589				      NULL_TREE);
14590  def_builtin ("__builtin_ppc_mftb", ftype, RS6000_BUILTIN_MFTB);
14591
14592  ftype = build_function_type_list (double_type_node, NULL_TREE);
14593  def_builtin ("__builtin_mffs", ftype, RS6000_BUILTIN_MFFS);
14594
14595  ftype = build_function_type_list (void_type_node,
14596				    intSI_type_node, double_type_node,
14597				    NULL_TREE);
14598  def_builtin ("__builtin_mtfsf", ftype, RS6000_BUILTIN_MTFSF);
14599
14600#if TARGET_XCOFF
14601  /* AIX libm provides clog as __clog.  */
14602  if ((tdecl = builtin_decl_explicit (BUILT_IN_CLOG)) != NULL_TREE)
14603    set_user_assembler_name (tdecl, "__clog");
14604#endif
14605
14606#ifdef SUBTARGET_INIT_BUILTINS
14607  SUBTARGET_INIT_BUILTINS;
14608#endif
14609}
14610
14611/* Returns the rs6000 builtin decl for CODE.  */
14612
14613static tree
14614rs6000_builtin_decl (unsigned code, bool initialize_p ATTRIBUTE_UNUSED)
14615{
14616  HOST_WIDE_INT fnmask;
14617
14618  if (code >= RS6000_BUILTIN_COUNT)
14619    return error_mark_node;
14620
14621  fnmask = rs6000_builtin_info[code].mask;
14622  if ((fnmask & rs6000_builtin_mask) != fnmask)
14623    {
14624      rs6000_invalid_builtin ((enum rs6000_builtins)code);
14625      return error_mark_node;
14626    }
14627
14628  return rs6000_builtin_decls[code];
14629}
14630
14631static void
14632spe_init_builtins (void)
14633{
14634  tree puint_type_node = build_pointer_type (unsigned_type_node);
14635  tree pushort_type_node = build_pointer_type (short_unsigned_type_node);
14636  const struct builtin_description *d;
14637  size_t i;
14638
14639  tree v2si_ftype_4_v2si
14640    = build_function_type_list (opaque_V2SI_type_node,
14641                                opaque_V2SI_type_node,
14642                                opaque_V2SI_type_node,
14643                                opaque_V2SI_type_node,
14644                                opaque_V2SI_type_node,
14645                                NULL_TREE);
14646
14647  tree v2sf_ftype_4_v2sf
14648    = build_function_type_list (opaque_V2SF_type_node,
14649                                opaque_V2SF_type_node,
14650                                opaque_V2SF_type_node,
14651                                opaque_V2SF_type_node,
14652                                opaque_V2SF_type_node,
14653                                NULL_TREE);
14654
14655  tree int_ftype_int_v2si_v2si
14656    = build_function_type_list (integer_type_node,
14657                                integer_type_node,
14658                                opaque_V2SI_type_node,
14659                                opaque_V2SI_type_node,
14660                                NULL_TREE);
14661
14662  tree int_ftype_int_v2sf_v2sf
14663    = build_function_type_list (integer_type_node,
14664                                integer_type_node,
14665                                opaque_V2SF_type_node,
14666                                opaque_V2SF_type_node,
14667                                NULL_TREE);
14668
14669  tree void_ftype_v2si_puint_int
14670    = build_function_type_list (void_type_node,
14671                                opaque_V2SI_type_node,
14672                                puint_type_node,
14673                                integer_type_node,
14674                                NULL_TREE);
14675
14676  tree void_ftype_v2si_puint_char
14677    = build_function_type_list (void_type_node,
14678                                opaque_V2SI_type_node,
14679                                puint_type_node,
14680                                char_type_node,
14681                                NULL_TREE);
14682
14683  tree void_ftype_v2si_pv2si_int
14684    = build_function_type_list (void_type_node,
14685                                opaque_V2SI_type_node,
14686                                opaque_p_V2SI_type_node,
14687                                integer_type_node,
14688                                NULL_TREE);
14689
14690  tree void_ftype_v2si_pv2si_char
14691    = build_function_type_list (void_type_node,
14692                                opaque_V2SI_type_node,
14693                                opaque_p_V2SI_type_node,
14694                                char_type_node,
14695                                NULL_TREE);
14696
14697  tree void_ftype_int
14698    = build_function_type_list (void_type_node, integer_type_node, NULL_TREE);
14699
14700  tree int_ftype_void
14701    = build_function_type_list (integer_type_node, NULL_TREE);
14702
14703  tree v2si_ftype_pv2si_int
14704    = build_function_type_list (opaque_V2SI_type_node,
14705                                opaque_p_V2SI_type_node,
14706                                integer_type_node,
14707                                NULL_TREE);
14708
14709  tree v2si_ftype_puint_int
14710    = build_function_type_list (opaque_V2SI_type_node,
14711                                puint_type_node,
14712                                integer_type_node,
14713                                NULL_TREE);
14714
14715  tree v2si_ftype_pushort_int
14716    = build_function_type_list (opaque_V2SI_type_node,
14717                                pushort_type_node,
14718                                integer_type_node,
14719                                NULL_TREE);
14720
14721  tree v2si_ftype_signed_char
14722    = build_function_type_list (opaque_V2SI_type_node,
14723                                signed_char_type_node,
14724                                NULL_TREE);
14725
14726  add_builtin_type ("__ev64_opaque__", opaque_V2SI_type_node);
14727
14728  /* Initialize irregular SPE builtins.  */
14729
14730  def_builtin ("__builtin_spe_mtspefscr", void_ftype_int, SPE_BUILTIN_MTSPEFSCR);
14731  def_builtin ("__builtin_spe_mfspefscr", int_ftype_void, SPE_BUILTIN_MFSPEFSCR);
14732  def_builtin ("__builtin_spe_evstddx", void_ftype_v2si_pv2si_int, SPE_BUILTIN_EVSTDDX);
14733  def_builtin ("__builtin_spe_evstdhx", void_ftype_v2si_pv2si_int, SPE_BUILTIN_EVSTDHX);
14734  def_builtin ("__builtin_spe_evstdwx", void_ftype_v2si_pv2si_int, SPE_BUILTIN_EVSTDWX);
14735  def_builtin ("__builtin_spe_evstwhex", void_ftype_v2si_puint_int, SPE_BUILTIN_EVSTWHEX);
14736  def_builtin ("__builtin_spe_evstwhox", void_ftype_v2si_puint_int, SPE_BUILTIN_EVSTWHOX);
14737  def_builtin ("__builtin_spe_evstwwex", void_ftype_v2si_puint_int, SPE_BUILTIN_EVSTWWEX);
14738  def_builtin ("__builtin_spe_evstwwox", void_ftype_v2si_puint_int, SPE_BUILTIN_EVSTWWOX);
14739  def_builtin ("__builtin_spe_evstdd", void_ftype_v2si_pv2si_char, SPE_BUILTIN_EVSTDD);
14740  def_builtin ("__builtin_spe_evstdh", void_ftype_v2si_pv2si_char, SPE_BUILTIN_EVSTDH);
14741  def_builtin ("__builtin_spe_evstdw", void_ftype_v2si_pv2si_char, SPE_BUILTIN_EVSTDW);
14742  def_builtin ("__builtin_spe_evstwhe", void_ftype_v2si_puint_char, SPE_BUILTIN_EVSTWHE);
14743  def_builtin ("__builtin_spe_evstwho", void_ftype_v2si_puint_char, SPE_BUILTIN_EVSTWHO);
14744  def_builtin ("__builtin_spe_evstwwe", void_ftype_v2si_puint_char, SPE_BUILTIN_EVSTWWE);
14745  def_builtin ("__builtin_spe_evstwwo", void_ftype_v2si_puint_char, SPE_BUILTIN_EVSTWWO);
14746  def_builtin ("__builtin_spe_evsplatfi", v2si_ftype_signed_char, SPE_BUILTIN_EVSPLATFI);
14747  def_builtin ("__builtin_spe_evsplati", v2si_ftype_signed_char, SPE_BUILTIN_EVSPLATI);
14748
14749  /* Loads.  */
14750  def_builtin ("__builtin_spe_evlddx", v2si_ftype_pv2si_int, SPE_BUILTIN_EVLDDX);
14751  def_builtin ("__builtin_spe_evldwx", v2si_ftype_pv2si_int, SPE_BUILTIN_EVLDWX);
14752  def_builtin ("__builtin_spe_evldhx", v2si_ftype_pv2si_int, SPE_BUILTIN_EVLDHX);
14753  def_builtin ("__builtin_spe_evlwhex", v2si_ftype_puint_int, SPE_BUILTIN_EVLWHEX);
14754  def_builtin ("__builtin_spe_evlwhoux", v2si_ftype_puint_int, SPE_BUILTIN_EVLWHOUX);
14755  def_builtin ("__builtin_spe_evlwhosx", v2si_ftype_puint_int, SPE_BUILTIN_EVLWHOSX);
14756  def_builtin ("__builtin_spe_evlwwsplatx", v2si_ftype_puint_int, SPE_BUILTIN_EVLWWSPLATX);
14757  def_builtin ("__builtin_spe_evlwhsplatx", v2si_ftype_puint_int, SPE_BUILTIN_EVLWHSPLATX);
14758  def_builtin ("__builtin_spe_evlhhesplatx", v2si_ftype_pushort_int, SPE_BUILTIN_EVLHHESPLATX);
14759  def_builtin ("__builtin_spe_evlhhousplatx", v2si_ftype_pushort_int, SPE_BUILTIN_EVLHHOUSPLATX);
14760  def_builtin ("__builtin_spe_evlhhossplatx", v2si_ftype_pushort_int, SPE_BUILTIN_EVLHHOSSPLATX);
14761  def_builtin ("__builtin_spe_evldd", v2si_ftype_pv2si_int, SPE_BUILTIN_EVLDD);
14762  def_builtin ("__builtin_spe_evldw", v2si_ftype_pv2si_int, SPE_BUILTIN_EVLDW);
14763  def_builtin ("__builtin_spe_evldh", v2si_ftype_pv2si_int, SPE_BUILTIN_EVLDH);
14764  def_builtin ("__builtin_spe_evlhhesplat", v2si_ftype_pushort_int, SPE_BUILTIN_EVLHHESPLAT);
14765  def_builtin ("__builtin_spe_evlhhossplat", v2si_ftype_pushort_int, SPE_BUILTIN_EVLHHOSSPLAT);
14766  def_builtin ("__builtin_spe_evlhhousplat", v2si_ftype_pushort_int, SPE_BUILTIN_EVLHHOUSPLAT);
14767  def_builtin ("__builtin_spe_evlwhe", v2si_ftype_puint_int, SPE_BUILTIN_EVLWHE);
14768  def_builtin ("__builtin_spe_evlwhos", v2si_ftype_puint_int, SPE_BUILTIN_EVLWHOS);
14769  def_builtin ("__builtin_spe_evlwhou", v2si_ftype_puint_int, SPE_BUILTIN_EVLWHOU);
14770  def_builtin ("__builtin_spe_evlwhsplat", v2si_ftype_puint_int, SPE_BUILTIN_EVLWHSPLAT);
14771  def_builtin ("__builtin_spe_evlwwsplat", v2si_ftype_puint_int, SPE_BUILTIN_EVLWWSPLAT);
14772
14773  /* Predicates.  */
14774  d = bdesc_spe_predicates;
14775  for (i = 0; i < ARRAY_SIZE (bdesc_spe_predicates); ++i, d++)
14776    {
14777      tree type;
14778
14779      switch (insn_data[d->icode].operand[1].mode)
14780	{
14781	case V2SImode:
14782	  type = int_ftype_int_v2si_v2si;
14783	  break;
14784	case V2SFmode:
14785	  type = int_ftype_int_v2sf_v2sf;
14786	  break;
14787	default:
14788	  gcc_unreachable ();
14789	}
14790
14791      def_builtin (d->name, type, d->code);
14792    }
14793
14794  /* Evsel predicates.  */
14795  d = bdesc_spe_evsel;
14796  for (i = 0; i < ARRAY_SIZE (bdesc_spe_evsel); ++i, d++)
14797    {
14798      tree type;
14799
14800      switch (insn_data[d->icode].operand[1].mode)
14801	{
14802	case V2SImode:
14803	  type = v2si_ftype_4_v2si;
14804	  break;
14805	case V2SFmode:
14806	  type = v2sf_ftype_4_v2sf;
14807	  break;
14808	default:
14809	  gcc_unreachable ();
14810	}
14811
14812      def_builtin (d->name, type, d->code);
14813    }
14814}
14815
14816static void
14817paired_init_builtins (void)
14818{
14819  const struct builtin_description *d;
14820  size_t i;
14821
14822   tree int_ftype_int_v2sf_v2sf
14823    = build_function_type_list (integer_type_node,
14824                                integer_type_node,
14825                                V2SF_type_node,
14826                                V2SF_type_node,
14827                                NULL_TREE);
14828  tree pcfloat_type_node =
14829    build_pointer_type (build_qualified_type
14830			(float_type_node, TYPE_QUAL_CONST));
14831
14832  tree v2sf_ftype_long_pcfloat = build_function_type_list (V2SF_type_node,
14833							   long_integer_type_node,
14834							   pcfloat_type_node,
14835							   NULL_TREE);
14836  tree void_ftype_v2sf_long_pcfloat =
14837    build_function_type_list (void_type_node,
14838			      V2SF_type_node,
14839			      long_integer_type_node,
14840			      pcfloat_type_node,
14841			      NULL_TREE);
14842
14843
14844  def_builtin ("__builtin_paired_lx", v2sf_ftype_long_pcfloat,
14845	       PAIRED_BUILTIN_LX);
14846
14847
14848  def_builtin ("__builtin_paired_stx", void_ftype_v2sf_long_pcfloat,
14849	       PAIRED_BUILTIN_STX);
14850
14851  /* Predicates.  */
14852  d = bdesc_paired_preds;
14853  for (i = 0; i < ARRAY_SIZE (bdesc_paired_preds); ++i, d++)
14854    {
14855      tree type;
14856
14857      if (TARGET_DEBUG_BUILTIN)
14858	fprintf (stderr, "paired pred #%d, insn = %s [%d], mode = %s\n",
14859		 (int)i, get_insn_name (d->icode), (int)d->icode,
14860		 GET_MODE_NAME (insn_data[d->icode].operand[1].mode));
14861
14862      switch (insn_data[d->icode].operand[1].mode)
14863	{
14864	case V2SFmode:
14865	  type = int_ftype_int_v2sf_v2sf;
14866	  break;
14867	default:
14868	  gcc_unreachable ();
14869	}
14870
14871      def_builtin (d->name, type, d->code);
14872    }
14873}
14874
14875static void
14876altivec_init_builtins (void)
14877{
14878  const struct builtin_description *d;
14879  size_t i;
14880  tree ftype;
14881  tree decl;
14882
14883  tree pvoid_type_node = build_pointer_type (void_type_node);
14884
14885  tree pcvoid_type_node
14886    = build_pointer_type (build_qualified_type (void_type_node,
14887						TYPE_QUAL_CONST));
14888
14889  tree int_ftype_opaque
14890    = build_function_type_list (integer_type_node,
14891				opaque_V4SI_type_node, NULL_TREE);
14892  tree opaque_ftype_opaque
14893    = build_function_type_list (integer_type_node, NULL_TREE);
14894  tree opaque_ftype_opaque_int
14895    = build_function_type_list (opaque_V4SI_type_node,
14896				opaque_V4SI_type_node, integer_type_node, NULL_TREE);
14897  tree opaque_ftype_opaque_opaque_int
14898    = build_function_type_list (opaque_V4SI_type_node,
14899				opaque_V4SI_type_node, opaque_V4SI_type_node,
14900				integer_type_node, NULL_TREE);
14901  tree int_ftype_int_opaque_opaque
14902    = build_function_type_list (integer_type_node,
14903                                integer_type_node, opaque_V4SI_type_node,
14904                                opaque_V4SI_type_node, NULL_TREE);
14905  tree int_ftype_int_v4si_v4si
14906    = build_function_type_list (integer_type_node,
14907				integer_type_node, V4SI_type_node,
14908				V4SI_type_node, NULL_TREE);
14909  tree int_ftype_int_v2di_v2di
14910    = build_function_type_list (integer_type_node,
14911				integer_type_node, V2DI_type_node,
14912				V2DI_type_node, NULL_TREE);
14913  tree void_ftype_v4si
14914    = build_function_type_list (void_type_node, V4SI_type_node, NULL_TREE);
14915  tree v8hi_ftype_void
14916    = build_function_type_list (V8HI_type_node, NULL_TREE);
14917  tree void_ftype_void
14918    = build_function_type_list (void_type_node, NULL_TREE);
14919  tree void_ftype_int
14920    = build_function_type_list (void_type_node, integer_type_node, NULL_TREE);
14921
14922  tree opaque_ftype_long_pcvoid
14923    = build_function_type_list (opaque_V4SI_type_node,
14924				long_integer_type_node, pcvoid_type_node,
14925				NULL_TREE);
14926  tree v16qi_ftype_long_pcvoid
14927    = build_function_type_list (V16QI_type_node,
14928				long_integer_type_node, pcvoid_type_node,
14929				NULL_TREE);
14930  tree v8hi_ftype_long_pcvoid
14931    = build_function_type_list (V8HI_type_node,
14932				long_integer_type_node, pcvoid_type_node,
14933				NULL_TREE);
14934  tree v4si_ftype_long_pcvoid
14935    = build_function_type_list (V4SI_type_node,
14936				long_integer_type_node, pcvoid_type_node,
14937				NULL_TREE);
14938  tree v4sf_ftype_long_pcvoid
14939    = build_function_type_list (V4SF_type_node,
14940				long_integer_type_node, pcvoid_type_node,
14941				NULL_TREE);
14942  tree v2df_ftype_long_pcvoid
14943    = build_function_type_list (V2DF_type_node,
14944				long_integer_type_node, pcvoid_type_node,
14945				NULL_TREE);
14946  tree v2di_ftype_long_pcvoid
14947    = build_function_type_list (V2DI_type_node,
14948				long_integer_type_node, pcvoid_type_node,
14949				NULL_TREE);
14950
14951  tree void_ftype_opaque_long_pvoid
14952    = build_function_type_list (void_type_node,
14953				opaque_V4SI_type_node, long_integer_type_node,
14954				pvoid_type_node, NULL_TREE);
14955  tree void_ftype_v4si_long_pvoid
14956    = build_function_type_list (void_type_node,
14957				V4SI_type_node, long_integer_type_node,
14958				pvoid_type_node, NULL_TREE);
14959  tree void_ftype_v16qi_long_pvoid
14960    = build_function_type_list (void_type_node,
14961				V16QI_type_node, long_integer_type_node,
14962				pvoid_type_node, NULL_TREE);
14963  tree void_ftype_v8hi_long_pvoid
14964    = build_function_type_list (void_type_node,
14965				V8HI_type_node, long_integer_type_node,
14966				pvoid_type_node, NULL_TREE);
14967  tree void_ftype_v4sf_long_pvoid
14968    = build_function_type_list (void_type_node,
14969				V4SF_type_node, long_integer_type_node,
14970				pvoid_type_node, NULL_TREE);
14971  tree void_ftype_v2df_long_pvoid
14972    = build_function_type_list (void_type_node,
14973				V2DF_type_node, long_integer_type_node,
14974				pvoid_type_node, NULL_TREE);
14975  tree void_ftype_v2di_long_pvoid
14976    = build_function_type_list (void_type_node,
14977				V2DI_type_node, long_integer_type_node,
14978				pvoid_type_node, NULL_TREE);
14979  tree int_ftype_int_v8hi_v8hi
14980    = build_function_type_list (integer_type_node,
14981				integer_type_node, V8HI_type_node,
14982				V8HI_type_node, NULL_TREE);
14983  tree int_ftype_int_v16qi_v16qi
14984    = build_function_type_list (integer_type_node,
14985				integer_type_node, V16QI_type_node,
14986				V16QI_type_node, NULL_TREE);
14987  tree int_ftype_int_v4sf_v4sf
14988    = build_function_type_list (integer_type_node,
14989				integer_type_node, V4SF_type_node,
14990				V4SF_type_node, NULL_TREE);
14991  tree int_ftype_int_v2df_v2df
14992    = build_function_type_list (integer_type_node,
14993				integer_type_node, V2DF_type_node,
14994				V2DF_type_node, NULL_TREE);
14995  tree v2di_ftype_v2di
14996    = build_function_type_list (V2DI_type_node, V2DI_type_node, NULL_TREE);
14997  tree v4si_ftype_v4si
14998    = build_function_type_list (V4SI_type_node, V4SI_type_node, NULL_TREE);
14999  tree v8hi_ftype_v8hi
15000    = build_function_type_list (V8HI_type_node, V8HI_type_node, NULL_TREE);
15001  tree v16qi_ftype_v16qi
15002    = build_function_type_list (V16QI_type_node, V16QI_type_node, NULL_TREE);
15003  tree v4sf_ftype_v4sf
15004    = build_function_type_list (V4SF_type_node, V4SF_type_node, NULL_TREE);
15005  tree v2df_ftype_v2df
15006    = build_function_type_list (V2DF_type_node, V2DF_type_node, NULL_TREE);
15007  tree void_ftype_pcvoid_int_int
15008    = build_function_type_list (void_type_node,
15009				pcvoid_type_node, integer_type_node,
15010				integer_type_node, NULL_TREE);
15011
15012  def_builtin ("__builtin_altivec_mtvscr", void_ftype_v4si, ALTIVEC_BUILTIN_MTVSCR);
15013  def_builtin ("__builtin_altivec_mfvscr", v8hi_ftype_void, ALTIVEC_BUILTIN_MFVSCR);
15014  def_builtin ("__builtin_altivec_dssall", void_ftype_void, ALTIVEC_BUILTIN_DSSALL);
15015  def_builtin ("__builtin_altivec_dss", void_ftype_int, ALTIVEC_BUILTIN_DSS);
15016  def_builtin ("__builtin_altivec_lvsl", v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_LVSL);
15017  def_builtin ("__builtin_altivec_lvsr", v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_LVSR);
15018  def_builtin ("__builtin_altivec_lvebx", v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_LVEBX);
15019  def_builtin ("__builtin_altivec_lvehx", v8hi_ftype_long_pcvoid, ALTIVEC_BUILTIN_LVEHX);
15020  def_builtin ("__builtin_altivec_lvewx", v4si_ftype_long_pcvoid, ALTIVEC_BUILTIN_LVEWX);
15021  def_builtin ("__builtin_altivec_lvxl", v4si_ftype_long_pcvoid, ALTIVEC_BUILTIN_LVXL);
15022  def_builtin ("__builtin_altivec_lvxl_v2df", v2df_ftype_long_pcvoid,
15023	       ALTIVEC_BUILTIN_LVXL_V2DF);
15024  def_builtin ("__builtin_altivec_lvxl_v2di", v2di_ftype_long_pcvoid,
15025	       ALTIVEC_BUILTIN_LVXL_V2DI);
15026  def_builtin ("__builtin_altivec_lvxl_v4sf", v4sf_ftype_long_pcvoid,
15027	       ALTIVEC_BUILTIN_LVXL_V4SF);
15028  def_builtin ("__builtin_altivec_lvxl_v4si", v4si_ftype_long_pcvoid,
15029	       ALTIVEC_BUILTIN_LVXL_V4SI);
15030  def_builtin ("__builtin_altivec_lvxl_v8hi", v8hi_ftype_long_pcvoid,
15031	       ALTIVEC_BUILTIN_LVXL_V8HI);
15032  def_builtin ("__builtin_altivec_lvxl_v16qi", v16qi_ftype_long_pcvoid,
15033	       ALTIVEC_BUILTIN_LVXL_V16QI);
15034  def_builtin ("__builtin_altivec_lvx", v4si_ftype_long_pcvoid, ALTIVEC_BUILTIN_LVX);
15035  def_builtin ("__builtin_altivec_lvx_v2df", v2df_ftype_long_pcvoid,
15036	       ALTIVEC_BUILTIN_LVX_V2DF);
15037  def_builtin ("__builtin_altivec_lvx_v2di", v2di_ftype_long_pcvoid,
15038	       ALTIVEC_BUILTIN_LVX_V2DI);
15039  def_builtin ("__builtin_altivec_lvx_v4sf", v4sf_ftype_long_pcvoid,
15040	       ALTIVEC_BUILTIN_LVX_V4SF);
15041  def_builtin ("__builtin_altivec_lvx_v4si", v4si_ftype_long_pcvoid,
15042	       ALTIVEC_BUILTIN_LVX_V4SI);
15043  def_builtin ("__builtin_altivec_lvx_v8hi", v8hi_ftype_long_pcvoid,
15044	       ALTIVEC_BUILTIN_LVX_V8HI);
15045  def_builtin ("__builtin_altivec_lvx_v16qi", v16qi_ftype_long_pcvoid,
15046	       ALTIVEC_BUILTIN_LVX_V16QI);
15047  def_builtin ("__builtin_altivec_stvx", void_ftype_v4si_long_pvoid, ALTIVEC_BUILTIN_STVX);
15048  def_builtin ("__builtin_altivec_stvx_v2df", void_ftype_v2df_long_pvoid,
15049	       ALTIVEC_BUILTIN_STVX_V2DF);
15050  def_builtin ("__builtin_altivec_stvx_v2di", void_ftype_v2di_long_pvoid,
15051	       ALTIVEC_BUILTIN_STVX_V2DI);
15052  def_builtin ("__builtin_altivec_stvx_v4sf", void_ftype_v4sf_long_pvoid,
15053	       ALTIVEC_BUILTIN_STVX_V4SF);
15054  def_builtin ("__builtin_altivec_stvx_v4si", void_ftype_v4si_long_pvoid,
15055	       ALTIVEC_BUILTIN_STVX_V4SI);
15056  def_builtin ("__builtin_altivec_stvx_v8hi", void_ftype_v8hi_long_pvoid,
15057	       ALTIVEC_BUILTIN_STVX_V8HI);
15058  def_builtin ("__builtin_altivec_stvx_v16qi", void_ftype_v16qi_long_pvoid,
15059	       ALTIVEC_BUILTIN_STVX_V16QI);
15060  def_builtin ("__builtin_altivec_stvewx", void_ftype_v4si_long_pvoid, ALTIVEC_BUILTIN_STVEWX);
15061  def_builtin ("__builtin_altivec_stvxl", void_ftype_v4si_long_pvoid, ALTIVEC_BUILTIN_STVXL);
15062  def_builtin ("__builtin_altivec_stvxl_v2df", void_ftype_v2df_long_pvoid,
15063	       ALTIVEC_BUILTIN_STVXL_V2DF);
15064  def_builtin ("__builtin_altivec_stvxl_v2di", void_ftype_v2di_long_pvoid,
15065	       ALTIVEC_BUILTIN_STVXL_V2DI);
15066  def_builtin ("__builtin_altivec_stvxl_v4sf", void_ftype_v4sf_long_pvoid,
15067	       ALTIVEC_BUILTIN_STVXL_V4SF);
15068  def_builtin ("__builtin_altivec_stvxl_v4si", void_ftype_v4si_long_pvoid,
15069	       ALTIVEC_BUILTIN_STVXL_V4SI);
15070  def_builtin ("__builtin_altivec_stvxl_v8hi", void_ftype_v8hi_long_pvoid,
15071	       ALTIVEC_BUILTIN_STVXL_V8HI);
15072  def_builtin ("__builtin_altivec_stvxl_v16qi", void_ftype_v16qi_long_pvoid,
15073	       ALTIVEC_BUILTIN_STVXL_V16QI);
15074  def_builtin ("__builtin_altivec_stvebx", void_ftype_v16qi_long_pvoid, ALTIVEC_BUILTIN_STVEBX);
15075  def_builtin ("__builtin_altivec_stvehx", void_ftype_v8hi_long_pvoid, ALTIVEC_BUILTIN_STVEHX);
15076  def_builtin ("__builtin_vec_ld", opaque_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LD);
15077  def_builtin ("__builtin_vec_lde", opaque_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LDE);
15078  def_builtin ("__builtin_vec_ldl", opaque_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LDL);
15079  def_builtin ("__builtin_vec_lvsl", v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LVSL);
15080  def_builtin ("__builtin_vec_lvsr", v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LVSR);
15081  def_builtin ("__builtin_vec_lvebx", v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LVEBX);
15082  def_builtin ("__builtin_vec_lvehx", v8hi_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LVEHX);
15083  def_builtin ("__builtin_vec_lvewx", v4si_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LVEWX);
15084  def_builtin ("__builtin_vec_st", void_ftype_opaque_long_pvoid, ALTIVEC_BUILTIN_VEC_ST);
15085  def_builtin ("__builtin_vec_ste", void_ftype_opaque_long_pvoid, ALTIVEC_BUILTIN_VEC_STE);
15086  def_builtin ("__builtin_vec_stl", void_ftype_opaque_long_pvoid, ALTIVEC_BUILTIN_VEC_STL);
15087  def_builtin ("__builtin_vec_stvewx", void_ftype_opaque_long_pvoid, ALTIVEC_BUILTIN_VEC_STVEWX);
15088  def_builtin ("__builtin_vec_stvebx", void_ftype_opaque_long_pvoid, ALTIVEC_BUILTIN_VEC_STVEBX);
15089  def_builtin ("__builtin_vec_stvehx", void_ftype_opaque_long_pvoid, ALTIVEC_BUILTIN_VEC_STVEHX);
15090
15091  def_builtin ("__builtin_vsx_lxvd2x_v2df", v2df_ftype_long_pcvoid,
15092	       VSX_BUILTIN_LXVD2X_V2DF);
15093  def_builtin ("__builtin_vsx_lxvd2x_v2di", v2di_ftype_long_pcvoid,
15094	       VSX_BUILTIN_LXVD2X_V2DI);
15095  def_builtin ("__builtin_vsx_lxvw4x_v4sf", v4sf_ftype_long_pcvoid,
15096	       VSX_BUILTIN_LXVW4X_V4SF);
15097  def_builtin ("__builtin_vsx_lxvw4x_v4si", v4si_ftype_long_pcvoid,
15098	       VSX_BUILTIN_LXVW4X_V4SI);
15099  def_builtin ("__builtin_vsx_lxvw4x_v8hi", v8hi_ftype_long_pcvoid,
15100	       VSX_BUILTIN_LXVW4X_V8HI);
15101  def_builtin ("__builtin_vsx_lxvw4x_v16qi", v16qi_ftype_long_pcvoid,
15102	       VSX_BUILTIN_LXVW4X_V16QI);
15103  def_builtin ("__builtin_vsx_stxvd2x_v2df", void_ftype_v2df_long_pvoid,
15104	       VSX_BUILTIN_STXVD2X_V2DF);
15105  def_builtin ("__builtin_vsx_stxvd2x_v2di", void_ftype_v2di_long_pvoid,
15106	       VSX_BUILTIN_STXVD2X_V2DI);
15107  def_builtin ("__builtin_vsx_stxvw4x_v4sf", void_ftype_v4sf_long_pvoid,
15108	       VSX_BUILTIN_STXVW4X_V4SF);
15109  def_builtin ("__builtin_vsx_stxvw4x_v4si", void_ftype_v4si_long_pvoid,
15110	       VSX_BUILTIN_STXVW4X_V4SI);
15111  def_builtin ("__builtin_vsx_stxvw4x_v8hi", void_ftype_v8hi_long_pvoid,
15112	       VSX_BUILTIN_STXVW4X_V8HI);
15113  def_builtin ("__builtin_vsx_stxvw4x_v16qi", void_ftype_v16qi_long_pvoid,
15114	       VSX_BUILTIN_STXVW4X_V16QI);
15115  def_builtin ("__builtin_vec_vsx_ld", opaque_ftype_long_pcvoid,
15116	       VSX_BUILTIN_VEC_LD);
15117  def_builtin ("__builtin_vec_vsx_st", void_ftype_opaque_long_pvoid,
15118	       VSX_BUILTIN_VEC_ST);
15119
15120  def_builtin ("__builtin_vec_step", int_ftype_opaque, ALTIVEC_BUILTIN_VEC_STEP);
15121  def_builtin ("__builtin_vec_splats", opaque_ftype_opaque, ALTIVEC_BUILTIN_VEC_SPLATS);
15122  def_builtin ("__builtin_vec_promote", opaque_ftype_opaque, ALTIVEC_BUILTIN_VEC_PROMOTE);
15123
15124  def_builtin ("__builtin_vec_sld", opaque_ftype_opaque_opaque_int, ALTIVEC_BUILTIN_VEC_SLD);
15125  def_builtin ("__builtin_vec_splat", opaque_ftype_opaque_int, ALTIVEC_BUILTIN_VEC_SPLAT);
15126  def_builtin ("__builtin_vec_extract", opaque_ftype_opaque_int, ALTIVEC_BUILTIN_VEC_EXTRACT);
15127  def_builtin ("__builtin_vec_insert", opaque_ftype_opaque_opaque_int, ALTIVEC_BUILTIN_VEC_INSERT);
15128  def_builtin ("__builtin_vec_vspltw", opaque_ftype_opaque_int, ALTIVEC_BUILTIN_VEC_VSPLTW);
15129  def_builtin ("__builtin_vec_vsplth", opaque_ftype_opaque_int, ALTIVEC_BUILTIN_VEC_VSPLTH);
15130  def_builtin ("__builtin_vec_vspltb", opaque_ftype_opaque_int, ALTIVEC_BUILTIN_VEC_VSPLTB);
15131  def_builtin ("__builtin_vec_ctf", opaque_ftype_opaque_int, ALTIVEC_BUILTIN_VEC_CTF);
15132  def_builtin ("__builtin_vec_vcfsx", opaque_ftype_opaque_int, ALTIVEC_BUILTIN_VEC_VCFSX);
15133  def_builtin ("__builtin_vec_vcfux", opaque_ftype_opaque_int, ALTIVEC_BUILTIN_VEC_VCFUX);
15134  def_builtin ("__builtin_vec_cts", opaque_ftype_opaque_int, ALTIVEC_BUILTIN_VEC_CTS);
15135  def_builtin ("__builtin_vec_ctu", opaque_ftype_opaque_int, ALTIVEC_BUILTIN_VEC_CTU);
15136
15137  /* Cell builtins.  */
15138  def_builtin ("__builtin_altivec_lvlx",  v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_LVLX);
15139  def_builtin ("__builtin_altivec_lvlxl", v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_LVLXL);
15140  def_builtin ("__builtin_altivec_lvrx",  v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_LVRX);
15141  def_builtin ("__builtin_altivec_lvrxl", v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_LVRXL);
15142
15143  def_builtin ("__builtin_vec_lvlx",  v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LVLX);
15144  def_builtin ("__builtin_vec_lvlxl", v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LVLXL);
15145  def_builtin ("__builtin_vec_lvrx",  v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LVRX);
15146  def_builtin ("__builtin_vec_lvrxl", v16qi_ftype_long_pcvoid, ALTIVEC_BUILTIN_VEC_LVRXL);
15147
15148  def_builtin ("__builtin_altivec_stvlx",  void_ftype_v16qi_long_pvoid, ALTIVEC_BUILTIN_STVLX);
15149  def_builtin ("__builtin_altivec_stvlxl", void_ftype_v16qi_long_pvoid, ALTIVEC_BUILTIN_STVLXL);
15150  def_builtin ("__builtin_altivec_stvrx",  void_ftype_v16qi_long_pvoid, ALTIVEC_BUILTIN_STVRX);
15151  def_builtin ("__builtin_altivec_stvrxl", void_ftype_v16qi_long_pvoid, ALTIVEC_BUILTIN_STVRXL);
15152
15153  def_builtin ("__builtin_vec_stvlx",  void_ftype_v16qi_long_pvoid, ALTIVEC_BUILTIN_VEC_STVLX);
15154  def_builtin ("__builtin_vec_stvlxl", void_ftype_v16qi_long_pvoid, ALTIVEC_BUILTIN_VEC_STVLXL);
15155  def_builtin ("__builtin_vec_stvrx",  void_ftype_v16qi_long_pvoid, ALTIVEC_BUILTIN_VEC_STVRX);
15156  def_builtin ("__builtin_vec_stvrxl", void_ftype_v16qi_long_pvoid, ALTIVEC_BUILTIN_VEC_STVRXL);
15157
15158  /* Add the DST variants.  */
15159  d = bdesc_dst;
15160  for (i = 0; i < ARRAY_SIZE (bdesc_dst); i++, d++)
15161    def_builtin (d->name, void_ftype_pcvoid_int_int, d->code);
15162
15163  /* Initialize the predicates.  */
15164  d = bdesc_altivec_preds;
15165  for (i = 0; i < ARRAY_SIZE (bdesc_altivec_preds); i++, d++)
15166    {
15167      machine_mode mode1;
15168      tree type;
15169
15170      if (rs6000_overloaded_builtin_p (d->code))
15171	mode1 = VOIDmode;
15172      else
15173	mode1 = insn_data[d->icode].operand[1].mode;
15174
15175      switch (mode1)
15176	{
15177	case VOIDmode:
15178	  type = int_ftype_int_opaque_opaque;
15179	  break;
15180	case V2DImode:
15181	  type = int_ftype_int_v2di_v2di;
15182	  break;
15183	case V4SImode:
15184	  type = int_ftype_int_v4si_v4si;
15185	  break;
15186	case V8HImode:
15187	  type = int_ftype_int_v8hi_v8hi;
15188	  break;
15189	case V16QImode:
15190	  type = int_ftype_int_v16qi_v16qi;
15191	  break;
15192	case V4SFmode:
15193	  type = int_ftype_int_v4sf_v4sf;
15194	  break;
15195	case V2DFmode:
15196	  type = int_ftype_int_v2df_v2df;
15197	  break;
15198	default:
15199	  gcc_unreachable ();
15200	}
15201
15202      def_builtin (d->name, type, d->code);
15203    }
15204
15205  /* Initialize the abs* operators.  */
15206  d = bdesc_abs;
15207  for (i = 0; i < ARRAY_SIZE (bdesc_abs); i++, d++)
15208    {
15209      machine_mode mode0;
15210      tree type;
15211
15212      mode0 = insn_data[d->icode].operand[0].mode;
15213
15214      switch (mode0)
15215	{
15216	case V2DImode:
15217	  type = v2di_ftype_v2di;
15218	  break;
15219	case V4SImode:
15220	  type = v4si_ftype_v4si;
15221	  break;
15222	case V8HImode:
15223	  type = v8hi_ftype_v8hi;
15224	  break;
15225	case V16QImode:
15226	  type = v16qi_ftype_v16qi;
15227	  break;
15228	case V4SFmode:
15229	  type = v4sf_ftype_v4sf;
15230	  break;
15231	case V2DFmode:
15232	  type = v2df_ftype_v2df;
15233	  break;
15234	default:
15235	  gcc_unreachable ();
15236	}
15237
15238      def_builtin (d->name, type, d->code);
15239    }
15240
15241  /* Initialize target builtin that implements
15242     targetm.vectorize.builtin_mask_for_load.  */
15243
15244  decl = add_builtin_function ("__builtin_altivec_mask_for_load",
15245			       v16qi_ftype_long_pcvoid,
15246			       ALTIVEC_BUILTIN_MASK_FOR_LOAD,
15247			       BUILT_IN_MD, NULL, NULL_TREE);
15248  TREE_READONLY (decl) = 1;
15249  /* Record the decl. Will be used by rs6000_builtin_mask_for_load.  */
15250  altivec_builtin_mask_for_load = decl;
15251
15252  /* Access to the vec_init patterns.  */
15253  ftype = build_function_type_list (V4SI_type_node, integer_type_node,
15254				    integer_type_node, integer_type_node,
15255				    integer_type_node, NULL_TREE);
15256  def_builtin ("__builtin_vec_init_v4si", ftype, ALTIVEC_BUILTIN_VEC_INIT_V4SI);
15257
15258  ftype = build_function_type_list (V8HI_type_node, short_integer_type_node,
15259				    short_integer_type_node,
15260				    short_integer_type_node,
15261				    short_integer_type_node,
15262				    short_integer_type_node,
15263				    short_integer_type_node,
15264				    short_integer_type_node,
15265				    short_integer_type_node, NULL_TREE);
15266  def_builtin ("__builtin_vec_init_v8hi", ftype, ALTIVEC_BUILTIN_VEC_INIT_V8HI);
15267
15268  ftype = build_function_type_list (V16QI_type_node, char_type_node,
15269				    char_type_node, char_type_node,
15270				    char_type_node, char_type_node,
15271				    char_type_node, char_type_node,
15272				    char_type_node, char_type_node,
15273				    char_type_node, char_type_node,
15274				    char_type_node, char_type_node,
15275				    char_type_node, char_type_node,
15276				    char_type_node, NULL_TREE);
15277  def_builtin ("__builtin_vec_init_v16qi", ftype,
15278	       ALTIVEC_BUILTIN_VEC_INIT_V16QI);
15279
15280  ftype = build_function_type_list (V4SF_type_node, float_type_node,
15281				    float_type_node, float_type_node,
15282				    float_type_node, NULL_TREE);
15283  def_builtin ("__builtin_vec_init_v4sf", ftype, ALTIVEC_BUILTIN_VEC_INIT_V4SF);
15284
15285  /* VSX builtins.  */
15286  ftype = build_function_type_list (V2DF_type_node, double_type_node,
15287				    double_type_node, NULL_TREE);
15288  def_builtin ("__builtin_vec_init_v2df", ftype, VSX_BUILTIN_VEC_INIT_V2DF);
15289
15290  ftype = build_function_type_list (V2DI_type_node, intDI_type_node,
15291				    intDI_type_node, NULL_TREE);
15292  def_builtin ("__builtin_vec_init_v2di", ftype, VSX_BUILTIN_VEC_INIT_V2DI);
15293
15294  /* Access to the vec_set patterns.  */
15295  ftype = build_function_type_list (V4SI_type_node, V4SI_type_node,
15296				    intSI_type_node,
15297				    integer_type_node, NULL_TREE);
15298  def_builtin ("__builtin_vec_set_v4si", ftype, ALTIVEC_BUILTIN_VEC_SET_V4SI);
15299
15300  ftype = build_function_type_list (V8HI_type_node, V8HI_type_node,
15301				    intHI_type_node,
15302				    integer_type_node, NULL_TREE);
15303  def_builtin ("__builtin_vec_set_v8hi", ftype, ALTIVEC_BUILTIN_VEC_SET_V8HI);
15304
15305  ftype = build_function_type_list (V16QI_type_node, V16QI_type_node,
15306				    intQI_type_node,
15307				    integer_type_node, NULL_TREE);
15308  def_builtin ("__builtin_vec_set_v16qi", ftype, ALTIVEC_BUILTIN_VEC_SET_V16QI);
15309
15310  ftype = build_function_type_list (V4SF_type_node, V4SF_type_node,
15311				    float_type_node,
15312				    integer_type_node, NULL_TREE);
15313  def_builtin ("__builtin_vec_set_v4sf", ftype, ALTIVEC_BUILTIN_VEC_SET_V4SF);
15314
15315  ftype = build_function_type_list (V2DF_type_node, V2DF_type_node,
15316				    double_type_node,
15317				    integer_type_node, NULL_TREE);
15318  def_builtin ("__builtin_vec_set_v2df", ftype, VSX_BUILTIN_VEC_SET_V2DF);
15319
15320  ftype = build_function_type_list (V2DI_type_node, V2DI_type_node,
15321				    intDI_type_node,
15322				    integer_type_node, NULL_TREE);
15323  def_builtin ("__builtin_vec_set_v2di", ftype, VSX_BUILTIN_VEC_SET_V2DI);
15324
15325  /* Access to the vec_extract patterns.  */
15326  ftype = build_function_type_list (intSI_type_node, V4SI_type_node,
15327				    integer_type_node, NULL_TREE);
15328  def_builtin ("__builtin_vec_ext_v4si", ftype, ALTIVEC_BUILTIN_VEC_EXT_V4SI);
15329
15330  ftype = build_function_type_list (intHI_type_node, V8HI_type_node,
15331				    integer_type_node, NULL_TREE);
15332  def_builtin ("__builtin_vec_ext_v8hi", ftype, ALTIVEC_BUILTIN_VEC_EXT_V8HI);
15333
15334  ftype = build_function_type_list (intQI_type_node, V16QI_type_node,
15335				    integer_type_node, NULL_TREE);
15336  def_builtin ("__builtin_vec_ext_v16qi", ftype, ALTIVEC_BUILTIN_VEC_EXT_V16QI);
15337
15338  ftype = build_function_type_list (float_type_node, V4SF_type_node,
15339				    integer_type_node, NULL_TREE);
15340  def_builtin ("__builtin_vec_ext_v4sf", ftype, ALTIVEC_BUILTIN_VEC_EXT_V4SF);
15341
15342  ftype = build_function_type_list (double_type_node, V2DF_type_node,
15343				    integer_type_node, NULL_TREE);
15344  def_builtin ("__builtin_vec_ext_v2df", ftype, VSX_BUILTIN_VEC_EXT_V2DF);
15345
15346  ftype = build_function_type_list (intDI_type_node, V2DI_type_node,
15347				    integer_type_node, NULL_TREE);
15348  def_builtin ("__builtin_vec_ext_v2di", ftype, VSX_BUILTIN_VEC_EXT_V2DI);
15349
15350
15351  if (V1TI_type_node)
15352    {
15353      tree v1ti_ftype_long_pcvoid
15354	= build_function_type_list (V1TI_type_node,
15355				    long_integer_type_node, pcvoid_type_node,
15356				    NULL_TREE);
15357      tree void_ftype_v1ti_long_pvoid
15358	= build_function_type_list (void_type_node,
15359				    V1TI_type_node, long_integer_type_node,
15360				    pvoid_type_node, NULL_TREE);
15361      def_builtin ("__builtin_vsx_lxvd2x_v1ti", v1ti_ftype_long_pcvoid,
15362		   VSX_BUILTIN_LXVD2X_V1TI);
15363      def_builtin ("__builtin_vsx_stxvd2x_v1ti", void_ftype_v1ti_long_pvoid,
15364		   VSX_BUILTIN_STXVD2X_V1TI);
15365      ftype = build_function_type_list (V1TI_type_node, intTI_type_node,
15366					NULL_TREE, NULL_TREE);
15367      def_builtin ("__builtin_vec_init_v1ti", ftype, VSX_BUILTIN_VEC_INIT_V1TI);
15368      ftype = build_function_type_list (V1TI_type_node, V1TI_type_node,
15369					intTI_type_node,
15370					integer_type_node, NULL_TREE);
15371      def_builtin ("__builtin_vec_set_v1ti", ftype, VSX_BUILTIN_VEC_SET_V1TI);
15372      ftype = build_function_type_list (intTI_type_node, V1TI_type_node,
15373					integer_type_node, NULL_TREE);
15374      def_builtin ("__builtin_vec_ext_v1ti", ftype, VSX_BUILTIN_VEC_EXT_V1TI);
15375    }
15376
15377}
15378
15379static void
15380htm_init_builtins (void)
15381{
15382  HOST_WIDE_INT builtin_mask = rs6000_builtin_mask;
15383  const struct builtin_description *d;
15384  size_t i;
15385
15386  d = bdesc_htm;
15387  for (i = 0; i < ARRAY_SIZE (bdesc_htm); i++, d++)
15388    {
15389      tree op[MAX_HTM_OPERANDS], type;
15390      HOST_WIDE_INT mask = d->mask;
15391      unsigned attr = rs6000_builtin_info[d->code].attr;
15392      bool void_func = (attr & RS6000_BTC_VOID);
15393      int attr_args = (attr & RS6000_BTC_TYPE_MASK);
15394      int nopnds = 0;
15395      tree gpr_type_node;
15396      tree rettype;
15397      tree argtype;
15398
15399      if (TARGET_32BIT && TARGET_POWERPC64)
15400	gpr_type_node = long_long_unsigned_type_node;
15401      else
15402	gpr_type_node = long_unsigned_type_node;
15403
15404      if (attr & RS6000_BTC_SPR)
15405	{
15406	  rettype = gpr_type_node;
15407	  argtype = gpr_type_node;
15408	}
15409      else if (d->code == HTM_BUILTIN_TABORTDC
15410	       || d->code == HTM_BUILTIN_TABORTDCI)
15411	{
15412	  rettype = unsigned_type_node;
15413	  argtype = gpr_type_node;
15414	}
15415      else
15416	{
15417	  rettype = unsigned_type_node;
15418	  argtype = unsigned_type_node;
15419	}
15420
15421      if ((mask & builtin_mask) != mask)
15422	{
15423	  if (TARGET_DEBUG_BUILTIN)
15424	    fprintf (stderr, "htm_builtin, skip binary %s\n", d->name);
15425	  continue;
15426	}
15427
15428      if (d->name == 0)
15429	{
15430	  if (TARGET_DEBUG_BUILTIN)
15431	    fprintf (stderr, "htm_builtin, bdesc_htm[%ld] no name\n",
15432		     (long unsigned) i);
15433	  continue;
15434	}
15435
15436      op[nopnds++] = (void_func) ? void_type_node : rettype;
15437
15438      if (attr_args == RS6000_BTC_UNARY)
15439	op[nopnds++] = argtype;
15440      else if (attr_args == RS6000_BTC_BINARY)
15441	{
15442	  op[nopnds++] = argtype;
15443	  op[nopnds++] = argtype;
15444	}
15445      else if (attr_args == RS6000_BTC_TERNARY)
15446	{
15447	  op[nopnds++] = argtype;
15448	  op[nopnds++] = argtype;
15449	  op[nopnds++] = argtype;
15450	}
15451
15452      switch (nopnds)
15453	{
15454	case 1:
15455	  type = build_function_type_list (op[0], NULL_TREE);
15456	  break;
15457	case 2:
15458	  type = build_function_type_list (op[0], op[1], NULL_TREE);
15459	  break;
15460	case 3:
15461	  type = build_function_type_list (op[0], op[1], op[2], NULL_TREE);
15462	  break;
15463	case 4:
15464	  type = build_function_type_list (op[0], op[1], op[2], op[3],
15465					   NULL_TREE);
15466	  break;
15467	default:
15468	  gcc_unreachable ();
15469	}
15470
15471      def_builtin (d->name, type, d->code);
15472    }
15473}
15474
15475/* Hash function for builtin functions with up to 3 arguments and a return
15476   type.  */
15477hashval_t
15478builtin_hasher::hash (builtin_hash_struct *bh)
15479{
15480  unsigned ret = 0;
15481  int i;
15482
15483  for (i = 0; i < 4; i++)
15484    {
15485      ret = (ret * (unsigned)MAX_MACHINE_MODE) + ((unsigned)bh->mode[i]);
15486      ret = (ret * 2) + bh->uns_p[i];
15487    }
15488
15489  return ret;
15490}
15491
15492/* Compare builtin hash entries H1 and H2 for equivalence.  */
15493bool
15494builtin_hasher::equal (builtin_hash_struct *p1, builtin_hash_struct *p2)
15495{
15496  return ((p1->mode[0] == p2->mode[0])
15497	  && (p1->mode[1] == p2->mode[1])
15498	  && (p1->mode[2] == p2->mode[2])
15499	  && (p1->mode[3] == p2->mode[3])
15500	  && (p1->uns_p[0] == p2->uns_p[0])
15501	  && (p1->uns_p[1] == p2->uns_p[1])
15502	  && (p1->uns_p[2] == p2->uns_p[2])
15503	  && (p1->uns_p[3] == p2->uns_p[3]));
15504}
15505
15506/* Map types for builtin functions with an explicit return type and up to 3
15507   arguments.  Functions with fewer than 3 arguments use VOIDmode as the type
15508   of the argument.  */
15509static tree
15510builtin_function_type (machine_mode mode_ret, machine_mode mode_arg0,
15511		       machine_mode mode_arg1, machine_mode mode_arg2,
15512		       enum rs6000_builtins builtin, const char *name)
15513{
15514  struct builtin_hash_struct h;
15515  struct builtin_hash_struct *h2;
15516  int num_args = 3;
15517  int i;
15518  tree ret_type = NULL_TREE;
15519  tree arg_type[3] = { NULL_TREE, NULL_TREE, NULL_TREE };
15520
15521  /* Create builtin_hash_table.  */
15522  if (builtin_hash_table == NULL)
15523    builtin_hash_table = hash_table<builtin_hasher>::create_ggc (1500);
15524
15525  h.type = NULL_TREE;
15526  h.mode[0] = mode_ret;
15527  h.mode[1] = mode_arg0;
15528  h.mode[2] = mode_arg1;
15529  h.mode[3] = mode_arg2;
15530  h.uns_p[0] = 0;
15531  h.uns_p[1] = 0;
15532  h.uns_p[2] = 0;
15533  h.uns_p[3] = 0;
15534
15535  /* If the builtin is a type that produces unsigned results or takes unsigned
15536     arguments, and it is returned as a decl for the vectorizer (such as
15537     widening multiplies, permute), make sure the arguments and return value
15538     are type correct.  */
15539  switch (builtin)
15540    {
15541      /* unsigned 1 argument functions.  */
15542    case CRYPTO_BUILTIN_VSBOX:
15543    case P8V_BUILTIN_VGBBD:
15544    case MISC_BUILTIN_CDTBCD:
15545    case MISC_BUILTIN_CBCDTD:
15546      h.uns_p[0] = 1;
15547      h.uns_p[1] = 1;
15548      break;
15549
15550      /* unsigned 2 argument functions.  */
15551    case ALTIVEC_BUILTIN_VMULEUB_UNS:
15552    case ALTIVEC_BUILTIN_VMULEUH_UNS:
15553    case ALTIVEC_BUILTIN_VMULOUB_UNS:
15554    case ALTIVEC_BUILTIN_VMULOUH_UNS:
15555    case CRYPTO_BUILTIN_VCIPHER:
15556    case CRYPTO_BUILTIN_VCIPHERLAST:
15557    case CRYPTO_BUILTIN_VNCIPHER:
15558    case CRYPTO_BUILTIN_VNCIPHERLAST:
15559    case CRYPTO_BUILTIN_VPMSUMB:
15560    case CRYPTO_BUILTIN_VPMSUMH:
15561    case CRYPTO_BUILTIN_VPMSUMW:
15562    case CRYPTO_BUILTIN_VPMSUMD:
15563    case CRYPTO_BUILTIN_VPMSUM:
15564    case MISC_BUILTIN_ADDG6S:
15565    case MISC_BUILTIN_DIVWEU:
15566    case MISC_BUILTIN_DIVWEUO:
15567    case MISC_BUILTIN_DIVDEU:
15568    case MISC_BUILTIN_DIVDEUO:
15569      h.uns_p[0] = 1;
15570      h.uns_p[1] = 1;
15571      h.uns_p[2] = 1;
15572      break;
15573
15574      /* unsigned 3 argument functions.  */
15575    case ALTIVEC_BUILTIN_VPERM_16QI_UNS:
15576    case ALTIVEC_BUILTIN_VPERM_8HI_UNS:
15577    case ALTIVEC_BUILTIN_VPERM_4SI_UNS:
15578    case ALTIVEC_BUILTIN_VPERM_2DI_UNS:
15579    case ALTIVEC_BUILTIN_VSEL_16QI_UNS:
15580    case ALTIVEC_BUILTIN_VSEL_8HI_UNS:
15581    case ALTIVEC_BUILTIN_VSEL_4SI_UNS:
15582    case ALTIVEC_BUILTIN_VSEL_2DI_UNS:
15583    case VSX_BUILTIN_VPERM_16QI_UNS:
15584    case VSX_BUILTIN_VPERM_8HI_UNS:
15585    case VSX_BUILTIN_VPERM_4SI_UNS:
15586    case VSX_BUILTIN_VPERM_2DI_UNS:
15587    case VSX_BUILTIN_XXSEL_16QI_UNS:
15588    case VSX_BUILTIN_XXSEL_8HI_UNS:
15589    case VSX_BUILTIN_XXSEL_4SI_UNS:
15590    case VSX_BUILTIN_XXSEL_2DI_UNS:
15591    case CRYPTO_BUILTIN_VPERMXOR:
15592    case CRYPTO_BUILTIN_VPERMXOR_V2DI:
15593    case CRYPTO_BUILTIN_VPERMXOR_V4SI:
15594    case CRYPTO_BUILTIN_VPERMXOR_V8HI:
15595    case CRYPTO_BUILTIN_VPERMXOR_V16QI:
15596    case CRYPTO_BUILTIN_VSHASIGMAW:
15597    case CRYPTO_BUILTIN_VSHASIGMAD:
15598    case CRYPTO_BUILTIN_VSHASIGMA:
15599      h.uns_p[0] = 1;
15600      h.uns_p[1] = 1;
15601      h.uns_p[2] = 1;
15602      h.uns_p[3] = 1;
15603      break;
15604
15605      /* signed permute functions with unsigned char mask.  */
15606    case ALTIVEC_BUILTIN_VPERM_16QI:
15607    case ALTIVEC_BUILTIN_VPERM_8HI:
15608    case ALTIVEC_BUILTIN_VPERM_4SI:
15609    case ALTIVEC_BUILTIN_VPERM_4SF:
15610    case ALTIVEC_BUILTIN_VPERM_2DI:
15611    case ALTIVEC_BUILTIN_VPERM_2DF:
15612    case VSX_BUILTIN_VPERM_16QI:
15613    case VSX_BUILTIN_VPERM_8HI:
15614    case VSX_BUILTIN_VPERM_4SI:
15615    case VSX_BUILTIN_VPERM_4SF:
15616    case VSX_BUILTIN_VPERM_2DI:
15617    case VSX_BUILTIN_VPERM_2DF:
15618      h.uns_p[3] = 1;
15619      break;
15620
15621      /* unsigned args, signed return.  */
15622    case VSX_BUILTIN_XVCVUXDDP_UNS:
15623    case ALTIVEC_BUILTIN_UNSFLOAT_V4SI_V4SF:
15624      h.uns_p[1] = 1;
15625      break;
15626
15627      /* signed args, unsigned return.  */
15628    case VSX_BUILTIN_XVCVDPUXDS_UNS:
15629    case ALTIVEC_BUILTIN_FIXUNS_V4SF_V4SI:
15630    case MISC_BUILTIN_UNPACK_TD:
15631    case MISC_BUILTIN_UNPACK_V1TI:
15632      h.uns_p[0] = 1;
15633      break;
15634
15635      /* unsigned arguments for 128-bit pack instructions.  */
15636    case MISC_BUILTIN_PACK_TD:
15637    case MISC_BUILTIN_PACK_V1TI:
15638      h.uns_p[1] = 1;
15639      h.uns_p[2] = 1;
15640      break;
15641
15642    default:
15643      break;
15644    }
15645
15646  /* Figure out how many args are present.  */
15647  while (num_args > 0 && h.mode[num_args] == VOIDmode)
15648    num_args--;
15649
15650  if (num_args == 0)
15651    fatal_error (input_location,
15652		 "internal error: builtin function %s had no type", name);
15653
15654  ret_type = builtin_mode_to_type[h.mode[0]][h.uns_p[0]];
15655  if (!ret_type && h.uns_p[0])
15656    ret_type = builtin_mode_to_type[h.mode[0]][0];
15657
15658  if (!ret_type)
15659    fatal_error (input_location,
15660		 "internal error: builtin function %s had an unexpected "
15661		 "return type %s", name, GET_MODE_NAME (h.mode[0]));
15662
15663  for (i = 0; i < (int) ARRAY_SIZE (arg_type); i++)
15664    arg_type[i] = NULL_TREE;
15665
15666  for (i = 0; i < num_args; i++)
15667    {
15668      int m = (int) h.mode[i+1];
15669      int uns_p = h.uns_p[i+1];
15670
15671      arg_type[i] = builtin_mode_to_type[m][uns_p];
15672      if (!arg_type[i] && uns_p)
15673	arg_type[i] = builtin_mode_to_type[m][0];
15674
15675      if (!arg_type[i])
15676	fatal_error (input_location,
15677		     "internal error: builtin function %s, argument %d "
15678		     "had unexpected argument type %s", name, i,
15679		     GET_MODE_NAME (m));
15680    }
15681
15682  builtin_hash_struct **found = builtin_hash_table->find_slot (&h, INSERT);
15683  if (*found == NULL)
15684    {
15685      h2 = ggc_alloc<builtin_hash_struct> ();
15686      *h2 = h;
15687      *found = h2;
15688
15689      h2->type = build_function_type_list (ret_type, arg_type[0], arg_type[1],
15690					   arg_type[2], NULL_TREE);
15691    }
15692
15693  return (*found)->type;
15694}
15695
15696static void
15697rs6000_common_init_builtins (void)
15698{
15699  const struct builtin_description *d;
15700  size_t i;
15701
15702  tree opaque_ftype_opaque = NULL_TREE;
15703  tree opaque_ftype_opaque_opaque = NULL_TREE;
15704  tree opaque_ftype_opaque_opaque_opaque = NULL_TREE;
15705  tree v2si_ftype_qi = NULL_TREE;
15706  tree v2si_ftype_v2si_qi = NULL_TREE;
15707  tree v2si_ftype_int_qi = NULL_TREE;
15708  HOST_WIDE_INT builtin_mask = rs6000_builtin_mask;
15709
15710  if (!TARGET_PAIRED_FLOAT)
15711    {
15712      builtin_mode_to_type[V2SImode][0] = opaque_V2SI_type_node;
15713      builtin_mode_to_type[V2SFmode][0] = opaque_V2SF_type_node;
15714    }
15715
15716  /* Paired and SPE builtins are only available if you build a compiler with
15717     the appropriate options, so only create those builtins with the
15718     appropriate compiler option.  Create Altivec and VSX builtins on machines
15719     with at least the general purpose extensions (970 and newer) to allow the
15720     use of the target attribute..  */
15721
15722  if (TARGET_EXTRA_BUILTINS)
15723    builtin_mask |= RS6000_BTM_COMMON;
15724
15725  /* Add the ternary operators.  */
15726  d = bdesc_3arg;
15727  for (i = 0; i < ARRAY_SIZE (bdesc_3arg); i++, d++)
15728    {
15729      tree type;
15730      HOST_WIDE_INT mask = d->mask;
15731
15732      if ((mask & builtin_mask) != mask)
15733	{
15734	  if (TARGET_DEBUG_BUILTIN)
15735	    fprintf (stderr, "rs6000_builtin, skip ternary %s\n", d->name);
15736	  continue;
15737	}
15738
15739      if (rs6000_overloaded_builtin_p (d->code))
15740	{
15741	  if (! (type = opaque_ftype_opaque_opaque_opaque))
15742	    type = opaque_ftype_opaque_opaque_opaque
15743	      = build_function_type_list (opaque_V4SI_type_node,
15744					  opaque_V4SI_type_node,
15745					  opaque_V4SI_type_node,
15746					  opaque_V4SI_type_node,
15747					  NULL_TREE);
15748	}
15749      else
15750	{
15751	  enum insn_code icode = d->icode;
15752	  if (d->name == 0)
15753	    {
15754	      if (TARGET_DEBUG_BUILTIN)
15755		fprintf (stderr, "rs6000_builtin, bdesc_3arg[%ld] no name\n",
15756			 (long unsigned)i);
15757
15758	      continue;
15759	    }
15760
15761          if (icode == CODE_FOR_nothing)
15762	    {
15763	      if (TARGET_DEBUG_BUILTIN)
15764		fprintf (stderr, "rs6000_builtin, skip ternary %s (no code)\n",
15765			 d->name);
15766
15767	      continue;
15768	    }
15769
15770	  type = builtin_function_type (insn_data[icode].operand[0].mode,
15771					insn_data[icode].operand[1].mode,
15772					insn_data[icode].operand[2].mode,
15773					insn_data[icode].operand[3].mode,
15774					d->code, d->name);
15775	}
15776
15777      def_builtin (d->name, type, d->code);
15778    }
15779
15780  /* Add the binary operators.  */
15781  d = bdesc_2arg;
15782  for (i = 0; i < ARRAY_SIZE (bdesc_2arg); i++, d++)
15783    {
15784      machine_mode mode0, mode1, mode2;
15785      tree type;
15786      HOST_WIDE_INT mask = d->mask;
15787
15788      if ((mask & builtin_mask) != mask)
15789	{
15790	  if (TARGET_DEBUG_BUILTIN)
15791	    fprintf (stderr, "rs6000_builtin, skip binary %s\n", d->name);
15792	  continue;
15793	}
15794
15795      if (rs6000_overloaded_builtin_p (d->code))
15796	{
15797	  if (! (type = opaque_ftype_opaque_opaque))
15798	    type = opaque_ftype_opaque_opaque
15799	      = build_function_type_list (opaque_V4SI_type_node,
15800					  opaque_V4SI_type_node,
15801					  opaque_V4SI_type_node,
15802					  NULL_TREE);
15803	}
15804      else
15805	{
15806	  enum insn_code icode = d->icode;
15807	  if (d->name == 0)
15808	    {
15809	      if (TARGET_DEBUG_BUILTIN)
15810		fprintf (stderr, "rs6000_builtin, bdesc_2arg[%ld] no name\n",
15811			 (long unsigned)i);
15812
15813	      continue;
15814	    }
15815
15816          if (icode == CODE_FOR_nothing)
15817	    {
15818	      if (TARGET_DEBUG_BUILTIN)
15819		fprintf (stderr, "rs6000_builtin, skip binary %s (no code)\n",
15820			 d->name);
15821
15822	      continue;
15823	    }
15824
15825          mode0 = insn_data[icode].operand[0].mode;
15826          mode1 = insn_data[icode].operand[1].mode;
15827          mode2 = insn_data[icode].operand[2].mode;
15828
15829	  if (mode0 == V2SImode && mode1 == V2SImode && mode2 == QImode)
15830	    {
15831	      if (! (type = v2si_ftype_v2si_qi))
15832		type = v2si_ftype_v2si_qi
15833		  = build_function_type_list (opaque_V2SI_type_node,
15834					      opaque_V2SI_type_node,
15835					      char_type_node,
15836					      NULL_TREE);
15837	    }
15838
15839	  else if (mode0 == V2SImode && GET_MODE_CLASS (mode1) == MODE_INT
15840		   && mode2 == QImode)
15841	    {
15842	      if (! (type = v2si_ftype_int_qi))
15843		type = v2si_ftype_int_qi
15844		  = build_function_type_list (opaque_V2SI_type_node,
15845					      integer_type_node,
15846					      char_type_node,
15847					      NULL_TREE);
15848	    }
15849
15850	  else
15851	    type = builtin_function_type (mode0, mode1, mode2, VOIDmode,
15852					  d->code, d->name);
15853	}
15854
15855      def_builtin (d->name, type, d->code);
15856    }
15857
15858  /* Add the simple unary operators.  */
15859  d = bdesc_1arg;
15860  for (i = 0; i < ARRAY_SIZE (bdesc_1arg); i++, d++)
15861    {
15862      machine_mode mode0, mode1;
15863      tree type;
15864      HOST_WIDE_INT mask = d->mask;
15865
15866      if ((mask & builtin_mask) != mask)
15867	{
15868	  if (TARGET_DEBUG_BUILTIN)
15869	    fprintf (stderr, "rs6000_builtin, skip unary %s\n", d->name);
15870	  continue;
15871	}
15872
15873      if (rs6000_overloaded_builtin_p (d->code))
15874	{
15875	  if (! (type = opaque_ftype_opaque))
15876	    type = opaque_ftype_opaque
15877	      = build_function_type_list (opaque_V4SI_type_node,
15878					  opaque_V4SI_type_node,
15879					  NULL_TREE);
15880	}
15881      else
15882        {
15883	  enum insn_code icode = d->icode;
15884	  if (d->name == 0)
15885	    {
15886	      if (TARGET_DEBUG_BUILTIN)
15887		fprintf (stderr, "rs6000_builtin, bdesc_1arg[%ld] no name\n",
15888			 (long unsigned)i);
15889
15890	      continue;
15891	    }
15892
15893          if (icode == CODE_FOR_nothing)
15894	    {
15895	      if (TARGET_DEBUG_BUILTIN)
15896		fprintf (stderr, "rs6000_builtin, skip unary %s (no code)\n",
15897			 d->name);
15898
15899	      continue;
15900	    }
15901
15902          mode0 = insn_data[icode].operand[0].mode;
15903          mode1 = insn_data[icode].operand[1].mode;
15904
15905	  if (mode0 == V2SImode && mode1 == QImode)
15906	    {
15907	      if (! (type = v2si_ftype_qi))
15908		type = v2si_ftype_qi
15909		  = build_function_type_list (opaque_V2SI_type_node,
15910					      char_type_node,
15911					      NULL_TREE);
15912	    }
15913
15914	  else
15915	    type = builtin_function_type (mode0, mode1, VOIDmode, VOIDmode,
15916					  d->code, d->name);
15917	}
15918
15919      def_builtin (d->name, type, d->code);
15920    }
15921}
15922
15923static void
15924rs6000_init_libfuncs (void)
15925{
15926  if (!TARGET_IEEEQUAD)
15927      /* AIX/Darwin/64-bit Linux quad floating point routines.  */
15928    if (!TARGET_XL_COMPAT)
15929      {
15930	set_optab_libfunc (add_optab, TFmode, "__gcc_qadd");
15931	set_optab_libfunc (sub_optab, TFmode, "__gcc_qsub");
15932	set_optab_libfunc (smul_optab, TFmode, "__gcc_qmul");
15933	set_optab_libfunc (sdiv_optab, TFmode, "__gcc_qdiv");
15934
15935	if (!(TARGET_HARD_FLOAT && (TARGET_FPRS || TARGET_E500_DOUBLE)))
15936	  {
15937	    set_optab_libfunc (neg_optab, TFmode, "__gcc_qneg");
15938	    set_optab_libfunc (eq_optab, TFmode, "__gcc_qeq");
15939	    set_optab_libfunc (ne_optab, TFmode, "__gcc_qne");
15940	    set_optab_libfunc (gt_optab, TFmode, "__gcc_qgt");
15941	    set_optab_libfunc (ge_optab, TFmode, "__gcc_qge");
15942	    set_optab_libfunc (lt_optab, TFmode, "__gcc_qlt");
15943	    set_optab_libfunc (le_optab, TFmode, "__gcc_qle");
15944
15945	    set_conv_libfunc (sext_optab, TFmode, SFmode, "__gcc_stoq");
15946	    set_conv_libfunc (sext_optab, TFmode, DFmode, "__gcc_dtoq");
15947	    set_conv_libfunc (trunc_optab, SFmode, TFmode, "__gcc_qtos");
15948	    set_conv_libfunc (trunc_optab, DFmode, TFmode, "__gcc_qtod");
15949	    set_conv_libfunc (sfix_optab, SImode, TFmode, "__gcc_qtoi");
15950	    set_conv_libfunc (ufix_optab, SImode, TFmode, "__gcc_qtou");
15951	    set_conv_libfunc (sfloat_optab, TFmode, SImode, "__gcc_itoq");
15952	    set_conv_libfunc (ufloat_optab, TFmode, SImode, "__gcc_utoq");
15953	  }
15954
15955	if (!(TARGET_HARD_FLOAT && TARGET_FPRS))
15956	  set_optab_libfunc (unord_optab, TFmode, "__gcc_qunord");
15957      }
15958    else
15959      {
15960	set_optab_libfunc (add_optab, TFmode, "_xlqadd");
15961	set_optab_libfunc (sub_optab, TFmode, "_xlqsub");
15962	set_optab_libfunc (smul_optab, TFmode, "_xlqmul");
15963	set_optab_libfunc (sdiv_optab, TFmode, "_xlqdiv");
15964      }
15965  else
15966    {
15967      /* 32-bit SVR4 quad floating point routines.  */
15968
15969      set_optab_libfunc (add_optab, TFmode, "_q_add");
15970      set_optab_libfunc (sub_optab, TFmode, "_q_sub");
15971      set_optab_libfunc (neg_optab, TFmode, "_q_neg");
15972      set_optab_libfunc (smul_optab, TFmode, "_q_mul");
15973      set_optab_libfunc (sdiv_optab, TFmode, "_q_div");
15974      if (TARGET_PPC_GPOPT)
15975	set_optab_libfunc (sqrt_optab, TFmode, "_q_sqrt");
15976
15977      set_optab_libfunc (eq_optab, TFmode, "_q_feq");
15978      set_optab_libfunc (ne_optab, TFmode, "_q_fne");
15979      set_optab_libfunc (gt_optab, TFmode, "_q_fgt");
15980      set_optab_libfunc (ge_optab, TFmode, "_q_fge");
15981      set_optab_libfunc (lt_optab, TFmode, "_q_flt");
15982      set_optab_libfunc (le_optab, TFmode, "_q_fle");
15983
15984      set_conv_libfunc (sext_optab, TFmode, SFmode, "_q_stoq");
15985      set_conv_libfunc (sext_optab, TFmode, DFmode, "_q_dtoq");
15986      set_conv_libfunc (trunc_optab, SFmode, TFmode, "_q_qtos");
15987      set_conv_libfunc (trunc_optab, DFmode, TFmode, "_q_qtod");
15988      set_conv_libfunc (sfix_optab, SImode, TFmode, "_q_qtoi");
15989      set_conv_libfunc (ufix_optab, SImode, TFmode, "_q_qtou");
15990      set_conv_libfunc (sfloat_optab, TFmode, SImode, "_q_itoq");
15991      set_conv_libfunc (ufloat_optab, TFmode, SImode, "_q_utoq");
15992    }
15993}
15994
15995
15996/* Expand a block clear operation, and return 1 if successful.  Return 0
15997   if we should let the compiler generate normal code.
15998
15999   operands[0] is the destination
16000   operands[1] is the length
16001   operands[3] is the alignment */
16002
16003int
16004expand_block_clear (rtx operands[])
16005{
16006  rtx orig_dest = operands[0];
16007  rtx bytes_rtx	= operands[1];
16008  rtx align_rtx = operands[3];
16009  bool constp	= (GET_CODE (bytes_rtx) == CONST_INT);
16010  HOST_WIDE_INT align;
16011  HOST_WIDE_INT bytes;
16012  int offset;
16013  int clear_bytes;
16014  int clear_step;
16015
16016  /* If this is not a fixed size move, just call memcpy */
16017  if (! constp)
16018    return 0;
16019
16020  /* This must be a fixed size alignment  */
16021  gcc_assert (GET_CODE (align_rtx) == CONST_INT);
16022  align = INTVAL (align_rtx) * BITS_PER_UNIT;
16023
16024  /* Anything to clear? */
16025  bytes = INTVAL (bytes_rtx);
16026  if (bytes <= 0)
16027    return 1;
16028
16029  /* Use the builtin memset after a point, to avoid huge code bloat.
16030     When optimize_size, avoid any significant code bloat; calling
16031     memset is about 4 instructions, so allow for one instruction to
16032     load zero and three to do clearing.  */
16033  if (TARGET_ALTIVEC && align >= 128)
16034    clear_step = 16;
16035  else if (TARGET_POWERPC64 && (align >= 64 || !STRICT_ALIGNMENT))
16036    clear_step = 8;
16037  else if (TARGET_SPE && align >= 64)
16038    clear_step = 8;
16039  else
16040    clear_step = 4;
16041
16042  if (optimize_size && bytes > 3 * clear_step)
16043    return 0;
16044  if (! optimize_size && bytes > 8 * clear_step)
16045    return 0;
16046
16047  for (offset = 0; bytes > 0; offset += clear_bytes, bytes -= clear_bytes)
16048    {
16049      machine_mode mode = BLKmode;
16050      rtx dest;
16051
16052      if (bytes >= 16 && TARGET_ALTIVEC && align >= 128)
16053	{
16054	  clear_bytes = 16;
16055	  mode = V4SImode;
16056	}
16057      else if (bytes >= 8 && TARGET_SPE && align >= 64)
16058        {
16059          clear_bytes = 8;
16060          mode = V2SImode;
16061        }
16062      else if (bytes >= 8 && TARGET_POWERPC64
16063	       && (align >= 64 || !STRICT_ALIGNMENT))
16064	{
16065	  clear_bytes = 8;
16066	  mode = DImode;
16067	  if (offset == 0 && align < 64)
16068	    {
16069	      rtx addr;
16070
16071	      /* If the address form is reg+offset with offset not a
16072		 multiple of four, reload into reg indirect form here
16073		 rather than waiting for reload.  This way we get one
16074		 reload, not one per store.  */
16075	      addr = XEXP (orig_dest, 0);
16076	      if ((GET_CODE (addr) == PLUS || GET_CODE (addr) == LO_SUM)
16077		  && GET_CODE (XEXP (addr, 1)) == CONST_INT
16078		  && (INTVAL (XEXP (addr, 1)) & 3) != 0)
16079		{
16080		  addr = copy_addr_to_reg (addr);
16081		  orig_dest = replace_equiv_address (orig_dest, addr);
16082		}
16083	    }
16084	}
16085      else if (bytes >= 4 && (align >= 32 || !STRICT_ALIGNMENT))
16086	{			/* move 4 bytes */
16087	  clear_bytes = 4;
16088	  mode = SImode;
16089	}
16090      else if (bytes >= 2 && (align >= 16 || !STRICT_ALIGNMENT))
16091	{			/* move 2 bytes */
16092	  clear_bytes = 2;
16093	  mode = HImode;
16094	}
16095      else /* move 1 byte at a time */
16096	{
16097	  clear_bytes = 1;
16098	  mode = QImode;
16099	}
16100
16101      dest = adjust_address (orig_dest, mode, offset);
16102
16103      emit_move_insn (dest, CONST0_RTX (mode));
16104    }
16105
16106  return 1;
16107}
16108
16109
16110/* Expand a block move operation, and return 1 if successful.  Return 0
16111   if we should let the compiler generate normal code.
16112
16113   operands[0] is the destination
16114   operands[1] is the source
16115   operands[2] is the length
16116   operands[3] is the alignment */
16117
16118#define MAX_MOVE_REG 4
16119
16120int
16121expand_block_move (rtx operands[])
16122{
16123  rtx orig_dest = operands[0];
16124  rtx orig_src	= operands[1];
16125  rtx bytes_rtx	= operands[2];
16126  rtx align_rtx = operands[3];
16127  int constp	= (GET_CODE (bytes_rtx) == CONST_INT);
16128  int align;
16129  int bytes;
16130  int offset;
16131  int move_bytes;
16132  rtx stores[MAX_MOVE_REG];
16133  int num_reg = 0;
16134
16135  /* If this is not a fixed size move, just call memcpy */
16136  if (! constp)
16137    return 0;
16138
16139  /* This must be a fixed size alignment */
16140  gcc_assert (GET_CODE (align_rtx) == CONST_INT);
16141  align = INTVAL (align_rtx) * BITS_PER_UNIT;
16142
16143  /* Anything to move? */
16144  bytes = INTVAL (bytes_rtx);
16145  if (bytes <= 0)
16146    return 1;
16147
16148  if (bytes > rs6000_block_move_inline_limit)
16149    return 0;
16150
16151  for (offset = 0; bytes > 0; offset += move_bytes, bytes -= move_bytes)
16152    {
16153      union {
16154	rtx (*movmemsi) (rtx, rtx, rtx, rtx);
16155	rtx (*mov) (rtx, rtx);
16156      } gen_func;
16157      machine_mode mode = BLKmode;
16158      rtx src, dest;
16159
16160      /* Altivec first, since it will be faster than a string move
16161	 when it applies, and usually not significantly larger.  */
16162      if (TARGET_ALTIVEC && bytes >= 16 && align >= 128)
16163	{
16164	  move_bytes = 16;
16165	  mode = V4SImode;
16166	  gen_func.mov = gen_movv4si;
16167	}
16168      else if (TARGET_SPE && bytes >= 8 && align >= 64)
16169        {
16170          move_bytes = 8;
16171          mode = V2SImode;
16172          gen_func.mov = gen_movv2si;
16173        }
16174      else if (TARGET_STRING
16175	  && bytes > 24		/* move up to 32 bytes at a time */
16176	  && ! fixed_regs[5]
16177	  && ! fixed_regs[6]
16178	  && ! fixed_regs[7]
16179	  && ! fixed_regs[8]
16180	  && ! fixed_regs[9]
16181	  && ! fixed_regs[10]
16182	  && ! fixed_regs[11]
16183	  && ! fixed_regs[12])
16184	{
16185	  move_bytes = (bytes > 32) ? 32 : bytes;
16186	  gen_func.movmemsi = gen_movmemsi_8reg;
16187	}
16188      else if (TARGET_STRING
16189	       && bytes > 16	/* move up to 24 bytes at a time */
16190	       && ! fixed_regs[5]
16191	       && ! fixed_regs[6]
16192	       && ! fixed_regs[7]
16193	       && ! fixed_regs[8]
16194	       && ! fixed_regs[9]
16195	       && ! fixed_regs[10])
16196	{
16197	  move_bytes = (bytes > 24) ? 24 : bytes;
16198	  gen_func.movmemsi = gen_movmemsi_6reg;
16199	}
16200      else if (TARGET_STRING
16201	       && bytes > 8	/* move up to 16 bytes at a time */
16202	       && ! fixed_regs[5]
16203	       && ! fixed_regs[6]
16204	       && ! fixed_regs[7]
16205	       && ! fixed_regs[8])
16206	{
16207	  move_bytes = (bytes > 16) ? 16 : bytes;
16208	  gen_func.movmemsi = gen_movmemsi_4reg;
16209	}
16210      else if (bytes >= 8 && TARGET_POWERPC64
16211	       && (align >= 64 || !STRICT_ALIGNMENT))
16212	{
16213	  move_bytes = 8;
16214	  mode = DImode;
16215	  gen_func.mov = gen_movdi;
16216	  if (offset == 0 && align < 64)
16217	    {
16218	      rtx addr;
16219
16220	      /* If the address form is reg+offset with offset not a
16221		 multiple of four, reload into reg indirect form here
16222		 rather than waiting for reload.  This way we get one
16223		 reload, not one per load and/or store.  */
16224	      addr = XEXP (orig_dest, 0);
16225	      if ((GET_CODE (addr) == PLUS || GET_CODE (addr) == LO_SUM)
16226		  && GET_CODE (XEXP (addr, 1)) == CONST_INT
16227		  && (INTVAL (XEXP (addr, 1)) & 3) != 0)
16228		{
16229		  addr = copy_addr_to_reg (addr);
16230		  orig_dest = replace_equiv_address (orig_dest, addr);
16231		}
16232	      addr = XEXP (orig_src, 0);
16233	      if ((GET_CODE (addr) == PLUS || GET_CODE (addr) == LO_SUM)
16234		  && GET_CODE (XEXP (addr, 1)) == CONST_INT
16235		  && (INTVAL (XEXP (addr, 1)) & 3) != 0)
16236		{
16237		  addr = copy_addr_to_reg (addr);
16238		  orig_src = replace_equiv_address (orig_src, addr);
16239		}
16240	    }
16241	}
16242      else if (TARGET_STRING && bytes > 4 && !TARGET_POWERPC64)
16243	{			/* move up to 8 bytes at a time */
16244	  move_bytes = (bytes > 8) ? 8 : bytes;
16245	  gen_func.movmemsi = gen_movmemsi_2reg;
16246	}
16247      else if (bytes >= 4 && (align >= 32 || !STRICT_ALIGNMENT))
16248	{			/* move 4 bytes */
16249	  move_bytes = 4;
16250	  mode = SImode;
16251	  gen_func.mov = gen_movsi;
16252	}
16253      else if (bytes >= 2 && (align >= 16 || !STRICT_ALIGNMENT))
16254	{			/* move 2 bytes */
16255	  move_bytes = 2;
16256	  mode = HImode;
16257	  gen_func.mov = gen_movhi;
16258	}
16259      else if (TARGET_STRING && bytes > 1)
16260	{			/* move up to 4 bytes at a time */
16261	  move_bytes = (bytes > 4) ? 4 : bytes;
16262	  gen_func.movmemsi = gen_movmemsi_1reg;
16263	}
16264      else /* move 1 byte at a time */
16265	{
16266	  move_bytes = 1;
16267	  mode = QImode;
16268	  gen_func.mov = gen_movqi;
16269	}
16270
16271      src = adjust_address (orig_src, mode, offset);
16272      dest = adjust_address (orig_dest, mode, offset);
16273
16274      if (mode != BLKmode)
16275	{
16276	  rtx tmp_reg = gen_reg_rtx (mode);
16277
16278	  emit_insn ((*gen_func.mov) (tmp_reg, src));
16279	  stores[num_reg++] = (*gen_func.mov) (dest, tmp_reg);
16280	}
16281
16282      if (mode == BLKmode || num_reg >= MAX_MOVE_REG || bytes == move_bytes)
16283	{
16284	  int i;
16285	  for (i = 0; i < num_reg; i++)
16286	    emit_insn (stores[i]);
16287	  num_reg = 0;
16288	}
16289
16290      if (mode == BLKmode)
16291	{
16292	  /* Move the address into scratch registers.  The movmemsi
16293	     patterns require zero offset.  */
16294	  if (!REG_P (XEXP (src, 0)))
16295	    {
16296	      rtx src_reg = copy_addr_to_reg (XEXP (src, 0));
16297	      src = replace_equiv_address (src, src_reg);
16298	    }
16299	  set_mem_size (src, move_bytes);
16300
16301	  if (!REG_P (XEXP (dest, 0)))
16302	    {
16303	      rtx dest_reg = copy_addr_to_reg (XEXP (dest, 0));
16304	      dest = replace_equiv_address (dest, dest_reg);
16305	    }
16306	  set_mem_size (dest, move_bytes);
16307
16308	  emit_insn ((*gen_func.movmemsi) (dest, src,
16309					   GEN_INT (move_bytes & 31),
16310					   align_rtx));
16311	}
16312    }
16313
16314  return 1;
16315}
16316
16317
16318/* Return a string to perform a load_multiple operation.
16319   operands[0] is the vector.
16320   operands[1] is the source address.
16321   operands[2] is the first destination register.  */
16322
16323const char *
16324rs6000_output_load_multiple (rtx operands[3])
16325{
16326  /* We have to handle the case where the pseudo used to contain the address
16327     is assigned to one of the output registers.  */
16328  int i, j;
16329  int words = XVECLEN (operands[0], 0);
16330  rtx xop[10];
16331
16332  if (XVECLEN (operands[0], 0) == 1)
16333    return "lwz %2,0(%1)";
16334
16335  for (i = 0; i < words; i++)
16336    if (refers_to_regno_p (REGNO (operands[2]) + i, operands[1]))
16337      {
16338	if (i == words-1)
16339	  {
16340	    xop[0] = GEN_INT (4 * (words-1));
16341	    xop[1] = operands[1];
16342	    xop[2] = operands[2];
16343	    output_asm_insn ("lswi %2,%1,%0\n\tlwz %1,%0(%1)", xop);
16344	    return "";
16345	  }
16346	else if (i == 0)
16347	  {
16348	    xop[0] = GEN_INT (4 * (words-1));
16349	    xop[1] = operands[1];
16350	    xop[2] = gen_rtx_REG (SImode, REGNO (operands[2]) + 1);
16351	    output_asm_insn ("addi %1,%1,4\n\tlswi %2,%1,%0\n\tlwz %1,-4(%1)", xop);
16352	    return "";
16353	  }
16354	else
16355	  {
16356	    for (j = 0; j < words; j++)
16357	      if (j != i)
16358		{
16359		  xop[0] = GEN_INT (j * 4);
16360		  xop[1] = operands[1];
16361		  xop[2] = gen_rtx_REG (SImode, REGNO (operands[2]) + j);
16362		  output_asm_insn ("lwz %2,%0(%1)", xop);
16363		}
16364	    xop[0] = GEN_INT (i * 4);
16365	    xop[1] = operands[1];
16366	    output_asm_insn ("lwz %1,%0(%1)", xop);
16367	    return "";
16368	  }
16369      }
16370
16371  return "lswi %2,%1,%N0";
16372}
16373
16374
16375/* A validation routine: say whether CODE, a condition code, and MODE
16376   match.  The other alternatives either don't make sense or should
16377   never be generated.  */
16378
16379void
16380validate_condition_mode (enum rtx_code code, machine_mode mode)
16381{
16382  gcc_assert ((GET_RTX_CLASS (code) == RTX_COMPARE
16383	       || GET_RTX_CLASS (code) == RTX_COMM_COMPARE)
16384	      && GET_MODE_CLASS (mode) == MODE_CC);
16385
16386  /* These don't make sense.  */
16387  gcc_assert ((code != GT && code != LT && code != GE && code != LE)
16388	      || mode != CCUNSmode);
16389
16390  gcc_assert ((code != GTU && code != LTU && code != GEU && code != LEU)
16391	      || mode == CCUNSmode);
16392
16393  gcc_assert (mode == CCFPmode
16394	      || (code != ORDERED && code != UNORDERED
16395		  && code != UNEQ && code != LTGT
16396		  && code != UNGT && code != UNLT
16397		  && code != UNGE && code != UNLE));
16398
16399  /* These should never be generated except for
16400     flag_finite_math_only.  */
16401  gcc_assert (mode != CCFPmode
16402	      || flag_finite_math_only
16403	      || (code != LE && code != GE
16404		  && code != UNEQ && code != LTGT
16405		  && code != UNGT && code != UNLT));
16406
16407  /* These are invalid; the information is not there.  */
16408  gcc_assert (mode != CCEQmode || code == EQ || code == NE);
16409}
16410
16411
16412/* Return 1 if ANDOP is a mask that has no bits on that are not in the
16413   mask required to convert the result of a rotate insn into a shift
16414   left insn of SHIFTOP bits.  Both are known to be SImode CONST_INT.  */
16415
16416int
16417includes_lshift_p (rtx shiftop, rtx andop)
16418{
16419  unsigned HOST_WIDE_INT shift_mask = ~(unsigned HOST_WIDE_INT) 0;
16420
16421  shift_mask <<= INTVAL (shiftop);
16422
16423  return (INTVAL (andop) & 0xffffffff & ~shift_mask) == 0;
16424}
16425
16426/* Similar, but for right shift.  */
16427
16428int
16429includes_rshift_p (rtx shiftop, rtx andop)
16430{
16431  unsigned HOST_WIDE_INT shift_mask = ~(unsigned HOST_WIDE_INT) 0;
16432
16433  shift_mask >>= INTVAL (shiftop);
16434
16435  return (INTVAL (andop) & 0xffffffff & ~shift_mask) == 0;
16436}
16437
16438/* Return 1 if ANDOP is a mask suitable for use with an rldic insn
16439   to perform a left shift.  It must have exactly SHIFTOP least
16440   significant 0's, then one or more 1's, then zero or more 0's.  */
16441
16442int
16443includes_rldic_lshift_p (rtx shiftop, rtx andop)
16444{
16445  if (GET_CODE (andop) == CONST_INT)
16446    {
16447      unsigned HOST_WIDE_INT c, lsb, shift_mask;
16448
16449      c = INTVAL (andop);
16450      if (c == 0 || c == HOST_WIDE_INT_M1U)
16451	return 0;
16452
16453      shift_mask = HOST_WIDE_INT_M1U;
16454      shift_mask <<= INTVAL (shiftop);
16455
16456      /* Find the least significant one bit.  */
16457      lsb = c & -c;
16458
16459      /* It must coincide with the LSB of the shift mask.  */
16460      if (-lsb != shift_mask)
16461	return 0;
16462
16463      /* Invert to look for the next transition (if any).  */
16464      c = ~c;
16465
16466      /* Remove the low group of ones (originally low group of zeros).  */
16467      c &= -lsb;
16468
16469      /* Again find the lsb, and check we have all 1's above.  */
16470      lsb = c & -c;
16471      return c == -lsb;
16472    }
16473  else
16474    return 0;
16475}
16476
16477/* Return 1 if ANDOP is a mask suitable for use with an rldicr insn
16478   to perform a left shift.  It must have SHIFTOP or more least
16479   significant 0's, with the remainder of the word 1's.  */
16480
16481int
16482includes_rldicr_lshift_p (rtx shiftop, rtx andop)
16483{
16484  if (GET_CODE (andop) == CONST_INT)
16485    {
16486      unsigned HOST_WIDE_INT c, lsb, shift_mask;
16487
16488      shift_mask = HOST_WIDE_INT_M1U;
16489      shift_mask <<= INTVAL (shiftop);
16490      c = INTVAL (andop);
16491
16492      /* Find the least significant one bit.  */
16493      lsb = c & -c;
16494
16495      /* It must be covered by the shift mask.
16496	 This test also rejects c == 0.  */
16497      if ((lsb & shift_mask) == 0)
16498	return 0;
16499
16500      /* Check we have all 1's above the transition, and reject all 1's.  */
16501      return c == -lsb && lsb != 1;
16502    }
16503  else
16504    return 0;
16505}
16506
16507/* Return 1 if operands will generate a valid arguments to rlwimi
16508instruction for insert with right shift in 64-bit mode.  The mask may
16509not start on the first bit or stop on the last bit because wrap-around
16510effects of instruction do not correspond to semantics of RTL insn.  */
16511
16512int
16513insvdi_rshift_rlwimi_p (rtx sizeop, rtx startop, rtx shiftop)
16514{
16515  if (INTVAL (startop) > 32
16516      && INTVAL (startop) < 64
16517      && INTVAL (sizeop) > 1
16518      && INTVAL (sizeop) + INTVAL (startop) < 64
16519      && INTVAL (shiftop) > 0
16520      && INTVAL (sizeop) + INTVAL (shiftop) < 32
16521      && (64 - (INTVAL (shiftop) & 63)) >= INTVAL (sizeop))
16522    return 1;
16523
16524  return 0;
16525}
16526
16527/* Return 1 if REGNO (reg1) == REGNO (reg2) - 1 making them candidates
16528   for lfq and stfq insns iff the registers are hard registers.   */
16529
16530int
16531registers_ok_for_quad_peep (rtx reg1, rtx reg2)
16532{
16533  /* We might have been passed a SUBREG.  */
16534  if (GET_CODE (reg1) != REG || GET_CODE (reg2) != REG)
16535    return 0;
16536
16537  /* We might have been passed non floating point registers.  */
16538  if (!FP_REGNO_P (REGNO (reg1))
16539      || !FP_REGNO_P (REGNO (reg2)))
16540    return 0;
16541
16542  return (REGNO (reg1) == REGNO (reg2) - 1);
16543}
16544
16545/* Return 1 if addr1 and addr2 are suitable for lfq or stfq insn.
16546   addr1 and addr2 must be in consecutive memory locations
16547   (addr2 == addr1 + 8).  */
16548
16549int
16550mems_ok_for_quad_peep (rtx mem1, rtx mem2)
16551{
16552  rtx addr1, addr2;
16553  unsigned int reg1, reg2;
16554  int offset1, offset2;
16555
16556  /* The mems cannot be volatile.  */
16557  if (MEM_VOLATILE_P (mem1) || MEM_VOLATILE_P (mem2))
16558    return 0;
16559
16560  addr1 = XEXP (mem1, 0);
16561  addr2 = XEXP (mem2, 0);
16562
16563  /* Extract an offset (if used) from the first addr.  */
16564  if (GET_CODE (addr1) == PLUS)
16565    {
16566      /* If not a REG, return zero.  */
16567      if (GET_CODE (XEXP (addr1, 0)) != REG)
16568	return 0;
16569      else
16570	{
16571	  reg1 = REGNO (XEXP (addr1, 0));
16572	  /* The offset must be constant!  */
16573	  if (GET_CODE (XEXP (addr1, 1)) != CONST_INT)
16574	    return 0;
16575	  offset1 = INTVAL (XEXP (addr1, 1));
16576	}
16577    }
16578  else if (GET_CODE (addr1) != REG)
16579    return 0;
16580  else
16581    {
16582      reg1 = REGNO (addr1);
16583      /* This was a simple (mem (reg)) expression.  Offset is 0.  */
16584      offset1 = 0;
16585    }
16586
16587  /* And now for the second addr.  */
16588  if (GET_CODE (addr2) == PLUS)
16589    {
16590      /* If not a REG, return zero.  */
16591      if (GET_CODE (XEXP (addr2, 0)) != REG)
16592	return 0;
16593      else
16594	{
16595	  reg2 = REGNO (XEXP (addr2, 0));
16596	  /* The offset must be constant. */
16597	  if (GET_CODE (XEXP (addr2, 1)) != CONST_INT)
16598	    return 0;
16599	  offset2 = INTVAL (XEXP (addr2, 1));
16600	}
16601    }
16602  else if (GET_CODE (addr2) != REG)
16603    return 0;
16604  else
16605    {
16606      reg2 = REGNO (addr2);
16607      /* This was a simple (mem (reg)) expression.  Offset is 0.  */
16608      offset2 = 0;
16609    }
16610
16611  /* Both of these must have the same base register.  */
16612  if (reg1 != reg2)
16613    return 0;
16614
16615  /* The offset for the second addr must be 8 more than the first addr.  */
16616  if (offset2 != offset1 + 8)
16617    return 0;
16618
16619  /* All the tests passed.  addr1 and addr2 are valid for lfq or stfq
16620     instructions.  */
16621  return 1;
16622}
16623
16624
16625rtx
16626rs6000_secondary_memory_needed_rtx (machine_mode mode)
16627{
16628  static bool eliminated = false;
16629  rtx ret;
16630
16631  if (mode != SDmode || TARGET_NO_SDMODE_STACK)
16632    ret = assign_stack_local (mode, GET_MODE_SIZE (mode), 0);
16633  else
16634    {
16635      rtx mem = cfun->machine->sdmode_stack_slot;
16636      gcc_assert (mem != NULL_RTX);
16637
16638      if (!eliminated)
16639	{
16640	  mem = eliminate_regs (mem, VOIDmode, NULL_RTX);
16641	  cfun->machine->sdmode_stack_slot = mem;
16642	  eliminated = true;
16643	}
16644      ret = mem;
16645    }
16646
16647  if (TARGET_DEBUG_ADDR)
16648    {
16649      fprintf (stderr, "\nrs6000_secondary_memory_needed_rtx, mode %s, rtx:\n",
16650	       GET_MODE_NAME (mode));
16651      if (!ret)
16652	fprintf (stderr, "\tNULL_RTX\n");
16653      else
16654	debug_rtx (ret);
16655    }
16656
16657  return ret;
16658}
16659
16660/* Return the mode to be used for memory when a secondary memory
16661   location is needed.  For SDmode values we need to use DDmode, in
16662   all other cases we can use the same mode.  */
16663machine_mode
16664rs6000_secondary_memory_needed_mode (machine_mode mode)
16665{
16666  if (lra_in_progress && mode == SDmode)
16667    return DDmode;
16668  return mode;
16669}
16670
16671static tree
16672rs6000_check_sdmode (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
16673{
16674  /* Don't walk into types.  */
16675  if (*tp == NULL_TREE || *tp == error_mark_node || TYPE_P (*tp))
16676    {
16677      *walk_subtrees = 0;
16678      return NULL_TREE;
16679    }
16680
16681  switch (TREE_CODE (*tp))
16682    {
16683    case VAR_DECL:
16684    case PARM_DECL:
16685    case FIELD_DECL:
16686    case RESULT_DECL:
16687    case SSA_NAME:
16688    case REAL_CST:
16689    case MEM_REF:
16690    case VIEW_CONVERT_EXPR:
16691      if (TYPE_MODE (TREE_TYPE (*tp)) == SDmode)
16692	return *tp;
16693      break;
16694    default:
16695      break;
16696    }
16697
16698  return NULL_TREE;
16699}
16700
16701/* Classify a register type.  Because the FMRGOW/FMRGEW instructions only work
16702   on traditional floating point registers, and the VMRGOW/VMRGEW instructions
16703   only work on the traditional altivec registers, note if an altivec register
16704   was chosen.  */
16705
16706static enum rs6000_reg_type
16707register_to_reg_type (rtx reg, bool *is_altivec)
16708{
16709  HOST_WIDE_INT regno;
16710  enum reg_class rclass;
16711
16712  if (GET_CODE (reg) == SUBREG)
16713    reg = SUBREG_REG (reg);
16714
16715  if (!REG_P (reg))
16716    return NO_REG_TYPE;
16717
16718  regno = REGNO (reg);
16719  if (regno >= FIRST_PSEUDO_REGISTER)
16720    {
16721      if (!lra_in_progress && !reload_in_progress && !reload_completed)
16722	return PSEUDO_REG_TYPE;
16723
16724      regno = true_regnum (reg);
16725      if (regno < 0 || regno >= FIRST_PSEUDO_REGISTER)
16726	return PSEUDO_REG_TYPE;
16727    }
16728
16729  gcc_assert (regno >= 0);
16730
16731  if (is_altivec && ALTIVEC_REGNO_P (regno))
16732    *is_altivec = true;
16733
16734  rclass = rs6000_regno_regclass[regno];
16735  return reg_class_to_reg_type[(int)rclass];
16736}
16737
16738/* Helper function to return the cost of adding a TOC entry address.  */
16739
16740static inline int
16741rs6000_secondary_reload_toc_costs (addr_mask_type addr_mask)
16742{
16743  int ret;
16744
16745  if (TARGET_CMODEL != CMODEL_SMALL)
16746    ret = ((addr_mask & RELOAD_REG_OFFSET) == 0) ? 1 : 2;
16747
16748  else
16749    ret = (TARGET_MINIMAL_TOC) ? 6 : 3;
16750
16751  return ret;
16752}
16753
16754/* Helper function for rs6000_secondary_reload to determine whether the memory
16755   address (ADDR) with a given register class (RCLASS) and machine mode (MODE)
16756   needs reloading.  Return negative if the memory is not handled by the memory
16757   helper functions and to try a different reload method, 0 if no additional
16758   instructions are need, and positive to give the extra cost for the
16759   memory.  */
16760
16761static int
16762rs6000_secondary_reload_memory (rtx addr,
16763				enum reg_class rclass,
16764				enum machine_mode mode)
16765{
16766  int extra_cost = 0;
16767  rtx reg, and_arg, plus_arg0, plus_arg1;
16768  addr_mask_type addr_mask;
16769  const char *type = NULL;
16770  const char *fail_msg = NULL;
16771
16772  if (GPR_REG_CLASS_P (rclass))
16773    addr_mask = reg_addr[mode].addr_mask[RELOAD_REG_GPR];
16774
16775  else if (rclass == FLOAT_REGS)
16776    addr_mask = reg_addr[mode].addr_mask[RELOAD_REG_FPR];
16777
16778  else if (rclass == ALTIVEC_REGS)
16779    addr_mask = reg_addr[mode].addr_mask[RELOAD_REG_VMX];
16780
16781  /* For the combined VSX_REGS, turn off Altivec AND -16.  */
16782  else if (rclass == VSX_REGS)
16783    addr_mask = (reg_addr[mode].addr_mask[RELOAD_REG_VMX]
16784		 & ~RELOAD_REG_AND_M16);
16785
16786  else
16787    {
16788      if (TARGET_DEBUG_ADDR)
16789	fprintf (stderr,
16790		 "rs6000_secondary_reload_memory: mode = %s, class = %s, "
16791		 "class is not GPR, FPR, VMX\n",
16792		 GET_MODE_NAME (mode), reg_class_names[rclass]);
16793
16794      return -1;
16795    }
16796
16797  /* If the register isn't valid in this register class, just return now.  */
16798  if ((addr_mask & RELOAD_REG_VALID) == 0)
16799    {
16800      if (TARGET_DEBUG_ADDR)
16801	fprintf (stderr,
16802		 "rs6000_secondary_reload_memory: mode = %s, class = %s, "
16803		 "not valid in class\n",
16804		 GET_MODE_NAME (mode), reg_class_names[rclass]);
16805
16806      return -1;
16807    }
16808
16809  switch (GET_CODE (addr))
16810    {
16811      /* Does the register class supports auto update forms for this mode?  We
16812	 don't need a scratch register, since the powerpc only supports
16813	 PRE_INC, PRE_DEC, and PRE_MODIFY.  */
16814    case PRE_INC:
16815    case PRE_DEC:
16816      reg = XEXP (addr, 0);
16817      if (!base_reg_operand (addr, GET_MODE (reg)))
16818	{
16819	  fail_msg = "no base register #1";
16820	  extra_cost = -1;
16821	}
16822
16823      else if ((addr_mask & RELOAD_REG_PRE_INCDEC) == 0)
16824	{
16825	  extra_cost = 1;
16826	  type = "update";
16827	}
16828      break;
16829
16830    case PRE_MODIFY:
16831      reg = XEXP (addr, 0);
16832      plus_arg1 = XEXP (addr, 1);
16833      if (!base_reg_operand (reg, GET_MODE (reg))
16834	  || GET_CODE (plus_arg1) != PLUS
16835	  || !rtx_equal_p (reg, XEXP (plus_arg1, 0)))
16836	{
16837	  fail_msg = "bad PRE_MODIFY";
16838	  extra_cost = -1;
16839	}
16840
16841      else if ((addr_mask & RELOAD_REG_PRE_MODIFY) == 0)
16842	{
16843	  extra_cost = 1;
16844	  type = "update";
16845	}
16846      break;
16847
16848      /* Do we need to simulate AND -16 to clear the bottom address bits used
16849	 in VMX load/stores?  Only allow the AND for vector sizes.  */
16850    case AND:
16851      and_arg = XEXP (addr, 0);
16852      if (GET_MODE_SIZE (mode) != 16
16853	  || GET_CODE (XEXP (addr, 1)) != CONST_INT
16854	  || INTVAL (XEXP (addr, 1)) != -16)
16855	{
16856	  fail_msg = "bad Altivec AND #1";
16857	  extra_cost = -1;
16858	}
16859
16860      if (rclass != ALTIVEC_REGS)
16861	{
16862	  if (legitimate_indirect_address_p (and_arg, false))
16863	    extra_cost = 1;
16864
16865	  else if (legitimate_indexed_address_p (and_arg, false))
16866	    extra_cost = 2;
16867
16868	  else
16869	    {
16870	      fail_msg = "bad Altivec AND #2";
16871	      extra_cost = -1;
16872	    }
16873
16874	  type = "and";
16875	}
16876      break;
16877
16878      /* If this is an indirect address, make sure it is a base register.  */
16879    case REG:
16880    case SUBREG:
16881      if (!legitimate_indirect_address_p (addr, false))
16882	{
16883	  extra_cost = 1;
16884	  type = "move";
16885	}
16886      break;
16887
16888      /* If this is an indexed address, make sure the register class can handle
16889	 indexed addresses for this mode.  */
16890    case PLUS:
16891      plus_arg0 = XEXP (addr, 0);
16892      plus_arg1 = XEXP (addr, 1);
16893
16894      /* (plus (plus (reg) (constant)) (constant)) is generated during
16895	 push_reload processing, so handle it now.  */
16896      if (GET_CODE (plus_arg0) == PLUS && CONST_INT_P (plus_arg1))
16897	{
16898	  if ((addr_mask & RELOAD_REG_OFFSET) == 0)
16899	    {
16900	      extra_cost = 1;
16901	      type = "offset";
16902	    }
16903	}
16904
16905      /* (plus (plus (reg) (constant)) (reg)) is also generated during
16906	 push_reload processing, so handle it now.  */
16907      else if (GET_CODE (plus_arg0) == PLUS && REG_P (plus_arg1))
16908	{
16909	  if ((addr_mask & RELOAD_REG_INDEXED) == 0)
16910	    {
16911	      extra_cost = 1;
16912	      type = "indexed #2";
16913	    }
16914	}
16915
16916      else if (!base_reg_operand (plus_arg0, GET_MODE (plus_arg0)))
16917	{
16918	  fail_msg = "no base register #2";
16919	  extra_cost = -1;
16920	}
16921
16922      else if (int_reg_operand (plus_arg1, GET_MODE (plus_arg1)))
16923	{
16924	  if ((addr_mask & RELOAD_REG_INDEXED) == 0
16925	      || !legitimate_indexed_address_p (addr, false))
16926	    {
16927	      extra_cost = 1;
16928	      type = "indexed";
16929	    }
16930	}
16931
16932      /* Make sure the register class can handle offset addresses.  */
16933      else if (rs6000_legitimate_offset_address_p (mode, addr, false, true))
16934	{
16935	  if ((addr_mask & RELOAD_REG_OFFSET) == 0)
16936	    {
16937	      extra_cost = 1;
16938	      type = "offset";
16939	    }
16940	}
16941
16942      else
16943	{
16944	  fail_msg = "bad PLUS";
16945	  extra_cost = -1;
16946	}
16947
16948      break;
16949
16950    case LO_SUM:
16951      if (!legitimate_lo_sum_address_p (mode, addr, false))
16952	{
16953	  fail_msg = "bad LO_SUM";
16954	  extra_cost = -1;
16955	}
16956
16957      if ((addr_mask & RELOAD_REG_OFFSET) == 0)
16958	{
16959	  extra_cost = 1;
16960	  type = "lo_sum";
16961	}
16962      break;
16963
16964      /* Static addresses need to create a TOC entry.  */
16965    case CONST:
16966    case SYMBOL_REF:
16967    case LABEL_REF:
16968      type = "address";
16969      extra_cost = rs6000_secondary_reload_toc_costs (addr_mask);
16970      break;
16971
16972      /* TOC references look like offsetable memory.  */
16973    case UNSPEC:
16974      if (TARGET_CMODEL == CMODEL_SMALL || XINT (addr, 1) != UNSPEC_TOCREL)
16975	{
16976	  fail_msg = "bad UNSPEC";
16977	  extra_cost = -1;
16978	}
16979
16980      else if ((addr_mask & RELOAD_REG_OFFSET) == 0)
16981	{
16982	  extra_cost = 1;
16983	  type = "toc reference";
16984	}
16985      break;
16986
16987    default:
16988	{
16989	  fail_msg = "bad address";
16990	  extra_cost = -1;
16991	}
16992    }
16993
16994  if (TARGET_DEBUG_ADDR /* && extra_cost != 0 */)
16995    {
16996      if (extra_cost < 0)
16997	fprintf (stderr,
16998		 "rs6000_secondary_reload_memory error: mode = %s, "
16999		 "class = %s, addr_mask = '%s', %s\n",
17000		 GET_MODE_NAME (mode),
17001		 reg_class_names[rclass],
17002		 rs6000_debug_addr_mask (addr_mask, false),
17003		 (fail_msg != NULL) ? fail_msg : "<bad address>");
17004
17005      else
17006	fprintf (stderr,
17007		 "rs6000_secondary_reload_memory: mode = %s, class = %s, "
17008		 "addr_mask = '%s', extra cost = %d, %s\n",
17009		 GET_MODE_NAME (mode),
17010		 reg_class_names[rclass],
17011		 rs6000_debug_addr_mask (addr_mask, false),
17012		 extra_cost,
17013		 (type) ? type : "<none>");
17014
17015      debug_rtx (addr);
17016    }
17017
17018  return extra_cost;
17019}
17020
17021/* Helper function for rs6000_secondary_reload to return true if a move to a
17022   different register classe is really a simple move.  */
17023
17024static bool
17025rs6000_secondary_reload_simple_move (enum rs6000_reg_type to_type,
17026				     enum rs6000_reg_type from_type,
17027				     machine_mode mode)
17028{
17029  int size;
17030
17031  /* Add support for various direct moves available.  In this function, we only
17032     look at cases where we don't need any extra registers, and one or more
17033     simple move insns are issued.  At present, 32-bit integers are not allowed
17034     in FPR/VSX registers.  Single precision binary floating is not a simple
17035     move because we need to convert to the single precision memory layout.
17036     The 4-byte SDmode can be moved.  */
17037  size = GET_MODE_SIZE (mode);
17038  if (TARGET_DIRECT_MOVE
17039      && ((mode == SDmode) || (TARGET_POWERPC64 && size == 8))
17040      && ((to_type == GPR_REG_TYPE && from_type == VSX_REG_TYPE)
17041	  || (to_type == VSX_REG_TYPE && from_type == GPR_REG_TYPE)))
17042    return true;
17043
17044  else if (TARGET_MFPGPR && TARGET_POWERPC64 && size == 8
17045	   && ((to_type == GPR_REG_TYPE && from_type == FPR_REG_TYPE)
17046	       || (to_type == FPR_REG_TYPE && from_type == GPR_REG_TYPE)))
17047    return true;
17048
17049  else if ((size == 4 || (TARGET_POWERPC64 && size == 8))
17050	   && ((to_type == GPR_REG_TYPE && from_type == SPR_REG_TYPE)
17051	       || (to_type == SPR_REG_TYPE && from_type == GPR_REG_TYPE)))
17052    return true;
17053
17054  return false;
17055}
17056
17057/* Power8 helper function for rs6000_secondary_reload, handle all of the
17058   special direct moves that involve allocating an extra register, return the
17059   insn code of the helper function if there is such a function or
17060   CODE_FOR_nothing if not.  */
17061
17062static bool
17063rs6000_secondary_reload_direct_move (enum rs6000_reg_type to_type,
17064				     enum rs6000_reg_type from_type,
17065				     machine_mode mode,
17066				     secondary_reload_info *sri,
17067				     bool altivec_p)
17068{
17069  bool ret = false;
17070  enum insn_code icode = CODE_FOR_nothing;
17071  int cost = 0;
17072  int size = GET_MODE_SIZE (mode);
17073
17074  if (TARGET_POWERPC64)
17075    {
17076      if (size == 16)
17077	{
17078	  /* Handle moving 128-bit values from GPRs to VSX point registers on
17079	     power8 when running in 64-bit mode using XXPERMDI to glue the two
17080	     64-bit values back together.  */
17081	  if (to_type == VSX_REG_TYPE && from_type == GPR_REG_TYPE)
17082	    {
17083	      cost = 3;			/* 2 mtvsrd's, 1 xxpermdi.  */
17084	      icode = reg_addr[mode].reload_vsx_gpr;
17085	    }
17086
17087	  /* Handle moving 128-bit values from VSX point registers to GPRs on
17088	     power8 when running in 64-bit mode using XXPERMDI to get access to the
17089	     bottom 64-bit value.  */
17090	  else if (to_type == GPR_REG_TYPE && from_type == VSX_REG_TYPE)
17091	    {
17092	      cost = 3;			/* 2 mfvsrd's, 1 xxpermdi.  */
17093	      icode = reg_addr[mode].reload_gpr_vsx;
17094	    }
17095	}
17096
17097      else if (mode == SFmode)
17098	{
17099	  if (to_type == GPR_REG_TYPE && from_type == VSX_REG_TYPE)
17100	    {
17101	      cost = 3;			/* xscvdpspn, mfvsrd, and.  */
17102	      icode = reg_addr[mode].reload_gpr_vsx;
17103	    }
17104
17105	  else if (to_type == VSX_REG_TYPE && from_type == GPR_REG_TYPE)
17106	    {
17107	      cost = 2;			/* mtvsrz, xscvspdpn.  */
17108	      icode = reg_addr[mode].reload_vsx_gpr;
17109	    }
17110	}
17111    }
17112
17113  if (TARGET_POWERPC64 && size == 16)
17114    {
17115      /* Handle moving 128-bit values from GPRs to VSX point registers on
17116	 power8 when running in 64-bit mode using XXPERMDI to glue the two
17117	 64-bit values back together.  */
17118      if (to_type == VSX_REG_TYPE && from_type == GPR_REG_TYPE)
17119	{
17120	  cost = 3;			/* 2 mtvsrd's, 1 xxpermdi.  */
17121	  icode = reg_addr[mode].reload_vsx_gpr;
17122	}
17123
17124      /* Handle moving 128-bit values from VSX point registers to GPRs on
17125	 power8 when running in 64-bit mode using XXPERMDI to get access to the
17126	 bottom 64-bit value.  */
17127      else if (to_type == GPR_REG_TYPE && from_type == VSX_REG_TYPE)
17128	{
17129	  cost = 3;			/* 2 mfvsrd's, 1 xxpermdi.  */
17130	  icode = reg_addr[mode].reload_gpr_vsx;
17131	}
17132    }
17133
17134  else if (!TARGET_POWERPC64 && size == 8)
17135    {
17136      /* Handle moving 64-bit values from GPRs to floating point registers on
17137	 power8 when running in 32-bit mode using FMRGOW to glue the two 32-bit
17138	 values back together.  Altivec register classes must be handled
17139	 specially since a different instruction is used, and the secondary
17140	 reload support requires a single instruction class in the scratch
17141	 register constraint.  However, right now TFmode is not allowed in
17142	 Altivec registers, so the pattern will never match.  */
17143      if (to_type == VSX_REG_TYPE && from_type == GPR_REG_TYPE && !altivec_p)
17144	{
17145	  cost = 3;			/* 2 mtvsrwz's, 1 fmrgow.  */
17146	  icode = reg_addr[mode].reload_fpr_gpr;
17147	}
17148    }
17149
17150  if (icode != CODE_FOR_nothing)
17151    {
17152      ret = true;
17153      if (sri)
17154	{
17155	  sri->icode = icode;
17156	  sri->extra_cost = cost;
17157	}
17158    }
17159
17160  return ret;
17161}
17162
17163/* Return whether a move between two register classes can be done either
17164   directly (simple move) or via a pattern that uses a single extra temporary
17165   (using power8's direct move in this case.  */
17166
17167static bool
17168rs6000_secondary_reload_move (enum rs6000_reg_type to_type,
17169			      enum rs6000_reg_type from_type,
17170			      machine_mode mode,
17171			      secondary_reload_info *sri,
17172			      bool altivec_p)
17173{
17174  /* Fall back to load/store reloads if either type is not a register.  */
17175  if (to_type == NO_REG_TYPE || from_type == NO_REG_TYPE)
17176    return false;
17177
17178  /* If we haven't allocated registers yet, assume the move can be done for the
17179     standard register types.  */
17180  if ((to_type == PSEUDO_REG_TYPE && from_type == PSEUDO_REG_TYPE)
17181      || (to_type == PSEUDO_REG_TYPE && IS_STD_REG_TYPE (from_type))
17182      || (from_type == PSEUDO_REG_TYPE && IS_STD_REG_TYPE (to_type)))
17183    return true;
17184
17185  /* Moves to the same set of registers is a simple move for non-specialized
17186     registers.  */
17187  if (to_type == from_type && IS_STD_REG_TYPE (to_type))
17188    return true;
17189
17190  /* Check whether a simple move can be done directly.  */
17191  if (rs6000_secondary_reload_simple_move (to_type, from_type, mode))
17192    {
17193      if (sri)
17194	{
17195	  sri->icode = CODE_FOR_nothing;
17196	  sri->extra_cost = 0;
17197	}
17198      return true;
17199    }
17200
17201  /* Now check if we can do it in a few steps.  */
17202  return rs6000_secondary_reload_direct_move (to_type, from_type, mode, sri,
17203					      altivec_p);
17204}
17205
17206/* Inform reload about cases where moving X with a mode MODE to a register in
17207   RCLASS requires an extra scratch or immediate register.  Return the class
17208   needed for the immediate register.
17209
17210   For VSX and Altivec, we may need a register to convert sp+offset into
17211   reg+sp.
17212
17213   For misaligned 64-bit gpr loads and stores we need a register to
17214   convert an offset address to indirect.  */
17215
17216static reg_class_t
17217rs6000_secondary_reload (bool in_p,
17218			 rtx x,
17219			 reg_class_t rclass_i,
17220			 machine_mode mode,
17221			 secondary_reload_info *sri)
17222{
17223  enum reg_class rclass = (enum reg_class) rclass_i;
17224  reg_class_t ret = ALL_REGS;
17225  enum insn_code icode;
17226  bool default_p = false;
17227  bool done_p = false;
17228
17229  /* Allow subreg of memory before/during reload.  */
17230  bool memory_p = (MEM_P (x)
17231		   || (!reload_completed && GET_CODE (x) == SUBREG
17232		       && MEM_P (SUBREG_REG (x))));
17233
17234  sri->icode = CODE_FOR_nothing;
17235  sri->extra_cost = 0;
17236  icode = ((in_p)
17237	   ? reg_addr[mode].reload_load
17238	   : reg_addr[mode].reload_store);
17239
17240  if (REG_P (x) || register_operand (x, mode))
17241    {
17242      enum rs6000_reg_type to_type = reg_class_to_reg_type[(int)rclass];
17243      bool altivec_p = (rclass == ALTIVEC_REGS);
17244      enum rs6000_reg_type from_type = register_to_reg_type (x, &altivec_p);
17245
17246      if (!in_p)
17247	{
17248	  enum rs6000_reg_type exchange = to_type;
17249	  to_type = from_type;
17250	  from_type = exchange;
17251	}
17252
17253      /* Can we do a direct move of some sort?  */
17254      if (rs6000_secondary_reload_move (to_type, from_type, mode, sri,
17255					altivec_p))
17256	{
17257	  icode = (enum insn_code)sri->icode;
17258	  default_p = false;
17259	  done_p = true;
17260	  ret = NO_REGS;
17261	}
17262    }
17263
17264  /* Make sure 0.0 is not reloaded or forced into memory.  */
17265  if (x == CONST0_RTX (mode) && VSX_REG_CLASS_P (rclass))
17266    {
17267      ret = NO_REGS;
17268      default_p = false;
17269      done_p = true;
17270    }
17271
17272  /* If this is a scalar floating point value and we want to load it into the
17273     traditional Altivec registers, do it via a move via a traditional floating
17274     point register.  Also make sure that non-zero constants use a FPR.  */
17275  if (!done_p && reg_addr[mode].scalar_in_vmx_p
17276      && (rclass == VSX_REGS || rclass == ALTIVEC_REGS)
17277      && (memory_p || (GET_CODE (x) == CONST_DOUBLE)))
17278    {
17279      ret = FLOAT_REGS;
17280      default_p = false;
17281      done_p = true;
17282    }
17283
17284  /* Handle reload of load/stores if we have reload helper functions.  */
17285  if (!done_p && icode != CODE_FOR_nothing && memory_p)
17286    {
17287      int extra_cost = rs6000_secondary_reload_memory (XEXP (x, 0), rclass,
17288						       mode);
17289
17290      if (extra_cost >= 0)
17291	{
17292	  done_p = true;
17293	  ret = NO_REGS;
17294	  if (extra_cost > 0)
17295	    {
17296	      sri->extra_cost = extra_cost;
17297	      sri->icode = icode;
17298	    }
17299	}
17300    }
17301
17302  /* Handle unaligned loads and stores of integer registers.  */
17303  if (!done_p && TARGET_POWERPC64
17304      && reg_class_to_reg_type[(int)rclass] == GPR_REG_TYPE
17305      && memory_p
17306      && GET_MODE_SIZE (GET_MODE (x)) >= UNITS_PER_WORD)
17307    {
17308      rtx addr = XEXP (x, 0);
17309      rtx off = address_offset (addr);
17310
17311      if (off != NULL_RTX)
17312	{
17313	  unsigned int extra = GET_MODE_SIZE (GET_MODE (x)) - UNITS_PER_WORD;
17314	  unsigned HOST_WIDE_INT offset = INTVAL (off);
17315
17316	  /* We need a secondary reload when our legitimate_address_p
17317	     says the address is good (as otherwise the entire address
17318	     will be reloaded), and the offset is not a multiple of
17319	     four or we have an address wrap.  Address wrap will only
17320	     occur for LO_SUMs since legitimate_offset_address_p
17321	     rejects addresses for 16-byte mems that will wrap.  */
17322	  if (GET_CODE (addr) == LO_SUM
17323	      ? (1 /* legitimate_address_p allows any offset for lo_sum */
17324		 && ((offset & 3) != 0
17325		     || ((offset & 0xffff) ^ 0x8000) >= 0x10000 - extra))
17326	      : (offset + 0x8000 < 0x10000 - extra /* legitimate_address_p */
17327		 && (offset & 3) != 0))
17328	    {
17329	      /* -m32 -mpowerpc64 needs to use a 32-bit scratch register.  */
17330	      if (in_p)
17331		sri->icode = ((TARGET_32BIT) ? CODE_FOR_reload_si_load
17332			      : CODE_FOR_reload_di_load);
17333	      else
17334		sri->icode = ((TARGET_32BIT) ? CODE_FOR_reload_si_store
17335			      : CODE_FOR_reload_di_store);
17336	      sri->extra_cost = 2;
17337	      ret = NO_REGS;
17338	      done_p = true;
17339	    }
17340	  else
17341	    default_p = true;
17342	}
17343      else
17344	default_p = true;
17345    }
17346
17347  if (!done_p && !TARGET_POWERPC64
17348      && reg_class_to_reg_type[(int)rclass] == GPR_REG_TYPE
17349      && memory_p
17350      && GET_MODE_SIZE (GET_MODE (x)) > UNITS_PER_WORD)
17351    {
17352      rtx addr = XEXP (x, 0);
17353      rtx off = address_offset (addr);
17354
17355      if (off != NULL_RTX)
17356	{
17357	  unsigned int extra = GET_MODE_SIZE (GET_MODE (x)) - UNITS_PER_WORD;
17358	  unsigned HOST_WIDE_INT offset = INTVAL (off);
17359
17360	  /* We need a secondary reload when our legitimate_address_p
17361	     says the address is good (as otherwise the entire address
17362	     will be reloaded), and we have a wrap.
17363
17364	     legitimate_lo_sum_address_p allows LO_SUM addresses to
17365	     have any offset so test for wrap in the low 16 bits.
17366
17367	     legitimate_offset_address_p checks for the range
17368	     [-0x8000,0x7fff] for mode size of 8 and [-0x8000,0x7ff7]
17369	     for mode size of 16.  We wrap at [0x7ffc,0x7fff] and
17370	     [0x7ff4,0x7fff] respectively, so test for the
17371	     intersection of these ranges, [0x7ffc,0x7fff] and
17372	     [0x7ff4,0x7ff7] respectively.
17373
17374	     Note that the address we see here may have been
17375	     manipulated by legitimize_reload_address.  */
17376	  if (GET_CODE (addr) == LO_SUM
17377	      ? ((offset & 0xffff) ^ 0x8000) >= 0x10000 - extra
17378	      : offset - (0x8000 - extra) < UNITS_PER_WORD)
17379	    {
17380	      if (in_p)
17381		sri->icode = CODE_FOR_reload_si_load;
17382	      else
17383		sri->icode = CODE_FOR_reload_si_store;
17384	      sri->extra_cost = 2;
17385	      ret = NO_REGS;
17386	      done_p = true;
17387	    }
17388	  else
17389	    default_p = true;
17390	}
17391      else
17392	default_p = true;
17393    }
17394
17395  if (!done_p)
17396    default_p = true;
17397
17398  if (default_p)
17399    ret = default_secondary_reload (in_p, x, rclass, mode, sri);
17400
17401  gcc_assert (ret != ALL_REGS);
17402
17403  if (TARGET_DEBUG_ADDR)
17404    {
17405      fprintf (stderr,
17406	       "\nrs6000_secondary_reload, return %s, in_p = %s, rclass = %s, "
17407	       "mode = %s",
17408	       reg_class_names[ret],
17409	       in_p ? "true" : "false",
17410	       reg_class_names[rclass],
17411	       GET_MODE_NAME (mode));
17412
17413      if (reload_completed)
17414	fputs (", after reload", stderr);
17415
17416      if (!done_p)
17417	fputs (", done_p not set", stderr);
17418
17419      if (default_p)
17420	fputs (", default secondary reload", stderr);
17421
17422      if (sri->icode != CODE_FOR_nothing)
17423	fprintf (stderr, ", reload func = %s, extra cost = %d",
17424		 insn_data[sri->icode].name, sri->extra_cost);
17425
17426      fputs ("\n", stderr);
17427      debug_rtx (x);
17428    }
17429
17430  return ret;
17431}
17432
17433/* Better tracing for rs6000_secondary_reload_inner.  */
17434
17435static void
17436rs6000_secondary_reload_trace (int line, rtx reg, rtx mem, rtx scratch,
17437			       bool store_p)
17438{
17439  rtx set, clobber;
17440
17441  gcc_assert (reg != NULL_RTX && mem != NULL_RTX && scratch != NULL_RTX);
17442
17443  fprintf (stderr, "rs6000_secondary_reload_inner:%d, type = %s\n", line,
17444	   store_p ? "store" : "load");
17445
17446  if (store_p)
17447    set = gen_rtx_SET (VOIDmode, mem, reg);
17448  else
17449    set = gen_rtx_SET (VOIDmode, reg, mem);
17450
17451  clobber = gen_rtx_CLOBBER (VOIDmode, scratch);
17452  debug_rtx (gen_rtx_PARALLEL (VOIDmode, gen_rtvec (2, set, clobber)));
17453}
17454
17455static void rs6000_secondary_reload_fail (int, rtx, rtx, rtx, bool)
17456  ATTRIBUTE_NORETURN;
17457
17458static void
17459rs6000_secondary_reload_fail (int line, rtx reg, rtx mem, rtx scratch,
17460			      bool store_p)
17461{
17462  rs6000_secondary_reload_trace (line, reg, mem, scratch, store_p);
17463  gcc_unreachable ();
17464}
17465
17466/* Fixup reload addresses for values in GPR, FPR, and VMX registers that have
17467   reload helper functions.  These were identified in
17468   rs6000_secondary_reload_memory, and if reload decided to use the secondary
17469   reload, it calls the insns:
17470	reload_<RELOAD:mode>_<P:mptrsize>_store
17471	reload_<RELOAD:mode>_<P:mptrsize>_load
17472
17473   which in turn calls this function, to do whatever is necessary to create
17474   valid addresses.  */
17475
17476void
17477rs6000_secondary_reload_inner (rtx reg, rtx mem, rtx scratch, bool store_p)
17478{
17479  int regno = true_regnum (reg);
17480  machine_mode mode = GET_MODE (reg);
17481  addr_mask_type addr_mask;
17482  rtx addr;
17483  rtx new_addr;
17484  rtx op_reg, op0, op1;
17485  rtx and_op;
17486  rtx cc_clobber;
17487  rtvec rv;
17488
17489  if (regno < 0 || regno >= FIRST_PSEUDO_REGISTER || !MEM_P (mem)
17490      || !base_reg_operand (scratch, GET_MODE (scratch)))
17491    rs6000_secondary_reload_fail (__LINE__, reg, mem, scratch, store_p);
17492
17493  if (IN_RANGE (regno, FIRST_GPR_REGNO, LAST_GPR_REGNO))
17494    addr_mask = reg_addr[mode].addr_mask[RELOAD_REG_GPR];
17495
17496  else if (IN_RANGE (regno, FIRST_FPR_REGNO, LAST_FPR_REGNO))
17497    addr_mask = reg_addr[mode].addr_mask[RELOAD_REG_FPR];
17498
17499  else if (IN_RANGE (regno, FIRST_ALTIVEC_REGNO, LAST_ALTIVEC_REGNO))
17500    addr_mask = reg_addr[mode].addr_mask[RELOAD_REG_VMX];
17501
17502  else
17503    rs6000_secondary_reload_fail (__LINE__, reg, mem, scratch, store_p);
17504
17505  /* Make sure the mode is valid in this register class.  */
17506  if ((addr_mask & RELOAD_REG_VALID) == 0)
17507    rs6000_secondary_reload_fail (__LINE__, reg, mem, scratch, store_p);
17508
17509  if (TARGET_DEBUG_ADDR)
17510    rs6000_secondary_reload_trace (__LINE__, reg, mem, scratch, store_p);
17511
17512  new_addr = addr = XEXP (mem, 0);
17513  switch (GET_CODE (addr))
17514    {
17515      /* Does the register class support auto update forms for this mode?  If
17516	 not, do the update now.  We don't need a scratch register, since the
17517	 powerpc only supports PRE_INC, PRE_DEC, and PRE_MODIFY.  */
17518    case PRE_INC:
17519    case PRE_DEC:
17520      op_reg = XEXP (addr, 0);
17521      if (!base_reg_operand (op_reg, Pmode))
17522	rs6000_secondary_reload_fail (__LINE__, reg, mem, scratch, store_p);
17523
17524      if ((addr_mask & RELOAD_REG_PRE_INCDEC) == 0)
17525	{
17526	  emit_insn (gen_add2_insn (op_reg, GEN_INT (GET_MODE_SIZE (mode))));
17527	  new_addr = op_reg;
17528	}
17529      break;
17530
17531    case PRE_MODIFY:
17532      op0 = XEXP (addr, 0);
17533      op1 = XEXP (addr, 1);
17534      if (!base_reg_operand (op0, Pmode)
17535	  || GET_CODE (op1) != PLUS
17536	  || !rtx_equal_p (op0, XEXP (op1, 0)))
17537	rs6000_secondary_reload_fail (__LINE__, reg, mem, scratch, store_p);
17538
17539      if ((addr_mask & RELOAD_REG_PRE_MODIFY) == 0)
17540	{
17541	  emit_insn (gen_rtx_SET (VOIDmode, op0, op1));
17542	  new_addr = reg;
17543	}
17544      break;
17545
17546      /* Do we need to simulate AND -16 to clear the bottom address bits used
17547	 in VMX load/stores?  */
17548    case AND:
17549      op0 = XEXP (addr, 0);
17550      op1 = XEXP (addr, 1);
17551      if ((addr_mask & RELOAD_REG_AND_M16) == 0)
17552	{
17553	  if (REG_P (op0) || GET_CODE (op0) == SUBREG)
17554	    op_reg = op0;
17555
17556	  else if (GET_CODE (op1) == PLUS)
17557	    {
17558	      emit_insn (gen_rtx_SET (VOIDmode, scratch, op1));
17559	      op_reg = scratch;
17560	    }
17561
17562	  else
17563	    rs6000_secondary_reload_fail (__LINE__, reg, mem, scratch, store_p);
17564
17565	  and_op = gen_rtx_AND (GET_MODE (scratch), op_reg, op1);
17566	  cc_clobber = gen_rtx_CLOBBER (VOIDmode, gen_rtx_SCRATCH (CCmode));
17567	  rv = gen_rtvec (2, gen_rtx_SET (VOIDmode, scratch, and_op), cc_clobber);
17568	  emit_insn (gen_rtx_PARALLEL (VOIDmode, rv));
17569	  new_addr = scratch;
17570	}
17571      break;
17572
17573      /* If this is an indirect address, make sure it is a base register.  */
17574    case REG:
17575    case SUBREG:
17576      if (!base_reg_operand (addr, GET_MODE (addr)))
17577	{
17578	  emit_insn (gen_rtx_SET (VOIDmode, scratch, addr));
17579	  new_addr = scratch;
17580	}
17581      break;
17582
17583      /* If this is an indexed address, make sure the register class can handle
17584	 indexed addresses for this mode.  */
17585    case PLUS:
17586      op0 = XEXP (addr, 0);
17587      op1 = XEXP (addr, 1);
17588      if (!base_reg_operand (op0, Pmode))
17589	rs6000_secondary_reload_fail (__LINE__, reg, mem, scratch, store_p);
17590
17591      else if (int_reg_operand (op1, Pmode))
17592	{
17593	  if ((addr_mask & RELOAD_REG_INDEXED) == 0)
17594	    {
17595	      emit_insn (gen_rtx_SET (VOIDmode, scratch, addr));
17596	      new_addr = scratch;
17597	    }
17598	}
17599
17600      /* Make sure the register class can handle offset addresses.  */
17601      else if (rs6000_legitimate_offset_address_p (mode, addr, false, true))
17602	{
17603	  if ((addr_mask & RELOAD_REG_OFFSET) == 0)
17604	    {
17605	      emit_insn (gen_rtx_SET (VOIDmode, scratch, addr));
17606	      new_addr = scratch;
17607	    }
17608	}
17609
17610      else
17611	rs6000_secondary_reload_fail (__LINE__, reg, mem, scratch, store_p);
17612
17613      break;
17614
17615    case LO_SUM:
17616      op0 = XEXP (addr, 0);
17617      op1 = XEXP (addr, 1);
17618      if (!base_reg_operand (op0, Pmode))
17619	rs6000_secondary_reload_fail (__LINE__, reg, mem, scratch, store_p);
17620
17621      else if (int_reg_operand (op1, Pmode))
17622	{
17623	  if ((addr_mask & RELOAD_REG_INDEXED) == 0)
17624	    {
17625	      emit_insn (gen_rtx_SET (VOIDmode, scratch, addr));
17626	      new_addr = scratch;
17627	    }
17628	}
17629
17630      /* Make sure the register class can handle offset addresses.  */
17631      else if (legitimate_lo_sum_address_p (mode, addr, false))
17632	{
17633	  if ((addr_mask & RELOAD_REG_OFFSET) == 0)
17634	    {
17635	      emit_insn (gen_rtx_SET (VOIDmode, scratch, addr));
17636	      new_addr = scratch;
17637	    }
17638	}
17639
17640      else
17641	rs6000_secondary_reload_fail (__LINE__, reg, mem, scratch, store_p);
17642
17643      break;
17644
17645    case SYMBOL_REF:
17646    case CONST:
17647    case LABEL_REF:
17648      rs6000_emit_move (scratch, addr, Pmode);
17649      new_addr = scratch;
17650      break;
17651
17652    default:
17653      rs6000_secondary_reload_fail (__LINE__, reg, mem, scratch, store_p);
17654    }
17655
17656  /* Adjust the address if it changed.  */
17657  if (addr != new_addr)
17658    {
17659      mem = replace_equiv_address_nv (mem, new_addr);
17660      if (TARGET_DEBUG_ADDR)
17661	fprintf (stderr, "\nrs6000_secondary_reload_inner, mem adjusted.\n");
17662    }
17663
17664  /* Now create the move.  */
17665  if (store_p)
17666    emit_insn (gen_rtx_SET (VOIDmode, mem, reg));
17667  else
17668    emit_insn (gen_rtx_SET (VOIDmode, reg, mem));
17669
17670  return;
17671}
17672
17673/* Convert reloads involving 64-bit gprs and misaligned offset
17674   addressing, or multiple 32-bit gprs and offsets that are too large,
17675   to use indirect addressing.  */
17676
17677void
17678rs6000_secondary_reload_gpr (rtx reg, rtx mem, rtx scratch, bool store_p)
17679{
17680  int regno = true_regnum (reg);
17681  enum reg_class rclass;
17682  rtx addr;
17683  rtx scratch_or_premodify = scratch;
17684
17685  if (TARGET_DEBUG_ADDR)
17686    {
17687      fprintf (stderr, "\nrs6000_secondary_reload_gpr, type = %s\n",
17688	       store_p ? "store" : "load");
17689      fprintf (stderr, "reg:\n");
17690      debug_rtx (reg);
17691      fprintf (stderr, "mem:\n");
17692      debug_rtx (mem);
17693      fprintf (stderr, "scratch:\n");
17694      debug_rtx (scratch);
17695    }
17696
17697  gcc_assert (regno >= 0 && regno < FIRST_PSEUDO_REGISTER);
17698  gcc_assert (GET_CODE (mem) == MEM);
17699  rclass = REGNO_REG_CLASS (regno);
17700  gcc_assert (rclass == GENERAL_REGS || rclass == BASE_REGS);
17701  addr = XEXP (mem, 0);
17702
17703  if (GET_CODE (addr) == PRE_MODIFY)
17704    {
17705      gcc_assert (REG_P (XEXP (addr, 0))
17706		  && GET_CODE (XEXP (addr, 1)) == PLUS
17707		  && XEXP (XEXP (addr, 1), 0) == XEXP (addr, 0));
17708      scratch_or_premodify = XEXP (addr, 0);
17709      if (!HARD_REGISTER_P (scratch_or_premodify))
17710	/* If we have a pseudo here then reload will have arranged
17711	   to have it replaced, but only in the original insn.
17712	   Use the replacement here too.  */
17713	scratch_or_premodify = find_replacement (&XEXP (addr, 0));
17714
17715      /* RTL emitted by rs6000_secondary_reload_gpr uses RTL
17716	 expressions from the original insn, without unsharing them.
17717	 Any RTL that points into the original insn will of course
17718	 have register replacements applied.  That is why we don't
17719	 need to look for replacements under the PLUS.  */
17720      addr = XEXP (addr, 1);
17721    }
17722  gcc_assert (GET_CODE (addr) == PLUS || GET_CODE (addr) == LO_SUM);
17723
17724  rs6000_emit_move (scratch_or_premodify, addr, Pmode);
17725
17726  mem = replace_equiv_address_nv (mem, scratch_or_premodify);
17727
17728  /* Now create the move.  */
17729  if (store_p)
17730    emit_insn (gen_rtx_SET (VOIDmode, mem, reg));
17731  else
17732    emit_insn (gen_rtx_SET (VOIDmode, reg, mem));
17733
17734  return;
17735}
17736
17737/* Allocate a 64-bit stack slot to be used for copying SDmode values through if
17738   this function has any SDmode references.  If we are on a power7 or later, we
17739   don't need the 64-bit stack slot since the LFIWZX and STIFWX instructions
17740   can load/store the value.  */
17741
17742static void
17743rs6000_alloc_sdmode_stack_slot (void)
17744{
17745  tree t;
17746  basic_block bb;
17747  gimple_stmt_iterator gsi;
17748
17749  gcc_assert (cfun->machine->sdmode_stack_slot == NULL_RTX);
17750  /* We use a different approach for dealing with the secondary
17751     memory in LRA.  */
17752  if (ira_use_lra_p)
17753    return;
17754
17755  if (TARGET_NO_SDMODE_STACK)
17756    return;
17757
17758  FOR_EACH_BB_FN (bb, cfun)
17759    for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
17760      {
17761	tree ret = walk_gimple_op (gsi_stmt (gsi), rs6000_check_sdmode, NULL);
17762	if (ret)
17763	  {
17764	    rtx stack = assign_stack_local (DDmode, GET_MODE_SIZE (DDmode), 0);
17765	    cfun->machine->sdmode_stack_slot = adjust_address_nv (stack,
17766								  SDmode, 0);
17767	    return;
17768	  }
17769      }
17770
17771  /* Check for any SDmode parameters of the function.  */
17772  for (t = DECL_ARGUMENTS (cfun->decl); t; t = DECL_CHAIN (t))
17773    {
17774      if (TREE_TYPE (t) == error_mark_node)
17775	continue;
17776
17777      if (TYPE_MODE (TREE_TYPE (t)) == SDmode
17778	  || TYPE_MODE (DECL_ARG_TYPE (t)) == SDmode)
17779	{
17780	  rtx stack = assign_stack_local (DDmode, GET_MODE_SIZE (DDmode), 0);
17781	  cfun->machine->sdmode_stack_slot = adjust_address_nv (stack,
17782								SDmode, 0);
17783	  return;
17784	}
17785    }
17786}
17787
17788static void
17789rs6000_instantiate_decls (void)
17790{
17791  if (cfun->machine->sdmode_stack_slot != NULL_RTX)
17792    instantiate_decl_rtl (cfun->machine->sdmode_stack_slot);
17793}
17794
17795/* Given an rtx X being reloaded into a reg required to be
17796   in class CLASS, return the class of reg to actually use.
17797   In general this is just CLASS; but on some machines
17798   in some cases it is preferable to use a more restrictive class.
17799
17800   On the RS/6000, we have to return NO_REGS when we want to reload a
17801   floating-point CONST_DOUBLE to force it to be copied to memory.
17802
17803   We also don't want to reload integer values into floating-point
17804   registers if we can at all help it.  In fact, this can
17805   cause reload to die, if it tries to generate a reload of CTR
17806   into a FP register and discovers it doesn't have the memory location
17807   required.
17808
17809   ??? Would it be a good idea to have reload do the converse, that is
17810   try to reload floating modes into FP registers if possible?
17811 */
17812
17813static enum reg_class
17814rs6000_preferred_reload_class (rtx x, enum reg_class rclass)
17815{
17816  machine_mode mode = GET_MODE (x);
17817  bool is_constant = CONSTANT_P (x);
17818
17819  /* For VSX, see if we should prefer FLOAT_REGS or ALTIVEC_REGS.  Do not allow
17820     the reloading of address expressions using PLUS into floating point
17821     registers.  */
17822  if (TARGET_VSX && VSX_REG_CLASS_P (rclass) && GET_CODE (x) != PLUS)
17823    {
17824      if (is_constant)
17825	{
17826	  /* Zero is always allowed in all VSX registers.  */
17827	  if (x == CONST0_RTX (mode))
17828	    return rclass;
17829
17830	  /* If this is a vector constant that can be formed with a few Altivec
17831	     instructions, we want altivec registers.  */
17832	  if (GET_CODE (x) == CONST_VECTOR && easy_vector_constant (x, mode))
17833	    return ALTIVEC_REGS;
17834
17835	  /* Force constant to memory.  */
17836	  return NO_REGS;
17837	}
17838
17839      /* If this is a scalar floating point value, prefer the traditional
17840	 floating point registers so that we can use D-form (register+offset)
17841	 addressing.  */
17842      if (GET_MODE_SIZE (mode) < 16)
17843	return FLOAT_REGS;
17844
17845      /* Prefer the Altivec registers if Altivec is handling the vector
17846	 operations (i.e. V16QI, V8HI, and V4SI), or if we prefer Altivec
17847	 loads.  */
17848      if (VECTOR_UNIT_ALTIVEC_P (mode) || VECTOR_MEM_ALTIVEC_P (mode)
17849	  || mode == V1TImode)
17850	return ALTIVEC_REGS;
17851
17852      return rclass;
17853    }
17854
17855  if (is_constant || GET_CODE (x) == PLUS)
17856    {
17857      if (reg_class_subset_p (GENERAL_REGS, rclass))
17858	return GENERAL_REGS;
17859      if (reg_class_subset_p (BASE_REGS, rclass))
17860	return BASE_REGS;
17861      return NO_REGS;
17862    }
17863
17864  if (GET_MODE_CLASS (mode) == MODE_INT && rclass == NON_SPECIAL_REGS)
17865    return GENERAL_REGS;
17866
17867  return rclass;
17868}
17869
17870/* Debug version of rs6000_preferred_reload_class.  */
17871static enum reg_class
17872rs6000_debug_preferred_reload_class (rtx x, enum reg_class rclass)
17873{
17874  enum reg_class ret = rs6000_preferred_reload_class (x, rclass);
17875
17876  fprintf (stderr,
17877	   "\nrs6000_preferred_reload_class, return %s, rclass = %s, "
17878	   "mode = %s, x:\n",
17879	   reg_class_names[ret], reg_class_names[rclass],
17880	   GET_MODE_NAME (GET_MODE (x)));
17881  debug_rtx (x);
17882
17883  return ret;
17884}
17885
17886/* If we are copying between FP or AltiVec registers and anything else, we need
17887   a memory location.  The exception is when we are targeting ppc64 and the
17888   move to/from fpr to gpr instructions are available.  Also, under VSX, you
17889   can copy vector registers from the FP register set to the Altivec register
17890   set and vice versa.  */
17891
17892static bool
17893rs6000_secondary_memory_needed (enum reg_class from_class,
17894				enum reg_class to_class,
17895				machine_mode mode)
17896{
17897  enum rs6000_reg_type from_type, to_type;
17898  bool altivec_p = ((from_class == ALTIVEC_REGS)
17899		    || (to_class == ALTIVEC_REGS));
17900
17901  /* If a simple/direct move is available, we don't need secondary memory  */
17902  from_type = reg_class_to_reg_type[(int)from_class];
17903  to_type = reg_class_to_reg_type[(int)to_class];
17904
17905  if (rs6000_secondary_reload_move (to_type, from_type, mode,
17906				    (secondary_reload_info *)0, altivec_p))
17907    return false;
17908
17909  /* If we have a floating point or vector register class, we need to use
17910     memory to transfer the data.  */
17911  if (IS_FP_VECT_REG_TYPE (from_type) || IS_FP_VECT_REG_TYPE (to_type))
17912    return true;
17913
17914  return false;
17915}
17916
17917/* Debug version of rs6000_secondary_memory_needed.  */
17918static bool
17919rs6000_debug_secondary_memory_needed (enum reg_class from_class,
17920				      enum reg_class to_class,
17921				      machine_mode mode)
17922{
17923  bool ret = rs6000_secondary_memory_needed (from_class, to_class, mode);
17924
17925  fprintf (stderr,
17926	   "rs6000_secondary_memory_needed, return: %s, from_class = %s, "
17927	   "to_class = %s, mode = %s\n",
17928	   ret ? "true" : "false",
17929	   reg_class_names[from_class],
17930	   reg_class_names[to_class],
17931	   GET_MODE_NAME (mode));
17932
17933  return ret;
17934}
17935
17936/* Return the register class of a scratch register needed to copy IN into
17937   or out of a register in RCLASS in MODE.  If it can be done directly,
17938   NO_REGS is returned.  */
17939
17940static enum reg_class
17941rs6000_secondary_reload_class (enum reg_class rclass, machine_mode mode,
17942			       rtx in)
17943{
17944  int regno;
17945
17946  if (TARGET_ELF || (DEFAULT_ABI == ABI_DARWIN
17947#if TARGET_MACHO
17948		     && MACHOPIC_INDIRECT
17949#endif
17950		     ))
17951    {
17952      /* We cannot copy a symbolic operand directly into anything
17953	 other than BASE_REGS for TARGET_ELF.  So indicate that a
17954	 register from BASE_REGS is needed as an intermediate
17955	 register.
17956
17957	 On Darwin, pic addresses require a load from memory, which
17958	 needs a base register.  */
17959      if (rclass != BASE_REGS
17960	  && (GET_CODE (in) == SYMBOL_REF
17961	      || GET_CODE (in) == HIGH
17962	      || GET_CODE (in) == LABEL_REF
17963	      || GET_CODE (in) == CONST))
17964	return BASE_REGS;
17965    }
17966
17967  if (GET_CODE (in) == REG)
17968    {
17969      regno = REGNO (in);
17970      if (regno >= FIRST_PSEUDO_REGISTER)
17971	{
17972	  regno = true_regnum (in);
17973	  if (regno >= FIRST_PSEUDO_REGISTER)
17974	    regno = -1;
17975	}
17976    }
17977  else if (GET_CODE (in) == SUBREG)
17978    {
17979      regno = true_regnum (in);
17980      if (regno >= FIRST_PSEUDO_REGISTER)
17981	regno = -1;
17982    }
17983  else
17984    regno = -1;
17985
17986  /* If we have VSX register moves, prefer moving scalar values between
17987     Altivec registers and GPR by going via an FPR (and then via memory)
17988     instead of reloading the secondary memory address for Altivec moves.  */
17989  if (TARGET_VSX
17990      && GET_MODE_SIZE (mode) < 16
17991      && (((rclass == GENERAL_REGS || rclass == BASE_REGS)
17992           && (regno >= 0 && ALTIVEC_REGNO_P (regno)))
17993          || ((rclass == VSX_REGS || rclass == ALTIVEC_REGS)
17994              && (regno >= 0 && INT_REGNO_P (regno)))))
17995    return FLOAT_REGS;
17996
17997  /* We can place anything into GENERAL_REGS and can put GENERAL_REGS
17998     into anything.  */
17999  if (rclass == GENERAL_REGS || rclass == BASE_REGS
18000      || (regno >= 0 && INT_REGNO_P (regno)))
18001    return NO_REGS;
18002
18003  /* Constants, memory, and VSX registers can go into VSX registers (both the
18004     traditional floating point and the altivec registers).  */
18005  if (rclass == VSX_REGS
18006      && (regno == -1 || VSX_REGNO_P (regno)))
18007    return NO_REGS;
18008
18009  /* Constants, memory, and FP registers can go into FP registers.  */
18010  if ((regno == -1 || FP_REGNO_P (regno))
18011      && (rclass == FLOAT_REGS || rclass == NON_SPECIAL_REGS))
18012    return (mode != SDmode || lra_in_progress) ? NO_REGS : GENERAL_REGS;
18013
18014  /* Memory, and AltiVec registers can go into AltiVec registers.  */
18015  if ((regno == -1 || ALTIVEC_REGNO_P (regno))
18016      && rclass == ALTIVEC_REGS)
18017    return NO_REGS;
18018
18019  /* We can copy among the CR registers.  */
18020  if ((rclass == CR_REGS || rclass == CR0_REGS)
18021      && regno >= 0 && CR_REGNO_P (regno))
18022    return NO_REGS;
18023
18024  /* Otherwise, we need GENERAL_REGS.  */
18025  return GENERAL_REGS;
18026}
18027
18028/* Debug version of rs6000_secondary_reload_class.  */
18029static enum reg_class
18030rs6000_debug_secondary_reload_class (enum reg_class rclass,
18031				     machine_mode mode, rtx in)
18032{
18033  enum reg_class ret = rs6000_secondary_reload_class (rclass, mode, in);
18034  fprintf (stderr,
18035	   "\nrs6000_secondary_reload_class, return %s, rclass = %s, "
18036	   "mode = %s, input rtx:\n",
18037	   reg_class_names[ret], reg_class_names[rclass],
18038	   GET_MODE_NAME (mode));
18039  debug_rtx (in);
18040
18041  return ret;
18042}
18043
18044/* Return nonzero if for CLASS a mode change from FROM to TO is invalid.  */
18045
18046static bool
18047rs6000_cannot_change_mode_class (machine_mode from,
18048				 machine_mode to,
18049				 enum reg_class rclass)
18050{
18051  unsigned from_size = GET_MODE_SIZE (from);
18052  unsigned to_size = GET_MODE_SIZE (to);
18053
18054  if (from_size != to_size)
18055    {
18056      enum reg_class xclass = (TARGET_VSX) ? VSX_REGS : FLOAT_REGS;
18057
18058      if (reg_classes_intersect_p (xclass, rclass))
18059	{
18060	  unsigned to_nregs = hard_regno_nregs[FIRST_FPR_REGNO][to];
18061	  unsigned from_nregs = hard_regno_nregs[FIRST_FPR_REGNO][from];
18062
18063	  /* Don't allow 64-bit types to overlap with 128-bit types that take a
18064	     single register under VSX because the scalar part of the register
18065	     is in the upper 64-bits, and not the lower 64-bits.  Types like
18066	     TFmode/TDmode that take 2 scalar register can overlap.  128-bit
18067	     IEEE floating point can't overlap, and neither can small
18068	     values.  */
18069
18070	  if (TARGET_IEEEQUAD && (to == TFmode || from == TFmode))
18071	    return true;
18072
18073	  /* TDmode in floating-mode registers must always go into a register
18074	     pair with the most significant word in the even-numbered register
18075	     to match ISA requirements.  In little-endian mode, this does not
18076	     match subreg numbering, so we cannot allow subregs.  */
18077	  if (!BYTES_BIG_ENDIAN && (to == TDmode || from == TDmode))
18078	    return true;
18079
18080	  if (from_size < 8 || to_size < 8)
18081	    return true;
18082
18083	  if (from_size == 8 && (8 * to_nregs) != to_size)
18084	    return true;
18085
18086	  if (to_size == 8 && (8 * from_nregs) != from_size)
18087	    return true;
18088
18089	  return false;
18090	}
18091      else
18092	return false;
18093    }
18094
18095  if (TARGET_E500_DOUBLE
18096      && ((((to) == DFmode) + ((from) == DFmode)) == 1
18097	  || (((to) == TFmode) + ((from) == TFmode)) == 1
18098	  || (((to) == DDmode) + ((from) == DDmode)) == 1
18099	  || (((to) == TDmode) + ((from) == TDmode)) == 1
18100	  || (((to) == DImode) + ((from) == DImode)) == 1))
18101    return true;
18102
18103  /* Since the VSX register set includes traditional floating point registers
18104     and altivec registers, just check for the size being different instead of
18105     trying to check whether the modes are vector modes.  Otherwise it won't
18106     allow say DF and DI to change classes.  For types like TFmode and TDmode
18107     that take 2 64-bit registers, rather than a single 128-bit register, don't
18108     allow subregs of those types to other 128 bit types.  */
18109  if (TARGET_VSX && VSX_REG_CLASS_P (rclass))
18110    {
18111      unsigned num_regs = (from_size + 15) / 16;
18112      if (hard_regno_nregs[FIRST_FPR_REGNO][to] > num_regs
18113	  || hard_regno_nregs[FIRST_FPR_REGNO][from] > num_regs)
18114	return true;
18115
18116      return (from_size != 8 && from_size != 16);
18117    }
18118
18119  if (TARGET_ALTIVEC && rclass == ALTIVEC_REGS
18120      && (ALTIVEC_VECTOR_MODE (from) + ALTIVEC_VECTOR_MODE (to)) == 1)
18121    return true;
18122
18123  if (TARGET_SPE && (SPE_VECTOR_MODE (from) + SPE_VECTOR_MODE (to)) == 1
18124      && reg_classes_intersect_p (GENERAL_REGS, rclass))
18125    return true;
18126
18127  return false;
18128}
18129
18130/* Debug version of rs6000_cannot_change_mode_class.  */
18131static bool
18132rs6000_debug_cannot_change_mode_class (machine_mode from,
18133				       machine_mode to,
18134				       enum reg_class rclass)
18135{
18136  bool ret = rs6000_cannot_change_mode_class (from, to, rclass);
18137
18138  fprintf (stderr,
18139	   "rs6000_cannot_change_mode_class, return %s, from = %s, "
18140	   "to = %s, rclass = %s\n",
18141	   ret ? "true" : "false",
18142	   GET_MODE_NAME (from), GET_MODE_NAME (to),
18143	   reg_class_names[rclass]);
18144
18145  return ret;
18146}
18147
18148/* Return a string to do a move operation of 128 bits of data.  */
18149
18150const char *
18151rs6000_output_move_128bit (rtx operands[])
18152{
18153  rtx dest = operands[0];
18154  rtx src = operands[1];
18155  machine_mode mode = GET_MODE (dest);
18156  int dest_regno;
18157  int src_regno;
18158  bool dest_gpr_p, dest_fp_p, dest_vmx_p, dest_vsx_p;
18159  bool src_gpr_p, src_fp_p, src_vmx_p, src_vsx_p;
18160
18161  if (REG_P (dest))
18162    {
18163      dest_regno = REGNO (dest);
18164      dest_gpr_p = INT_REGNO_P (dest_regno);
18165      dest_fp_p = FP_REGNO_P (dest_regno);
18166      dest_vmx_p = ALTIVEC_REGNO_P (dest_regno);
18167      dest_vsx_p = dest_fp_p | dest_vmx_p;
18168    }
18169  else
18170    {
18171      dest_regno = -1;
18172      dest_gpr_p = dest_fp_p = dest_vmx_p = dest_vsx_p = false;
18173    }
18174
18175  if (REG_P (src))
18176    {
18177      src_regno = REGNO (src);
18178      src_gpr_p = INT_REGNO_P (src_regno);
18179      src_fp_p = FP_REGNO_P (src_regno);
18180      src_vmx_p = ALTIVEC_REGNO_P (src_regno);
18181      src_vsx_p = src_fp_p | src_vmx_p;
18182    }
18183  else
18184    {
18185      src_regno = -1;
18186      src_gpr_p = src_fp_p = src_vmx_p = src_vsx_p = false;
18187    }
18188
18189  /* Register moves.  */
18190  if (dest_regno >= 0 && src_regno >= 0)
18191    {
18192      if (dest_gpr_p)
18193	{
18194	  if (src_gpr_p)
18195	    return "#";
18196
18197	  else if (TARGET_VSX && TARGET_DIRECT_MOVE && src_vsx_p)
18198	    return "#";
18199	}
18200
18201      else if (TARGET_VSX && dest_vsx_p)
18202	{
18203	  if (src_vsx_p)
18204	    return "xxlor %x0,%x1,%x1";
18205
18206	  else if (TARGET_DIRECT_MOVE && src_gpr_p)
18207	    return "#";
18208	}
18209
18210      else if (TARGET_ALTIVEC && dest_vmx_p && src_vmx_p)
18211	return "vor %0,%1,%1";
18212
18213      else if (dest_fp_p && src_fp_p)
18214	return "#";
18215    }
18216
18217  /* Loads.  */
18218  else if (dest_regno >= 0 && MEM_P (src))
18219    {
18220      if (dest_gpr_p)
18221	{
18222	  if (TARGET_QUAD_MEMORY && quad_load_store_p (dest, src))
18223	    return "lq %0,%1";
18224	  else
18225	    return "#";
18226	}
18227
18228      else if (TARGET_ALTIVEC && dest_vmx_p
18229	       && altivec_indexed_or_indirect_operand (src, mode))
18230	return "lvx %0,%y1";
18231
18232      else if (TARGET_VSX && dest_vsx_p)
18233	{
18234	  if (mode == V16QImode || mode == V8HImode || mode == V4SImode)
18235	    return "lxvw4x %x0,%y1";
18236	  else
18237	    return "lxvd2x %x0,%y1";
18238	}
18239
18240      else if (TARGET_ALTIVEC && dest_vmx_p)
18241	return "lvx %0,%y1";
18242
18243      else if (dest_fp_p)
18244	return "#";
18245    }
18246
18247  /* Stores.  */
18248  else if (src_regno >= 0 && MEM_P (dest))
18249    {
18250      if (src_gpr_p)
18251	{
18252 	  if (TARGET_QUAD_MEMORY && quad_load_store_p (dest, src))
18253	    return "stq %1,%0";
18254	  else
18255	    return "#";
18256	}
18257
18258      else if (TARGET_ALTIVEC && src_vmx_p
18259	       && altivec_indexed_or_indirect_operand (src, mode))
18260	return "stvx %1,%y0";
18261
18262      else if (TARGET_VSX && src_vsx_p)
18263	{
18264	  if (mode == V16QImode || mode == V8HImode || mode == V4SImode)
18265	    return "stxvw4x %x1,%y0";
18266	  else
18267	    return "stxvd2x %x1,%y0";
18268	}
18269
18270      else if (TARGET_ALTIVEC && src_vmx_p)
18271	return "stvx %1,%y0";
18272
18273      else if (src_fp_p)
18274	return "#";
18275    }
18276
18277  /* Constants.  */
18278  else if (dest_regno >= 0
18279	   && (GET_CODE (src) == CONST_INT
18280	       || GET_CODE (src) == CONST_WIDE_INT
18281	       || GET_CODE (src) == CONST_DOUBLE
18282	       || GET_CODE (src) == CONST_VECTOR))
18283    {
18284      if (dest_gpr_p)
18285	return "#";
18286
18287      else if (TARGET_VSX && dest_vsx_p && zero_constant (src, mode))
18288	return "xxlxor %x0,%x0,%x0";
18289
18290      else if (TARGET_ALTIVEC && dest_vmx_p)
18291	return output_vec_const_move (operands);
18292    }
18293
18294  if (TARGET_DEBUG_ADDR)
18295    {
18296      fprintf (stderr, "\n===== Bad 128 bit move:\n");
18297      debug_rtx (gen_rtx_SET (VOIDmode, dest, src));
18298    }
18299
18300  gcc_unreachable ();
18301}
18302
18303/* Validate a 128-bit move.  */
18304bool
18305rs6000_move_128bit_ok_p (rtx operands[])
18306{
18307  machine_mode mode = GET_MODE (operands[0]);
18308  return (gpc_reg_operand (operands[0], mode)
18309	  || gpc_reg_operand (operands[1], mode));
18310}
18311
18312/* Return true if a 128-bit move needs to be split.  */
18313bool
18314rs6000_split_128bit_ok_p (rtx operands[])
18315{
18316  if (!reload_completed)
18317    return false;
18318
18319  if (!gpr_or_gpr_p (operands[0], operands[1]))
18320    return false;
18321
18322  if (quad_load_store_p (operands[0], operands[1]))
18323    return false;
18324
18325  return true;
18326}
18327
18328
18329/* Given a comparison operation, return the bit number in CCR to test.  We
18330   know this is a valid comparison.
18331
18332   SCC_P is 1 if this is for an scc.  That means that %D will have been
18333   used instead of %C, so the bits will be in different places.
18334
18335   Return -1 if OP isn't a valid comparison for some reason.  */
18336
18337int
18338ccr_bit (rtx op, int scc_p)
18339{
18340  enum rtx_code code = GET_CODE (op);
18341  machine_mode cc_mode;
18342  int cc_regnum;
18343  int base_bit;
18344  rtx reg;
18345
18346  if (!COMPARISON_P (op))
18347    return -1;
18348
18349  reg = XEXP (op, 0);
18350
18351  gcc_assert (GET_CODE (reg) == REG && CR_REGNO_P (REGNO (reg)));
18352
18353  cc_mode = GET_MODE (reg);
18354  cc_regnum = REGNO (reg);
18355  base_bit = 4 * (cc_regnum - CR0_REGNO);
18356
18357  validate_condition_mode (code, cc_mode);
18358
18359  /* When generating a sCOND operation, only positive conditions are
18360     allowed.  */
18361  gcc_assert (!scc_p
18362	      || code == EQ || code == GT || code == LT || code == UNORDERED
18363	      || code == GTU || code == LTU);
18364
18365  switch (code)
18366    {
18367    case NE:
18368      return scc_p ? base_bit + 3 : base_bit + 2;
18369    case EQ:
18370      return base_bit + 2;
18371    case GT:  case GTU:  case UNLE:
18372      return base_bit + 1;
18373    case LT:  case LTU:  case UNGE:
18374      return base_bit;
18375    case ORDERED:  case UNORDERED:
18376      return base_bit + 3;
18377
18378    case GE:  case GEU:
18379      /* If scc, we will have done a cror to put the bit in the
18380	 unordered position.  So test that bit.  For integer, this is ! LT
18381	 unless this is an scc insn.  */
18382      return scc_p ? base_bit + 3 : base_bit;
18383
18384    case LE:  case LEU:
18385      return scc_p ? base_bit + 3 : base_bit + 1;
18386
18387    default:
18388      gcc_unreachable ();
18389    }
18390}
18391
18392/* Return the GOT register.  */
18393
18394rtx
18395rs6000_got_register (rtx value ATTRIBUTE_UNUSED)
18396{
18397  /* The second flow pass currently (June 1999) can't update
18398     regs_ever_live without disturbing other parts of the compiler, so
18399     update it here to make the prolog/epilogue code happy.  */
18400  if (!can_create_pseudo_p ()
18401      && !df_regs_ever_live_p (RS6000_PIC_OFFSET_TABLE_REGNUM))
18402    df_set_regs_ever_live (RS6000_PIC_OFFSET_TABLE_REGNUM, true);
18403
18404  crtl->uses_pic_offset_table = 1;
18405
18406  return pic_offset_table_rtx;
18407}
18408
18409static rs6000_stack_t stack_info;
18410
18411/* Function to init struct machine_function.
18412   This will be called, via a pointer variable,
18413   from push_function_context.  */
18414
18415static struct machine_function *
18416rs6000_init_machine_status (void)
18417{
18418  stack_info.reload_completed = 0;
18419  return ggc_cleared_alloc<machine_function> ();
18420}
18421
18422#define INT_P(X) (GET_CODE (X) == CONST_INT && GET_MODE (X) == VOIDmode)
18423
18424int
18425extract_MB (rtx op)
18426{
18427  int i;
18428  unsigned long val = INTVAL (op);
18429
18430  /* If the high bit is zero, the value is the first 1 bit we find
18431     from the left.  */
18432  if ((val & 0x80000000) == 0)
18433    {
18434      gcc_assert (val & 0xffffffff);
18435
18436      i = 1;
18437      while (((val <<= 1) & 0x80000000) == 0)
18438	++i;
18439      return i;
18440    }
18441
18442  /* If the high bit is set and the low bit is not, or the mask is all
18443     1's, the value is zero.  */
18444  if ((val & 1) == 0 || (val & 0xffffffff) == 0xffffffff)
18445    return 0;
18446
18447  /* Otherwise we have a wrap-around mask.  Look for the first 0 bit
18448     from the right.  */
18449  i = 31;
18450  while (((val >>= 1) & 1) != 0)
18451    --i;
18452
18453  return i;
18454}
18455
18456int
18457extract_ME (rtx op)
18458{
18459  int i;
18460  unsigned long val = INTVAL (op);
18461
18462  /* If the low bit is zero, the value is the first 1 bit we find from
18463     the right.  */
18464  if ((val & 1) == 0)
18465    {
18466      gcc_assert (val & 0xffffffff);
18467
18468      i = 30;
18469      while (((val >>= 1) & 1) == 0)
18470	--i;
18471
18472      return i;
18473    }
18474
18475  /* If the low bit is set and the high bit is not, or the mask is all
18476     1's, the value is 31.  */
18477  if ((val & 0x80000000) == 0 || (val & 0xffffffff) == 0xffffffff)
18478    return 31;
18479
18480  /* Otherwise we have a wrap-around mask.  Look for the first 0 bit
18481     from the left.  */
18482  i = 0;
18483  while (((val <<= 1) & 0x80000000) != 0)
18484    ++i;
18485
18486  return i;
18487}
18488
18489/* Write out a function code label.  */
18490
18491void
18492rs6000_output_function_entry (FILE *file, const char *fname)
18493{
18494  if (fname[0] != '.')
18495    {
18496      switch (DEFAULT_ABI)
18497	{
18498	default:
18499	  gcc_unreachable ();
18500
18501	case ABI_AIX:
18502	  if (DOT_SYMBOLS)
18503	    putc ('.', file);
18504	  else
18505	    ASM_OUTPUT_INTERNAL_LABEL_PREFIX (file, "L.");
18506	  break;
18507
18508	case ABI_ELFv2:
18509	case ABI_V4:
18510	case ABI_DARWIN:
18511	  break;
18512	}
18513    }
18514
18515  RS6000_OUTPUT_BASENAME (file, fname);
18516}
18517
18518/* Print an operand.  Recognize special options, documented below.  */
18519
18520#if TARGET_ELF
18521#define SMALL_DATA_RELOC ((rs6000_sdata == SDATA_EABI) ? "sda21" : "sdarel")
18522#define SMALL_DATA_REG ((rs6000_sdata == SDATA_EABI) ? 0 : 13)
18523#else
18524#define SMALL_DATA_RELOC "sda21"
18525#define SMALL_DATA_REG 0
18526#endif
18527
18528void
18529print_operand (FILE *file, rtx x, int code)
18530{
18531  int i;
18532  unsigned HOST_WIDE_INT uval;
18533
18534  switch (code)
18535    {
18536      /* %a is output_address.  */
18537
18538    case 'b':
18539      /* If constant, low-order 16 bits of constant, unsigned.
18540	 Otherwise, write normally.  */
18541      if (INT_P (x))
18542	fprintf (file, HOST_WIDE_INT_PRINT_DEC, INTVAL (x) & 0xffff);
18543      else
18544	print_operand (file, x, 0);
18545      return;
18546
18547    case 'B':
18548      /* If the low-order bit is zero, write 'r'; otherwise, write 'l'
18549	 for 64-bit mask direction.  */
18550      putc (((INTVAL (x) & 1) == 0 ? 'r' : 'l'), file);
18551      return;
18552
18553      /* %c is output_addr_const if a CONSTANT_ADDRESS_P, otherwise
18554	 output_operand.  */
18555
18556    case 'D':
18557      /* Like 'J' but get to the GT bit only.  */
18558      gcc_assert (REG_P (x));
18559
18560      /* Bit 1 is GT bit.  */
18561      i = 4 * (REGNO (x) - CR0_REGNO) + 1;
18562
18563      /* Add one for shift count in rlinm for scc.  */
18564      fprintf (file, "%d", i + 1);
18565      return;
18566
18567    case 'e':
18568      /* If the low 16 bits are 0, but some other bit is set, write 's'.  */
18569      if (! INT_P (x))
18570	{
18571	  output_operand_lossage ("invalid %%e value");
18572	  return;
18573	}
18574
18575      uval = INTVAL (x);
18576      if ((uval & 0xffff) == 0 && uval != 0)
18577	putc ('s', file);
18578      return;
18579
18580    case 'E':
18581      /* X is a CR register.  Print the number of the EQ bit of the CR */
18582      if (GET_CODE (x) != REG || ! CR_REGNO_P (REGNO (x)))
18583	output_operand_lossage ("invalid %%E value");
18584      else
18585	fprintf (file, "%d", 4 * (REGNO (x) - CR0_REGNO) + 2);
18586      return;
18587
18588    case 'f':
18589      /* X is a CR register.  Print the shift count needed to move it
18590	 to the high-order four bits.  */
18591      if (GET_CODE (x) != REG || ! CR_REGNO_P (REGNO (x)))
18592	output_operand_lossage ("invalid %%f value");
18593      else
18594	fprintf (file, "%d", 4 * (REGNO (x) - CR0_REGNO));
18595      return;
18596
18597    case 'F':
18598      /* Similar, but print the count for the rotate in the opposite
18599	 direction.  */
18600      if (GET_CODE (x) != REG || ! CR_REGNO_P (REGNO (x)))
18601	output_operand_lossage ("invalid %%F value");
18602      else
18603	fprintf (file, "%d", 32 - 4 * (REGNO (x) - CR0_REGNO));
18604      return;
18605
18606    case 'G':
18607      /* X is a constant integer.  If it is negative, print "m",
18608	 otherwise print "z".  This is to make an aze or ame insn.  */
18609      if (GET_CODE (x) != CONST_INT)
18610	output_operand_lossage ("invalid %%G value");
18611      else if (INTVAL (x) >= 0)
18612	putc ('z', file);
18613      else
18614	putc ('m', file);
18615      return;
18616
18617    case 'h':
18618      /* If constant, output low-order five bits.  Otherwise, write
18619	 normally.  */
18620      if (INT_P (x))
18621	fprintf (file, HOST_WIDE_INT_PRINT_DEC, INTVAL (x) & 31);
18622      else
18623	print_operand (file, x, 0);
18624      return;
18625
18626    case 'H':
18627      /* If constant, output low-order six bits.  Otherwise, write
18628	 normally.  */
18629      if (INT_P (x))
18630	fprintf (file, HOST_WIDE_INT_PRINT_DEC, INTVAL (x) & 63);
18631      else
18632	print_operand (file, x, 0);
18633      return;
18634
18635    case 'I':
18636      /* Print `i' if this is a constant, else nothing.  */
18637      if (INT_P (x))
18638	putc ('i', file);
18639      return;
18640
18641    case 'j':
18642      /* Write the bit number in CCR for jump.  */
18643      i = ccr_bit (x, 0);
18644      if (i == -1)
18645	output_operand_lossage ("invalid %%j code");
18646      else
18647	fprintf (file, "%d", i);
18648      return;
18649
18650    case 'J':
18651      /* Similar, but add one for shift count in rlinm for scc and pass
18652	 scc flag to `ccr_bit'.  */
18653      i = ccr_bit (x, 1);
18654      if (i == -1)
18655	output_operand_lossage ("invalid %%J code");
18656      else
18657	/* If we want bit 31, write a shift count of zero, not 32.  */
18658	fprintf (file, "%d", i == 31 ? 0 : i + 1);
18659      return;
18660
18661    case 'k':
18662      /* X must be a constant.  Write the 1's complement of the
18663	 constant.  */
18664      if (! INT_P (x))
18665	output_operand_lossage ("invalid %%k value");
18666      else
18667	fprintf (file, HOST_WIDE_INT_PRINT_DEC, ~ INTVAL (x));
18668      return;
18669
18670    case 'K':
18671      /* X must be a symbolic constant on ELF.  Write an
18672	 expression suitable for an 'addi' that adds in the low 16
18673	 bits of the MEM.  */
18674      if (GET_CODE (x) == CONST)
18675	{
18676	  if (GET_CODE (XEXP (x, 0)) != PLUS
18677	      || (GET_CODE (XEXP (XEXP (x, 0), 0)) != SYMBOL_REF
18678		  && GET_CODE (XEXP (XEXP (x, 0), 0)) != LABEL_REF)
18679	      || GET_CODE (XEXP (XEXP (x, 0), 1)) != CONST_INT)
18680	    output_operand_lossage ("invalid %%K value");
18681	}
18682      print_operand_address (file, x);
18683      fputs ("@l", file);
18684      return;
18685
18686      /* %l is output_asm_label.  */
18687
18688    case 'L':
18689      /* Write second word of DImode or DFmode reference.  Works on register
18690	 or non-indexed memory only.  */
18691      if (REG_P (x))
18692	fputs (reg_names[REGNO (x) + 1], file);
18693      else if (MEM_P (x))
18694	{
18695	  /* Handle possible auto-increment.  Since it is pre-increment and
18696	     we have already done it, we can just use an offset of word.  */
18697	  if (GET_CODE (XEXP (x, 0)) == PRE_INC
18698	      || GET_CODE (XEXP (x, 0)) == PRE_DEC)
18699	    output_address (plus_constant (Pmode, XEXP (XEXP (x, 0), 0),
18700					   UNITS_PER_WORD));
18701	  else if (GET_CODE (XEXP (x, 0)) == PRE_MODIFY)
18702	    output_address (plus_constant (Pmode, XEXP (XEXP (x, 0), 0),
18703					   UNITS_PER_WORD));
18704	  else
18705	    output_address (XEXP (adjust_address_nv (x, SImode,
18706						     UNITS_PER_WORD),
18707				  0));
18708
18709	  if (small_data_operand (x, GET_MODE (x)))
18710	    fprintf (file, "@%s(%s)", SMALL_DATA_RELOC,
18711		     reg_names[SMALL_DATA_REG]);
18712	}
18713      return;
18714
18715    case 'm':
18716      /* MB value for a mask operand.  */
18717      if (! mask_operand (x, SImode))
18718	output_operand_lossage ("invalid %%m value");
18719
18720      fprintf (file, "%d", extract_MB (x));
18721      return;
18722
18723    case 'M':
18724      /* ME value for a mask operand.  */
18725      if (! mask_operand (x, SImode))
18726	output_operand_lossage ("invalid %%M value");
18727
18728      fprintf (file, "%d", extract_ME (x));
18729      return;
18730
18731      /* %n outputs the negative of its operand.  */
18732
18733    case 'N':
18734      /* Write the number of elements in the vector times 4.  */
18735      if (GET_CODE (x) != PARALLEL)
18736	output_operand_lossage ("invalid %%N value");
18737      else
18738	fprintf (file, "%d", XVECLEN (x, 0) * 4);
18739      return;
18740
18741    case 'O':
18742      /* Similar, but subtract 1 first.  */
18743      if (GET_CODE (x) != PARALLEL)
18744	output_operand_lossage ("invalid %%O value");
18745      else
18746	fprintf (file, "%d", (XVECLEN (x, 0) - 1) * 4);
18747      return;
18748
18749    case 'p':
18750      /* X is a CONST_INT that is a power of two.  Output the logarithm.  */
18751      if (! INT_P (x)
18752	  || INTVAL (x) < 0
18753	  || (i = exact_log2 (INTVAL (x))) < 0)
18754	output_operand_lossage ("invalid %%p value");
18755      else
18756	fprintf (file, "%d", i);
18757      return;
18758
18759    case 'P':
18760      /* The operand must be an indirect memory reference.  The result
18761	 is the register name.  */
18762      if (GET_CODE (x) != MEM || GET_CODE (XEXP (x, 0)) != REG
18763	  || REGNO (XEXP (x, 0)) >= 32)
18764	output_operand_lossage ("invalid %%P value");
18765      else
18766	fputs (reg_names[REGNO (XEXP (x, 0))], file);
18767      return;
18768
18769    case 'q':
18770      /* This outputs the logical code corresponding to a boolean
18771	 expression.  The expression may have one or both operands
18772	 negated (if one, only the first one).  For condition register
18773	 logical operations, it will also treat the negated
18774	 CR codes as NOTs, but not handle NOTs of them.  */
18775      {
18776	const char *const *t = 0;
18777	const char *s;
18778	enum rtx_code code = GET_CODE (x);
18779	static const char * const tbl[3][3] = {
18780	  { "and", "andc", "nor" },
18781	  { "or", "orc", "nand" },
18782	  { "xor", "eqv", "xor" } };
18783
18784	if (code == AND)
18785	  t = tbl[0];
18786	else if (code == IOR)
18787	  t = tbl[1];
18788	else if (code == XOR)
18789	  t = tbl[2];
18790	else
18791	  output_operand_lossage ("invalid %%q value");
18792
18793	if (GET_CODE (XEXP (x, 0)) != NOT)
18794	  s = t[0];
18795	else
18796	  {
18797	    if (GET_CODE (XEXP (x, 1)) == NOT)
18798	      s = t[2];
18799	    else
18800	      s = t[1];
18801	  }
18802
18803	fputs (s, file);
18804      }
18805      return;
18806
18807    case 'Q':
18808      if (! TARGET_MFCRF)
18809	return;
18810      fputc (',', file);
18811      /* FALLTHRU */
18812
18813    case 'R':
18814      /* X is a CR register.  Print the mask for `mtcrf'.  */
18815      if (GET_CODE (x) != REG || ! CR_REGNO_P (REGNO (x)))
18816	output_operand_lossage ("invalid %%R value");
18817      else
18818	fprintf (file, "%d", 128 >> (REGNO (x) - CR0_REGNO));
18819      return;
18820
18821    case 's':
18822      /* Low 5 bits of 32 - value */
18823      if (! INT_P (x))
18824	output_operand_lossage ("invalid %%s value");
18825      else
18826	fprintf (file, HOST_WIDE_INT_PRINT_DEC, (32 - INTVAL (x)) & 31);
18827      return;
18828
18829    case 'S':
18830      /* PowerPC64 mask position.  All 0's is excluded.
18831	 CONST_INT 32-bit mask is considered sign-extended so any
18832	 transition must occur within the CONST_INT, not on the boundary.  */
18833      if (! mask64_operand (x, DImode))
18834	output_operand_lossage ("invalid %%S value");
18835
18836      uval = INTVAL (x);
18837
18838      if (uval & 1)	/* Clear Left */
18839	{
18840#if HOST_BITS_PER_WIDE_INT > 64
18841	  uval &= ((unsigned HOST_WIDE_INT) 1 << 64) - 1;
18842#endif
18843	  i = 64;
18844	}
18845      else		/* Clear Right */
18846	{
18847	  uval = ~uval;
18848#if HOST_BITS_PER_WIDE_INT > 64
18849	  uval &= ((unsigned HOST_WIDE_INT) 1 << 64) - 1;
18850#endif
18851	  i = 63;
18852	}
18853      while (uval != 0)
18854	--i, uval >>= 1;
18855      gcc_assert (i >= 0);
18856      fprintf (file, "%d", i);
18857      return;
18858
18859    case 't':
18860      /* Like 'J' but get to the OVERFLOW/UNORDERED bit.  */
18861      gcc_assert (REG_P (x) && GET_MODE (x) == CCmode);
18862
18863      /* Bit 3 is OV bit.  */
18864      i = 4 * (REGNO (x) - CR0_REGNO) + 3;
18865
18866      /* If we want bit 31, write a shift count of zero, not 32.  */
18867      fprintf (file, "%d", i == 31 ? 0 : i + 1);
18868      return;
18869
18870    case 'T':
18871      /* Print the symbolic name of a branch target register.  */
18872      if (GET_CODE (x) != REG || (REGNO (x) != LR_REGNO
18873				  && REGNO (x) != CTR_REGNO))
18874	output_operand_lossage ("invalid %%T value");
18875      else if (REGNO (x) == LR_REGNO)
18876	fputs ("lr", file);
18877      else
18878	fputs ("ctr", file);
18879      return;
18880
18881    case 'u':
18882      /* High-order or low-order 16 bits of constant, whichever is non-zero,
18883	 for use in unsigned operand.  */
18884      if (! INT_P (x))
18885	{
18886	  output_operand_lossage ("invalid %%u value");
18887	  return;
18888	}
18889
18890      uval = INTVAL (x);
18891      if ((uval & 0xffff) == 0)
18892	uval >>= 16;
18893
18894      fprintf (file, HOST_WIDE_INT_PRINT_HEX, uval & 0xffff);
18895      return;
18896
18897    case 'v':
18898      /* High-order 16 bits of constant for use in signed operand.  */
18899      if (! INT_P (x))
18900	output_operand_lossage ("invalid %%v value");
18901      else
18902	fprintf (file, HOST_WIDE_INT_PRINT_HEX,
18903		 (INTVAL (x) >> 16) & 0xffff);
18904      return;
18905
18906    case 'U':
18907      /* Print `u' if this has an auto-increment or auto-decrement.  */
18908      if (MEM_P (x)
18909	  && (GET_CODE (XEXP (x, 0)) == PRE_INC
18910	      || GET_CODE (XEXP (x, 0)) == PRE_DEC
18911	      || GET_CODE (XEXP (x, 0)) == PRE_MODIFY))
18912	putc ('u', file);
18913      return;
18914
18915    case 'V':
18916      /* Print the trap code for this operand.  */
18917      switch (GET_CODE (x))
18918	{
18919	case EQ:
18920	  fputs ("eq", file);   /* 4 */
18921	  break;
18922	case NE:
18923	  fputs ("ne", file);   /* 24 */
18924	  break;
18925	case LT:
18926	  fputs ("lt", file);   /* 16 */
18927	  break;
18928	case LE:
18929	  fputs ("le", file);   /* 20 */
18930	  break;
18931	case GT:
18932	  fputs ("gt", file);   /* 8 */
18933	  break;
18934	case GE:
18935	  fputs ("ge", file);   /* 12 */
18936	  break;
18937	case LTU:
18938	  fputs ("llt", file);  /* 2 */
18939	  break;
18940	case LEU:
18941	  fputs ("lle", file);  /* 6 */
18942	  break;
18943	case GTU:
18944	  fputs ("lgt", file);  /* 1 */
18945	  break;
18946	case GEU:
18947	  fputs ("lge", file);  /* 5 */
18948	  break;
18949	default:
18950	  gcc_unreachable ();
18951	}
18952      break;
18953
18954    case 'w':
18955      /* If constant, low-order 16 bits of constant, signed.  Otherwise, write
18956	 normally.  */
18957      if (INT_P (x))
18958	fprintf (file, HOST_WIDE_INT_PRINT_DEC,
18959		 ((INTVAL (x) & 0xffff) ^ 0x8000) - 0x8000);
18960      else
18961	print_operand (file, x, 0);
18962      return;
18963
18964    case 'W':
18965      /* MB value for a PowerPC64 rldic operand.  */
18966      i = clz_hwi (INTVAL (x));
18967
18968      fprintf (file, "%d", i);
18969      return;
18970
18971    case 'x':
18972      /* X is a FPR or Altivec register used in a VSX context.  */
18973      if (GET_CODE (x) != REG || !VSX_REGNO_P (REGNO (x)))
18974	output_operand_lossage ("invalid %%x value");
18975      else
18976	{
18977	  int reg = REGNO (x);
18978	  int vsx_reg = (FP_REGNO_P (reg)
18979			 ? reg - 32
18980			 : reg - FIRST_ALTIVEC_REGNO + 32);
18981
18982#ifdef TARGET_REGNAMES
18983	  if (TARGET_REGNAMES)
18984	    fprintf (file, "%%vs%d", vsx_reg);
18985	  else
18986#endif
18987	    fprintf (file, "%d", vsx_reg);
18988	}
18989      return;
18990
18991    case 'X':
18992      if (MEM_P (x)
18993	  && (legitimate_indexed_address_p (XEXP (x, 0), 0)
18994	      || (GET_CODE (XEXP (x, 0)) == PRE_MODIFY
18995		  && legitimate_indexed_address_p (XEXP (XEXP (x, 0), 1), 0))))
18996	putc ('x', file);
18997      return;
18998
18999    case 'Y':
19000      /* Like 'L', for third word of TImode/PTImode  */
19001      if (REG_P (x))
19002	fputs (reg_names[REGNO (x) + 2], file);
19003      else if (MEM_P (x))
19004	{
19005	  if (GET_CODE (XEXP (x, 0)) == PRE_INC
19006	      || GET_CODE (XEXP (x, 0)) == PRE_DEC)
19007	    output_address (plus_constant (Pmode, XEXP (XEXP (x, 0), 0), 8));
19008	  else if (GET_CODE (XEXP (x, 0)) == PRE_MODIFY)
19009	    output_address (plus_constant (Pmode, XEXP (XEXP (x, 0), 0), 8));
19010	  else
19011	    output_address (XEXP (adjust_address_nv (x, SImode, 8), 0));
19012	  if (small_data_operand (x, GET_MODE (x)))
19013	    fprintf (file, "@%s(%s)", SMALL_DATA_RELOC,
19014		     reg_names[SMALL_DATA_REG]);
19015	}
19016      return;
19017
19018    case 'z':
19019      /* X is a SYMBOL_REF.  Write out the name preceded by a
19020	 period and without any trailing data in brackets.  Used for function
19021	 names.  If we are configured for System V (or the embedded ABI) on
19022	 the PowerPC, do not emit the period, since those systems do not use
19023	 TOCs and the like.  */
19024      gcc_assert (GET_CODE (x) == SYMBOL_REF);
19025
19026      /* For macho, check to see if we need a stub.  */
19027      if (TARGET_MACHO)
19028	{
19029	  const char *name = XSTR (x, 0);
19030#if TARGET_MACHO
19031	  if (darwin_emit_branch_islands
19032	      && MACHOPIC_INDIRECT
19033	      && machopic_classify_symbol (x) == MACHOPIC_UNDEFINED_FUNCTION)
19034	    name = machopic_indirection_name (x, /*stub_p=*/true);
19035#endif
19036	  assemble_name (file, name);
19037	}
19038      else if (!DOT_SYMBOLS)
19039	assemble_name (file, XSTR (x, 0));
19040      else
19041	rs6000_output_function_entry (file, XSTR (x, 0));
19042      return;
19043
19044    case 'Z':
19045      /* Like 'L', for last word of TImode/PTImode.  */
19046      if (REG_P (x))
19047	fputs (reg_names[REGNO (x) + 3], file);
19048      else if (MEM_P (x))
19049	{
19050	  if (GET_CODE (XEXP (x, 0)) == PRE_INC
19051	      || GET_CODE (XEXP (x, 0)) == PRE_DEC)
19052	    output_address (plus_constant (Pmode, XEXP (XEXP (x, 0), 0), 12));
19053	  else if (GET_CODE (XEXP (x, 0)) == PRE_MODIFY)
19054	    output_address (plus_constant (Pmode, XEXP (XEXP (x, 0), 0), 12));
19055	  else
19056	    output_address (XEXP (adjust_address_nv (x, SImode, 12), 0));
19057	  if (small_data_operand (x, GET_MODE (x)))
19058	    fprintf (file, "@%s(%s)", SMALL_DATA_RELOC,
19059		     reg_names[SMALL_DATA_REG]);
19060	}
19061      return;
19062
19063      /* Print AltiVec or SPE memory operand.  */
19064    case 'y':
19065      {
19066	rtx tmp;
19067
19068	gcc_assert (MEM_P (x));
19069
19070	tmp = XEXP (x, 0);
19071
19072	/* Ugly hack because %y is overloaded.  */
19073	if ((TARGET_SPE || TARGET_E500_DOUBLE)
19074	    && (GET_MODE_SIZE (GET_MODE (x)) == 8
19075		|| GET_MODE (x) == TFmode
19076		|| GET_MODE (x) == TImode
19077		|| GET_MODE (x) == PTImode))
19078	  {
19079	    /* Handle [reg].  */
19080	    if (REG_P (tmp))
19081	      {
19082		fprintf (file, "0(%s)", reg_names[REGNO (tmp)]);
19083		break;
19084	      }
19085	    /* Handle [reg+UIMM].  */
19086	    else if (GET_CODE (tmp) == PLUS &&
19087		     GET_CODE (XEXP (tmp, 1)) == CONST_INT)
19088	      {
19089		int x;
19090
19091		gcc_assert (REG_P (XEXP (tmp, 0)));
19092
19093		x = INTVAL (XEXP (tmp, 1));
19094		fprintf (file, "%d(%s)", x, reg_names[REGNO (XEXP (tmp, 0))]);
19095		break;
19096	      }
19097
19098	    /* Fall through.  Must be [reg+reg].  */
19099	  }
19100	if (VECTOR_MEM_ALTIVEC_P (GET_MODE (x))
19101	    && GET_CODE (tmp) == AND
19102	    && GET_CODE (XEXP (tmp, 1)) == CONST_INT
19103	    && INTVAL (XEXP (tmp, 1)) == -16)
19104	  tmp = XEXP (tmp, 0);
19105	else if (VECTOR_MEM_VSX_P (GET_MODE (x))
19106		 && GET_CODE (tmp) == PRE_MODIFY)
19107	  tmp = XEXP (tmp, 1);
19108	if (REG_P (tmp))
19109	  fprintf (file, "0,%s", reg_names[REGNO (tmp)]);
19110	else
19111	  {
19112	    if (GET_CODE (tmp) != PLUS
19113		|| !REG_P (XEXP (tmp, 0))
19114		|| !REG_P (XEXP (tmp, 1)))
19115	      {
19116		output_operand_lossage ("invalid %%y value, try using the 'Z' constraint");
19117		break;
19118	      }
19119
19120	    if (REGNO (XEXP (tmp, 0)) == 0)
19121	      fprintf (file, "%s,%s", reg_names[ REGNO (XEXP (tmp, 1)) ],
19122		       reg_names[ REGNO (XEXP (tmp, 0)) ]);
19123	    else
19124	      fprintf (file, "%s,%s", reg_names[ REGNO (XEXP (tmp, 0)) ],
19125		       reg_names[ REGNO (XEXP (tmp, 1)) ]);
19126	  }
19127	break;
19128      }
19129
19130    case 0:
19131      if (REG_P (x))
19132	fprintf (file, "%s", reg_names[REGNO (x)]);
19133      else if (MEM_P (x))
19134	{
19135	  /* We need to handle PRE_INC and PRE_DEC here, since we need to
19136	     know the width from the mode.  */
19137	  if (GET_CODE (XEXP (x, 0)) == PRE_INC)
19138	    fprintf (file, "%d(%s)", GET_MODE_SIZE (GET_MODE (x)),
19139		     reg_names[REGNO (XEXP (XEXP (x, 0), 0))]);
19140	  else if (GET_CODE (XEXP (x, 0)) == PRE_DEC)
19141	    fprintf (file, "%d(%s)", - GET_MODE_SIZE (GET_MODE (x)),
19142		     reg_names[REGNO (XEXP (XEXP (x, 0), 0))]);
19143	  else if (GET_CODE (XEXP (x, 0)) == PRE_MODIFY)
19144	    output_address (XEXP (XEXP (x, 0), 1));
19145	  else
19146	    output_address (XEXP (x, 0));
19147	}
19148      else
19149	{
19150	  if (toc_relative_expr_p (x, false))
19151	    /* This hack along with a corresponding hack in
19152	       rs6000_output_addr_const_extra arranges to output addends
19153	       where the assembler expects to find them.  eg.
19154	       (plus (unspec [(symbol_ref ("x")) (reg 2)] tocrel) 4)
19155	       without this hack would be output as "x@toc+4".  We
19156	       want "x+4@toc".  */
19157	    output_addr_const (file, CONST_CAST_RTX (tocrel_base));
19158	  else
19159	    output_addr_const (file, x);
19160	}
19161      return;
19162
19163    case '&':
19164      if (const char *name = get_some_local_dynamic_name ())
19165	assemble_name (file, name);
19166      else
19167	output_operand_lossage ("'%%&' used without any "
19168				"local dynamic TLS references");
19169      return;
19170
19171    default:
19172      output_operand_lossage ("invalid %%xn code");
19173    }
19174}
19175
19176/* Print the address of an operand.  */
19177
19178void
19179print_operand_address (FILE *file, rtx x)
19180{
19181  if (REG_P (x))
19182    fprintf (file, "0(%s)", reg_names[ REGNO (x) ]);
19183  else if (GET_CODE (x) == SYMBOL_REF || GET_CODE (x) == CONST
19184	   || GET_CODE (x) == LABEL_REF)
19185    {
19186      output_addr_const (file, x);
19187      if (small_data_operand (x, GET_MODE (x)))
19188	fprintf (file, "@%s(%s)", SMALL_DATA_RELOC,
19189		 reg_names[SMALL_DATA_REG]);
19190      else
19191	gcc_assert (!TARGET_TOC);
19192    }
19193  else if (GET_CODE (x) == PLUS && REG_P (XEXP (x, 0))
19194	   && REG_P (XEXP (x, 1)))
19195    {
19196      if (REGNO (XEXP (x, 0)) == 0)
19197	fprintf (file, "%s,%s", reg_names[ REGNO (XEXP (x, 1)) ],
19198		 reg_names[ REGNO (XEXP (x, 0)) ]);
19199      else
19200	fprintf (file, "%s,%s", reg_names[ REGNO (XEXP (x, 0)) ],
19201		 reg_names[ REGNO (XEXP (x, 1)) ]);
19202    }
19203  else if (GET_CODE (x) == PLUS && REG_P (XEXP (x, 0))
19204	   && GET_CODE (XEXP (x, 1)) == CONST_INT)
19205    fprintf (file, HOST_WIDE_INT_PRINT_DEC "(%s)",
19206	     INTVAL (XEXP (x, 1)), reg_names[ REGNO (XEXP (x, 0)) ]);
19207#if TARGET_MACHO
19208  else if (GET_CODE (x) == LO_SUM && REG_P (XEXP (x, 0))
19209	   && CONSTANT_P (XEXP (x, 1)))
19210    {
19211      fprintf (file, "lo16(");
19212      output_addr_const (file, XEXP (x, 1));
19213      fprintf (file, ")(%s)", reg_names[ REGNO (XEXP (x, 0)) ]);
19214    }
19215#endif
19216#if TARGET_ELF
19217  else if (GET_CODE (x) == LO_SUM && REG_P (XEXP (x, 0))
19218	   && CONSTANT_P (XEXP (x, 1)))
19219    {
19220      output_addr_const (file, XEXP (x, 1));
19221      fprintf (file, "@l(%s)", reg_names[ REGNO (XEXP (x, 0)) ]);
19222    }
19223#endif
19224  else if (toc_relative_expr_p (x, false))
19225    {
19226      /* This hack along with a corresponding hack in
19227	 rs6000_output_addr_const_extra arranges to output addends
19228	 where the assembler expects to find them.  eg.
19229	 (lo_sum (reg 9)
19230	 .       (plus (unspec [(symbol_ref ("x")) (reg 2)] tocrel) 8))
19231	 without this hack would be output as "x@toc+8@l(9)".  We
19232	 want "x+8@toc@l(9)".  */
19233      output_addr_const (file, CONST_CAST_RTX (tocrel_base));
19234      if (GET_CODE (x) == LO_SUM)
19235	fprintf (file, "@l(%s)", reg_names[REGNO (XEXP (x, 0))]);
19236      else
19237	fprintf (file, "(%s)", reg_names[REGNO (XVECEXP (tocrel_base, 0, 1))]);
19238    }
19239  else
19240    gcc_unreachable ();
19241}
19242
19243/* Implement TARGET_OUTPUT_ADDR_CONST_EXTRA.  */
19244
19245static bool
19246rs6000_output_addr_const_extra (FILE *file, rtx x)
19247{
19248  if (GET_CODE (x) == UNSPEC)
19249    switch (XINT (x, 1))
19250      {
19251      case UNSPEC_TOCREL:
19252	gcc_checking_assert (GET_CODE (XVECEXP (x, 0, 0)) == SYMBOL_REF
19253			     && REG_P (XVECEXP (x, 0, 1))
19254			     && REGNO (XVECEXP (x, 0, 1)) == TOC_REGISTER);
19255	output_addr_const (file, XVECEXP (x, 0, 0));
19256	if (x == tocrel_base && tocrel_offset != const0_rtx)
19257	  {
19258	    if (INTVAL (tocrel_offset) >= 0)
19259	      fprintf (file, "+");
19260	    output_addr_const (file, CONST_CAST_RTX (tocrel_offset));
19261	  }
19262	if (!TARGET_AIX || (TARGET_ELF && TARGET_MINIMAL_TOC))
19263	  {
19264	    putc ('-', file);
19265	    assemble_name (file, toc_label_name);
19266	  }
19267	else if (TARGET_ELF)
19268	  fputs ("@toc", file);
19269	return true;
19270
19271#if TARGET_MACHO
19272      case UNSPEC_MACHOPIC_OFFSET:
19273	output_addr_const (file, XVECEXP (x, 0, 0));
19274	putc ('-', file);
19275	machopic_output_function_base_name (file);
19276	return true;
19277#endif
19278      }
19279  return false;
19280}
19281
19282/* Target hook for assembling integer objects.  The PowerPC version has
19283   to handle fixup entries for relocatable code if RELOCATABLE_NEEDS_FIXUP
19284   is defined.  It also needs to handle DI-mode objects on 64-bit
19285   targets.  */
19286
19287static bool
19288rs6000_assemble_integer (rtx x, unsigned int size, int aligned_p)
19289{
19290#ifdef RELOCATABLE_NEEDS_FIXUP
19291  /* Special handling for SI values.  */
19292  if (RELOCATABLE_NEEDS_FIXUP && size == 4 && aligned_p)
19293    {
19294      static int recurse = 0;
19295
19296      /* For -mrelocatable, we mark all addresses that need to be fixed up in
19297	 the .fixup section.  Since the TOC section is already relocated, we
19298	 don't need to mark it here.  We used to skip the text section, but it
19299	 should never be valid for relocated addresses to be placed in the text
19300	 section.  */
19301      if (TARGET_RELOCATABLE
19302	  && in_section != toc_section
19303	  && !recurse
19304	  && !CONST_SCALAR_INT_P (x)
19305	  && CONSTANT_P (x))
19306	{
19307	  char buf[256];
19308
19309	  recurse = 1;
19310	  ASM_GENERATE_INTERNAL_LABEL (buf, "LCP", fixuplabelno);
19311	  fixuplabelno++;
19312	  ASM_OUTPUT_LABEL (asm_out_file, buf);
19313	  fprintf (asm_out_file, "\t.long\t(");
19314	  output_addr_const (asm_out_file, x);
19315	  fprintf (asm_out_file, ")@fixup\n");
19316	  fprintf (asm_out_file, "\t.section\t\".fixup\",\"aw\"\n");
19317	  ASM_OUTPUT_ALIGN (asm_out_file, 2);
19318	  fprintf (asm_out_file, "\t.long\t");
19319	  assemble_name (asm_out_file, buf);
19320	  fprintf (asm_out_file, "\n\t.previous\n");
19321	  recurse = 0;
19322	  return true;
19323	}
19324      /* Remove initial .'s to turn a -mcall-aixdesc function
19325	 address into the address of the descriptor, not the function
19326	 itself.  */
19327      else if (GET_CODE (x) == SYMBOL_REF
19328	       && XSTR (x, 0)[0] == '.'
19329	       && DEFAULT_ABI == ABI_AIX)
19330	{
19331	  const char *name = XSTR (x, 0);
19332	  while (*name == '.')
19333	    name++;
19334
19335	  fprintf (asm_out_file, "\t.long\t%s\n", name);
19336	  return true;
19337	}
19338    }
19339#endif /* RELOCATABLE_NEEDS_FIXUP */
19340  return default_assemble_integer (x, size, aligned_p);
19341}
19342
19343#if defined (HAVE_GAS_HIDDEN) && !TARGET_MACHO
19344/* Emit an assembler directive to set symbol visibility for DECL to
19345   VISIBILITY_TYPE.  */
19346
19347static void
19348rs6000_assemble_visibility (tree decl, int vis)
19349{
19350  if (TARGET_XCOFF)
19351    return;
19352
19353  /* Functions need to have their entry point symbol visibility set as
19354     well as their descriptor symbol visibility.  */
19355  if (DEFAULT_ABI == ABI_AIX
19356      && DOT_SYMBOLS
19357      && TREE_CODE (decl) == FUNCTION_DECL)
19358    {
19359      static const char * const visibility_types[] = {
19360	NULL, "internal", "hidden", "protected"
19361      };
19362
19363      const char *name, *type;
19364
19365      name = ((* targetm.strip_name_encoding)
19366	      (IDENTIFIER_POINTER (DECL_ASSEMBLER_NAME (decl))));
19367      type = visibility_types[vis];
19368
19369      fprintf (asm_out_file, "\t.%s\t%s\n", type, name);
19370      fprintf (asm_out_file, "\t.%s\t.%s\n", type, name);
19371    }
19372  else
19373    default_assemble_visibility (decl, vis);
19374}
19375#endif
19376
19377enum rtx_code
19378rs6000_reverse_condition (machine_mode mode, enum rtx_code code)
19379{
19380  /* Reversal of FP compares takes care -- an ordered compare
19381     becomes an unordered compare and vice versa.  */
19382  if (mode == CCFPmode
19383      && (!flag_finite_math_only
19384	  || code == UNLT || code == UNLE || code == UNGT || code == UNGE
19385	  || code == UNEQ || code == LTGT))
19386    return reverse_condition_maybe_unordered (code);
19387  else
19388    return reverse_condition (code);
19389}
19390
19391/* Generate a compare for CODE.  Return a brand-new rtx that
19392   represents the result of the compare.  */
19393
19394static rtx
19395rs6000_generate_compare (rtx cmp, machine_mode mode)
19396{
19397  machine_mode comp_mode;
19398  rtx compare_result;
19399  enum rtx_code code = GET_CODE (cmp);
19400  rtx op0 = XEXP (cmp, 0);
19401  rtx op1 = XEXP (cmp, 1);
19402
19403  if (FLOAT_MODE_P (mode))
19404    comp_mode = CCFPmode;
19405  else if (code == GTU || code == LTU
19406	   || code == GEU || code == LEU)
19407    comp_mode = CCUNSmode;
19408  else if ((code == EQ || code == NE)
19409	   && unsigned_reg_p (op0)
19410	   && (unsigned_reg_p (op1)
19411	       || (CONST_INT_P (op1) && INTVAL (op1) != 0)))
19412    /* These are unsigned values, perhaps there will be a later
19413       ordering compare that can be shared with this one.  */
19414    comp_mode = CCUNSmode;
19415  else
19416    comp_mode = CCmode;
19417
19418  /* If we have an unsigned compare, make sure we don't have a signed value as
19419     an immediate.  */
19420  if (comp_mode == CCUNSmode && GET_CODE (op1) == CONST_INT
19421      && INTVAL (op1) < 0)
19422    {
19423      op0 = copy_rtx_if_shared (op0);
19424      op1 = force_reg (GET_MODE (op0), op1);
19425      cmp = gen_rtx_fmt_ee (code, GET_MODE (cmp), op0, op1);
19426    }
19427
19428  /* First, the compare.  */
19429  compare_result = gen_reg_rtx (comp_mode);
19430
19431  /* E500 FP compare instructions on the GPRs.  Yuck!  */
19432  if ((!TARGET_FPRS && TARGET_HARD_FLOAT)
19433      && FLOAT_MODE_P (mode))
19434    {
19435      rtx cmp, or_result, compare_result2;
19436      machine_mode op_mode = GET_MODE (op0);
19437      bool reverse_p;
19438
19439      if (op_mode == VOIDmode)
19440	op_mode = GET_MODE (op1);
19441
19442      /* First reverse the condition codes that aren't directly supported.  */
19443      switch (code)
19444	{
19445	  case NE:
19446	  case UNLT:
19447	  case UNLE:
19448	  case UNGT:
19449	  case UNGE:
19450	    code = reverse_condition_maybe_unordered (code);
19451	    reverse_p = true;
19452	    break;
19453
19454	  case EQ:
19455	  case LT:
19456	  case LE:
19457	  case GT:
19458	  case GE:
19459	    reverse_p = false;
19460	    break;
19461
19462	  default:
19463	    gcc_unreachable ();
19464	}
19465
19466      /* The E500 FP compare instructions toggle the GT bit (CR bit 1) only.
19467	 This explains the following mess.  */
19468
19469      switch (code)
19470	{
19471	case EQ:
19472	  switch (op_mode)
19473	    {
19474	    case SFmode:
19475	      cmp = (flag_finite_math_only && !flag_trapping_math)
19476		? gen_tstsfeq_gpr (compare_result, op0, op1)
19477		: gen_cmpsfeq_gpr (compare_result, op0, op1);
19478	      break;
19479
19480	    case DFmode:
19481	      cmp = (flag_finite_math_only && !flag_trapping_math)
19482		? gen_tstdfeq_gpr (compare_result, op0, op1)
19483		: gen_cmpdfeq_gpr (compare_result, op0, op1);
19484	      break;
19485
19486	    case TFmode:
19487	      cmp = (flag_finite_math_only && !flag_trapping_math)
19488		? gen_tsttfeq_gpr (compare_result, op0, op1)
19489		: gen_cmptfeq_gpr (compare_result, op0, op1);
19490	      break;
19491
19492	    default:
19493	      gcc_unreachable ();
19494	    }
19495	  break;
19496
19497	case GT:
19498	case GE:
19499	  switch (op_mode)
19500	    {
19501	    case SFmode:
19502	      cmp = (flag_finite_math_only && !flag_trapping_math)
19503		? gen_tstsfgt_gpr (compare_result, op0, op1)
19504		: gen_cmpsfgt_gpr (compare_result, op0, op1);
19505	      break;
19506
19507	    case DFmode:
19508	      cmp = (flag_finite_math_only && !flag_trapping_math)
19509		? gen_tstdfgt_gpr (compare_result, op0, op1)
19510		: gen_cmpdfgt_gpr (compare_result, op0, op1);
19511	      break;
19512
19513	    case TFmode:
19514	      cmp = (flag_finite_math_only && !flag_trapping_math)
19515		? gen_tsttfgt_gpr (compare_result, op0, op1)
19516		: gen_cmptfgt_gpr (compare_result, op0, op1);
19517	      break;
19518
19519	    default:
19520	      gcc_unreachable ();
19521	    }
19522	  break;
19523
19524	case LT:
19525	case LE:
19526	  switch (op_mode)
19527	    {
19528	    case SFmode:
19529	      cmp = (flag_finite_math_only && !flag_trapping_math)
19530		? gen_tstsflt_gpr (compare_result, op0, op1)
19531		: gen_cmpsflt_gpr (compare_result, op0, op1);
19532	      break;
19533
19534	    case DFmode:
19535	      cmp = (flag_finite_math_only && !flag_trapping_math)
19536		? gen_tstdflt_gpr (compare_result, op0, op1)
19537		: gen_cmpdflt_gpr (compare_result, op0, op1);
19538	      break;
19539
19540	    case TFmode:
19541	      cmp = (flag_finite_math_only && !flag_trapping_math)
19542		? gen_tsttflt_gpr (compare_result, op0, op1)
19543		: gen_cmptflt_gpr (compare_result, op0, op1);
19544	      break;
19545
19546	    default:
19547	      gcc_unreachable ();
19548	    }
19549	  break;
19550
19551        default:
19552          gcc_unreachable ();
19553	}
19554
19555      /* Synthesize LE and GE from LT/GT || EQ.  */
19556      if (code == LE || code == GE)
19557	{
19558	  emit_insn (cmp);
19559
19560	  compare_result2 = gen_reg_rtx (CCFPmode);
19561
19562	  /* Do the EQ.  */
19563	  switch (op_mode)
19564	    {
19565	    case SFmode:
19566	      cmp = (flag_finite_math_only && !flag_trapping_math)
19567		? gen_tstsfeq_gpr (compare_result2, op0, op1)
19568		: gen_cmpsfeq_gpr (compare_result2, op0, op1);
19569	      break;
19570
19571	    case DFmode:
19572	      cmp = (flag_finite_math_only && !flag_trapping_math)
19573		? gen_tstdfeq_gpr (compare_result2, op0, op1)
19574		: gen_cmpdfeq_gpr (compare_result2, op0, op1);
19575	      break;
19576
19577	    case TFmode:
19578	      cmp = (flag_finite_math_only && !flag_trapping_math)
19579		? gen_tsttfeq_gpr (compare_result2, op0, op1)
19580		: gen_cmptfeq_gpr (compare_result2, op0, op1);
19581	      break;
19582
19583	    default:
19584	      gcc_unreachable ();
19585	    }
19586
19587	  emit_insn (cmp);
19588
19589	  /* OR them together.  */
19590	  or_result = gen_reg_rtx (CCFPmode);
19591	  cmp = gen_e500_cr_ior_compare (or_result, compare_result,
19592					 compare_result2);
19593	  compare_result = or_result;
19594	}
19595
19596      code = reverse_p ? NE : EQ;
19597
19598      emit_insn (cmp);
19599    }
19600  else
19601    {
19602      /* Generate XLC-compatible TFmode compare as PARALLEL with extra
19603	 CLOBBERs to match cmptf_internal2 pattern.  */
19604      if (comp_mode == CCFPmode && TARGET_XL_COMPAT
19605	  && GET_MODE (op0) == TFmode
19606	  && !TARGET_IEEEQUAD
19607	  && TARGET_HARD_FLOAT && TARGET_FPRS && TARGET_LONG_DOUBLE_128)
19608	emit_insn (gen_rtx_PARALLEL (VOIDmode,
19609	  gen_rtvec (10,
19610		     gen_rtx_SET (VOIDmode,
19611				  compare_result,
19612				  gen_rtx_COMPARE (comp_mode, op0, op1)),
19613		     gen_rtx_CLOBBER (VOIDmode, gen_rtx_SCRATCH (DFmode)),
19614		     gen_rtx_CLOBBER (VOIDmode, gen_rtx_SCRATCH (DFmode)),
19615		     gen_rtx_CLOBBER (VOIDmode, gen_rtx_SCRATCH (DFmode)),
19616		     gen_rtx_CLOBBER (VOIDmode, gen_rtx_SCRATCH (DFmode)),
19617		     gen_rtx_CLOBBER (VOIDmode, gen_rtx_SCRATCH (DFmode)),
19618		     gen_rtx_CLOBBER (VOIDmode, gen_rtx_SCRATCH (DFmode)),
19619		     gen_rtx_CLOBBER (VOIDmode, gen_rtx_SCRATCH (DFmode)),
19620		     gen_rtx_CLOBBER (VOIDmode, gen_rtx_SCRATCH (DFmode)),
19621		     gen_rtx_CLOBBER (VOIDmode, gen_rtx_SCRATCH (Pmode)))));
19622      else if (GET_CODE (op1) == UNSPEC
19623	       && XINT (op1, 1) == UNSPEC_SP_TEST)
19624	{
19625	  rtx op1b = XVECEXP (op1, 0, 0);
19626	  comp_mode = CCEQmode;
19627	  compare_result = gen_reg_rtx (CCEQmode);
19628	  if (TARGET_64BIT)
19629	    emit_insn (gen_stack_protect_testdi (compare_result, op0, op1b));
19630	  else
19631	    emit_insn (gen_stack_protect_testsi (compare_result, op0, op1b));
19632	}
19633      else
19634	emit_insn (gen_rtx_SET (VOIDmode, compare_result,
19635				gen_rtx_COMPARE (comp_mode, op0, op1)));
19636    }
19637
19638  /* Some kinds of FP comparisons need an OR operation;
19639     under flag_finite_math_only we don't bother.  */
19640  if (FLOAT_MODE_P (mode)
19641      && !flag_finite_math_only
19642      && !(TARGET_HARD_FLOAT && !TARGET_FPRS)
19643      && (code == LE || code == GE
19644	  || code == UNEQ || code == LTGT
19645	  || code == UNGT || code == UNLT))
19646    {
19647      enum rtx_code or1, or2;
19648      rtx or1_rtx, or2_rtx, compare2_rtx;
19649      rtx or_result = gen_reg_rtx (CCEQmode);
19650
19651      switch (code)
19652	{
19653	case LE: or1 = LT;  or2 = EQ;  break;
19654	case GE: or1 = GT;  or2 = EQ;  break;
19655	case UNEQ: or1 = UNORDERED;  or2 = EQ;  break;
19656	case LTGT: or1 = LT;  or2 = GT;  break;
19657	case UNGT: or1 = UNORDERED;  or2 = GT;  break;
19658	case UNLT: or1 = UNORDERED;  or2 = LT;  break;
19659	default:  gcc_unreachable ();
19660	}
19661      validate_condition_mode (or1, comp_mode);
19662      validate_condition_mode (or2, comp_mode);
19663      or1_rtx = gen_rtx_fmt_ee (or1, SImode, compare_result, const0_rtx);
19664      or2_rtx = gen_rtx_fmt_ee (or2, SImode, compare_result, const0_rtx);
19665      compare2_rtx = gen_rtx_COMPARE (CCEQmode,
19666				      gen_rtx_IOR (SImode, or1_rtx, or2_rtx),
19667				      const_true_rtx);
19668      emit_insn (gen_rtx_SET (VOIDmode, or_result, compare2_rtx));
19669
19670      compare_result = or_result;
19671      code = EQ;
19672    }
19673
19674  validate_condition_mode (code, GET_MODE (compare_result));
19675
19676  return gen_rtx_fmt_ee (code, VOIDmode, compare_result, const0_rtx);
19677}
19678
19679
19680/* Emit the RTL for an sISEL pattern.  */
19681
19682void
19683rs6000_emit_sISEL (machine_mode mode ATTRIBUTE_UNUSED, rtx operands[])
19684{
19685  rs6000_emit_int_cmove (operands[0], operands[1], const1_rtx, const0_rtx);
19686}
19687
19688/* Emit RTL that sets a register to zero if OP1 and OP2 are equal.  SCRATCH
19689   can be used as that dest register.  Return the dest register.  */
19690
19691rtx
19692rs6000_emit_eqne (machine_mode mode, rtx op1, rtx op2, rtx scratch)
19693{
19694  if (op2 == const0_rtx)
19695    return op1;
19696
19697  if (GET_CODE (scratch) == SCRATCH)
19698    scratch = gen_reg_rtx (mode);
19699
19700  if (logical_operand (op2, mode))
19701    emit_insn (gen_rtx_SET (VOIDmode, scratch, gen_rtx_XOR (mode, op1, op2)));
19702  else
19703    emit_insn (gen_rtx_SET (VOIDmode, scratch,
19704			    gen_rtx_PLUS (mode, op1, negate_rtx (mode, op2))));
19705
19706  return scratch;
19707}
19708
19709void
19710rs6000_emit_sCOND (machine_mode mode, rtx operands[])
19711{
19712  rtx condition_rtx;
19713  machine_mode op_mode;
19714  enum rtx_code cond_code;
19715  rtx result = operands[0];
19716
19717  condition_rtx = rs6000_generate_compare (operands[1], mode);
19718  cond_code = GET_CODE (condition_rtx);
19719
19720  if (FLOAT_MODE_P (mode)
19721      && !TARGET_FPRS && TARGET_HARD_FLOAT)
19722    {
19723      rtx t;
19724
19725      PUT_MODE (condition_rtx, SImode);
19726      t = XEXP (condition_rtx, 0);
19727
19728      gcc_assert (cond_code == NE || cond_code == EQ);
19729
19730      if (cond_code == NE)
19731	emit_insn (gen_e500_flip_gt_bit (t, t));
19732
19733      emit_insn (gen_move_from_CR_gt_bit (result, t));
19734      return;
19735    }
19736
19737  if (cond_code == NE
19738      || cond_code == GE || cond_code == LE
19739      || cond_code == GEU || cond_code == LEU
19740      || cond_code == ORDERED || cond_code == UNGE || cond_code == UNLE)
19741    {
19742      rtx not_result = gen_reg_rtx (CCEQmode);
19743      rtx not_op, rev_cond_rtx;
19744      machine_mode cc_mode;
19745
19746      cc_mode = GET_MODE (XEXP (condition_rtx, 0));
19747
19748      rev_cond_rtx = gen_rtx_fmt_ee (rs6000_reverse_condition (cc_mode, cond_code),
19749				     SImode, XEXP (condition_rtx, 0), const0_rtx);
19750      not_op = gen_rtx_COMPARE (CCEQmode, rev_cond_rtx, const0_rtx);
19751      emit_insn (gen_rtx_SET (VOIDmode, not_result, not_op));
19752      condition_rtx = gen_rtx_EQ (VOIDmode, not_result, const0_rtx);
19753    }
19754
19755  op_mode = GET_MODE (XEXP (operands[1], 0));
19756  if (op_mode == VOIDmode)
19757    op_mode = GET_MODE (XEXP (operands[1], 1));
19758
19759  if (TARGET_POWERPC64 && (op_mode == DImode || FLOAT_MODE_P (mode)))
19760    {
19761      PUT_MODE (condition_rtx, DImode);
19762      convert_move (result, condition_rtx, 0);
19763    }
19764  else
19765    {
19766      PUT_MODE (condition_rtx, SImode);
19767      emit_insn (gen_rtx_SET (VOIDmode, result, condition_rtx));
19768    }
19769}
19770
19771/* Emit a branch of kind CODE to location LOC.  */
19772
19773void
19774rs6000_emit_cbranch (machine_mode mode, rtx operands[])
19775{
19776  rtx condition_rtx, loc_ref;
19777
19778  condition_rtx = rs6000_generate_compare (operands[0], mode);
19779  loc_ref = gen_rtx_LABEL_REF (VOIDmode, operands[3]);
19780  emit_jump_insn (gen_rtx_SET (VOIDmode, pc_rtx,
19781			       gen_rtx_IF_THEN_ELSE (VOIDmode, condition_rtx,
19782						     loc_ref, pc_rtx)));
19783}
19784
19785/* Return the string to output a conditional branch to LABEL, which is
19786   the operand template of the label, or NULL if the branch is really a
19787   conditional return.
19788
19789   OP is the conditional expression.  XEXP (OP, 0) is assumed to be a
19790   condition code register and its mode specifies what kind of
19791   comparison we made.
19792
19793   REVERSED is nonzero if we should reverse the sense of the comparison.
19794
19795   INSN is the insn.  */
19796
19797char *
19798output_cbranch (rtx op, const char *label, int reversed, rtx_insn *insn)
19799{
19800  static char string[64];
19801  enum rtx_code code = GET_CODE (op);
19802  rtx cc_reg = XEXP (op, 0);
19803  machine_mode mode = GET_MODE (cc_reg);
19804  int cc_regno = REGNO (cc_reg) - CR0_REGNO;
19805  int need_longbranch = label != NULL && get_attr_length (insn) == 8;
19806  int really_reversed = reversed ^ need_longbranch;
19807  char *s = string;
19808  const char *ccode;
19809  const char *pred;
19810  rtx note;
19811
19812  validate_condition_mode (code, mode);
19813
19814  /* Work out which way this really branches.  We could use
19815     reverse_condition_maybe_unordered here always but this
19816     makes the resulting assembler clearer.  */
19817  if (really_reversed)
19818    {
19819      /* Reversal of FP compares takes care -- an ordered compare
19820	 becomes an unordered compare and vice versa.  */
19821      if (mode == CCFPmode)
19822	code = reverse_condition_maybe_unordered (code);
19823      else
19824	code = reverse_condition (code);
19825    }
19826
19827  if ((!TARGET_FPRS && TARGET_HARD_FLOAT) && mode == CCFPmode)
19828    {
19829      /* The efscmp/tst* instructions twiddle bit 2, which maps nicely
19830	 to the GT bit.  */
19831      switch (code)
19832	{
19833	case EQ:
19834	  /* Opposite of GT.  */
19835	  code = GT;
19836	  break;
19837
19838	case NE:
19839	  code = UNLE;
19840	  break;
19841
19842	default:
19843	  gcc_unreachable ();
19844	}
19845    }
19846
19847  switch (code)
19848    {
19849      /* Not all of these are actually distinct opcodes, but
19850	 we distinguish them for clarity of the resulting assembler.  */
19851    case NE: case LTGT:
19852      ccode = "ne"; break;
19853    case EQ: case UNEQ:
19854      ccode = "eq"; break;
19855    case GE: case GEU:
19856      ccode = "ge"; break;
19857    case GT: case GTU: case UNGT:
19858      ccode = "gt"; break;
19859    case LE: case LEU:
19860      ccode = "le"; break;
19861    case LT: case LTU: case UNLT:
19862      ccode = "lt"; break;
19863    case UNORDERED: ccode = "un"; break;
19864    case ORDERED: ccode = "nu"; break;
19865    case UNGE: ccode = "nl"; break;
19866    case UNLE: ccode = "ng"; break;
19867    default:
19868      gcc_unreachable ();
19869    }
19870
19871  /* Maybe we have a guess as to how likely the branch is.  */
19872  pred = "";
19873  note = find_reg_note (insn, REG_BR_PROB, NULL_RTX);
19874  if (note != NULL_RTX)
19875    {
19876      /* PROB is the difference from 50%.  */
19877      int prob = XINT (note, 0) - REG_BR_PROB_BASE / 2;
19878
19879      /* Only hint for highly probable/improbable branches on newer
19880	 cpus as static prediction overrides processor dynamic
19881	 prediction.  For older cpus we may as well always hint, but
19882	 assume not taken for branches that are very close to 50% as a
19883	 mispredicted taken branch is more expensive than a
19884	 mispredicted not-taken branch.  */
19885      if (rs6000_always_hint
19886	  || (abs (prob) > REG_BR_PROB_BASE / 100 * 48
19887	      && br_prob_note_reliable_p (note)))
19888	{
19889	  if (abs (prob) > REG_BR_PROB_BASE / 20
19890	      && ((prob > 0) ^ need_longbranch))
19891	    pred = "+";
19892	  else
19893	    pred = "-";
19894	}
19895    }
19896
19897  if (label == NULL)
19898    s += sprintf (s, "b%slr%s ", ccode, pred);
19899  else
19900    s += sprintf (s, "b%s%s ", ccode, pred);
19901
19902  /* We need to escape any '%' characters in the reg_names string.
19903     Assume they'd only be the first character....  */
19904  if (reg_names[cc_regno + CR0_REGNO][0] == '%')
19905    *s++ = '%';
19906  s += sprintf (s, "%s", reg_names[cc_regno + CR0_REGNO]);
19907
19908  if (label != NULL)
19909    {
19910      /* If the branch distance was too far, we may have to use an
19911	 unconditional branch to go the distance.  */
19912      if (need_longbranch)
19913	s += sprintf (s, ",$+8\n\tb %s", label);
19914      else
19915	s += sprintf (s, ",%s", label);
19916    }
19917
19918  return string;
19919}
19920
19921/* Return the string to flip the GT bit on a CR.  */
19922char *
19923output_e500_flip_gt_bit (rtx dst, rtx src)
19924{
19925  static char string[64];
19926  int a, b;
19927
19928  gcc_assert (GET_CODE (dst) == REG && CR_REGNO_P (REGNO (dst))
19929	      && GET_CODE (src) == REG && CR_REGNO_P (REGNO (src)));
19930
19931  /* GT bit.  */
19932  a = 4 * (REGNO (dst) - CR0_REGNO) + 1;
19933  b = 4 * (REGNO (src) - CR0_REGNO) + 1;
19934
19935  sprintf (string, "crnot %d,%d", a, b);
19936  return string;
19937}
19938
19939/* Return insn for VSX or Altivec comparisons.  */
19940
19941static rtx
19942rs6000_emit_vector_compare_inner (enum rtx_code code, rtx op0, rtx op1)
19943{
19944  rtx mask;
19945  machine_mode mode = GET_MODE (op0);
19946
19947  switch (code)
19948    {
19949    default:
19950      break;
19951
19952    case GE:
19953      if (GET_MODE_CLASS (mode) == MODE_VECTOR_INT)
19954	return NULL_RTX;
19955
19956    case EQ:
19957    case GT:
19958    case GTU:
19959    case ORDERED:
19960    case UNORDERED:
19961    case UNEQ:
19962    case LTGT:
19963      mask = gen_reg_rtx (mode);
19964      emit_insn (gen_rtx_SET (VOIDmode,
19965			      mask,
19966			      gen_rtx_fmt_ee (code, mode, op0, op1)));
19967      return mask;
19968    }
19969
19970  return NULL_RTX;
19971}
19972
19973/* Emit vector compare for operands OP0 and OP1 using code RCODE.
19974   DMODE is expected destination mode. This is a recursive function.  */
19975
19976static rtx
19977rs6000_emit_vector_compare (enum rtx_code rcode,
19978			    rtx op0, rtx op1,
19979			    machine_mode dmode)
19980{
19981  rtx mask;
19982  bool swap_operands = false;
19983  bool try_again = false;
19984
19985  gcc_assert (VECTOR_UNIT_ALTIVEC_OR_VSX_P (dmode));
19986  gcc_assert (GET_MODE (op0) == GET_MODE (op1));
19987
19988  /* See if the comparison works as is.  */
19989  mask = rs6000_emit_vector_compare_inner (rcode, op0, op1);
19990  if (mask)
19991    return mask;
19992
19993  switch (rcode)
19994    {
19995    case LT:
19996      rcode = GT;
19997      swap_operands = true;
19998      try_again = true;
19999      break;
20000    case LTU:
20001      rcode = GTU;
20002      swap_operands = true;
20003      try_again = true;
20004      break;
20005    case NE:
20006    case UNLE:
20007    case UNLT:
20008    case UNGE:
20009    case UNGT:
20010      /* Invert condition and try again.
20011	 e.g., A != B becomes ~(A==B).  */
20012      {
20013	enum rtx_code rev_code;
20014	enum insn_code nor_code;
20015	rtx mask2;
20016
20017	rev_code = reverse_condition_maybe_unordered (rcode);
20018	if (rev_code == UNKNOWN)
20019	  return NULL_RTX;
20020
20021	nor_code = optab_handler (one_cmpl_optab, dmode);
20022	if (nor_code == CODE_FOR_nothing)
20023	  return NULL_RTX;
20024
20025	mask2 = rs6000_emit_vector_compare (rev_code, op0, op1, dmode);
20026	if (!mask2)
20027	  return NULL_RTX;
20028
20029	mask = gen_reg_rtx (dmode);
20030	emit_insn (GEN_FCN (nor_code) (mask, mask2));
20031	return mask;
20032      }
20033      break;
20034    case GE:
20035    case GEU:
20036    case LE:
20037    case LEU:
20038      /* Try GT/GTU/LT/LTU OR EQ */
20039      {
20040	rtx c_rtx, eq_rtx;
20041	enum insn_code ior_code;
20042	enum rtx_code new_code;
20043
20044	switch (rcode)
20045	  {
20046	  case  GE:
20047	    new_code = GT;
20048	    break;
20049
20050	  case GEU:
20051	    new_code = GTU;
20052	    break;
20053
20054	  case LE:
20055	    new_code = LT;
20056	    break;
20057
20058	  case LEU:
20059	    new_code = LTU;
20060	    break;
20061
20062	  default:
20063	    gcc_unreachable ();
20064	  }
20065
20066	ior_code = optab_handler (ior_optab, dmode);
20067	if (ior_code == CODE_FOR_nothing)
20068	  return NULL_RTX;
20069
20070	c_rtx = rs6000_emit_vector_compare (new_code, op0, op1, dmode);
20071	if (!c_rtx)
20072	  return NULL_RTX;
20073
20074	eq_rtx = rs6000_emit_vector_compare (EQ, op0, op1, dmode);
20075	if (!eq_rtx)
20076	  return NULL_RTX;
20077
20078	mask = gen_reg_rtx (dmode);
20079	emit_insn (GEN_FCN (ior_code) (mask, c_rtx, eq_rtx));
20080	return mask;
20081      }
20082      break;
20083    default:
20084      return NULL_RTX;
20085    }
20086
20087  if (try_again)
20088    {
20089      if (swap_operands)
20090	std::swap (op0, op1);
20091
20092      mask = rs6000_emit_vector_compare_inner (rcode, op0, op1);
20093      if (mask)
20094	return mask;
20095    }
20096
20097  /* You only get two chances.  */
20098  return NULL_RTX;
20099}
20100
20101/* Emit vector conditional expression.  DEST is destination. OP_TRUE and
20102   OP_FALSE are two VEC_COND_EXPR operands.  CC_OP0 and CC_OP1 are the two
20103   operands for the relation operation COND.  */
20104
20105int
20106rs6000_emit_vector_cond_expr (rtx dest, rtx op_true, rtx op_false,
20107			      rtx cond, rtx cc_op0, rtx cc_op1)
20108{
20109  machine_mode dest_mode = GET_MODE (dest);
20110  machine_mode mask_mode = GET_MODE (cc_op0);
20111  enum rtx_code rcode = GET_CODE (cond);
20112  machine_mode cc_mode = CCmode;
20113  rtx mask;
20114  rtx cond2;
20115  rtx tmp;
20116  bool invert_move = false;
20117
20118  if (VECTOR_UNIT_NONE_P (dest_mode))
20119    return 0;
20120
20121  gcc_assert (GET_MODE_SIZE (dest_mode) == GET_MODE_SIZE (mask_mode)
20122	      && GET_MODE_NUNITS (dest_mode) == GET_MODE_NUNITS (mask_mode));
20123
20124  switch (rcode)
20125    {
20126      /* Swap operands if we can, and fall back to doing the operation as
20127	 specified, and doing a NOR to invert the test.  */
20128    case NE:
20129    case UNLE:
20130    case UNLT:
20131    case UNGE:
20132    case UNGT:
20133      /* Invert condition and try again.
20134	 e.g., A  = (B != C) ? D : E becomes A = (B == C) ? E : D.  */
20135      invert_move = true;
20136      rcode = reverse_condition_maybe_unordered (rcode);
20137      if (rcode == UNKNOWN)
20138	return 0;
20139      break;
20140
20141      /* Mark unsigned tests with CCUNSmode.  */
20142    case GTU:
20143    case GEU:
20144    case LTU:
20145    case LEU:
20146      cc_mode = CCUNSmode;
20147      break;
20148
20149    default:
20150      break;
20151    }
20152
20153  /* Get the vector mask for the given relational operations.  */
20154  mask = rs6000_emit_vector_compare (rcode, cc_op0, cc_op1, mask_mode);
20155
20156  if (!mask)
20157    return 0;
20158
20159  if (invert_move)
20160    {
20161      tmp = op_true;
20162      op_true = op_false;
20163      op_false = tmp;
20164    }
20165
20166  cond2 = gen_rtx_fmt_ee (NE, cc_mode, gen_lowpart (dest_mode, mask),
20167			  CONST0_RTX (dest_mode));
20168  emit_insn (gen_rtx_SET (VOIDmode,
20169			  dest,
20170			  gen_rtx_IF_THEN_ELSE (dest_mode,
20171						cond2,
20172						op_true,
20173						op_false)));
20174  return 1;
20175}
20176
20177/* Emit a conditional move: move TRUE_COND to DEST if OP of the
20178   operands of the last comparison is nonzero/true, FALSE_COND if it
20179   is zero/false.  Return 0 if the hardware has no such operation.  */
20180
20181int
20182rs6000_emit_cmove (rtx dest, rtx op, rtx true_cond, rtx false_cond)
20183{
20184  enum rtx_code code = GET_CODE (op);
20185  rtx op0 = XEXP (op, 0);
20186  rtx op1 = XEXP (op, 1);
20187  REAL_VALUE_TYPE c1;
20188  machine_mode compare_mode = GET_MODE (op0);
20189  machine_mode result_mode = GET_MODE (dest);
20190  rtx temp;
20191  bool is_against_zero;
20192
20193  /* These modes should always match.  */
20194  if (GET_MODE (op1) != compare_mode
20195      /* In the isel case however, we can use a compare immediate, so
20196	 op1 may be a small constant.  */
20197      && (!TARGET_ISEL || !short_cint_operand (op1, VOIDmode)))
20198    return 0;
20199  if (GET_MODE (true_cond) != result_mode)
20200    return 0;
20201  if (GET_MODE (false_cond) != result_mode)
20202    return 0;
20203
20204  /* Don't allow using floating point comparisons for integer results for
20205     now.  */
20206  if (FLOAT_MODE_P (compare_mode) && !FLOAT_MODE_P (result_mode))
20207    return 0;
20208
20209  /* First, work out if the hardware can do this at all, or
20210     if it's too slow....  */
20211  if (!FLOAT_MODE_P (compare_mode))
20212    {
20213      if (TARGET_ISEL)
20214	return rs6000_emit_int_cmove (dest, op, true_cond, false_cond);
20215      return 0;
20216    }
20217  else if (TARGET_HARD_FLOAT && !TARGET_FPRS
20218	   && SCALAR_FLOAT_MODE_P (compare_mode))
20219    return 0;
20220
20221  is_against_zero = op1 == CONST0_RTX (compare_mode);
20222
20223  /* A floating-point subtract might overflow, underflow, or produce
20224     an inexact result, thus changing the floating-point flags, so it
20225     can't be generated if we care about that.  It's safe if one side
20226     of the construct is zero, since then no subtract will be
20227     generated.  */
20228  if (SCALAR_FLOAT_MODE_P (compare_mode)
20229      && flag_trapping_math && ! is_against_zero)
20230    return 0;
20231
20232  /* Eliminate half of the comparisons by switching operands, this
20233     makes the remaining code simpler.  */
20234  if (code == UNLT || code == UNGT || code == UNORDERED || code == NE
20235      || code == LTGT || code == LT || code == UNLE)
20236    {
20237      code = reverse_condition_maybe_unordered (code);
20238      temp = true_cond;
20239      true_cond = false_cond;
20240      false_cond = temp;
20241    }
20242
20243  /* UNEQ and LTGT take four instructions for a comparison with zero,
20244     it'll probably be faster to use a branch here too.  */
20245  if (code == UNEQ && HONOR_NANS (compare_mode))
20246    return 0;
20247
20248  if (GET_CODE (op1) == CONST_DOUBLE)
20249    REAL_VALUE_FROM_CONST_DOUBLE (c1, op1);
20250
20251  /* We're going to try to implement comparisons by performing
20252     a subtract, then comparing against zero.  Unfortunately,
20253     Inf - Inf is NaN which is not zero, and so if we don't
20254     know that the operand is finite and the comparison
20255     would treat EQ different to UNORDERED, we can't do it.  */
20256  if (HONOR_INFINITIES (compare_mode)
20257      && code != GT && code != UNGE
20258      && (GET_CODE (op1) != CONST_DOUBLE || real_isinf (&c1))
20259      /* Constructs of the form (a OP b ? a : b) are safe.  */
20260      && ((! rtx_equal_p (op0, false_cond) && ! rtx_equal_p (op1, false_cond))
20261	  || (! rtx_equal_p (op0, true_cond)
20262	      && ! rtx_equal_p (op1, true_cond))))
20263    return 0;
20264
20265  /* At this point we know we can use fsel.  */
20266
20267  /* Reduce the comparison to a comparison against zero.  */
20268  if (! is_against_zero)
20269    {
20270      temp = gen_reg_rtx (compare_mode);
20271      emit_insn (gen_rtx_SET (VOIDmode, temp,
20272			      gen_rtx_MINUS (compare_mode, op0, op1)));
20273      op0 = temp;
20274      op1 = CONST0_RTX (compare_mode);
20275    }
20276
20277  /* If we don't care about NaNs we can reduce some of the comparisons
20278     down to faster ones.  */
20279  if (! HONOR_NANS (compare_mode))
20280    switch (code)
20281      {
20282      case GT:
20283	code = LE;
20284	temp = true_cond;
20285	true_cond = false_cond;
20286	false_cond = temp;
20287	break;
20288      case UNGE:
20289	code = GE;
20290	break;
20291      case UNEQ:
20292	code = EQ;
20293	break;
20294      default:
20295	break;
20296      }
20297
20298  /* Now, reduce everything down to a GE.  */
20299  switch (code)
20300    {
20301    case GE:
20302      break;
20303
20304    case LE:
20305      temp = gen_reg_rtx (compare_mode);
20306      emit_insn (gen_rtx_SET (VOIDmode, temp, gen_rtx_NEG (compare_mode, op0)));
20307      op0 = temp;
20308      break;
20309
20310    case ORDERED:
20311      temp = gen_reg_rtx (compare_mode);
20312      emit_insn (gen_rtx_SET (VOIDmode, temp, gen_rtx_ABS (compare_mode, op0)));
20313      op0 = temp;
20314      break;
20315
20316    case EQ:
20317      temp = gen_reg_rtx (compare_mode);
20318      emit_insn (gen_rtx_SET (VOIDmode, temp,
20319			      gen_rtx_NEG (compare_mode,
20320					   gen_rtx_ABS (compare_mode, op0))));
20321      op0 = temp;
20322      break;
20323
20324    case UNGE:
20325      /* a UNGE 0 <-> (a GE 0 || -a UNLT 0) */
20326      temp = gen_reg_rtx (result_mode);
20327      emit_insn (gen_rtx_SET (VOIDmode, temp,
20328			      gen_rtx_IF_THEN_ELSE (result_mode,
20329						    gen_rtx_GE (VOIDmode,
20330								op0, op1),
20331						    true_cond, false_cond)));
20332      false_cond = true_cond;
20333      true_cond = temp;
20334
20335      temp = gen_reg_rtx (compare_mode);
20336      emit_insn (gen_rtx_SET (VOIDmode, temp, gen_rtx_NEG (compare_mode, op0)));
20337      op0 = temp;
20338      break;
20339
20340    case GT:
20341      /* a GT 0 <-> (a GE 0 && -a UNLT 0) */
20342      temp = gen_reg_rtx (result_mode);
20343      emit_insn (gen_rtx_SET (VOIDmode, temp,
20344			      gen_rtx_IF_THEN_ELSE (result_mode,
20345						    gen_rtx_GE (VOIDmode,
20346								op0, op1),
20347						    true_cond, false_cond)));
20348      true_cond = false_cond;
20349      false_cond = temp;
20350
20351      temp = gen_reg_rtx (compare_mode);
20352      emit_insn (gen_rtx_SET (VOIDmode, temp, gen_rtx_NEG (compare_mode, op0)));
20353      op0 = temp;
20354      break;
20355
20356    default:
20357      gcc_unreachable ();
20358    }
20359
20360  emit_insn (gen_rtx_SET (VOIDmode, dest,
20361			  gen_rtx_IF_THEN_ELSE (result_mode,
20362						gen_rtx_GE (VOIDmode,
20363							    op0, op1),
20364						true_cond, false_cond)));
20365  return 1;
20366}
20367
20368/* Same as above, but for ints (isel).  */
20369
20370static int
20371rs6000_emit_int_cmove (rtx dest, rtx op, rtx true_cond, rtx false_cond)
20372{
20373  rtx condition_rtx, cr;
20374  machine_mode mode = GET_MODE (dest);
20375  enum rtx_code cond_code;
20376  rtx (*isel_func) (rtx, rtx, rtx, rtx, rtx);
20377  bool signedp;
20378
20379  if (mode != SImode && (!TARGET_POWERPC64 || mode != DImode))
20380    return 0;
20381
20382  /* We still have to do the compare, because isel doesn't do a
20383     compare, it just looks at the CRx bits set by a previous compare
20384     instruction.  */
20385  condition_rtx = rs6000_generate_compare (op, mode);
20386  cond_code = GET_CODE (condition_rtx);
20387  cr = XEXP (condition_rtx, 0);
20388  signedp = GET_MODE (cr) == CCmode;
20389
20390  isel_func = (mode == SImode
20391	       ? (signedp ? gen_isel_signed_si : gen_isel_unsigned_si)
20392	       : (signedp ? gen_isel_signed_di : gen_isel_unsigned_di));
20393
20394  switch (cond_code)
20395    {
20396    case LT: case GT: case LTU: case GTU: case EQ:
20397      /* isel handles these directly.  */
20398      break;
20399
20400    default:
20401      /* We need to swap the sense of the comparison.  */
20402      {
20403	std::swap (false_cond, true_cond);
20404	PUT_CODE (condition_rtx, reverse_condition (cond_code));
20405      }
20406      break;
20407    }
20408
20409  false_cond = force_reg (mode, false_cond);
20410  if (true_cond != const0_rtx)
20411    true_cond = force_reg (mode, true_cond);
20412
20413  emit_insn (isel_func (dest, condition_rtx, true_cond, false_cond, cr));
20414
20415  return 1;
20416}
20417
20418const char *
20419output_isel (rtx *operands)
20420{
20421  enum rtx_code code;
20422
20423  code = GET_CODE (operands[1]);
20424
20425  if (code == GE || code == GEU || code == LE || code == LEU || code == NE)
20426    {
20427      gcc_assert (GET_CODE (operands[2]) == REG
20428		  && GET_CODE (operands[3]) == REG);
20429      PUT_CODE (operands[1], reverse_condition (code));
20430      return "isel %0,%3,%2,%j1";
20431    }
20432
20433  return "isel %0,%2,%3,%j1";
20434}
20435
20436void
20437rs6000_emit_minmax (rtx dest, enum rtx_code code, rtx op0, rtx op1)
20438{
20439  machine_mode mode = GET_MODE (op0);
20440  enum rtx_code c;
20441  rtx target;
20442
20443  /* VSX/altivec have direct min/max insns.  */
20444  if ((code == SMAX || code == SMIN)
20445      && (VECTOR_UNIT_ALTIVEC_OR_VSX_P (mode)
20446	  || (mode == SFmode && VECTOR_UNIT_VSX_P (DFmode))))
20447    {
20448      emit_insn (gen_rtx_SET (VOIDmode,
20449			      dest,
20450			      gen_rtx_fmt_ee (code, mode, op0, op1)));
20451      return;
20452    }
20453
20454  if (code == SMAX || code == SMIN)
20455    c = GE;
20456  else
20457    c = GEU;
20458
20459  if (code == SMAX || code == UMAX)
20460    target = emit_conditional_move (dest, c, op0, op1, mode,
20461				    op0, op1, mode, 0);
20462  else
20463    target = emit_conditional_move (dest, c, op0, op1, mode,
20464				    op1, op0, mode, 0);
20465  gcc_assert (target);
20466  if (target != dest)
20467    emit_move_insn (dest, target);
20468}
20469
20470/* A subroutine of the atomic operation splitters.  Jump to LABEL if
20471   COND is true.  Mark the jump as unlikely to be taken.  */
20472
20473static void
20474emit_unlikely_jump (rtx cond, rtx label)
20475{
20476  int very_unlikely = REG_BR_PROB_BASE / 100 - 1;
20477  rtx x;
20478
20479  x = gen_rtx_IF_THEN_ELSE (VOIDmode, cond, label, pc_rtx);
20480  x = emit_jump_insn (gen_rtx_SET (VOIDmode, pc_rtx, x));
20481  add_int_reg_note (x, REG_BR_PROB, very_unlikely);
20482}
20483
20484/* A subroutine of the atomic operation splitters.  Emit a load-locked
20485   instruction in MODE.  For QI/HImode, possibly use a pattern than includes
20486   the zero_extend operation.  */
20487
20488static void
20489emit_load_locked (machine_mode mode, rtx reg, rtx mem)
20490{
20491  rtx (*fn) (rtx, rtx) = NULL;
20492
20493  switch (mode)
20494    {
20495    case QImode:
20496      fn = gen_load_lockedqi;
20497      break;
20498    case HImode:
20499      fn = gen_load_lockedhi;
20500      break;
20501    case SImode:
20502      if (GET_MODE (mem) == QImode)
20503	fn = gen_load_lockedqi_si;
20504      else if (GET_MODE (mem) == HImode)
20505	fn = gen_load_lockedhi_si;
20506      else
20507	fn = gen_load_lockedsi;
20508      break;
20509    case DImode:
20510      fn = gen_load_lockeddi;
20511      break;
20512    case TImode:
20513      fn = gen_load_lockedti;
20514      break;
20515    default:
20516      gcc_unreachable ();
20517    }
20518  emit_insn (fn (reg, mem));
20519}
20520
20521/* A subroutine of the atomic operation splitters.  Emit a store-conditional
20522   instruction in MODE.  */
20523
20524static void
20525emit_store_conditional (machine_mode mode, rtx res, rtx mem, rtx val)
20526{
20527  rtx (*fn) (rtx, rtx, rtx) = NULL;
20528
20529  switch (mode)
20530    {
20531    case QImode:
20532      fn = gen_store_conditionalqi;
20533      break;
20534    case HImode:
20535      fn = gen_store_conditionalhi;
20536      break;
20537    case SImode:
20538      fn = gen_store_conditionalsi;
20539      break;
20540    case DImode:
20541      fn = gen_store_conditionaldi;
20542      break;
20543    case TImode:
20544      fn = gen_store_conditionalti;
20545      break;
20546    default:
20547      gcc_unreachable ();
20548    }
20549
20550  /* Emit sync before stwcx. to address PPC405 Erratum.  */
20551  if (PPC405_ERRATUM77)
20552    emit_insn (gen_hwsync ());
20553
20554  emit_insn (fn (res, mem, val));
20555}
20556
20557/* Expand barriers before and after a load_locked/store_cond sequence.  */
20558
20559static rtx
20560rs6000_pre_atomic_barrier (rtx mem, enum memmodel model)
20561{
20562  rtx addr = XEXP (mem, 0);
20563  int strict_p = (reload_in_progress || reload_completed);
20564
20565  if (!legitimate_indirect_address_p (addr, strict_p)
20566      && !legitimate_indexed_address_p (addr, strict_p))
20567    {
20568      addr = force_reg (Pmode, addr);
20569      mem = replace_equiv_address_nv (mem, addr);
20570    }
20571
20572  switch (model)
20573    {
20574    case MEMMODEL_RELAXED:
20575    case MEMMODEL_CONSUME:
20576    case MEMMODEL_ACQUIRE:
20577    case MEMMODEL_SYNC_ACQUIRE:
20578      break;
20579    case MEMMODEL_RELEASE:
20580    case MEMMODEL_SYNC_RELEASE:
20581    case MEMMODEL_ACQ_REL:
20582      emit_insn (gen_lwsync ());
20583      break;
20584    case MEMMODEL_SEQ_CST:
20585    case MEMMODEL_SYNC_SEQ_CST:
20586      emit_insn (gen_hwsync ());
20587      break;
20588    default:
20589      gcc_unreachable ();
20590    }
20591  return mem;
20592}
20593
20594static void
20595rs6000_post_atomic_barrier (enum memmodel model)
20596{
20597  switch (model)
20598    {
20599    case MEMMODEL_RELAXED:
20600    case MEMMODEL_CONSUME:
20601    case MEMMODEL_RELEASE:
20602    case MEMMODEL_SYNC_RELEASE:
20603      break;
20604    case MEMMODEL_ACQUIRE:
20605    case MEMMODEL_SYNC_ACQUIRE:
20606    case MEMMODEL_ACQ_REL:
20607    case MEMMODEL_SEQ_CST:
20608    case MEMMODEL_SYNC_SEQ_CST:
20609      emit_insn (gen_isync ());
20610      break;
20611    default:
20612      gcc_unreachable ();
20613    }
20614}
20615
20616/* A subroutine of the various atomic expanders.  For sub-word operations,
20617   we must adjust things to operate on SImode.  Given the original MEM,
20618   return a new aligned memory.  Also build and return the quantities by
20619   which to shift and mask.  */
20620
20621static rtx
20622rs6000_adjust_atomic_subword (rtx orig_mem, rtx *pshift, rtx *pmask)
20623{
20624  rtx addr, align, shift, mask, mem;
20625  HOST_WIDE_INT shift_mask;
20626  machine_mode mode = GET_MODE (orig_mem);
20627
20628  /* For smaller modes, we have to implement this via SImode.  */
20629  shift_mask = (mode == QImode ? 0x18 : 0x10);
20630
20631  addr = XEXP (orig_mem, 0);
20632  addr = force_reg (GET_MODE (addr), addr);
20633
20634  /* Aligned memory containing subword.  Generate a new memory.  We
20635     do not want any of the existing MEM_ATTR data, as we're now
20636     accessing memory outside the original object.  */
20637  align = expand_simple_binop (Pmode, AND, addr, GEN_INT (-4),
20638			       NULL_RTX, 1, OPTAB_LIB_WIDEN);
20639  mem = gen_rtx_MEM (SImode, align);
20640  MEM_VOLATILE_P (mem) = MEM_VOLATILE_P (orig_mem);
20641  if (MEM_ALIAS_SET (orig_mem) == ALIAS_SET_MEMORY_BARRIER)
20642    set_mem_alias_set (mem, ALIAS_SET_MEMORY_BARRIER);
20643
20644  /* Shift amount for subword relative to aligned word.  */
20645  shift = gen_reg_rtx (SImode);
20646  addr = gen_lowpart (SImode, addr);
20647  emit_insn (gen_rlwinm (shift, addr, GEN_INT (3), GEN_INT (shift_mask)));
20648  if (BYTES_BIG_ENDIAN)
20649    shift = expand_simple_binop (SImode, XOR, shift, GEN_INT (shift_mask),
20650			         shift, 1, OPTAB_LIB_WIDEN);
20651  *pshift = shift;
20652
20653  /* Mask for insertion.  */
20654  mask = expand_simple_binop (SImode, ASHIFT, GEN_INT (GET_MODE_MASK (mode)),
20655			      shift, NULL_RTX, 1, OPTAB_LIB_WIDEN);
20656  *pmask = mask;
20657
20658  return mem;
20659}
20660
20661/* A subroutine of the various atomic expanders.  For sub-word operands,
20662   combine OLDVAL and NEWVAL via MASK.  Returns a new pseduo.  */
20663
20664static rtx
20665rs6000_mask_atomic_subword (rtx oldval, rtx newval, rtx mask)
20666{
20667  rtx x;
20668
20669  x = gen_reg_rtx (SImode);
20670  emit_insn (gen_rtx_SET (VOIDmode, x,
20671			  gen_rtx_AND (SImode,
20672				       gen_rtx_NOT (SImode, mask),
20673				       oldval)));
20674
20675  x = expand_simple_binop (SImode, IOR, newval, x, x, 1, OPTAB_LIB_WIDEN);
20676
20677  return x;
20678}
20679
20680/* A subroutine of the various atomic expanders.  For sub-word operands,
20681   extract WIDE to NARROW via SHIFT.  */
20682
20683static void
20684rs6000_finish_atomic_subword (rtx narrow, rtx wide, rtx shift)
20685{
20686  wide = expand_simple_binop (SImode, LSHIFTRT, wide, shift,
20687			      wide, 1, OPTAB_LIB_WIDEN);
20688  emit_move_insn (narrow, gen_lowpart (GET_MODE (narrow), wide));
20689}
20690
20691/* Expand an atomic compare and swap operation.  */
20692
20693void
20694rs6000_expand_atomic_compare_and_swap (rtx operands[])
20695{
20696  rtx boolval, retval, mem, oldval, newval, cond;
20697  rtx label1, label2, x, mask, shift;
20698  machine_mode mode, orig_mode;
20699  enum memmodel mod_s, mod_f;
20700  bool is_weak;
20701
20702  boolval = operands[0];
20703  retval = operands[1];
20704  mem = operands[2];
20705  oldval = operands[3];
20706  newval = operands[4];
20707  is_weak = (INTVAL (operands[5]) != 0);
20708  mod_s = memmodel_from_int (INTVAL (operands[6]));
20709  mod_f = memmodel_from_int (INTVAL (operands[7]));
20710  orig_mode = mode = GET_MODE (mem);
20711
20712  mask = shift = NULL_RTX;
20713  if (mode == QImode || mode == HImode)
20714    {
20715      /* Before power8, we didn't have access to lbarx/lharx, so generate a
20716	 lwarx and shift/mask operations.  With power8, we need to do the
20717	 comparison in SImode, but the store is still done in QI/HImode.  */
20718      oldval = convert_modes (SImode, mode, oldval, 1);
20719
20720      if (!TARGET_SYNC_HI_QI)
20721	{
20722	  mem = rs6000_adjust_atomic_subword (mem, &shift, &mask);
20723
20724	  /* Shift and mask OLDVAL into position with the word.  */
20725	  oldval = expand_simple_binop (SImode, ASHIFT, oldval, shift,
20726					NULL_RTX, 1, OPTAB_LIB_WIDEN);
20727
20728	  /* Shift and mask NEWVAL into position within the word.  */
20729	  newval = convert_modes (SImode, mode, newval, 1);
20730	  newval = expand_simple_binop (SImode, ASHIFT, newval, shift,
20731					NULL_RTX, 1, OPTAB_LIB_WIDEN);
20732	}
20733
20734      /* Prepare to adjust the return value.  */
20735      retval = gen_reg_rtx (SImode);
20736      mode = SImode;
20737    }
20738  else if (reg_overlap_mentioned_p (retval, oldval))
20739    oldval = copy_to_reg (oldval);
20740
20741  if (mode != TImode && !reg_or_short_operand (oldval, mode))
20742    oldval = copy_to_mode_reg (mode, oldval);
20743
20744  if (reg_overlap_mentioned_p (retval, newval))
20745    newval = copy_to_reg (newval);
20746
20747  mem = rs6000_pre_atomic_barrier (mem, mod_s);
20748
20749  label1 = NULL_RTX;
20750  if (!is_weak)
20751    {
20752      label1 = gen_rtx_LABEL_REF (VOIDmode, gen_label_rtx ());
20753      emit_label (XEXP (label1, 0));
20754    }
20755  label2 = gen_rtx_LABEL_REF (VOIDmode, gen_label_rtx ());
20756
20757  emit_load_locked (mode, retval, mem);
20758
20759  x = retval;
20760  if (mask)
20761    x = expand_simple_binop (SImode, AND, retval, mask,
20762			     NULL_RTX, 1, OPTAB_LIB_WIDEN);
20763
20764  cond = gen_reg_rtx (CCmode);
20765  /* If we have TImode, synthesize a comparison.  */
20766  if (mode != TImode)
20767    x = gen_rtx_COMPARE (CCmode, x, oldval);
20768  else
20769    {
20770      rtx xor1_result = gen_reg_rtx (DImode);
20771      rtx xor2_result = gen_reg_rtx (DImode);
20772      rtx or_result = gen_reg_rtx (DImode);
20773      rtx new_word0 = simplify_gen_subreg (DImode, x, TImode, 0);
20774      rtx new_word1 = simplify_gen_subreg (DImode, x, TImode, 8);
20775      rtx old_word0 = simplify_gen_subreg (DImode, oldval, TImode, 0);
20776      rtx old_word1 = simplify_gen_subreg (DImode, oldval, TImode, 8);
20777
20778      emit_insn (gen_xordi3 (xor1_result, new_word0, old_word0));
20779      emit_insn (gen_xordi3 (xor2_result, new_word1, old_word1));
20780      emit_insn (gen_iordi3 (or_result, xor1_result, xor2_result));
20781      x = gen_rtx_COMPARE (CCmode, or_result, const0_rtx);
20782    }
20783
20784  emit_insn (gen_rtx_SET (VOIDmode, cond, x));
20785
20786  x = gen_rtx_NE (VOIDmode, cond, const0_rtx);
20787  emit_unlikely_jump (x, label2);
20788
20789  x = newval;
20790  if (mask)
20791    x = rs6000_mask_atomic_subword (retval, newval, mask);
20792
20793  emit_store_conditional (orig_mode, cond, mem, x);
20794
20795  if (!is_weak)
20796    {
20797      x = gen_rtx_NE (VOIDmode, cond, const0_rtx);
20798      emit_unlikely_jump (x, label1);
20799    }
20800
20801  if (!is_mm_relaxed (mod_f))
20802    emit_label (XEXP (label2, 0));
20803
20804  rs6000_post_atomic_barrier (mod_s);
20805
20806  if (is_mm_relaxed (mod_f))
20807    emit_label (XEXP (label2, 0));
20808
20809  if (shift)
20810    rs6000_finish_atomic_subword (operands[1], retval, shift);
20811  else if (mode != GET_MODE (operands[1]))
20812    convert_move (operands[1], retval, 1);
20813
20814  /* In all cases, CR0 contains EQ on success, and NE on failure.  */
20815  x = gen_rtx_EQ (SImode, cond, const0_rtx);
20816  emit_insn (gen_rtx_SET (VOIDmode, boolval, x));
20817}
20818
20819/* Expand an atomic exchange operation.  */
20820
20821void
20822rs6000_expand_atomic_exchange (rtx operands[])
20823{
20824  rtx retval, mem, val, cond;
20825  machine_mode mode;
20826  enum memmodel model;
20827  rtx label, x, mask, shift;
20828
20829  retval = operands[0];
20830  mem = operands[1];
20831  val = operands[2];
20832  model = (enum memmodel) INTVAL (operands[3]);
20833  mode = GET_MODE (mem);
20834
20835  mask = shift = NULL_RTX;
20836  if (!TARGET_SYNC_HI_QI && (mode == QImode || mode == HImode))
20837    {
20838      mem = rs6000_adjust_atomic_subword (mem, &shift, &mask);
20839
20840      /* Shift and mask VAL into position with the word.  */
20841      val = convert_modes (SImode, mode, val, 1);
20842      val = expand_simple_binop (SImode, ASHIFT, val, shift,
20843				 NULL_RTX, 1, OPTAB_LIB_WIDEN);
20844
20845      /* Prepare to adjust the return value.  */
20846      retval = gen_reg_rtx (SImode);
20847      mode = SImode;
20848    }
20849
20850  mem = rs6000_pre_atomic_barrier (mem, model);
20851
20852  label = gen_rtx_LABEL_REF (VOIDmode, gen_label_rtx ());
20853  emit_label (XEXP (label, 0));
20854
20855  emit_load_locked (mode, retval, mem);
20856
20857  x = val;
20858  if (mask)
20859    x = rs6000_mask_atomic_subword (retval, val, mask);
20860
20861  cond = gen_reg_rtx (CCmode);
20862  emit_store_conditional (mode, cond, mem, x);
20863
20864  x = gen_rtx_NE (VOIDmode, cond, const0_rtx);
20865  emit_unlikely_jump (x, label);
20866
20867  rs6000_post_atomic_barrier (model);
20868
20869  if (shift)
20870    rs6000_finish_atomic_subword (operands[0], retval, shift);
20871}
20872
20873/* Expand an atomic fetch-and-operate pattern.  CODE is the binary operation
20874   to perform.  MEM is the memory on which to operate.  VAL is the second
20875   operand of the binary operator.  BEFORE and AFTER are optional locations to
20876   return the value of MEM either before of after the operation.  MODEL_RTX
20877   is a CONST_INT containing the memory model to use.  */
20878
20879void
20880rs6000_expand_atomic_op (enum rtx_code code, rtx mem, rtx val,
20881			 rtx orig_before, rtx orig_after, rtx model_rtx)
20882{
20883  enum memmodel model = (enum memmodel) INTVAL (model_rtx);
20884  machine_mode mode = GET_MODE (mem);
20885  machine_mode store_mode = mode;
20886  rtx label, x, cond, mask, shift;
20887  rtx before = orig_before, after = orig_after;
20888
20889  mask = shift = NULL_RTX;
20890  /* On power8, we want to use SImode for the operation.  On previous systems,
20891     use the operation in a subword and shift/mask to get the proper byte or
20892     halfword.  */
20893  if (mode == QImode || mode == HImode)
20894    {
20895      if (TARGET_SYNC_HI_QI)
20896	{
20897	  val = convert_modes (SImode, mode, val, 1);
20898
20899	  /* Prepare to adjust the return value.  */
20900	  before = gen_reg_rtx (SImode);
20901	  if (after)
20902	    after = gen_reg_rtx (SImode);
20903	  mode = SImode;
20904	}
20905      else
20906	{
20907	  mem = rs6000_adjust_atomic_subword (mem, &shift, &mask);
20908
20909	  /* Shift and mask VAL into position with the word.  */
20910	  val = convert_modes (SImode, mode, val, 1);
20911	  val = expand_simple_binop (SImode, ASHIFT, val, shift,
20912				     NULL_RTX, 1, OPTAB_LIB_WIDEN);
20913
20914	  switch (code)
20915	    {
20916	    case IOR:
20917	    case XOR:
20918	      /* We've already zero-extended VAL.  That is sufficient to
20919		 make certain that it does not affect other bits.  */
20920	      mask = NULL;
20921	      break;
20922
20923	    case AND:
20924	      /* If we make certain that all of the other bits in VAL are
20925		 set, that will be sufficient to not affect other bits.  */
20926	      x = gen_rtx_NOT (SImode, mask);
20927	      x = gen_rtx_IOR (SImode, x, val);
20928	      emit_insn (gen_rtx_SET (VOIDmode, val, x));
20929	      mask = NULL;
20930	      break;
20931
20932	    case NOT:
20933	    case PLUS:
20934	    case MINUS:
20935	      /* These will all affect bits outside the field and need
20936		 adjustment via MASK within the loop.  */
20937	      break;
20938
20939	    default:
20940	      gcc_unreachable ();
20941	    }
20942
20943	  /* Prepare to adjust the return value.  */
20944	  before = gen_reg_rtx (SImode);
20945	  if (after)
20946	    after = gen_reg_rtx (SImode);
20947	  store_mode = mode = SImode;
20948	}
20949    }
20950
20951  mem = rs6000_pre_atomic_barrier (mem, model);
20952
20953  label = gen_label_rtx ();
20954  emit_label (label);
20955  label = gen_rtx_LABEL_REF (VOIDmode, label);
20956
20957  if (before == NULL_RTX)
20958    before = gen_reg_rtx (mode);
20959
20960  emit_load_locked (mode, before, mem);
20961
20962  if (code == NOT)
20963    {
20964      x = expand_simple_binop (mode, AND, before, val,
20965			       NULL_RTX, 1, OPTAB_LIB_WIDEN);
20966      after = expand_simple_unop (mode, NOT, x, after, 1);
20967    }
20968  else
20969    {
20970      after = expand_simple_binop (mode, code, before, val,
20971				   after, 1, OPTAB_LIB_WIDEN);
20972    }
20973
20974  x = after;
20975  if (mask)
20976    {
20977      x = expand_simple_binop (SImode, AND, after, mask,
20978			       NULL_RTX, 1, OPTAB_LIB_WIDEN);
20979      x = rs6000_mask_atomic_subword (before, x, mask);
20980    }
20981  else if (store_mode != mode)
20982    x = convert_modes (store_mode, mode, x, 1);
20983
20984  cond = gen_reg_rtx (CCmode);
20985  emit_store_conditional (store_mode, cond, mem, x);
20986
20987  x = gen_rtx_NE (VOIDmode, cond, const0_rtx);
20988  emit_unlikely_jump (x, label);
20989
20990  rs6000_post_atomic_barrier (model);
20991
20992  if (shift)
20993    {
20994      /* QImode/HImode on machines without lbarx/lharx where we do a lwarx and
20995	 then do the calcuations in a SImode register.  */
20996      if (orig_before)
20997	rs6000_finish_atomic_subword (orig_before, before, shift);
20998      if (orig_after)
20999	rs6000_finish_atomic_subword (orig_after, after, shift);
21000    }
21001  else if (store_mode != mode)
21002    {
21003      /* QImode/HImode on machines with lbarx/lharx where we do the native
21004	 operation and then do the calcuations in a SImode register.  */
21005      if (orig_before)
21006	convert_move (orig_before, before, 1);
21007      if (orig_after)
21008	convert_move (orig_after, after, 1);
21009    }
21010  else if (orig_after && after != orig_after)
21011    emit_move_insn (orig_after, after);
21012}
21013
21014/* Emit instructions to move SRC to DST.  Called by splitters for
21015   multi-register moves.  It will emit at most one instruction for
21016   each register that is accessed; that is, it won't emit li/lis pairs
21017   (or equivalent for 64-bit code).  One of SRC or DST must be a hard
21018   register.  */
21019
21020void
21021rs6000_split_multireg_move (rtx dst, rtx src)
21022{
21023  /* The register number of the first register being moved.  */
21024  int reg;
21025  /* The mode that is to be moved.  */
21026  machine_mode mode;
21027  /* The mode that the move is being done in, and its size.  */
21028  machine_mode reg_mode;
21029  int reg_mode_size;
21030  /* The number of registers that will be moved.  */
21031  int nregs;
21032
21033  reg = REG_P (dst) ? REGNO (dst) : REGNO (src);
21034  mode = GET_MODE (dst);
21035  nregs = hard_regno_nregs[reg][mode];
21036  if (FP_REGNO_P (reg))
21037    reg_mode = DECIMAL_FLOAT_MODE_P (mode) ? DDmode :
21038	((TARGET_HARD_FLOAT && TARGET_DOUBLE_FLOAT) ? DFmode : SFmode);
21039  else if (ALTIVEC_REGNO_P (reg))
21040    reg_mode = V16QImode;
21041  else if (TARGET_E500_DOUBLE && mode == TFmode)
21042    reg_mode = DFmode;
21043  else
21044    reg_mode = word_mode;
21045  reg_mode_size = GET_MODE_SIZE (reg_mode);
21046
21047  gcc_assert (reg_mode_size * nregs == GET_MODE_SIZE (mode));
21048
21049  /* TDmode residing in FP registers is special, since the ISA requires that
21050     the lower-numbered word of a register pair is always the most significant
21051     word, even in little-endian mode.  This does not match the usual subreg
21052     semantics, so we cannnot use simplify_gen_subreg in those cases.  Access
21053     the appropriate constituent registers "by hand" in little-endian mode.
21054
21055     Note we do not need to check for destructive overlap here since TDmode
21056     can only reside in even/odd register pairs.  */
21057  if (FP_REGNO_P (reg) && DECIMAL_FLOAT_MODE_P (mode) && !BYTES_BIG_ENDIAN)
21058    {
21059      rtx p_src, p_dst;
21060      int i;
21061
21062      for (i = 0; i < nregs; i++)
21063	{
21064	  if (REG_P (src) && FP_REGNO_P (REGNO (src)))
21065	    p_src = gen_rtx_REG (reg_mode, REGNO (src) + nregs - 1 - i);
21066	  else
21067	    p_src = simplify_gen_subreg (reg_mode, src, mode,
21068					 i * reg_mode_size);
21069
21070	  if (REG_P (dst) && FP_REGNO_P (REGNO (dst)))
21071	    p_dst = gen_rtx_REG (reg_mode, REGNO (dst) + nregs - 1 - i);
21072	  else
21073	    p_dst = simplify_gen_subreg (reg_mode, dst, mode,
21074					 i * reg_mode_size);
21075
21076	  emit_insn (gen_rtx_SET (VOIDmode, p_dst, p_src));
21077	}
21078
21079      return;
21080    }
21081
21082  if (REG_P (src) && REG_P (dst) && (REGNO (src) < REGNO (dst)))
21083    {
21084      /* Move register range backwards, if we might have destructive
21085	 overlap.  */
21086      int i;
21087      for (i = nregs - 1; i >= 0; i--)
21088	emit_insn (gen_rtx_SET (VOIDmode,
21089				simplify_gen_subreg (reg_mode, dst, mode,
21090						     i * reg_mode_size),
21091				simplify_gen_subreg (reg_mode, src, mode,
21092						     i * reg_mode_size)));
21093    }
21094  else
21095    {
21096      int i;
21097      int j = -1;
21098      bool used_update = false;
21099      rtx restore_basereg = NULL_RTX;
21100
21101      if (MEM_P (src) && INT_REGNO_P (reg))
21102	{
21103	  rtx breg;
21104
21105	  if (GET_CODE (XEXP (src, 0)) == PRE_INC
21106	      || GET_CODE (XEXP (src, 0)) == PRE_DEC)
21107	    {
21108	      rtx delta_rtx;
21109	      breg = XEXP (XEXP (src, 0), 0);
21110	      delta_rtx = (GET_CODE (XEXP (src, 0)) == PRE_INC
21111			   ? GEN_INT (GET_MODE_SIZE (GET_MODE (src)))
21112			   : GEN_INT (-GET_MODE_SIZE (GET_MODE (src))));
21113	      emit_insn (gen_add3_insn (breg, breg, delta_rtx));
21114	      src = replace_equiv_address (src, breg);
21115	    }
21116	  else if (! rs6000_offsettable_memref_p (src, reg_mode))
21117	    {
21118	      if (GET_CODE (XEXP (src, 0)) == PRE_MODIFY)
21119		{
21120		  rtx basereg = XEXP (XEXP (src, 0), 0);
21121		  if (TARGET_UPDATE)
21122		    {
21123		      rtx ndst = simplify_gen_subreg (reg_mode, dst, mode, 0);
21124		      emit_insn (gen_rtx_SET (VOIDmode, ndst,
21125				 gen_rtx_MEM (reg_mode, XEXP (src, 0))));
21126		      used_update = true;
21127		    }
21128		  else
21129		    emit_insn (gen_rtx_SET (VOIDmode, basereg,
21130			       XEXP (XEXP (src, 0), 1)));
21131		  src = replace_equiv_address (src, basereg);
21132		}
21133	      else
21134		{
21135		  rtx basereg = gen_rtx_REG (Pmode, reg);
21136		  emit_insn (gen_rtx_SET (VOIDmode, basereg, XEXP (src, 0)));
21137		  src = replace_equiv_address (src, basereg);
21138		}
21139	    }
21140
21141	  breg = XEXP (src, 0);
21142	  if (GET_CODE (breg) == PLUS || GET_CODE (breg) == LO_SUM)
21143	    breg = XEXP (breg, 0);
21144
21145	  /* If the base register we are using to address memory is
21146	     also a destination reg, then change that register last.  */
21147	  if (REG_P (breg)
21148	      && REGNO (breg) >= REGNO (dst)
21149	      && REGNO (breg) < REGNO (dst) + nregs)
21150	    j = REGNO (breg) - REGNO (dst);
21151	}
21152      else if (MEM_P (dst) && INT_REGNO_P (reg))
21153	{
21154	  rtx breg;
21155
21156	  if (GET_CODE (XEXP (dst, 0)) == PRE_INC
21157	      || GET_CODE (XEXP (dst, 0)) == PRE_DEC)
21158	    {
21159	      rtx delta_rtx;
21160	      breg = XEXP (XEXP (dst, 0), 0);
21161	      delta_rtx = (GET_CODE (XEXP (dst, 0)) == PRE_INC
21162			   ? GEN_INT (GET_MODE_SIZE (GET_MODE (dst)))
21163			   : GEN_INT (-GET_MODE_SIZE (GET_MODE (dst))));
21164
21165	      /* We have to update the breg before doing the store.
21166		 Use store with update, if available.  */
21167
21168	      if (TARGET_UPDATE)
21169		{
21170		  rtx nsrc = simplify_gen_subreg (reg_mode, src, mode, 0);
21171		  emit_insn (TARGET_32BIT
21172			     ? (TARGET_POWERPC64
21173				? gen_movdi_si_update (breg, breg, delta_rtx, nsrc)
21174				: gen_movsi_update (breg, breg, delta_rtx, nsrc))
21175			     : gen_movdi_di_update (breg, breg, delta_rtx, nsrc));
21176		  used_update = true;
21177		}
21178	      else
21179		emit_insn (gen_add3_insn (breg, breg, delta_rtx));
21180	      dst = replace_equiv_address (dst, breg);
21181	    }
21182	  else if (!rs6000_offsettable_memref_p (dst, reg_mode)
21183		   && GET_CODE (XEXP (dst, 0)) != LO_SUM)
21184	    {
21185	      if (GET_CODE (XEXP (dst, 0)) == PRE_MODIFY)
21186		{
21187		  rtx basereg = XEXP (XEXP (dst, 0), 0);
21188		  if (TARGET_UPDATE)
21189		    {
21190		      rtx nsrc = simplify_gen_subreg (reg_mode, src, mode, 0);
21191		      emit_insn (gen_rtx_SET (VOIDmode,
21192				 gen_rtx_MEM (reg_mode, XEXP (dst, 0)), nsrc));
21193		      used_update = true;
21194		    }
21195		  else
21196		    emit_insn (gen_rtx_SET (VOIDmode, basereg,
21197			       XEXP (XEXP (dst, 0), 1)));
21198		  dst = replace_equiv_address (dst, basereg);
21199		}
21200	      else
21201		{
21202		  rtx basereg = XEXP (XEXP (dst, 0), 0);
21203		  rtx offsetreg = XEXP (XEXP (dst, 0), 1);
21204		  gcc_assert (GET_CODE (XEXP (dst, 0)) == PLUS
21205			      && REG_P (basereg)
21206			      && REG_P (offsetreg)
21207			      && REGNO (basereg) != REGNO (offsetreg));
21208		  if (REGNO (basereg) == 0)
21209		    {
21210		      rtx tmp = offsetreg;
21211		      offsetreg = basereg;
21212		      basereg = tmp;
21213		    }
21214		  emit_insn (gen_add3_insn (basereg, basereg, offsetreg));
21215		  restore_basereg = gen_sub3_insn (basereg, basereg, offsetreg);
21216		  dst = replace_equiv_address (dst, basereg);
21217		}
21218	    }
21219	  else if (GET_CODE (XEXP (dst, 0)) != LO_SUM)
21220	    gcc_assert (rs6000_offsettable_memref_p (dst, reg_mode));
21221	}
21222
21223      for (i = 0; i < nregs; i++)
21224	{
21225	  /* Calculate index to next subword.  */
21226	  ++j;
21227	  if (j == nregs)
21228	    j = 0;
21229
21230	  /* If compiler already emitted move of first word by
21231	     store with update, no need to do anything.  */
21232	  if (j == 0 && used_update)
21233	    continue;
21234
21235	  emit_insn (gen_rtx_SET (VOIDmode,
21236				  simplify_gen_subreg (reg_mode, dst, mode,
21237						       j * reg_mode_size),
21238				  simplify_gen_subreg (reg_mode, src, mode,
21239						       j * reg_mode_size)));
21240	}
21241      if (restore_basereg != NULL_RTX)
21242	emit_insn (restore_basereg);
21243    }
21244}
21245
21246
21247/* This page contains routines that are used to determine what the
21248   function prologue and epilogue code will do and write them out.  */
21249
21250static inline bool
21251save_reg_p (int r)
21252{
21253  return !call_used_regs[r] && df_regs_ever_live_p (r);
21254}
21255
21256/* Return the first fixed-point register that is required to be
21257   saved. 32 if none.  */
21258
21259int
21260first_reg_to_save (void)
21261{
21262  int first_reg;
21263
21264  /* Find lowest numbered live register.  */
21265  for (first_reg = 13; first_reg <= 31; first_reg++)
21266    if (save_reg_p (first_reg))
21267      break;
21268
21269  if (first_reg > RS6000_PIC_OFFSET_TABLE_REGNUM
21270      && ((DEFAULT_ABI == ABI_V4 && flag_pic != 0)
21271	  || (DEFAULT_ABI == ABI_DARWIN && flag_pic)
21272	  || (TARGET_TOC && TARGET_MINIMAL_TOC))
21273      && df_regs_ever_live_p (RS6000_PIC_OFFSET_TABLE_REGNUM))
21274    first_reg = RS6000_PIC_OFFSET_TABLE_REGNUM;
21275
21276#if TARGET_MACHO
21277  if (flag_pic
21278      && crtl->uses_pic_offset_table
21279      && first_reg > RS6000_PIC_OFFSET_TABLE_REGNUM)
21280    return RS6000_PIC_OFFSET_TABLE_REGNUM;
21281#endif
21282
21283  return first_reg;
21284}
21285
21286/* Similar, for FP regs.  */
21287
21288int
21289first_fp_reg_to_save (void)
21290{
21291  int first_reg;
21292
21293  /* Find lowest numbered live register.  */
21294  for (first_reg = 14 + 32; first_reg <= 63; first_reg++)
21295    if (save_reg_p (first_reg))
21296      break;
21297
21298  return first_reg;
21299}
21300
21301/* Similar, for AltiVec regs.  */
21302
21303static int
21304first_altivec_reg_to_save (void)
21305{
21306  int i;
21307
21308  /* Stack frame remains as is unless we are in AltiVec ABI.  */
21309  if (! TARGET_ALTIVEC_ABI)
21310    return LAST_ALTIVEC_REGNO + 1;
21311
21312  /* On Darwin, the unwind routines are compiled without
21313     TARGET_ALTIVEC, and use save_world to save/restore the
21314     altivec registers when necessary.  */
21315  if (DEFAULT_ABI == ABI_DARWIN && crtl->calls_eh_return
21316      && ! TARGET_ALTIVEC)
21317    return FIRST_ALTIVEC_REGNO + 20;
21318
21319  /* Find lowest numbered live register.  */
21320  for (i = FIRST_ALTIVEC_REGNO + 20; i <= LAST_ALTIVEC_REGNO; ++i)
21321    if (save_reg_p (i))
21322      break;
21323
21324  return i;
21325}
21326
21327/* Return a 32-bit mask of the AltiVec registers we need to set in
21328   VRSAVE.  Bit n of the return value is 1 if Vn is live.  The MSB in
21329   the 32-bit word is 0.  */
21330
21331static unsigned int
21332compute_vrsave_mask (void)
21333{
21334  unsigned int i, mask = 0;
21335
21336  /* On Darwin, the unwind routines are compiled without
21337     TARGET_ALTIVEC, and use save_world to save/restore the
21338     call-saved altivec registers when necessary.  */
21339  if (DEFAULT_ABI == ABI_DARWIN && crtl->calls_eh_return
21340      && ! TARGET_ALTIVEC)
21341    mask |= 0xFFF;
21342
21343  /* First, find out if we use _any_ altivec registers.  */
21344  for (i = FIRST_ALTIVEC_REGNO; i <= LAST_ALTIVEC_REGNO; ++i)
21345    if (df_regs_ever_live_p (i))
21346      mask |= ALTIVEC_REG_BIT (i);
21347
21348  if (mask == 0)
21349    return mask;
21350
21351  /* Next, remove the argument registers from the set.  These must
21352     be in the VRSAVE mask set by the caller, so we don't need to add
21353     them in again.  More importantly, the mask we compute here is
21354     used to generate CLOBBERs in the set_vrsave insn, and we do not
21355     wish the argument registers to die.  */
21356  for (i = ALTIVEC_ARG_MIN_REG; i < (unsigned) crtl->args.info.vregno; i++)
21357    mask &= ~ALTIVEC_REG_BIT (i);
21358
21359  /* Similarly, remove the return value from the set.  */
21360  {
21361    bool yes = false;
21362    diddle_return_value (is_altivec_return_reg, &yes);
21363    if (yes)
21364      mask &= ~ALTIVEC_REG_BIT (ALTIVEC_ARG_RETURN);
21365  }
21366
21367  return mask;
21368}
21369
21370/* For a very restricted set of circumstances, we can cut down the
21371   size of prologues/epilogues by calling our own save/restore-the-world
21372   routines.  */
21373
21374static void
21375compute_save_world_info (rs6000_stack_t *info_ptr)
21376{
21377  info_ptr->world_save_p = 1;
21378  info_ptr->world_save_p
21379    = (WORLD_SAVE_P (info_ptr)
21380       && DEFAULT_ABI == ABI_DARWIN
21381       && !cfun->has_nonlocal_label
21382       && info_ptr->first_fp_reg_save == FIRST_SAVED_FP_REGNO
21383       && info_ptr->first_gp_reg_save == FIRST_SAVED_GP_REGNO
21384       && info_ptr->first_altivec_reg_save == FIRST_SAVED_ALTIVEC_REGNO
21385       && info_ptr->cr_save_p);
21386
21387  /* This will not work in conjunction with sibcalls.  Make sure there
21388     are none.  (This check is expensive, but seldom executed.) */
21389  if (WORLD_SAVE_P (info_ptr))
21390    {
21391      rtx_insn *insn;
21392      for (insn = get_last_insn_anywhere (); insn; insn = PREV_INSN (insn))
21393	if (CALL_P (insn) && SIBLING_CALL_P (insn))
21394	  {
21395	    info_ptr->world_save_p = 0;
21396	    break;
21397	  }
21398    }
21399
21400  if (WORLD_SAVE_P (info_ptr))
21401    {
21402      /* Even if we're not touching VRsave, make sure there's room on the
21403	 stack for it, if it looks like we're calling SAVE_WORLD, which
21404	 will attempt to save it. */
21405      info_ptr->vrsave_size  = 4;
21406
21407      /* If we are going to save the world, we need to save the link register too.  */
21408      info_ptr->lr_save_p = 1;
21409
21410      /* "Save" the VRsave register too if we're saving the world.  */
21411      if (info_ptr->vrsave_mask == 0)
21412	info_ptr->vrsave_mask = compute_vrsave_mask ();
21413
21414      /* Because the Darwin register save/restore routines only handle
21415	 F14 .. F31 and V20 .. V31 as per the ABI, perform a consistency
21416	 check.  */
21417      gcc_assert (info_ptr->first_fp_reg_save >= FIRST_SAVED_FP_REGNO
21418		  && (info_ptr->first_altivec_reg_save
21419		      >= FIRST_SAVED_ALTIVEC_REGNO));
21420    }
21421  return;
21422}
21423
21424
21425static void
21426is_altivec_return_reg (rtx reg, void *xyes)
21427{
21428  bool *yes = (bool *) xyes;
21429  if (REGNO (reg) == ALTIVEC_ARG_RETURN)
21430    *yes = true;
21431}
21432
21433
21434/* Look for user-defined global regs in the range FIRST to LAST-1.
21435   We should not restore these, and so cannot use lmw or out-of-line
21436   restore functions if there are any.  We also can't save them
21437   (well, emit frame notes for them), because frame unwinding during
21438   exception handling will restore saved registers.  */
21439
21440static bool
21441global_regs_p (unsigned first, unsigned last)
21442{
21443  while (first < last)
21444    if (global_regs[first++])
21445      return true;
21446  return false;
21447}
21448
21449/* Determine the strategy for savings/restoring registers.  */
21450
21451enum {
21452  SAVRES_MULTIPLE = 0x1,
21453  SAVE_INLINE_FPRS = 0x2,
21454  SAVE_INLINE_GPRS = 0x4,
21455  REST_INLINE_FPRS = 0x8,
21456  REST_INLINE_GPRS = 0x10,
21457  SAVE_NOINLINE_GPRS_SAVES_LR = 0x20,
21458  SAVE_NOINLINE_FPRS_SAVES_LR = 0x40,
21459  REST_NOINLINE_FPRS_DOESNT_RESTORE_LR = 0x80,
21460  SAVE_INLINE_VRS = 0x100,
21461  REST_INLINE_VRS = 0x200
21462};
21463
21464static int
21465rs6000_savres_strategy (rs6000_stack_t *info,
21466			bool using_static_chain_p)
21467{
21468  int strategy = 0;
21469  bool lr_save_p;
21470
21471  if (TARGET_MULTIPLE
21472      && !TARGET_POWERPC64
21473      && !(TARGET_SPE_ABI && info->spe_64bit_regs_used)
21474      && info->first_gp_reg_save < 31
21475      && !global_regs_p (info->first_gp_reg_save, 32))
21476    strategy |= SAVRES_MULTIPLE;
21477
21478  if (crtl->calls_eh_return
21479      || cfun->machine->ra_need_lr)
21480    strategy |= (SAVE_INLINE_FPRS | REST_INLINE_FPRS
21481		 | SAVE_INLINE_GPRS | REST_INLINE_GPRS
21482		 | SAVE_INLINE_VRS | REST_INLINE_VRS);
21483
21484  if (info->first_fp_reg_save == 64
21485      /* The out-of-line FP routines use double-precision stores;
21486	 we can't use those routines if we don't have such stores.  */
21487      || (TARGET_HARD_FLOAT && !TARGET_DOUBLE_FLOAT)
21488      || global_regs_p (info->first_fp_reg_save, 64))
21489    strategy |= SAVE_INLINE_FPRS | REST_INLINE_FPRS;
21490
21491  if (info->first_gp_reg_save == 32
21492      || (!(strategy & SAVRES_MULTIPLE)
21493	  && global_regs_p (info->first_gp_reg_save, 32)))
21494    strategy |= SAVE_INLINE_GPRS | REST_INLINE_GPRS;
21495
21496  if (info->first_altivec_reg_save == LAST_ALTIVEC_REGNO + 1
21497      || global_regs_p (info->first_altivec_reg_save, LAST_ALTIVEC_REGNO + 1))
21498    strategy |= SAVE_INLINE_VRS | REST_INLINE_VRS;
21499
21500  /* Define cutoff for using out-of-line functions to save registers.  */
21501  if (DEFAULT_ABI == ABI_V4 || TARGET_ELF)
21502    {
21503      if (!optimize_size)
21504	{
21505	  strategy |= SAVE_INLINE_FPRS | REST_INLINE_FPRS;
21506	  strategy |= SAVE_INLINE_GPRS | REST_INLINE_GPRS;
21507	  strategy |= SAVE_INLINE_VRS | REST_INLINE_VRS;
21508	}
21509      else
21510	{
21511	  /* Prefer out-of-line restore if it will exit.  */
21512	  if (info->first_fp_reg_save > 61)
21513	    strategy |= SAVE_INLINE_FPRS;
21514	  if (info->first_gp_reg_save > 29)
21515	    {
21516	      if (info->first_fp_reg_save == 64)
21517		strategy |= SAVE_INLINE_GPRS;
21518	      else
21519		strategy |= SAVE_INLINE_GPRS | REST_INLINE_GPRS;
21520	    }
21521	  if (info->first_altivec_reg_save == LAST_ALTIVEC_REGNO)
21522	    strategy |= SAVE_INLINE_VRS | REST_INLINE_VRS;
21523	}
21524    }
21525  else if (DEFAULT_ABI == ABI_DARWIN)
21526    {
21527      if (info->first_fp_reg_save > 60)
21528	strategy |= SAVE_INLINE_FPRS | REST_INLINE_FPRS;
21529      if (info->first_gp_reg_save > 29)
21530	strategy |= SAVE_INLINE_GPRS | REST_INLINE_GPRS;
21531      strategy |= SAVE_INLINE_VRS | REST_INLINE_VRS;
21532    }
21533  else
21534    {
21535      gcc_checking_assert (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2);
21536      if (info->first_fp_reg_save > 61)
21537	strategy |= SAVE_INLINE_FPRS | REST_INLINE_FPRS;
21538      strategy |= SAVE_INLINE_GPRS | REST_INLINE_GPRS;
21539      strategy |= SAVE_INLINE_VRS | REST_INLINE_VRS;
21540    }
21541
21542  /* Don't bother to try to save things out-of-line if r11 is occupied
21543     by the static chain.  It would require too much fiddling and the
21544     static chain is rarely used anyway.  FPRs are saved w.r.t the stack
21545     pointer on Darwin, and AIX uses r1 or r12.  */
21546  if (using_static_chain_p
21547      && (DEFAULT_ABI == ABI_V4 || DEFAULT_ABI == ABI_DARWIN))
21548    strategy |= ((DEFAULT_ABI == ABI_DARWIN ? 0 : SAVE_INLINE_FPRS)
21549		 | SAVE_INLINE_GPRS
21550		 | SAVE_INLINE_VRS | REST_INLINE_VRS);
21551
21552  /* We can only use the out-of-line routines to restore if we've
21553     saved all the registers from first_fp_reg_save in the prologue.
21554     Otherwise, we risk loading garbage.  */
21555  if ((strategy & (SAVE_INLINE_FPRS | REST_INLINE_FPRS)) == SAVE_INLINE_FPRS)
21556    {
21557      int i;
21558
21559      for (i = info->first_fp_reg_save; i < 64; i++)
21560	if (!save_reg_p (i))
21561	  {
21562	    strategy |= REST_INLINE_FPRS;
21563	    break;
21564	  }
21565    }
21566
21567  /* If we are going to use store multiple, then don't even bother
21568     with the out-of-line routines, since the store-multiple
21569     instruction will always be smaller.  */
21570  if ((strategy & SAVRES_MULTIPLE))
21571    strategy |= SAVE_INLINE_GPRS;
21572
21573  /* info->lr_save_p isn't yet set if the only reason lr needs to be
21574     saved is an out-of-line save or restore.  Set up the value for
21575     the next test (excluding out-of-line gpr restore).  */
21576  lr_save_p = (info->lr_save_p
21577	       || !(strategy & SAVE_INLINE_GPRS)
21578	       || !(strategy & SAVE_INLINE_FPRS)
21579	       || !(strategy & SAVE_INLINE_VRS)
21580	       || !(strategy & REST_INLINE_FPRS)
21581	       || !(strategy & REST_INLINE_VRS));
21582
21583  /* The situation is more complicated with load multiple.  We'd
21584     prefer to use the out-of-line routines for restores, since the
21585     "exit" out-of-line routines can handle the restore of LR and the
21586     frame teardown.  However if doesn't make sense to use the
21587     out-of-line routine if that is the only reason we'd need to save
21588     LR, and we can't use the "exit" out-of-line gpr restore if we
21589     have saved some fprs; In those cases it is advantageous to use
21590     load multiple when available.  */
21591  if ((strategy & SAVRES_MULTIPLE)
21592      && (!lr_save_p
21593	  || info->first_fp_reg_save != 64))
21594    strategy |= REST_INLINE_GPRS;
21595
21596  /* Saving CR interferes with the exit routines used on the SPE, so
21597     just punt here.  */
21598  if (TARGET_SPE_ABI
21599      && info->spe_64bit_regs_used
21600      && info->cr_save_p)
21601    strategy |= REST_INLINE_GPRS;
21602
21603  /* We can only use load multiple or the out-of-line routines to
21604     restore if we've used store multiple or out-of-line routines
21605     in the prologue, i.e. if we've saved all the registers from
21606     first_gp_reg_save.  Otherwise, we risk loading garbage.  */
21607  if ((strategy & (SAVE_INLINE_GPRS | REST_INLINE_GPRS | SAVRES_MULTIPLE))
21608      == SAVE_INLINE_GPRS)
21609    {
21610      int i;
21611
21612      for (i = info->first_gp_reg_save; i < 32; i++)
21613	if (!save_reg_p (i))
21614	  {
21615	    strategy |= REST_INLINE_GPRS;
21616	    break;
21617	  }
21618    }
21619
21620  if (TARGET_ELF && TARGET_64BIT)
21621    {
21622      if (!(strategy & SAVE_INLINE_FPRS))
21623	strategy |= SAVE_NOINLINE_FPRS_SAVES_LR;
21624      else if (!(strategy & SAVE_INLINE_GPRS)
21625	       && info->first_fp_reg_save == 64)
21626	strategy |= SAVE_NOINLINE_GPRS_SAVES_LR;
21627    }
21628  else if (TARGET_AIX && !(strategy & REST_INLINE_FPRS))
21629    strategy |= REST_NOINLINE_FPRS_DOESNT_RESTORE_LR;
21630
21631  if (TARGET_MACHO && !(strategy & SAVE_INLINE_FPRS))
21632    strategy |= SAVE_NOINLINE_FPRS_SAVES_LR;
21633
21634  return strategy;
21635}
21636
21637/* Calculate the stack information for the current function.  This is
21638   complicated by having two separate calling sequences, the AIX calling
21639   sequence and the V.4 calling sequence.
21640
21641   AIX (and Darwin/Mac OS X) stack frames look like:
21642							  32-bit  64-bit
21643	SP---->	+---------------------------------------+
21644		| back chain to caller			| 0	  0
21645		+---------------------------------------+
21646		| saved CR				| 4       8 (8-11)
21647		+---------------------------------------+
21648		| saved LR				| 8       16
21649		+---------------------------------------+
21650		| reserved for compilers		| 12      24
21651		+---------------------------------------+
21652		| reserved for binders			| 16      32
21653		+---------------------------------------+
21654		| saved TOC pointer			| 20      40
21655		+---------------------------------------+
21656		| Parameter save area (P)		| 24      48
21657		+---------------------------------------+
21658		| Alloca space (A)			| 24+P    etc.
21659		+---------------------------------------+
21660		| Local variable space (L)		| 24+P+A
21661		+---------------------------------------+
21662		| Float/int conversion temporary (X)	| 24+P+A+L
21663		+---------------------------------------+
21664		| Save area for AltiVec registers (W)	| 24+P+A+L+X
21665		+---------------------------------------+
21666		| AltiVec alignment padding (Y)		| 24+P+A+L+X+W
21667		+---------------------------------------+
21668		| Save area for VRSAVE register (Z)	| 24+P+A+L+X+W+Y
21669		+---------------------------------------+
21670		| Save area for GP registers (G)	| 24+P+A+X+L+X+W+Y+Z
21671		+---------------------------------------+
21672		| Save area for FP registers (F)	| 24+P+A+X+L+X+W+Y+Z+G
21673		+---------------------------------------+
21674	old SP->| back chain to caller's caller		|
21675		+---------------------------------------+
21676
21677   The required alignment for AIX configurations is two words (i.e., 8
21678   or 16 bytes).
21679
21680   The ELFv2 ABI is a variant of the AIX ABI.  Stack frames look like:
21681
21682	SP---->	+---------------------------------------+
21683		| Back chain to caller			|  0
21684		+---------------------------------------+
21685		| Save area for CR			|  8
21686		+---------------------------------------+
21687		| Saved LR				|  16
21688		+---------------------------------------+
21689		| Saved TOC pointer			|  24
21690		+---------------------------------------+
21691		| Parameter save area (P)		|  32
21692		+---------------------------------------+
21693		| Alloca space (A)			|  32+P
21694		+---------------------------------------+
21695		| Local variable space (L)		|  32+P+A
21696		+---------------------------------------+
21697		| Save area for AltiVec registers (W)	|  32+P+A+L
21698		+---------------------------------------+
21699		| AltiVec alignment padding (Y)		|  32+P+A+L+W
21700		+---------------------------------------+
21701		| Save area for GP registers (G)	|  32+P+A+L+W+Y
21702		+---------------------------------------+
21703		| Save area for FP registers (F)	|  32+P+A+L+W+Y+G
21704		+---------------------------------------+
21705	old SP->| back chain to caller's caller		|  32+P+A+L+W+Y+G+F
21706		+---------------------------------------+
21707
21708
21709   V.4 stack frames look like:
21710
21711	SP---->	+---------------------------------------+
21712		| back chain to caller			| 0
21713		+---------------------------------------+
21714		| caller's saved LR			| 4
21715		+---------------------------------------+
21716		| Parameter save area (P)		| 8
21717		+---------------------------------------+
21718		| Alloca space (A)			| 8+P
21719		+---------------------------------------+
21720		| Varargs save area (V)			| 8+P+A
21721		+---------------------------------------+
21722		| Local variable space (L)		| 8+P+A+V
21723		+---------------------------------------+
21724		| Float/int conversion temporary (X)	| 8+P+A+V+L
21725		+---------------------------------------+
21726		| Save area for AltiVec registers (W)	| 8+P+A+V+L+X
21727		+---------------------------------------+
21728		| AltiVec alignment padding (Y)		| 8+P+A+V+L+X+W
21729		+---------------------------------------+
21730		| Save area for VRSAVE register (Z)	| 8+P+A+V+L+X+W+Y
21731		+---------------------------------------+
21732		| SPE: area for 64-bit GP registers	|
21733		+---------------------------------------+
21734		| SPE alignment padding			|
21735		+---------------------------------------+
21736		| saved CR (C)				| 8+P+A+V+L+X+W+Y+Z
21737		+---------------------------------------+
21738		| Save area for GP registers (G)	| 8+P+A+V+L+X+W+Y+Z+C
21739		+---------------------------------------+
21740		| Save area for FP registers (F)	| 8+P+A+V+L+X+W+Y+Z+C+G
21741		+---------------------------------------+
21742	old SP->| back chain to caller's caller		|
21743		+---------------------------------------+
21744
21745   The required alignment for V.4 is 16 bytes, or 8 bytes if -meabi is
21746   given.  (But note below and in sysv4.h that we require only 8 and
21747   may round up the size of our stack frame anyways.  The historical
21748   reason is early versions of powerpc-linux which didn't properly
21749   align the stack at program startup.  A happy side-effect is that
21750   -mno-eabi libraries can be used with -meabi programs.)
21751
21752   The EABI configuration defaults to the V.4 layout.  However,
21753   the stack alignment requirements may differ.  If -mno-eabi is not
21754   given, the required stack alignment is 8 bytes; if -mno-eabi is
21755   given, the required alignment is 16 bytes.  (But see V.4 comment
21756   above.)  */
21757
21758#ifndef ABI_STACK_BOUNDARY
21759#define ABI_STACK_BOUNDARY STACK_BOUNDARY
21760#endif
21761
21762static rs6000_stack_t *
21763rs6000_stack_info (void)
21764{
21765  /* We should never be called for thunks, we are not set up for that.  */
21766  gcc_assert (!cfun->is_thunk);
21767
21768  rs6000_stack_t *info_ptr = &stack_info;
21769  int reg_size = TARGET_32BIT ? 4 : 8;
21770  int ehrd_size;
21771  int ehcr_size;
21772  int save_align;
21773  int first_gp;
21774  HOST_WIDE_INT non_fixed_size;
21775  bool using_static_chain_p;
21776
21777  if (reload_completed && info_ptr->reload_completed)
21778    return info_ptr;
21779
21780  memset (info_ptr, 0, sizeof (*info_ptr));
21781  info_ptr->reload_completed = reload_completed;
21782
21783  if (TARGET_SPE)
21784    {
21785      /* Cache value so we don't rescan instruction chain over and over.  */
21786      if (cfun->machine->insn_chain_scanned_p == 0)
21787	cfun->machine->insn_chain_scanned_p
21788	  = spe_func_has_64bit_regs_p () + 1;
21789      info_ptr->spe_64bit_regs_used = cfun->machine->insn_chain_scanned_p - 1;
21790    }
21791
21792  /* Select which calling sequence.  */
21793  info_ptr->abi = DEFAULT_ABI;
21794
21795  /* Calculate which registers need to be saved & save area size.  */
21796  info_ptr->first_gp_reg_save = first_reg_to_save ();
21797  /* Assume that we will have to save RS6000_PIC_OFFSET_TABLE_REGNUM,
21798     even if it currently looks like we won't.  Reload may need it to
21799     get at a constant; if so, it will have already created a constant
21800     pool entry for it.  */
21801  if (((TARGET_TOC && TARGET_MINIMAL_TOC)
21802       || (flag_pic == 1 && DEFAULT_ABI == ABI_V4)
21803       || (flag_pic && DEFAULT_ABI == ABI_DARWIN))
21804      && crtl->uses_const_pool
21805      && info_ptr->first_gp_reg_save > RS6000_PIC_OFFSET_TABLE_REGNUM)
21806    first_gp = RS6000_PIC_OFFSET_TABLE_REGNUM;
21807  else
21808    first_gp = info_ptr->first_gp_reg_save;
21809
21810  info_ptr->gp_size = reg_size * (32 - first_gp);
21811
21812  /* For the SPE, we have an additional upper 32-bits on each GPR.
21813     Ideally we should save the entire 64-bits only when the upper
21814     half is used in SIMD instructions.  Since we only record
21815     registers live (not the size they are used in), this proves
21816     difficult because we'd have to traverse the instruction chain at
21817     the right time, taking reload into account.  This is a real pain,
21818     so we opt to save the GPRs in 64-bits always if but one register
21819     gets used in 64-bits.  Otherwise, all the registers in the frame
21820     get saved in 32-bits.
21821
21822     So... since when we save all GPRs (except the SP) in 64-bits, the
21823     traditional GP save area will be empty.  */
21824  if (TARGET_SPE_ABI && info_ptr->spe_64bit_regs_used != 0)
21825    info_ptr->gp_size = 0;
21826
21827  info_ptr->first_fp_reg_save = first_fp_reg_to_save ();
21828  info_ptr->fp_size = 8 * (64 - info_ptr->first_fp_reg_save);
21829
21830  info_ptr->first_altivec_reg_save = first_altivec_reg_to_save ();
21831  info_ptr->altivec_size = 16 * (LAST_ALTIVEC_REGNO + 1
21832				 - info_ptr->first_altivec_reg_save);
21833
21834  /* Does this function call anything?  */
21835  info_ptr->calls_p = (! crtl->is_leaf
21836		       || cfun->machine->ra_needs_full_frame);
21837
21838  /* Determine if we need to save the condition code registers.  */
21839  if (df_regs_ever_live_p (CR2_REGNO)
21840      || df_regs_ever_live_p (CR3_REGNO)
21841      || df_regs_ever_live_p (CR4_REGNO))
21842    {
21843      info_ptr->cr_save_p = 1;
21844      if (DEFAULT_ABI == ABI_V4)
21845	info_ptr->cr_size = reg_size;
21846    }
21847
21848  /* If the current function calls __builtin_eh_return, then we need
21849     to allocate stack space for registers that will hold data for
21850     the exception handler.  */
21851  if (crtl->calls_eh_return)
21852    {
21853      unsigned int i;
21854      for (i = 0; EH_RETURN_DATA_REGNO (i) != INVALID_REGNUM; ++i)
21855	continue;
21856
21857      /* SPE saves EH registers in 64-bits.  */
21858      ehrd_size = i * (TARGET_SPE_ABI
21859		       && info_ptr->spe_64bit_regs_used != 0
21860		       ? UNITS_PER_SPE_WORD : UNITS_PER_WORD);
21861    }
21862  else
21863    ehrd_size = 0;
21864
21865  /* In the ELFv2 ABI, we also need to allocate space for separate
21866     CR field save areas if the function calls __builtin_eh_return.  */
21867  if (DEFAULT_ABI == ABI_ELFv2 && crtl->calls_eh_return)
21868    {
21869      /* This hard-codes that we have three call-saved CR fields.  */
21870      ehcr_size = 3 * reg_size;
21871      /* We do *not* use the regular CR save mechanism.  */
21872      info_ptr->cr_save_p = 0;
21873    }
21874  else
21875    ehcr_size = 0;
21876
21877  /* Determine various sizes.  */
21878  info_ptr->reg_size     = reg_size;
21879  info_ptr->fixed_size   = RS6000_SAVE_AREA;
21880  info_ptr->vars_size    = RS6000_ALIGN (get_frame_size (), 8);
21881  info_ptr->parm_size    = RS6000_ALIGN (crtl->outgoing_args_size,
21882					 TARGET_ALTIVEC ? 16 : 8);
21883  if (FRAME_GROWS_DOWNWARD)
21884    info_ptr->vars_size
21885      += RS6000_ALIGN (info_ptr->fixed_size + info_ptr->vars_size
21886		       + info_ptr->parm_size,
21887		       ABI_STACK_BOUNDARY / BITS_PER_UNIT)
21888	 - (info_ptr->fixed_size + info_ptr->vars_size
21889	    + info_ptr->parm_size);
21890
21891  if (TARGET_SPE_ABI && info_ptr->spe_64bit_regs_used != 0)
21892    info_ptr->spe_gp_size = 8 * (32 - first_gp);
21893  else
21894    info_ptr->spe_gp_size = 0;
21895
21896  if (TARGET_ALTIVEC_ABI)
21897    info_ptr->vrsave_mask = compute_vrsave_mask ();
21898  else
21899    info_ptr->vrsave_mask = 0;
21900
21901  if (TARGET_ALTIVEC_VRSAVE && info_ptr->vrsave_mask)
21902    info_ptr->vrsave_size  = 4;
21903  else
21904    info_ptr->vrsave_size  = 0;
21905
21906  compute_save_world_info (info_ptr);
21907
21908  /* Calculate the offsets.  */
21909  switch (DEFAULT_ABI)
21910    {
21911    case ABI_NONE:
21912    default:
21913      gcc_unreachable ();
21914
21915    case ABI_AIX:
21916    case ABI_ELFv2:
21917    case ABI_DARWIN:
21918      info_ptr->fp_save_offset   = - info_ptr->fp_size;
21919      info_ptr->gp_save_offset   = info_ptr->fp_save_offset - info_ptr->gp_size;
21920
21921      if (TARGET_ALTIVEC_ABI)
21922	{
21923	  info_ptr->vrsave_save_offset
21924	    = info_ptr->gp_save_offset - info_ptr->vrsave_size;
21925
21926	  /* Align stack so vector save area is on a quadword boundary.
21927	     The padding goes above the vectors.  */
21928	  if (info_ptr->altivec_size != 0)
21929	    info_ptr->altivec_padding_size
21930	      = info_ptr->vrsave_save_offset & 0xF;
21931	  else
21932	    info_ptr->altivec_padding_size = 0;
21933
21934	  info_ptr->altivec_save_offset
21935	    = info_ptr->vrsave_save_offset
21936	    - info_ptr->altivec_padding_size
21937	    - info_ptr->altivec_size;
21938	  gcc_assert (info_ptr->altivec_size == 0
21939		      || info_ptr->altivec_save_offset % 16 == 0);
21940
21941	  /* Adjust for AltiVec case.  */
21942	  info_ptr->ehrd_offset = info_ptr->altivec_save_offset - ehrd_size;
21943	}
21944      else
21945	info_ptr->ehrd_offset      = info_ptr->gp_save_offset - ehrd_size;
21946
21947      info_ptr->ehcr_offset      = info_ptr->ehrd_offset - ehcr_size;
21948      info_ptr->cr_save_offset   = reg_size; /* first word when 64-bit.  */
21949      info_ptr->lr_save_offset   = 2*reg_size;
21950      break;
21951
21952    case ABI_V4:
21953      info_ptr->fp_save_offset   = - info_ptr->fp_size;
21954      info_ptr->gp_save_offset   = info_ptr->fp_save_offset - info_ptr->gp_size;
21955      info_ptr->cr_save_offset   = info_ptr->gp_save_offset - info_ptr->cr_size;
21956
21957      if (TARGET_SPE_ABI && info_ptr->spe_64bit_regs_used != 0)
21958	{
21959	  /* Align stack so SPE GPR save area is aligned on a
21960	     double-word boundary.  */
21961	  if (info_ptr->spe_gp_size != 0 && info_ptr->cr_save_offset != 0)
21962	    info_ptr->spe_padding_size
21963	      = 8 - (-info_ptr->cr_save_offset % 8);
21964	  else
21965	    info_ptr->spe_padding_size = 0;
21966
21967	  info_ptr->spe_gp_save_offset
21968	    = info_ptr->cr_save_offset
21969	    - info_ptr->spe_padding_size
21970	    - info_ptr->spe_gp_size;
21971
21972	  /* Adjust for SPE case.  */
21973	  info_ptr->ehrd_offset = info_ptr->spe_gp_save_offset;
21974	}
21975      else if (TARGET_ALTIVEC_ABI)
21976	{
21977	  info_ptr->vrsave_save_offset
21978	    = info_ptr->cr_save_offset - info_ptr->vrsave_size;
21979
21980	  /* Align stack so vector save area is on a quadword boundary.  */
21981	  if (info_ptr->altivec_size != 0)
21982	    info_ptr->altivec_padding_size
21983	      = 16 - (-info_ptr->vrsave_save_offset % 16);
21984	  else
21985	    info_ptr->altivec_padding_size = 0;
21986
21987	  info_ptr->altivec_save_offset
21988	    = info_ptr->vrsave_save_offset
21989	    - info_ptr->altivec_padding_size
21990	    - info_ptr->altivec_size;
21991
21992	  /* Adjust for AltiVec case.  */
21993	  info_ptr->ehrd_offset = info_ptr->altivec_save_offset;
21994	}
21995      else
21996	info_ptr->ehrd_offset    = info_ptr->cr_save_offset;
21997      info_ptr->ehrd_offset      -= ehrd_size;
21998      info_ptr->lr_save_offset   = reg_size;
21999      break;
22000    }
22001
22002  save_align = (TARGET_ALTIVEC_ABI || DEFAULT_ABI == ABI_DARWIN) ? 16 : 8;
22003  info_ptr->save_size    = RS6000_ALIGN (info_ptr->fp_size
22004					 + info_ptr->gp_size
22005					 + info_ptr->altivec_size
22006					 + info_ptr->altivec_padding_size
22007					 + info_ptr->spe_gp_size
22008					 + info_ptr->spe_padding_size
22009					 + ehrd_size
22010					 + ehcr_size
22011					 + info_ptr->cr_size
22012					 + info_ptr->vrsave_size,
22013					 save_align);
22014
22015  non_fixed_size	 = (info_ptr->vars_size
22016			    + info_ptr->parm_size
22017			    + info_ptr->save_size);
22018
22019  info_ptr->total_size = RS6000_ALIGN (non_fixed_size + info_ptr->fixed_size,
22020				       ABI_STACK_BOUNDARY / BITS_PER_UNIT);
22021
22022  /* Determine if we need to save the link register.  */
22023  if (info_ptr->calls_p
22024      || ((DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
22025	  && crtl->profile
22026	  && !TARGET_PROFILE_KERNEL)
22027      || (DEFAULT_ABI == ABI_V4 && cfun->calls_alloca)
22028#ifdef TARGET_RELOCATABLE
22029      || (TARGET_RELOCATABLE && (get_pool_size () != 0))
22030#endif
22031      || rs6000_ra_ever_killed ())
22032    info_ptr->lr_save_p = 1;
22033
22034  using_static_chain_p = (cfun->static_chain_decl != NULL_TREE
22035			  && df_regs_ever_live_p (STATIC_CHAIN_REGNUM)
22036			  && call_used_regs[STATIC_CHAIN_REGNUM]);
22037  info_ptr->savres_strategy = rs6000_savres_strategy (info_ptr,
22038						      using_static_chain_p);
22039
22040  if (!(info_ptr->savres_strategy & SAVE_INLINE_GPRS)
22041      || !(info_ptr->savres_strategy & SAVE_INLINE_FPRS)
22042      || !(info_ptr->savres_strategy & SAVE_INLINE_VRS)
22043      || !(info_ptr->savres_strategy & REST_INLINE_GPRS)
22044      || !(info_ptr->savres_strategy & REST_INLINE_FPRS)
22045      || !(info_ptr->savres_strategy & REST_INLINE_VRS))
22046    info_ptr->lr_save_p = 1;
22047
22048  if (info_ptr->lr_save_p)
22049    df_set_regs_ever_live (LR_REGNO, true);
22050
22051  /* Determine if we need to allocate any stack frame:
22052
22053     For AIX we need to push the stack if a frame pointer is needed
22054     (because the stack might be dynamically adjusted), if we are
22055     debugging, if we make calls, or if the sum of fp_save, gp_save,
22056     and local variables are more than the space needed to save all
22057     non-volatile registers: 32-bit: 18*8 + 19*4 = 220 or 64-bit: 18*8
22058     + 18*8 = 288 (GPR13 reserved).
22059
22060     For V.4 we don't have the stack cushion that AIX uses, but assume
22061     that the debugger can handle stackless frames.  */
22062
22063  if (info_ptr->calls_p)
22064    info_ptr->push_p = 1;
22065
22066  else if (DEFAULT_ABI == ABI_V4)
22067    info_ptr->push_p = non_fixed_size != 0;
22068
22069  else if (frame_pointer_needed)
22070    info_ptr->push_p = 1;
22071
22072  else if (TARGET_XCOFF && write_symbols != NO_DEBUG)
22073    info_ptr->push_p = 1;
22074
22075  else
22076    info_ptr->push_p = non_fixed_size > (TARGET_32BIT ? 220 : 288);
22077
22078  /* Zero offsets if we're not saving those registers.  */
22079  if (info_ptr->fp_size == 0)
22080    info_ptr->fp_save_offset = 0;
22081
22082  if (info_ptr->gp_size == 0)
22083    info_ptr->gp_save_offset = 0;
22084
22085  if (! TARGET_ALTIVEC_ABI || info_ptr->altivec_size == 0)
22086    info_ptr->altivec_save_offset = 0;
22087
22088  /* Zero VRSAVE offset if not saved and restored.  */
22089  if (! TARGET_ALTIVEC_VRSAVE || info_ptr->vrsave_mask == 0)
22090    info_ptr->vrsave_save_offset = 0;
22091
22092  if (! TARGET_SPE_ABI
22093      || info_ptr->spe_64bit_regs_used == 0
22094      || info_ptr->spe_gp_size == 0)
22095    info_ptr->spe_gp_save_offset = 0;
22096
22097  if (! info_ptr->lr_save_p)
22098    info_ptr->lr_save_offset = 0;
22099
22100  if (! info_ptr->cr_save_p)
22101    info_ptr->cr_save_offset = 0;
22102
22103  return info_ptr;
22104}
22105
22106/* Return true if the current function uses any GPRs in 64-bit SIMD
22107   mode.  */
22108
22109static bool
22110spe_func_has_64bit_regs_p (void)
22111{
22112  rtx_insn *insns, *insn;
22113
22114  /* Functions that save and restore all the call-saved registers will
22115     need to save/restore the registers in 64-bits.  */
22116  if (crtl->calls_eh_return
22117      || cfun->calls_setjmp
22118      || crtl->has_nonlocal_goto)
22119    return true;
22120
22121  insns = get_insns ();
22122
22123  for (insn = NEXT_INSN (insns); insn != NULL_RTX; insn = NEXT_INSN (insn))
22124    {
22125      if (INSN_P (insn))
22126	{
22127	  rtx i;
22128
22129	  /* FIXME: This should be implemented with attributes...
22130
22131	         (set_attr "spe64" "true")....then,
22132	         if (get_spe64(insn)) return true;
22133
22134	     It's the only reliable way to do the stuff below.  */
22135
22136	  i = PATTERN (insn);
22137	  if (GET_CODE (i) == SET)
22138	    {
22139	      machine_mode mode = GET_MODE (SET_SRC (i));
22140
22141	      if (SPE_VECTOR_MODE (mode))
22142		return true;
22143	      if (TARGET_E500_DOUBLE && (mode == DFmode || mode == TFmode))
22144		return true;
22145	    }
22146	}
22147    }
22148
22149  return false;
22150}
22151
22152static void
22153debug_stack_info (rs6000_stack_t *info)
22154{
22155  const char *abi_string;
22156
22157  if (! info)
22158    info = rs6000_stack_info ();
22159
22160  fprintf (stderr, "\nStack information for function %s:\n",
22161	   ((current_function_decl && DECL_NAME (current_function_decl))
22162	    ? IDENTIFIER_POINTER (DECL_NAME (current_function_decl))
22163	    : "<unknown>"));
22164
22165  switch (info->abi)
22166    {
22167    default:		 abi_string = "Unknown";	break;
22168    case ABI_NONE:	 abi_string = "NONE";		break;
22169    case ABI_AIX:	 abi_string = "AIX";		break;
22170    case ABI_ELFv2:	 abi_string = "ELFv2";		break;
22171    case ABI_DARWIN:	 abi_string = "Darwin";		break;
22172    case ABI_V4:	 abi_string = "V.4";		break;
22173    }
22174
22175  fprintf (stderr, "\tABI                 = %5s\n", abi_string);
22176
22177  if (TARGET_ALTIVEC_ABI)
22178    fprintf (stderr, "\tALTIVEC ABI extensions enabled.\n");
22179
22180  if (TARGET_SPE_ABI)
22181    fprintf (stderr, "\tSPE ABI extensions enabled.\n");
22182
22183  if (info->first_gp_reg_save != 32)
22184    fprintf (stderr, "\tfirst_gp_reg_save   = %5d\n", info->first_gp_reg_save);
22185
22186  if (info->first_fp_reg_save != 64)
22187    fprintf (stderr, "\tfirst_fp_reg_save   = %5d\n", info->first_fp_reg_save);
22188
22189  if (info->first_altivec_reg_save <= LAST_ALTIVEC_REGNO)
22190    fprintf (stderr, "\tfirst_altivec_reg_save = %5d\n",
22191	     info->first_altivec_reg_save);
22192
22193  if (info->lr_save_p)
22194    fprintf (stderr, "\tlr_save_p           = %5d\n", info->lr_save_p);
22195
22196  if (info->cr_save_p)
22197    fprintf (stderr, "\tcr_save_p           = %5d\n", info->cr_save_p);
22198
22199  if (info->vrsave_mask)
22200    fprintf (stderr, "\tvrsave_mask         = 0x%x\n", info->vrsave_mask);
22201
22202  if (info->push_p)
22203    fprintf (stderr, "\tpush_p              = %5d\n", info->push_p);
22204
22205  if (info->calls_p)
22206    fprintf (stderr, "\tcalls_p             = %5d\n", info->calls_p);
22207
22208  if (info->gp_save_offset)
22209    fprintf (stderr, "\tgp_save_offset      = %5d\n", info->gp_save_offset);
22210
22211  if (info->fp_save_offset)
22212    fprintf (stderr, "\tfp_save_offset      = %5d\n", info->fp_save_offset);
22213
22214  if (info->altivec_save_offset)
22215    fprintf (stderr, "\taltivec_save_offset = %5d\n",
22216	     info->altivec_save_offset);
22217
22218  if (info->spe_gp_save_offset)
22219    fprintf (stderr, "\tspe_gp_save_offset  = %5d\n",
22220	     info->spe_gp_save_offset);
22221
22222  if (info->vrsave_save_offset)
22223    fprintf (stderr, "\tvrsave_save_offset  = %5d\n",
22224	     info->vrsave_save_offset);
22225
22226  if (info->lr_save_offset)
22227    fprintf (stderr, "\tlr_save_offset      = %5d\n", info->lr_save_offset);
22228
22229  if (info->cr_save_offset)
22230    fprintf (stderr, "\tcr_save_offset      = %5d\n", info->cr_save_offset);
22231
22232  if (info->varargs_save_offset)
22233    fprintf (stderr, "\tvarargs_save_offset = %5d\n", info->varargs_save_offset);
22234
22235  if (info->total_size)
22236    fprintf (stderr, "\ttotal_size          = "HOST_WIDE_INT_PRINT_DEC"\n",
22237	     info->total_size);
22238
22239  if (info->vars_size)
22240    fprintf (stderr, "\tvars_size           = "HOST_WIDE_INT_PRINT_DEC"\n",
22241	     info->vars_size);
22242
22243  if (info->parm_size)
22244    fprintf (stderr, "\tparm_size           = %5d\n", info->parm_size);
22245
22246  if (info->fixed_size)
22247    fprintf (stderr, "\tfixed_size          = %5d\n", info->fixed_size);
22248
22249  if (info->gp_size)
22250    fprintf (stderr, "\tgp_size             = %5d\n", info->gp_size);
22251
22252  if (info->spe_gp_size)
22253    fprintf (stderr, "\tspe_gp_size         = %5d\n", info->spe_gp_size);
22254
22255  if (info->fp_size)
22256    fprintf (stderr, "\tfp_size             = %5d\n", info->fp_size);
22257
22258  if (info->altivec_size)
22259    fprintf (stderr, "\taltivec_size        = %5d\n", info->altivec_size);
22260
22261  if (info->vrsave_size)
22262    fprintf (stderr, "\tvrsave_size         = %5d\n", info->vrsave_size);
22263
22264  if (info->altivec_padding_size)
22265    fprintf (stderr, "\taltivec_padding_size= %5d\n",
22266	     info->altivec_padding_size);
22267
22268  if (info->spe_padding_size)
22269    fprintf (stderr, "\tspe_padding_size    = %5d\n",
22270	     info->spe_padding_size);
22271
22272  if (info->cr_size)
22273    fprintf (stderr, "\tcr_size             = %5d\n", info->cr_size);
22274
22275  if (info->save_size)
22276    fprintf (stderr, "\tsave_size           = %5d\n", info->save_size);
22277
22278  if (info->reg_size != 4)
22279    fprintf (stderr, "\treg_size            = %5d\n", info->reg_size);
22280
22281    fprintf (stderr, "\tsave-strategy       =  %04x\n", info->savres_strategy);
22282
22283  fprintf (stderr, "\n");
22284}
22285
22286rtx
22287rs6000_return_addr (int count, rtx frame)
22288{
22289  /* Currently we don't optimize very well between prolog and body
22290     code and for PIC code the code can be actually quite bad, so
22291     don't try to be too clever here.  */
22292  if (count != 0
22293      || ((DEFAULT_ABI == ABI_V4 || DEFAULT_ABI == ABI_DARWIN) && flag_pic))
22294    {
22295      cfun->machine->ra_needs_full_frame = 1;
22296
22297      return
22298	gen_rtx_MEM
22299	  (Pmode,
22300	   memory_address
22301	   (Pmode,
22302	    plus_constant (Pmode,
22303			   copy_to_reg
22304			   (gen_rtx_MEM (Pmode,
22305					 memory_address (Pmode, frame))),
22306			   RETURN_ADDRESS_OFFSET)));
22307    }
22308
22309  cfun->machine->ra_need_lr = 1;
22310  return get_hard_reg_initial_val (Pmode, LR_REGNO);
22311}
22312
22313/* Say whether a function is a candidate for sibcall handling or not.  */
22314
22315static bool
22316rs6000_function_ok_for_sibcall (tree decl, tree exp)
22317{
22318  tree fntype;
22319
22320  if (decl)
22321    fntype = TREE_TYPE (decl);
22322  else
22323    fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (exp)));
22324
22325  /* We can't do it if the called function has more vector parameters
22326     than the current function; there's nowhere to put the VRsave code.  */
22327  if (TARGET_ALTIVEC_ABI
22328      && TARGET_ALTIVEC_VRSAVE
22329      && !(decl && decl == current_function_decl))
22330    {
22331      function_args_iterator args_iter;
22332      tree type;
22333      int nvreg = 0;
22334
22335      /* Functions with vector parameters are required to have a
22336	 prototype, so the argument type info must be available
22337	 here.  */
22338      FOREACH_FUNCTION_ARGS(fntype, type, args_iter)
22339	if (TREE_CODE (type) == VECTOR_TYPE
22340	    && ALTIVEC_OR_VSX_VECTOR_MODE (TYPE_MODE (type)))
22341	  nvreg++;
22342
22343      FOREACH_FUNCTION_ARGS(TREE_TYPE (current_function_decl), type, args_iter)
22344	if (TREE_CODE (type) == VECTOR_TYPE
22345	    && ALTIVEC_OR_VSX_VECTOR_MODE (TYPE_MODE (type)))
22346	  nvreg--;
22347
22348      if (nvreg > 0)
22349	return false;
22350    }
22351
22352  /* Under the AIX or ELFv2 ABIs we can't allow calls to non-local
22353     functions, because the callee may have a different TOC pointer to
22354     the caller and there's no way to ensure we restore the TOC when
22355     we return.  With the secure-plt SYSV ABI we can't make non-local
22356     calls when -fpic/PIC because the plt call stubs use r30.  */
22357  if (DEFAULT_ABI == ABI_DARWIN
22358      || ((DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
22359	  && decl
22360	  && !DECL_EXTERNAL (decl)
22361	  && !DECL_WEAK (decl)
22362	  && (*targetm.binds_local_p) (decl))
22363      || (DEFAULT_ABI == ABI_V4
22364	  && (!TARGET_SECURE_PLT
22365	      || !flag_pic
22366	      || (decl
22367		  && (*targetm.binds_local_p) (decl)))))
22368    {
22369      tree attr_list = TYPE_ATTRIBUTES (fntype);
22370
22371      if (!lookup_attribute ("longcall", attr_list)
22372	  || lookup_attribute ("shortcall", attr_list))
22373	return true;
22374    }
22375
22376  return false;
22377}
22378
22379static int
22380rs6000_ra_ever_killed (void)
22381{
22382  rtx_insn *top;
22383  rtx reg;
22384  rtx_insn *insn;
22385
22386  if (cfun->is_thunk)
22387    return 0;
22388
22389  if (cfun->machine->lr_save_state)
22390    return cfun->machine->lr_save_state - 1;
22391
22392  /* regs_ever_live has LR marked as used if any sibcalls are present,
22393     but this should not force saving and restoring in the
22394     pro/epilogue.  Likewise, reg_set_between_p thinks a sibcall
22395     clobbers LR, so that is inappropriate.  */
22396
22397  /* Also, the prologue can generate a store into LR that
22398     doesn't really count, like this:
22399
22400        move LR->R0
22401        bcl to set PIC register
22402        move LR->R31
22403        move R0->LR
22404
22405     When we're called from the epilogue, we need to avoid counting
22406     this as a store.  */
22407
22408  push_topmost_sequence ();
22409  top = get_insns ();
22410  pop_topmost_sequence ();
22411  reg = gen_rtx_REG (Pmode, LR_REGNO);
22412
22413  for (insn = NEXT_INSN (top); insn != NULL_RTX; insn = NEXT_INSN (insn))
22414    {
22415      if (INSN_P (insn))
22416	{
22417	  if (CALL_P (insn))
22418	    {
22419	      if (!SIBLING_CALL_P (insn))
22420		return 1;
22421	    }
22422	  else if (find_regno_note (insn, REG_INC, LR_REGNO))
22423	    return 1;
22424	  else if (set_of (reg, insn) != NULL_RTX
22425		   && !prologue_epilogue_contains (insn))
22426	    return 1;
22427    	}
22428    }
22429  return 0;
22430}
22431
22432/* Emit instructions needed to load the TOC register.
22433   This is only needed when TARGET_TOC, TARGET_MINIMAL_TOC, and there is
22434   a constant pool; or for SVR4 -fpic.  */
22435
22436void
22437rs6000_emit_load_toc_table (int fromprolog)
22438{
22439  rtx dest;
22440  dest = gen_rtx_REG (Pmode, RS6000_PIC_OFFSET_TABLE_REGNUM);
22441
22442  if (TARGET_ELF && TARGET_SECURE_PLT && DEFAULT_ABI == ABI_V4 && flag_pic)
22443    {
22444      char buf[30];
22445      rtx lab, tmp1, tmp2, got;
22446
22447      lab = gen_label_rtx ();
22448      ASM_GENERATE_INTERNAL_LABEL (buf, "L", CODE_LABEL_NUMBER (lab));
22449      lab = gen_rtx_SYMBOL_REF (Pmode, ggc_strdup (buf));
22450      if (flag_pic == 2)
22451	got = gen_rtx_SYMBOL_REF (Pmode, toc_label_name);
22452      else
22453	got = rs6000_got_sym ();
22454      tmp1 = tmp2 = dest;
22455      if (!fromprolog)
22456	{
22457	  tmp1 = gen_reg_rtx (Pmode);
22458	  tmp2 = gen_reg_rtx (Pmode);
22459	}
22460      emit_insn (gen_load_toc_v4_PIC_1 (lab));
22461      emit_move_insn (tmp1, gen_rtx_REG (Pmode, LR_REGNO));
22462      emit_insn (gen_load_toc_v4_PIC_3b (tmp2, tmp1, got, lab));
22463      emit_insn (gen_load_toc_v4_PIC_3c (dest, tmp2, got, lab));
22464    }
22465  else if (TARGET_ELF && DEFAULT_ABI == ABI_V4 && flag_pic == 1)
22466    {
22467      emit_insn (gen_load_toc_v4_pic_si ());
22468      emit_move_insn (dest, gen_rtx_REG (Pmode, LR_REGNO));
22469    }
22470  else if (TARGET_ELF && DEFAULT_ABI == ABI_V4 && flag_pic == 2)
22471    {
22472      char buf[30];
22473      rtx temp0 = (fromprolog
22474		   ? gen_rtx_REG (Pmode, 0)
22475		   : gen_reg_rtx (Pmode));
22476
22477      if (fromprolog)
22478	{
22479	  rtx symF, symL;
22480
22481	  ASM_GENERATE_INTERNAL_LABEL (buf, "LCF", rs6000_pic_labelno);
22482	  symF = gen_rtx_SYMBOL_REF (Pmode, ggc_strdup (buf));
22483
22484	  ASM_GENERATE_INTERNAL_LABEL (buf, "LCL", rs6000_pic_labelno);
22485	  symL = gen_rtx_SYMBOL_REF (Pmode, ggc_strdup (buf));
22486
22487	  emit_insn (gen_load_toc_v4_PIC_1 (symF));
22488	  emit_move_insn (dest, gen_rtx_REG (Pmode, LR_REGNO));
22489	  emit_insn (gen_load_toc_v4_PIC_2 (temp0, dest, symL, symF));
22490	}
22491      else
22492	{
22493	  rtx tocsym, lab;
22494
22495	  tocsym = gen_rtx_SYMBOL_REF (Pmode, toc_label_name);
22496	  lab = gen_label_rtx ();
22497	  emit_insn (gen_load_toc_v4_PIC_1b (tocsym, lab));
22498	  emit_move_insn (dest, gen_rtx_REG (Pmode, LR_REGNO));
22499	  if (TARGET_LINK_STACK)
22500	    emit_insn (gen_addsi3 (dest, dest, GEN_INT (4)));
22501	  emit_move_insn (temp0, gen_rtx_MEM (Pmode, dest));
22502	}
22503      emit_insn (gen_addsi3 (dest, temp0, dest));
22504    }
22505  else if (TARGET_ELF && !TARGET_AIX && flag_pic == 0 && TARGET_MINIMAL_TOC)
22506    {
22507      /* This is for AIX code running in non-PIC ELF32.  */
22508      char buf[30];
22509      rtx realsym;
22510      ASM_GENERATE_INTERNAL_LABEL (buf, "LCTOC", 1);
22511      realsym = gen_rtx_SYMBOL_REF (Pmode, ggc_strdup (buf));
22512
22513      emit_insn (gen_elf_high (dest, realsym));
22514      emit_insn (gen_elf_low (dest, dest, realsym));
22515    }
22516  else
22517    {
22518      gcc_assert (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2);
22519
22520      if (TARGET_32BIT)
22521	emit_insn (gen_load_toc_aix_si (dest));
22522      else
22523	emit_insn (gen_load_toc_aix_di (dest));
22524    }
22525}
22526
22527/* Emit instructions to restore the link register after determining where
22528   its value has been stored.  */
22529
22530void
22531rs6000_emit_eh_reg_restore (rtx source, rtx scratch)
22532{
22533  rs6000_stack_t *info = rs6000_stack_info ();
22534  rtx operands[2];
22535
22536  operands[0] = source;
22537  operands[1] = scratch;
22538
22539  if (info->lr_save_p)
22540    {
22541      rtx frame_rtx = stack_pointer_rtx;
22542      HOST_WIDE_INT sp_offset = 0;
22543      rtx tmp;
22544
22545      if (frame_pointer_needed
22546	  || cfun->calls_alloca
22547	  || info->total_size > 32767)
22548	{
22549	  tmp = gen_frame_mem (Pmode, frame_rtx);
22550	  emit_move_insn (operands[1], tmp);
22551	  frame_rtx = operands[1];
22552	}
22553      else if (info->push_p)
22554	sp_offset = info->total_size;
22555
22556      tmp = plus_constant (Pmode, frame_rtx,
22557			   info->lr_save_offset + sp_offset);
22558      tmp = gen_frame_mem (Pmode, tmp);
22559      emit_move_insn (tmp, operands[0]);
22560    }
22561  else
22562    emit_move_insn (gen_rtx_REG (Pmode, LR_REGNO), operands[0]);
22563
22564  /* Freeze lr_save_p.  We've just emitted rtl that depends on the
22565     state of lr_save_p so any change from here on would be a bug.  In
22566     particular, stop rs6000_ra_ever_killed from considering the SET
22567     of lr we may have added just above.  */
22568  cfun->machine->lr_save_state = info->lr_save_p + 1;
22569}
22570
22571static GTY(()) alias_set_type set = -1;
22572
22573alias_set_type
22574get_TOC_alias_set (void)
22575{
22576  if (set == -1)
22577    set = new_alias_set ();
22578  return set;
22579}
22580
22581/* This returns nonzero if the current function uses the TOC.  This is
22582   determined by the presence of (use (unspec ... UNSPEC_TOC)), which
22583   is generated by the ABI_V4 load_toc_* patterns.  */
22584#if TARGET_ELF
22585static int
22586uses_TOC (void)
22587{
22588  rtx_insn *insn;
22589
22590  for (insn = get_insns (); insn; insn = NEXT_INSN (insn))
22591    if (INSN_P (insn))
22592      {
22593	rtx pat = PATTERN (insn);
22594	int i;
22595
22596	if (GET_CODE (pat) == PARALLEL)
22597	  for (i = 0; i < XVECLEN (pat, 0); i++)
22598	    {
22599	      rtx sub = XVECEXP (pat, 0, i);
22600	      if (GET_CODE (sub) == USE)
22601		{
22602		  sub = XEXP (sub, 0);
22603		  if (GET_CODE (sub) == UNSPEC
22604		      && XINT (sub, 1) == UNSPEC_TOC)
22605		    return 1;
22606		}
22607	    }
22608      }
22609  return 0;
22610}
22611#endif
22612
22613rtx
22614create_TOC_reference (rtx symbol, rtx largetoc_reg)
22615{
22616  rtx tocrel, tocreg, hi;
22617
22618  if (TARGET_DEBUG_ADDR)
22619    {
22620      if (GET_CODE (symbol) == SYMBOL_REF)
22621	fprintf (stderr, "\ncreate_TOC_reference, (symbol_ref %s)\n",
22622		 XSTR (symbol, 0));
22623      else
22624	{
22625	  fprintf (stderr, "\ncreate_TOC_reference, code %s:\n",
22626		   GET_RTX_NAME (GET_CODE (symbol)));
22627	  debug_rtx (symbol);
22628	}
22629    }
22630
22631  if (!can_create_pseudo_p ())
22632    df_set_regs_ever_live (TOC_REGISTER, true);
22633
22634  tocreg = gen_rtx_REG (Pmode, TOC_REGISTER);
22635  tocrel = gen_rtx_UNSPEC (Pmode, gen_rtvec (2, symbol, tocreg), UNSPEC_TOCREL);
22636  if (TARGET_CMODEL == CMODEL_SMALL || can_create_pseudo_p ())
22637    return tocrel;
22638
22639  hi = gen_rtx_HIGH (Pmode, copy_rtx (tocrel));
22640  if (largetoc_reg != NULL)
22641    {
22642      emit_move_insn (largetoc_reg, hi);
22643      hi = largetoc_reg;
22644    }
22645  return gen_rtx_LO_SUM (Pmode, hi, tocrel);
22646}
22647
22648/* Issue assembly directives that create a reference to the given DWARF
22649   FRAME_TABLE_LABEL from the current function section.  */
22650void
22651rs6000_aix_asm_output_dwarf_table_ref (char * frame_table_label)
22652{
22653  fprintf (asm_out_file, "\t.ref %s\n",
22654	   (* targetm.strip_name_encoding) (frame_table_label));
22655}
22656
22657/* This ties together stack memory (MEM with an alias set of frame_alias_set)
22658   and the change to the stack pointer.  */
22659
22660static void
22661rs6000_emit_stack_tie (rtx fp, bool hard_frame_needed)
22662{
22663  rtvec p;
22664  int i;
22665  rtx regs[3];
22666
22667  i = 0;
22668  regs[i++] = gen_rtx_REG (Pmode, STACK_POINTER_REGNUM);
22669  if (hard_frame_needed)
22670    regs[i++] = gen_rtx_REG (Pmode, HARD_FRAME_POINTER_REGNUM);
22671  if (!(REGNO (fp) == STACK_POINTER_REGNUM
22672	|| (hard_frame_needed
22673	    && REGNO (fp) == HARD_FRAME_POINTER_REGNUM)))
22674    regs[i++] = fp;
22675
22676  p = rtvec_alloc (i);
22677  while (--i >= 0)
22678    {
22679      rtx mem = gen_frame_mem (BLKmode, regs[i]);
22680      RTVEC_ELT (p, i) = gen_rtx_SET (VOIDmode, mem, const0_rtx);
22681    }
22682
22683  emit_insn (gen_stack_tie (gen_rtx_PARALLEL (VOIDmode, p)));
22684}
22685
22686/* Emit the correct code for allocating stack space, as insns.
22687   If COPY_REG, make sure a copy of the old frame is left there.
22688   The generated code may use hard register 0 as a temporary.  */
22689
22690static void
22691rs6000_emit_allocate_stack (HOST_WIDE_INT size, rtx copy_reg, int copy_off)
22692{
22693  rtx_insn *insn;
22694  rtx stack_reg = gen_rtx_REG (Pmode, STACK_POINTER_REGNUM);
22695  rtx tmp_reg = gen_rtx_REG (Pmode, 0);
22696  rtx todec = gen_int_mode (-size, Pmode);
22697  rtx par, set, mem;
22698
22699  if (INTVAL (todec) != -size)
22700    {
22701      warning (0, "stack frame too large");
22702      emit_insn (gen_trap ());
22703      return;
22704    }
22705
22706  if (crtl->limit_stack)
22707    {
22708      if (REG_P (stack_limit_rtx)
22709	  && REGNO (stack_limit_rtx) > 1
22710	  && REGNO (stack_limit_rtx) <= 31)
22711	{
22712	  emit_insn (gen_add3_insn (tmp_reg, stack_limit_rtx, GEN_INT (size)));
22713	  emit_insn (gen_cond_trap (LTU, stack_reg, tmp_reg,
22714				    const0_rtx));
22715	}
22716      else if (GET_CODE (stack_limit_rtx) == SYMBOL_REF
22717	       && TARGET_32BIT
22718	       && DEFAULT_ABI == ABI_V4)
22719	{
22720	  rtx toload = gen_rtx_CONST (VOIDmode,
22721				      gen_rtx_PLUS (Pmode,
22722						    stack_limit_rtx,
22723						    GEN_INT (size)));
22724
22725	  emit_insn (gen_elf_high (tmp_reg, toload));
22726	  emit_insn (gen_elf_low (tmp_reg, tmp_reg, toload));
22727	  emit_insn (gen_cond_trap (LTU, stack_reg, tmp_reg,
22728				    const0_rtx));
22729	}
22730      else
22731	warning (0, "stack limit expression is not supported");
22732    }
22733
22734  if (copy_reg)
22735    {
22736      if (copy_off != 0)
22737	emit_insn (gen_add3_insn (copy_reg, stack_reg, GEN_INT (copy_off)));
22738      else
22739	emit_move_insn (copy_reg, stack_reg);
22740    }
22741
22742  if (size > 32767)
22743    {
22744      /* Need a note here so that try_split doesn't get confused.  */
22745      if (get_last_insn () == NULL_RTX)
22746	emit_note (NOTE_INSN_DELETED);
22747      insn = emit_move_insn (tmp_reg, todec);
22748      try_split (PATTERN (insn), insn, 0);
22749      todec = tmp_reg;
22750    }
22751
22752  insn = emit_insn (TARGET_32BIT
22753		    ? gen_movsi_update_stack (stack_reg, stack_reg,
22754					todec, stack_reg)
22755		    : gen_movdi_di_update_stack (stack_reg, stack_reg,
22756					   todec, stack_reg));
22757  /* Since we didn't use gen_frame_mem to generate the MEM, grab
22758     it now and set the alias set/attributes. The above gen_*_update
22759     calls will generate a PARALLEL with the MEM set being the first
22760     operation. */
22761  par = PATTERN (insn);
22762  gcc_assert (GET_CODE (par) == PARALLEL);
22763  set = XVECEXP (par, 0, 0);
22764  gcc_assert (GET_CODE (set) == SET);
22765  mem = SET_DEST (set);
22766  gcc_assert (MEM_P (mem));
22767  MEM_NOTRAP_P (mem) = 1;
22768  set_mem_alias_set (mem, get_frame_alias_set ());
22769
22770  RTX_FRAME_RELATED_P (insn) = 1;
22771  add_reg_note (insn, REG_FRAME_RELATED_EXPR,
22772		gen_rtx_SET (VOIDmode, stack_reg,
22773			     gen_rtx_PLUS (Pmode, stack_reg,
22774					   GEN_INT (-size))));
22775}
22776
22777#define PROBE_INTERVAL (1 << STACK_CHECK_PROBE_INTERVAL_EXP)
22778
22779#if PROBE_INTERVAL > 32768
22780#error Cannot use indexed addressing mode for stack probing
22781#endif
22782
22783/* Emit code to probe a range of stack addresses from FIRST to FIRST+SIZE,
22784   inclusive.  These are offsets from the current stack pointer.  */
22785
22786static void
22787rs6000_emit_probe_stack_range (HOST_WIDE_INT first, HOST_WIDE_INT size)
22788{
22789  /* See if we have a constant small number of probes to generate.  If so,
22790     that's the easy case.  */
22791  if (first + size <= 32768)
22792    {
22793      HOST_WIDE_INT i;
22794
22795      /* Probe at FIRST + N * PROBE_INTERVAL for values of N from 1 until
22796	 it exceeds SIZE.  If only one probe is needed, this will not
22797	 generate any code.  Then probe at FIRST + SIZE.  */
22798      for (i = PROBE_INTERVAL; i < size; i += PROBE_INTERVAL)
22799	emit_stack_probe (plus_constant (Pmode, stack_pointer_rtx,
22800					 -(first + i)));
22801
22802      emit_stack_probe (plus_constant (Pmode, stack_pointer_rtx,
22803				       -(first + size)));
22804    }
22805
22806  /* Otherwise, do the same as above, but in a loop.  Note that we must be
22807     extra careful with variables wrapping around because we might be at
22808     the very top (or the very bottom) of the address space and we have
22809     to be able to handle this case properly; in particular, we use an
22810     equality test for the loop condition.  */
22811  else
22812    {
22813      HOST_WIDE_INT rounded_size;
22814      rtx r12 = gen_rtx_REG (Pmode, 12);
22815      rtx r0 = gen_rtx_REG (Pmode, 0);
22816
22817      /* Sanity check for the addressing mode we're going to use.  */
22818      gcc_assert (first <= 32768);
22819
22820      /* Step 1: round SIZE to the previous multiple of the interval.  */
22821
22822      rounded_size = size & -PROBE_INTERVAL;
22823
22824
22825      /* Step 2: compute initial and final value of the loop counter.  */
22826
22827      /* TEST_ADDR = SP + FIRST.  */
22828      emit_insn (gen_rtx_SET (VOIDmode, r12,
22829			      plus_constant (Pmode, stack_pointer_rtx,
22830					     -first)));
22831
22832      /* LAST_ADDR = SP + FIRST + ROUNDED_SIZE.  */
22833      if (rounded_size > 32768)
22834	{
22835	  emit_move_insn (r0, GEN_INT (-rounded_size));
22836	  emit_insn (gen_rtx_SET (VOIDmode, r0,
22837				  gen_rtx_PLUS (Pmode, r12, r0)));
22838	}
22839      else
22840	emit_insn (gen_rtx_SET (VOIDmode, r0,
22841			        plus_constant (Pmode, r12, -rounded_size)));
22842
22843
22844      /* Step 3: the loop
22845
22846	 while (TEST_ADDR != LAST_ADDR)
22847	   {
22848	     TEST_ADDR = TEST_ADDR + PROBE_INTERVAL
22849	     probe at TEST_ADDR
22850	   }
22851
22852	 probes at FIRST + N * PROBE_INTERVAL for values of N from 1
22853	 until it is equal to ROUNDED_SIZE.  */
22854
22855      if (TARGET_64BIT)
22856	emit_insn (gen_probe_stack_rangedi (r12, r12, r0));
22857      else
22858	emit_insn (gen_probe_stack_rangesi (r12, r12, r0));
22859
22860
22861      /* Step 4: probe at FIRST + SIZE if we cannot assert at compile-time
22862	 that SIZE is equal to ROUNDED_SIZE.  */
22863
22864      if (size != rounded_size)
22865	emit_stack_probe (plus_constant (Pmode, r12, rounded_size - size));
22866    }
22867}
22868
22869/* Probe a range of stack addresses from REG1 to REG2 inclusive.  These are
22870   absolute addresses.  */
22871
22872const char *
22873output_probe_stack_range (rtx reg1, rtx reg2)
22874{
22875  static int labelno = 0;
22876  char loop_lab[32], end_lab[32];
22877  rtx xops[2];
22878
22879  ASM_GENERATE_INTERNAL_LABEL (loop_lab, "LPSRL", labelno);
22880  ASM_GENERATE_INTERNAL_LABEL (end_lab, "LPSRE", labelno++);
22881
22882  ASM_OUTPUT_INTERNAL_LABEL (asm_out_file, loop_lab);
22883
22884  /* Jump to END_LAB if TEST_ADDR == LAST_ADDR.  */
22885  xops[0] = reg1;
22886  xops[1] = reg2;
22887  if (TARGET_64BIT)
22888    output_asm_insn ("cmpd 0,%0,%1", xops);
22889  else
22890    output_asm_insn ("cmpw 0,%0,%1", xops);
22891
22892  fputs ("\tbeq 0,", asm_out_file);
22893  assemble_name_raw (asm_out_file, end_lab);
22894  fputc ('\n', asm_out_file);
22895
22896  /* TEST_ADDR = TEST_ADDR + PROBE_INTERVAL.  */
22897  xops[1] = GEN_INT (-PROBE_INTERVAL);
22898  output_asm_insn ("addi %0,%0,%1", xops);
22899
22900  /* Probe at TEST_ADDR and branch.  */
22901  xops[1] = gen_rtx_REG (Pmode, 0);
22902  output_asm_insn ("stw %1,0(%0)", xops);
22903  fprintf (asm_out_file, "\tb ");
22904  assemble_name_raw (asm_out_file, loop_lab);
22905  fputc ('\n', asm_out_file);
22906
22907  ASM_OUTPUT_INTERNAL_LABEL (asm_out_file, end_lab);
22908
22909  return "";
22910}
22911
22912/* Add to 'insn' a note which is PATTERN (INSN) but with REG replaced
22913   with (plus:P (reg 1) VAL), and with REG2 replaced with RREG if REG2
22914   is not NULL.  It would be nice if dwarf2out_frame_debug_expr could
22915   deduce these equivalences by itself so it wasn't necessary to hold
22916   its hand so much.  Don't be tempted to always supply d2_f_d_e with
22917   the actual cfa register, ie. r31 when we are using a hard frame
22918   pointer.  That fails when saving regs off r1, and sched moves the
22919   r31 setup past the reg saves.  */
22920
22921static rtx
22922rs6000_frame_related (rtx insn, rtx reg, HOST_WIDE_INT val,
22923		      rtx reg2, rtx rreg)
22924{
22925  rtx real, temp;
22926
22927  if (REGNO (reg) == STACK_POINTER_REGNUM && reg2 == NULL_RTX)
22928    {
22929      /* No need for any replacement.  Just set RTX_FRAME_RELATED_P.  */
22930      int i;
22931
22932      gcc_checking_assert (val == 0);
22933      real = PATTERN (insn);
22934      if (GET_CODE (real) == PARALLEL)
22935	for (i = 0; i < XVECLEN (real, 0); i++)
22936	  if (GET_CODE (XVECEXP (real, 0, i)) == SET)
22937	    {
22938	      rtx set = XVECEXP (real, 0, i);
22939
22940	      RTX_FRAME_RELATED_P (set) = 1;
22941	    }
22942      RTX_FRAME_RELATED_P (insn) = 1;
22943      return insn;
22944    }
22945
22946  /* copy_rtx will not make unique copies of registers, so we need to
22947     ensure we don't have unwanted sharing here.  */
22948  if (reg == reg2)
22949    reg = gen_raw_REG (GET_MODE (reg), REGNO (reg));
22950
22951  if (reg == rreg)
22952    reg = gen_raw_REG (GET_MODE (reg), REGNO (reg));
22953
22954  real = copy_rtx (PATTERN (insn));
22955
22956  if (reg2 != NULL_RTX)
22957    real = replace_rtx (real, reg2, rreg);
22958
22959  if (REGNO (reg) == STACK_POINTER_REGNUM)
22960    gcc_checking_assert (val == 0);
22961  else
22962    real = replace_rtx (real, reg,
22963			gen_rtx_PLUS (Pmode, gen_rtx_REG (Pmode,
22964							  STACK_POINTER_REGNUM),
22965				      GEN_INT (val)));
22966
22967  /* We expect that 'real' is either a SET or a PARALLEL containing
22968     SETs (and possibly other stuff).  In a PARALLEL, all the SETs
22969     are important so they all have to be marked RTX_FRAME_RELATED_P.  */
22970
22971  if (GET_CODE (real) == SET)
22972    {
22973      rtx set = real;
22974
22975      temp = simplify_rtx (SET_SRC (set));
22976      if (temp)
22977	SET_SRC (set) = temp;
22978      temp = simplify_rtx (SET_DEST (set));
22979      if (temp)
22980	SET_DEST (set) = temp;
22981      if (GET_CODE (SET_DEST (set)) == MEM)
22982	{
22983	  temp = simplify_rtx (XEXP (SET_DEST (set), 0));
22984	  if (temp)
22985	    XEXP (SET_DEST (set), 0) = temp;
22986	}
22987    }
22988  else
22989    {
22990      int i;
22991
22992      gcc_assert (GET_CODE (real) == PARALLEL);
22993      for (i = 0; i < XVECLEN (real, 0); i++)
22994	if (GET_CODE (XVECEXP (real, 0, i)) == SET)
22995	  {
22996	    rtx set = XVECEXP (real, 0, i);
22997
22998	    temp = simplify_rtx (SET_SRC (set));
22999	    if (temp)
23000	      SET_SRC (set) = temp;
23001	    temp = simplify_rtx (SET_DEST (set));
23002	    if (temp)
23003	      SET_DEST (set) = temp;
23004	    if (GET_CODE (SET_DEST (set)) == MEM)
23005	      {
23006		temp = simplify_rtx (XEXP (SET_DEST (set), 0));
23007		if (temp)
23008		  XEXP (SET_DEST (set), 0) = temp;
23009	      }
23010	    RTX_FRAME_RELATED_P (set) = 1;
23011	  }
23012    }
23013
23014  RTX_FRAME_RELATED_P (insn) = 1;
23015  add_reg_note (insn, REG_FRAME_RELATED_EXPR, real);
23016
23017  return insn;
23018}
23019
23020/* Returns an insn that has a vrsave set operation with the
23021   appropriate CLOBBERs.  */
23022
23023static rtx
23024generate_set_vrsave (rtx reg, rs6000_stack_t *info, int epiloguep)
23025{
23026  int nclobs, i;
23027  rtx insn, clobs[TOTAL_ALTIVEC_REGS + 1];
23028  rtx vrsave = gen_rtx_REG (SImode, VRSAVE_REGNO);
23029
23030  clobs[0]
23031    = gen_rtx_SET (VOIDmode,
23032		   vrsave,
23033		   gen_rtx_UNSPEC_VOLATILE (SImode,
23034					    gen_rtvec (2, reg, vrsave),
23035					    UNSPECV_SET_VRSAVE));
23036
23037  nclobs = 1;
23038
23039  /* We need to clobber the registers in the mask so the scheduler
23040     does not move sets to VRSAVE before sets of AltiVec registers.
23041
23042     However, if the function receives nonlocal gotos, reload will set
23043     all call saved registers live.  We will end up with:
23044
23045     	(set (reg 999) (mem))
23046	(parallel [ (set (reg vrsave) (unspec blah))
23047		    (clobber (reg 999))])
23048
23049     The clobber will cause the store into reg 999 to be dead, and
23050     flow will attempt to delete an epilogue insn.  In this case, we
23051     need an unspec use/set of the register.  */
23052
23053  for (i = FIRST_ALTIVEC_REGNO; i <= LAST_ALTIVEC_REGNO; ++i)
23054    if (info->vrsave_mask & ALTIVEC_REG_BIT (i))
23055      {
23056	if (!epiloguep || call_used_regs [i])
23057	  clobs[nclobs++] = gen_rtx_CLOBBER (VOIDmode,
23058					     gen_rtx_REG (V4SImode, i));
23059	else
23060	  {
23061	    rtx reg = gen_rtx_REG (V4SImode, i);
23062
23063	    clobs[nclobs++]
23064	      = gen_rtx_SET (VOIDmode,
23065			     reg,
23066			     gen_rtx_UNSPEC (V4SImode,
23067					     gen_rtvec (1, reg), 27));
23068	  }
23069      }
23070
23071  insn = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (nclobs));
23072
23073  for (i = 0; i < nclobs; ++i)
23074    XVECEXP (insn, 0, i) = clobs[i];
23075
23076  return insn;
23077}
23078
23079static rtx
23080gen_frame_set (rtx reg, rtx frame_reg, int offset, bool store)
23081{
23082  rtx addr, mem;
23083
23084  addr = gen_rtx_PLUS (Pmode, frame_reg, GEN_INT (offset));
23085  mem = gen_frame_mem (GET_MODE (reg), addr);
23086  return gen_rtx_SET (VOIDmode, store ? mem : reg, store ? reg : mem);
23087}
23088
23089static rtx
23090gen_frame_load (rtx reg, rtx frame_reg, int offset)
23091{
23092  return gen_frame_set (reg, frame_reg, offset, false);
23093}
23094
23095static rtx
23096gen_frame_store (rtx reg, rtx frame_reg, int offset)
23097{
23098  return gen_frame_set (reg, frame_reg, offset, true);
23099}
23100
23101/* Save a register into the frame, and emit RTX_FRAME_RELATED_P notes.
23102   Save REGNO into [FRAME_REG + OFFSET] in mode MODE.  */
23103
23104static rtx
23105emit_frame_save (rtx frame_reg, machine_mode mode,
23106		 unsigned int regno, int offset, HOST_WIDE_INT frame_reg_to_sp)
23107{
23108  rtx reg, insn;
23109
23110  /* Some cases that need register indexed addressing.  */
23111  gcc_checking_assert (!((TARGET_ALTIVEC_ABI && ALTIVEC_VECTOR_MODE (mode))
23112			 || (TARGET_VSX && ALTIVEC_OR_VSX_VECTOR_MODE (mode))
23113			 || (TARGET_E500_DOUBLE && mode == DFmode)
23114			 || (TARGET_SPE_ABI
23115			     && SPE_VECTOR_MODE (mode)
23116			     && !SPE_CONST_OFFSET_OK (offset))));
23117
23118  reg = gen_rtx_REG (mode, regno);
23119  insn = emit_insn (gen_frame_store (reg, frame_reg, offset));
23120  return rs6000_frame_related (insn, frame_reg, frame_reg_to_sp,
23121			       NULL_RTX, NULL_RTX);
23122}
23123
23124/* Emit an offset memory reference suitable for a frame store, while
23125   converting to a valid addressing mode.  */
23126
23127static rtx
23128gen_frame_mem_offset (machine_mode mode, rtx reg, int offset)
23129{
23130  rtx int_rtx, offset_rtx;
23131
23132  int_rtx = GEN_INT (offset);
23133
23134  if ((TARGET_SPE_ABI && SPE_VECTOR_MODE (mode) && !SPE_CONST_OFFSET_OK (offset))
23135      || (TARGET_E500_DOUBLE && mode == DFmode))
23136    {
23137      offset_rtx = gen_rtx_REG (Pmode, FIXED_SCRATCH);
23138      emit_move_insn (offset_rtx, int_rtx);
23139    }
23140  else
23141    offset_rtx = int_rtx;
23142
23143  return gen_frame_mem (mode, gen_rtx_PLUS (Pmode, reg, offset_rtx));
23144}
23145
23146#ifndef TARGET_FIX_AND_CONTINUE
23147#define TARGET_FIX_AND_CONTINUE 0
23148#endif
23149
23150/* It's really GPR 13 or 14, FPR 14 and VR 20.  We need the smallest.  */
23151#define FIRST_SAVRES_REGISTER FIRST_SAVED_GP_REGNO
23152#define LAST_SAVRES_REGISTER 31
23153#define N_SAVRES_REGISTERS (LAST_SAVRES_REGISTER - FIRST_SAVRES_REGISTER + 1)
23154
23155enum {
23156  SAVRES_LR = 0x1,
23157  SAVRES_SAVE = 0x2,
23158  SAVRES_REG = 0x0c,
23159  SAVRES_GPR = 0,
23160  SAVRES_FPR = 4,
23161  SAVRES_VR  = 8
23162};
23163
23164static GTY(()) rtx savres_routine_syms[N_SAVRES_REGISTERS][12];
23165
23166/* Temporary holding space for an out-of-line register save/restore
23167   routine name.  */
23168static char savres_routine_name[30];
23169
23170/* Return the name for an out-of-line register save/restore routine.
23171   We are saving/restoring GPRs if GPR is true.  */
23172
23173static char *
23174rs6000_savres_routine_name (rs6000_stack_t *info, int regno, int sel)
23175{
23176  const char *prefix = "";
23177  const char *suffix = "";
23178
23179  /* Different targets are supposed to define
23180     {SAVE,RESTORE}_FP_{PREFIX,SUFFIX} with the idea that the needed
23181     routine name could be defined with:
23182
23183     sprintf (name, "%s%d%s", SAVE_FP_PREFIX, regno, SAVE_FP_SUFFIX)
23184
23185     This is a nice idea in practice, but in reality, things are
23186     complicated in several ways:
23187
23188     - ELF targets have save/restore routines for GPRs.
23189
23190     - SPE targets use different prefixes for 32/64-bit registers, and
23191       neither of them fit neatly in the FOO_{PREFIX,SUFFIX} regimen.
23192
23193     - PPC64 ELF targets have routines for save/restore of GPRs that
23194       differ in what they do with the link register, so having a set
23195       prefix doesn't work.  (We only use one of the save routines at
23196       the moment, though.)
23197
23198     - PPC32 elf targets have "exit" versions of the restore routines
23199       that restore the link register and can save some extra space.
23200       These require an extra suffix.  (There are also "tail" versions
23201       of the restore routines and "GOT" versions of the save routines,
23202       but we don't generate those at present.  Same problems apply,
23203       though.)
23204
23205     We deal with all this by synthesizing our own prefix/suffix and
23206     using that for the simple sprintf call shown above.  */
23207  if (TARGET_SPE)
23208    {
23209      /* No floating point saves on the SPE.  */
23210      gcc_assert ((sel & SAVRES_REG) == SAVRES_GPR);
23211
23212      if ((sel & SAVRES_SAVE))
23213	prefix = info->spe_64bit_regs_used ? "_save64gpr_" : "_save32gpr_";
23214      else
23215	prefix = info->spe_64bit_regs_used ? "_rest64gpr_" : "_rest32gpr_";
23216
23217      if ((sel & SAVRES_LR))
23218	suffix = "_x";
23219    }
23220  else if (DEFAULT_ABI == ABI_V4)
23221    {
23222      if (TARGET_64BIT)
23223	goto aix_names;
23224
23225      if ((sel & SAVRES_REG) == SAVRES_GPR)
23226	prefix = (sel & SAVRES_SAVE) ? "_savegpr_" : "_restgpr_";
23227      else if ((sel & SAVRES_REG) == SAVRES_FPR)
23228	prefix = (sel & SAVRES_SAVE) ? "_savefpr_" : "_restfpr_";
23229      else if ((sel & SAVRES_REG) == SAVRES_VR)
23230	prefix = (sel & SAVRES_SAVE) ? "_savevr_" : "_restvr_";
23231      else
23232	abort ();
23233
23234      if ((sel & SAVRES_LR))
23235	suffix = "_x";
23236    }
23237  else if (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
23238    {
23239#if !defined (POWERPC_LINUX) && !defined (POWERPC_FREEBSD)
23240      /* No out-of-line save/restore routines for GPRs on AIX.  */
23241      gcc_assert (!TARGET_AIX || (sel & SAVRES_REG) != SAVRES_GPR);
23242#endif
23243
23244    aix_names:
23245      if ((sel & SAVRES_REG) == SAVRES_GPR)
23246	prefix = ((sel & SAVRES_SAVE)
23247		  ? ((sel & SAVRES_LR) ? "_savegpr0_" : "_savegpr1_")
23248		  : ((sel & SAVRES_LR) ? "_restgpr0_" : "_restgpr1_"));
23249      else if ((sel & SAVRES_REG) == SAVRES_FPR)
23250	{
23251#if defined (POWERPC_LINUX) || defined (POWERPC_FREEBSD)
23252	  if ((sel & SAVRES_LR))
23253	    prefix = ((sel & SAVRES_SAVE) ? "_savefpr_" : "_restfpr_");
23254	  else
23255#endif
23256	    {
23257	      prefix = (sel & SAVRES_SAVE) ? SAVE_FP_PREFIX : RESTORE_FP_PREFIX;
23258	      suffix = (sel & SAVRES_SAVE) ? SAVE_FP_SUFFIX : RESTORE_FP_SUFFIX;
23259	    }
23260	}
23261      else if ((sel & SAVRES_REG) == SAVRES_VR)
23262	prefix = (sel & SAVRES_SAVE) ? "_savevr_" : "_restvr_";
23263      else
23264	abort ();
23265    }
23266
23267   if (DEFAULT_ABI == ABI_DARWIN)
23268    {
23269      /* The Darwin approach is (slightly) different, in order to be
23270	 compatible with code generated by the system toolchain.  There is a
23271	 single symbol for the start of save sequence, and the code here
23272	 embeds an offset into that code on the basis of the first register
23273	 to be saved.  */
23274      prefix = (sel & SAVRES_SAVE) ? "save" : "rest" ;
23275      if ((sel & SAVRES_REG) == SAVRES_GPR)
23276	sprintf (savres_routine_name, "*%sGPR%s%s%.0d ; %s r%d-r31", prefix,
23277		 ((sel & SAVRES_LR) ? "x" : ""), (regno == 13 ? "" : "+"),
23278		 (regno - 13) * 4, prefix, regno);
23279      else if ((sel & SAVRES_REG) == SAVRES_FPR)
23280	sprintf (savres_routine_name, "*%sFP%s%.0d ; %s f%d-f31", prefix,
23281		 (regno == 14 ? "" : "+"), (regno - 14) * 4, prefix, regno);
23282      else if ((sel & SAVRES_REG) == SAVRES_VR)
23283	sprintf (savres_routine_name, "*%sVEC%s%.0d ; %s v%d-v31", prefix,
23284		 (regno == 20 ? "" : "+"), (regno - 20) * 8, prefix, regno);
23285      else
23286	abort ();
23287    }
23288  else
23289    sprintf (savres_routine_name, "%s%d%s", prefix, regno, suffix);
23290
23291  return savres_routine_name;
23292}
23293
23294/* Return an RTL SYMBOL_REF for an out-of-line register save/restore routine.
23295   We are saving/restoring GPRs if GPR is true.  */
23296
23297static rtx
23298rs6000_savres_routine_sym (rs6000_stack_t *info, int sel)
23299{
23300  int regno = ((sel & SAVRES_REG) == SAVRES_GPR
23301	       ? info->first_gp_reg_save
23302	       : (sel & SAVRES_REG) == SAVRES_FPR
23303	       ? info->first_fp_reg_save - 32
23304	       : (sel & SAVRES_REG) == SAVRES_VR
23305	       ? info->first_altivec_reg_save - FIRST_ALTIVEC_REGNO
23306	       : -1);
23307  rtx sym;
23308  int select = sel;
23309
23310  /* On the SPE, we never have any FPRs, but we do have 32/64-bit
23311     versions of the gpr routines.  */
23312  if (TARGET_SPE_ABI && (sel & SAVRES_REG) == SAVRES_GPR
23313      && info->spe_64bit_regs_used)
23314    select ^= SAVRES_FPR ^ SAVRES_GPR;
23315
23316  /* Don't generate bogus routine names.  */
23317  gcc_assert (FIRST_SAVRES_REGISTER <= regno
23318	      && regno <= LAST_SAVRES_REGISTER
23319	      && select >= 0 && select <= 12);
23320
23321  sym = savres_routine_syms[regno-FIRST_SAVRES_REGISTER][select];
23322
23323  if (sym == NULL)
23324    {
23325      char *name;
23326
23327      name = rs6000_savres_routine_name (info, regno, sel);
23328
23329      sym = savres_routine_syms[regno-FIRST_SAVRES_REGISTER][select]
23330	= gen_rtx_SYMBOL_REF (Pmode, ggc_strdup (name));
23331      SYMBOL_REF_FLAGS (sym) |= SYMBOL_FLAG_FUNCTION;
23332    }
23333
23334  return sym;
23335}
23336
23337/* Emit a sequence of insns, including a stack tie if needed, for
23338   resetting the stack pointer.  If UPDT_REGNO is not 1, then don't
23339   reset the stack pointer, but move the base of the frame into
23340   reg UPDT_REGNO for use by out-of-line register restore routines.  */
23341
23342static rtx
23343rs6000_emit_stack_reset (rs6000_stack_t *info,
23344			 rtx frame_reg_rtx, HOST_WIDE_INT frame_off,
23345			 unsigned updt_regno)
23346{
23347  rtx updt_reg_rtx;
23348
23349  /* This blockage is needed so that sched doesn't decide to move
23350     the sp change before the register restores.  */
23351  if (DEFAULT_ABI == ABI_V4
23352      || (TARGET_SPE_ABI
23353	  && info->spe_64bit_regs_used != 0
23354	  && info->first_gp_reg_save != 32))
23355    rs6000_emit_stack_tie (frame_reg_rtx, frame_pointer_needed);
23356
23357  /* If we are restoring registers out-of-line, we will be using the
23358     "exit" variants of the restore routines, which will reset the
23359     stack for us.  But we do need to point updt_reg into the
23360     right place for those routines.  */
23361  updt_reg_rtx = gen_rtx_REG (Pmode, updt_regno);
23362
23363  if (frame_off != 0)
23364    return emit_insn (gen_add3_insn (updt_reg_rtx,
23365				     frame_reg_rtx, GEN_INT (frame_off)));
23366  else if (REGNO (frame_reg_rtx) != updt_regno)
23367    return emit_move_insn (updt_reg_rtx, frame_reg_rtx);
23368
23369  return NULL_RTX;
23370}
23371
23372/* Return the register number used as a pointer by out-of-line
23373   save/restore functions.  */
23374
23375static inline unsigned
23376ptr_regno_for_savres (int sel)
23377{
23378  if (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
23379    return (sel & SAVRES_REG) == SAVRES_FPR || (sel & SAVRES_LR) ? 1 : 12;
23380  return DEFAULT_ABI == ABI_DARWIN && (sel & SAVRES_REG) == SAVRES_FPR ? 1 : 11;
23381}
23382
23383/* Construct a parallel rtx describing the effect of a call to an
23384   out-of-line register save/restore routine, and emit the insn
23385   or jump_insn as appropriate.  */
23386
23387static rtx
23388rs6000_emit_savres_rtx (rs6000_stack_t *info,
23389			rtx frame_reg_rtx, int save_area_offset, int lr_offset,
23390			machine_mode reg_mode, int sel)
23391{
23392  int i;
23393  int offset, start_reg, end_reg, n_regs, use_reg;
23394  int reg_size = GET_MODE_SIZE (reg_mode);
23395  rtx sym;
23396  rtvec p;
23397  rtx par, insn;
23398
23399  offset = 0;
23400  start_reg = ((sel & SAVRES_REG) == SAVRES_GPR
23401	       ? info->first_gp_reg_save
23402	       : (sel & SAVRES_REG) == SAVRES_FPR
23403	       ? info->first_fp_reg_save
23404	       : (sel & SAVRES_REG) == SAVRES_VR
23405	       ? info->first_altivec_reg_save
23406	       : -1);
23407  end_reg = ((sel & SAVRES_REG) == SAVRES_GPR
23408	     ? 32
23409	     : (sel & SAVRES_REG) == SAVRES_FPR
23410	     ? 64
23411	     : (sel & SAVRES_REG) == SAVRES_VR
23412	     ? LAST_ALTIVEC_REGNO + 1
23413	     : -1);
23414  n_regs = end_reg - start_reg;
23415  p = rtvec_alloc (3 + ((sel & SAVRES_LR) ? 1 : 0)
23416		   + ((sel & SAVRES_REG) == SAVRES_VR ? 1 : 0)
23417		   + n_regs);
23418
23419  if (!(sel & SAVRES_SAVE) && (sel & SAVRES_LR))
23420    RTVEC_ELT (p, offset++) = ret_rtx;
23421
23422  RTVEC_ELT (p, offset++)
23423    = gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (Pmode, LR_REGNO));
23424
23425  sym = rs6000_savres_routine_sym (info, sel);
23426  RTVEC_ELT (p, offset++) = gen_rtx_USE (VOIDmode, sym);
23427
23428  use_reg = ptr_regno_for_savres (sel);
23429  if ((sel & SAVRES_REG) == SAVRES_VR)
23430    {
23431      /* Vector regs are saved/restored using [reg+reg] addressing.  */
23432      RTVEC_ELT (p, offset++)
23433	= gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (Pmode, use_reg));
23434      RTVEC_ELT (p, offset++)
23435	= gen_rtx_USE (VOIDmode, gen_rtx_REG (Pmode, 0));
23436    }
23437  else
23438    RTVEC_ELT (p, offset++)
23439      = gen_rtx_USE (VOIDmode, gen_rtx_REG (Pmode, use_reg));
23440
23441  for (i = 0; i < end_reg - start_reg; i++)
23442    RTVEC_ELT (p, i + offset)
23443      = gen_frame_set (gen_rtx_REG (reg_mode, start_reg + i),
23444		       frame_reg_rtx, save_area_offset + reg_size * i,
23445		       (sel & SAVRES_SAVE) != 0);
23446
23447  if ((sel & SAVRES_SAVE) && (sel & SAVRES_LR))
23448    RTVEC_ELT (p, i + offset)
23449      = gen_frame_store (gen_rtx_REG (Pmode, 0), frame_reg_rtx, lr_offset);
23450
23451  par = gen_rtx_PARALLEL (VOIDmode, p);
23452
23453  if (!(sel & SAVRES_SAVE) && (sel & SAVRES_LR))
23454    {
23455      insn = emit_jump_insn (par);
23456      JUMP_LABEL (insn) = ret_rtx;
23457    }
23458  else
23459    insn = emit_insn (par);
23460  return insn;
23461}
23462
23463/* Emit code to store CR fields that need to be saved into REG.  */
23464
23465static void
23466rs6000_emit_move_from_cr (rtx reg)
23467{
23468  /* Only the ELFv2 ABI allows storing only selected fields.  */
23469  if (DEFAULT_ABI == ABI_ELFv2 && TARGET_MFCRF)
23470    {
23471      int i, cr_reg[8], count = 0;
23472
23473      /* Collect CR fields that must be saved.  */
23474      for (i = 0; i < 8; i++)
23475	if (save_reg_p (CR0_REGNO + i))
23476	  cr_reg[count++] = i;
23477
23478      /* If it's just a single one, use mfcrf.  */
23479      if (count == 1)
23480	{
23481	  rtvec p = rtvec_alloc (1);
23482	  rtvec r = rtvec_alloc (2);
23483	  RTVEC_ELT (r, 0) = gen_rtx_REG (CCmode, CR0_REGNO + cr_reg[0]);
23484	  RTVEC_ELT (r, 1) = GEN_INT (1 << (7 - cr_reg[0]));
23485	  RTVEC_ELT (p, 0)
23486	    = gen_rtx_SET (VOIDmode, reg,
23487			   gen_rtx_UNSPEC (SImode, r, UNSPEC_MOVESI_FROM_CR));
23488
23489	  emit_insn (gen_rtx_PARALLEL (VOIDmode, p));
23490	  return;
23491	}
23492
23493      /* ??? It might be better to handle count == 2 / 3 cases here
23494	 as well, using logical operations to combine the values.  */
23495    }
23496
23497  emit_insn (gen_movesi_from_cr (reg));
23498}
23499
23500/* Determine whether the gp REG is really used.  */
23501
23502static bool
23503rs6000_reg_live_or_pic_offset_p (int reg)
23504{
23505  /* If the function calls eh_return, claim used all the registers that would
23506     be checked for liveness otherwise.  This is required for the PIC offset
23507     register with -mminimal-toc on AIX, as it is advertised as "fixed" for
23508     register allocation purposes in this case.  */
23509
23510  return (((crtl->calls_eh_return || df_regs_ever_live_p (reg))
23511           && (!call_used_regs[reg]
23512               || (reg == RS6000_PIC_OFFSET_TABLE_REGNUM
23513		   && !TARGET_SINGLE_PIC_BASE
23514                   && TARGET_TOC && TARGET_MINIMAL_TOC)))
23515          || (reg == RS6000_PIC_OFFSET_TABLE_REGNUM
23516	      && !TARGET_SINGLE_PIC_BASE
23517              && ((DEFAULT_ABI == ABI_V4 && flag_pic != 0)
23518                  || (DEFAULT_ABI == ABI_DARWIN && flag_pic))));
23519}
23520
23521/* Emit function prologue as insns.  */
23522
23523void
23524rs6000_emit_prologue (void)
23525{
23526  rs6000_stack_t *info = rs6000_stack_info ();
23527  machine_mode reg_mode = Pmode;
23528  int reg_size = TARGET_32BIT ? 4 : 8;
23529  rtx sp_reg_rtx = gen_rtx_REG (Pmode, STACK_POINTER_REGNUM);
23530  rtx frame_reg_rtx = sp_reg_rtx;
23531  unsigned int cr_save_regno;
23532  rtx cr_save_rtx = NULL_RTX;
23533  rtx insn;
23534  int strategy;
23535  int using_static_chain_p = (cfun->static_chain_decl != NULL_TREE
23536			      && df_regs_ever_live_p (STATIC_CHAIN_REGNUM)
23537			      && call_used_regs[STATIC_CHAIN_REGNUM]);
23538  /* Offset to top of frame for frame_reg and sp respectively.  */
23539  HOST_WIDE_INT frame_off = 0;
23540  HOST_WIDE_INT sp_off = 0;
23541
23542#ifdef ENABLE_CHECKING
23543  /* Track and check usage of r0, r11, r12.  */
23544  int reg_inuse = using_static_chain_p ? 1 << 11 : 0;
23545#define START_USE(R) do \
23546  {						\
23547    gcc_assert ((reg_inuse & (1 << (R))) == 0);	\
23548    reg_inuse |= 1 << (R);			\
23549  } while (0)
23550#define END_USE(R) do \
23551  {						\
23552    gcc_assert ((reg_inuse & (1 << (R))) != 0);	\
23553    reg_inuse &= ~(1 << (R));			\
23554  } while (0)
23555#define NOT_INUSE(R) do \
23556  {						\
23557    gcc_assert ((reg_inuse & (1 << (R))) == 0);	\
23558  } while (0)
23559#else
23560#define START_USE(R) do {} while (0)
23561#define END_USE(R) do {} while (0)
23562#define NOT_INUSE(R) do {} while (0)
23563#endif
23564
23565  if (DEFAULT_ABI == ABI_ELFv2)
23566    {
23567      cfun->machine->r2_setup_needed = df_regs_ever_live_p (TOC_REGNUM);
23568
23569      /* With -mminimal-toc we may generate an extra use of r2 below.  */
23570      if (!TARGET_SINGLE_PIC_BASE
23571	  && TARGET_TOC && TARGET_MINIMAL_TOC && get_pool_size () != 0)
23572	cfun->machine->r2_setup_needed = true;
23573    }
23574
23575
23576  if (flag_stack_usage_info)
23577    current_function_static_stack_size = info->total_size;
23578
23579  if (flag_stack_check == STATIC_BUILTIN_STACK_CHECK)
23580    {
23581      HOST_WIDE_INT size = info->total_size;
23582
23583      if (crtl->is_leaf && !cfun->calls_alloca)
23584	{
23585	  if (size > PROBE_INTERVAL && size > STACK_CHECK_PROTECT)
23586	    rs6000_emit_probe_stack_range (STACK_CHECK_PROTECT,
23587					   size - STACK_CHECK_PROTECT);
23588	}
23589      else if (size > 0)
23590	rs6000_emit_probe_stack_range (STACK_CHECK_PROTECT, size);
23591    }
23592
23593  if (TARGET_FIX_AND_CONTINUE)
23594    {
23595      /* gdb on darwin arranges to forward a function from the old
23596	 address by modifying the first 5 instructions of the function
23597	 to branch to the overriding function.  This is necessary to
23598	 permit function pointers that point to the old function to
23599	 actually forward to the new function.  */
23600      emit_insn (gen_nop ());
23601      emit_insn (gen_nop ());
23602      emit_insn (gen_nop ());
23603      emit_insn (gen_nop ());
23604      emit_insn (gen_nop ());
23605    }
23606
23607  if (TARGET_SPE_ABI && info->spe_64bit_regs_used != 0)
23608    {
23609      reg_mode = V2SImode;
23610      reg_size = 8;
23611    }
23612
23613  /* Handle world saves specially here.  */
23614  if (WORLD_SAVE_P (info))
23615    {
23616      int i, j, sz;
23617      rtx treg;
23618      rtvec p;
23619      rtx reg0;
23620
23621      /* save_world expects lr in r0. */
23622      reg0 = gen_rtx_REG (Pmode, 0);
23623      if (info->lr_save_p)
23624	{
23625	  insn = emit_move_insn (reg0,
23626				 gen_rtx_REG (Pmode, LR_REGNO));
23627	  RTX_FRAME_RELATED_P (insn) = 1;
23628	}
23629
23630      /* The SAVE_WORLD and RESTORE_WORLD routines make a number of
23631	 assumptions about the offsets of various bits of the stack
23632	 frame.  */
23633      gcc_assert (info->gp_save_offset == -220
23634		  && info->fp_save_offset == -144
23635		  && info->lr_save_offset == 8
23636		  && info->cr_save_offset == 4
23637		  && info->push_p
23638		  && info->lr_save_p
23639		  && (!crtl->calls_eh_return
23640		      || info->ehrd_offset == -432)
23641		  && info->vrsave_save_offset == -224
23642		  && info->altivec_save_offset == -416);
23643
23644      treg = gen_rtx_REG (SImode, 11);
23645      emit_move_insn (treg, GEN_INT (-info->total_size));
23646
23647      /* SAVE_WORLD takes the caller's LR in R0 and the frame size
23648	 in R11.  It also clobbers R12, so beware!  */
23649
23650      /* Preserve CR2 for save_world prologues */
23651      sz = 5;
23652      sz += 32 - info->first_gp_reg_save;
23653      sz += 64 - info->first_fp_reg_save;
23654      sz += LAST_ALTIVEC_REGNO - info->first_altivec_reg_save + 1;
23655      p = rtvec_alloc (sz);
23656      j = 0;
23657      RTVEC_ELT (p, j++) = gen_rtx_CLOBBER (VOIDmode,
23658					    gen_rtx_REG (SImode,
23659							 LR_REGNO));
23660      RTVEC_ELT (p, j++) = gen_rtx_USE (VOIDmode,
23661					gen_rtx_SYMBOL_REF (Pmode,
23662							    "*save_world"));
23663      /* We do floats first so that the instruction pattern matches
23664	 properly.  */
23665      for (i = 0; i < 64 - info->first_fp_reg_save; i++)
23666	RTVEC_ELT (p, j++)
23667	  = gen_frame_store (gen_rtx_REG (TARGET_HARD_FLOAT && TARGET_DOUBLE_FLOAT
23668					  ? DFmode : SFmode,
23669					  info->first_fp_reg_save + i),
23670			     frame_reg_rtx,
23671			     info->fp_save_offset + frame_off + 8 * i);
23672      for (i = 0; info->first_altivec_reg_save + i <= LAST_ALTIVEC_REGNO; i++)
23673	RTVEC_ELT (p, j++)
23674	  = gen_frame_store (gen_rtx_REG (V4SImode,
23675					  info->first_altivec_reg_save + i),
23676			     frame_reg_rtx,
23677			     info->altivec_save_offset + frame_off + 16 * i);
23678      for (i = 0; i < 32 - info->first_gp_reg_save; i++)
23679	RTVEC_ELT (p, j++)
23680	  = gen_frame_store (gen_rtx_REG (reg_mode, info->first_gp_reg_save + i),
23681			     frame_reg_rtx,
23682			     info->gp_save_offset + frame_off + reg_size * i);
23683
23684      /* CR register traditionally saved as CR2.  */
23685      RTVEC_ELT (p, j++)
23686	= gen_frame_store (gen_rtx_REG (SImode, CR2_REGNO),
23687			   frame_reg_rtx, info->cr_save_offset + frame_off);
23688      /* Explain about use of R0.  */
23689      if (info->lr_save_p)
23690	RTVEC_ELT (p, j++)
23691	  = gen_frame_store (reg0,
23692			     frame_reg_rtx, info->lr_save_offset + frame_off);
23693      /* Explain what happens to the stack pointer.  */
23694      {
23695	rtx newval = gen_rtx_PLUS (Pmode, sp_reg_rtx, treg);
23696	RTVEC_ELT (p, j++) = gen_rtx_SET (VOIDmode, sp_reg_rtx, newval);
23697      }
23698
23699      insn = emit_insn (gen_rtx_PARALLEL (VOIDmode, p));
23700      rs6000_frame_related (insn, frame_reg_rtx, sp_off - frame_off,
23701			    treg, GEN_INT (-info->total_size));
23702      sp_off = frame_off = info->total_size;
23703    }
23704
23705  strategy = info->savres_strategy;
23706
23707  /* For V.4, update stack before we do any saving and set back pointer.  */
23708  if (! WORLD_SAVE_P (info)
23709      && info->push_p
23710      && (DEFAULT_ABI == ABI_V4
23711	  || crtl->calls_eh_return))
23712    {
23713      bool need_r11 = (TARGET_SPE
23714		       ? (!(strategy & SAVE_INLINE_GPRS)
23715			  && info->spe_64bit_regs_used == 0)
23716		       : (!(strategy & SAVE_INLINE_FPRS)
23717			  || !(strategy & SAVE_INLINE_GPRS)
23718			  || !(strategy & SAVE_INLINE_VRS)));
23719      int ptr_regno = -1;
23720      rtx ptr_reg = NULL_RTX;
23721      int ptr_off = 0;
23722
23723      if (info->total_size < 32767)
23724	frame_off = info->total_size;
23725      else if (need_r11)
23726	ptr_regno = 11;
23727      else if (info->cr_save_p
23728	       || info->lr_save_p
23729	       || info->first_fp_reg_save < 64
23730	       || info->first_gp_reg_save < 32
23731	       || info->altivec_size != 0
23732	       || info->vrsave_mask != 0
23733	       || crtl->calls_eh_return)
23734	ptr_regno = 12;
23735      else
23736	{
23737	  /* The prologue won't be saving any regs so there is no need
23738	     to set up a frame register to access any frame save area.
23739	     We also won't be using frame_off anywhere below, but set
23740	     the correct value anyway to protect against future
23741	     changes to this function.  */
23742	  frame_off = info->total_size;
23743	}
23744      if (ptr_regno != -1)
23745	{
23746	  /* Set up the frame offset to that needed by the first
23747	     out-of-line save function.  */
23748	  START_USE (ptr_regno);
23749	  ptr_reg = gen_rtx_REG (Pmode, ptr_regno);
23750	  frame_reg_rtx = ptr_reg;
23751	  if (!(strategy & SAVE_INLINE_FPRS) && info->fp_size != 0)
23752	    gcc_checking_assert (info->fp_save_offset + info->fp_size == 0);
23753	  else if (!(strategy & SAVE_INLINE_GPRS) && info->first_gp_reg_save < 32)
23754	    ptr_off = info->gp_save_offset + info->gp_size;
23755	  else if (!(strategy & SAVE_INLINE_VRS) && info->altivec_size != 0)
23756	    ptr_off = info->altivec_save_offset + info->altivec_size;
23757	  frame_off = -ptr_off;
23758	}
23759      rs6000_emit_allocate_stack (info->total_size, ptr_reg, ptr_off);
23760      sp_off = info->total_size;
23761      if (frame_reg_rtx != sp_reg_rtx)
23762	rs6000_emit_stack_tie (frame_reg_rtx, false);
23763    }
23764
23765  /* If we use the link register, get it into r0.  */
23766  if (!WORLD_SAVE_P (info) && info->lr_save_p)
23767    {
23768      rtx addr, reg, mem;
23769
23770      reg = gen_rtx_REG (Pmode, 0);
23771      START_USE (0);
23772      insn = emit_move_insn (reg, gen_rtx_REG (Pmode, LR_REGNO));
23773      RTX_FRAME_RELATED_P (insn) = 1;
23774
23775      if (!(strategy & (SAVE_NOINLINE_GPRS_SAVES_LR
23776			| SAVE_NOINLINE_FPRS_SAVES_LR)))
23777	{
23778	  addr = gen_rtx_PLUS (Pmode, frame_reg_rtx,
23779			       GEN_INT (info->lr_save_offset + frame_off));
23780	  mem = gen_rtx_MEM (Pmode, addr);
23781	  /* This should not be of rs6000_sr_alias_set, because of
23782	     __builtin_return_address.  */
23783
23784	  insn = emit_move_insn (mem, reg);
23785	  rs6000_frame_related (insn, frame_reg_rtx, sp_off - frame_off,
23786				NULL_RTX, NULL_RTX);
23787	  END_USE (0);
23788	}
23789    }
23790
23791  /* If we need to save CR, put it into r12 or r11.  Choose r12 except when
23792     r12 will be needed by out-of-line gpr restore.  */
23793  cr_save_regno = ((DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
23794		   && !(strategy & (SAVE_INLINE_GPRS
23795				    | SAVE_NOINLINE_GPRS_SAVES_LR))
23796		   ? 11 : 12);
23797  if (!WORLD_SAVE_P (info)
23798      && info->cr_save_p
23799      && REGNO (frame_reg_rtx) != cr_save_regno
23800      && !(using_static_chain_p && cr_save_regno == 11))
23801    {
23802      cr_save_rtx = gen_rtx_REG (SImode, cr_save_regno);
23803      START_USE (cr_save_regno);
23804      rs6000_emit_move_from_cr (cr_save_rtx);
23805    }
23806
23807  /* Do any required saving of fpr's.  If only one or two to save, do
23808     it ourselves.  Otherwise, call function.  */
23809  if (!WORLD_SAVE_P (info) && (strategy & SAVE_INLINE_FPRS))
23810    {
23811      int i;
23812      for (i = 0; i < 64 - info->first_fp_reg_save; i++)
23813	if (save_reg_p (info->first_fp_reg_save + i))
23814	  emit_frame_save (frame_reg_rtx,
23815			   (TARGET_HARD_FLOAT && TARGET_DOUBLE_FLOAT
23816			    ? DFmode : SFmode),
23817			   info->first_fp_reg_save + i,
23818			   info->fp_save_offset + frame_off + 8 * i,
23819			   sp_off - frame_off);
23820    }
23821  else if (!WORLD_SAVE_P (info) && info->first_fp_reg_save != 64)
23822    {
23823      bool lr = (strategy & SAVE_NOINLINE_FPRS_SAVES_LR) != 0;
23824      int sel = SAVRES_SAVE | SAVRES_FPR | (lr ? SAVRES_LR : 0);
23825      unsigned ptr_regno = ptr_regno_for_savres (sel);
23826      rtx ptr_reg = frame_reg_rtx;
23827
23828      if (REGNO (frame_reg_rtx) == ptr_regno)
23829	gcc_checking_assert (frame_off == 0);
23830      else
23831	{
23832	  ptr_reg = gen_rtx_REG (Pmode, ptr_regno);
23833	  NOT_INUSE (ptr_regno);
23834	  emit_insn (gen_add3_insn (ptr_reg,
23835				    frame_reg_rtx, GEN_INT (frame_off)));
23836	}
23837      insn = rs6000_emit_savres_rtx (info, ptr_reg,
23838				     info->fp_save_offset,
23839				     info->lr_save_offset,
23840				     DFmode, sel);
23841      rs6000_frame_related (insn, ptr_reg, sp_off,
23842			    NULL_RTX, NULL_RTX);
23843      if (lr)
23844	END_USE (0);
23845    }
23846
23847  /* Save GPRs.  This is done as a PARALLEL if we are using
23848     the store-multiple instructions.  */
23849  if (!WORLD_SAVE_P (info)
23850      && TARGET_SPE_ABI
23851      && info->spe_64bit_regs_used != 0
23852      && info->first_gp_reg_save != 32)
23853    {
23854      int i;
23855      rtx spe_save_area_ptr;
23856      HOST_WIDE_INT save_off;
23857      int ool_adjust = 0;
23858
23859      /* Determine whether we can address all of the registers that need
23860	 to be saved with an offset from frame_reg_rtx that fits in
23861	 the small const field for SPE memory instructions.  */
23862      int spe_regs_addressable
23863	= (SPE_CONST_OFFSET_OK (info->spe_gp_save_offset + frame_off
23864				+ reg_size * (32 - info->first_gp_reg_save - 1))
23865	   && (strategy & SAVE_INLINE_GPRS));
23866
23867      if (spe_regs_addressable)
23868	{
23869	  spe_save_area_ptr = frame_reg_rtx;
23870	  save_off = frame_off;
23871	}
23872      else
23873	{
23874	  /* Make r11 point to the start of the SPE save area.  We need
23875	     to be careful here if r11 is holding the static chain.  If
23876	     it is, then temporarily save it in r0.  */
23877	  HOST_WIDE_INT offset;
23878
23879	  if (!(strategy & SAVE_INLINE_GPRS))
23880	    ool_adjust = 8 * (info->first_gp_reg_save - FIRST_SAVED_GP_REGNO);
23881	  offset = info->spe_gp_save_offset + frame_off - ool_adjust;
23882	  spe_save_area_ptr = gen_rtx_REG (Pmode, 11);
23883	  save_off = frame_off - offset;
23884
23885	  if (using_static_chain_p)
23886	    {
23887	      rtx r0 = gen_rtx_REG (Pmode, 0);
23888
23889	      START_USE (0);
23890	      gcc_assert (info->first_gp_reg_save > 11);
23891
23892	      emit_move_insn (r0, spe_save_area_ptr);
23893	    }
23894	  else if (REGNO (frame_reg_rtx) != 11)
23895	    START_USE (11);
23896
23897	  emit_insn (gen_addsi3 (spe_save_area_ptr,
23898				 frame_reg_rtx, GEN_INT (offset)));
23899	  if (!using_static_chain_p && REGNO (frame_reg_rtx) == 11)
23900	    frame_off = -info->spe_gp_save_offset + ool_adjust;
23901	}
23902
23903      if ((strategy & SAVE_INLINE_GPRS))
23904	{
23905	  for (i = 0; i < 32 - info->first_gp_reg_save; i++)
23906	    if (rs6000_reg_live_or_pic_offset_p (info->first_gp_reg_save + i))
23907	      emit_frame_save (spe_save_area_ptr, reg_mode,
23908			       info->first_gp_reg_save + i,
23909			       (info->spe_gp_save_offset + save_off
23910				+ reg_size * i),
23911			       sp_off - save_off);
23912	}
23913      else
23914	{
23915	  insn = rs6000_emit_savres_rtx (info, spe_save_area_ptr,
23916					 info->spe_gp_save_offset + save_off,
23917					 0, reg_mode,
23918					 SAVRES_SAVE | SAVRES_GPR);
23919
23920	  rs6000_frame_related (insn, spe_save_area_ptr, sp_off - save_off,
23921				NULL_RTX, NULL_RTX);
23922	}
23923
23924      /* Move the static chain pointer back.  */
23925      if (!spe_regs_addressable)
23926	{
23927	  if (using_static_chain_p)
23928	    {
23929	      emit_move_insn (spe_save_area_ptr, gen_rtx_REG (Pmode, 0));
23930	      END_USE (0);
23931	    }
23932	  else if (REGNO (frame_reg_rtx) != 11)
23933	    END_USE (11);
23934	}
23935    }
23936  else if (!WORLD_SAVE_P (info) && !(strategy & SAVE_INLINE_GPRS))
23937    {
23938      bool lr = (strategy & SAVE_NOINLINE_GPRS_SAVES_LR) != 0;
23939      int sel = SAVRES_SAVE | SAVRES_GPR | (lr ? SAVRES_LR : 0);
23940      unsigned ptr_regno = ptr_regno_for_savres (sel);
23941      rtx ptr_reg = frame_reg_rtx;
23942      bool ptr_set_up = REGNO (ptr_reg) == ptr_regno;
23943      int end_save = info->gp_save_offset + info->gp_size;
23944      int ptr_off;
23945
23946      if (!ptr_set_up)
23947	ptr_reg = gen_rtx_REG (Pmode, ptr_regno);
23948
23949      /* Need to adjust r11 (r12) if we saved any FPRs.  */
23950      if (end_save + frame_off != 0)
23951	{
23952	  rtx offset = GEN_INT (end_save + frame_off);
23953
23954	  if (ptr_set_up)
23955	    frame_off = -end_save;
23956	  else
23957	    NOT_INUSE (ptr_regno);
23958	  emit_insn (gen_add3_insn (ptr_reg, frame_reg_rtx, offset));
23959	}
23960      else if (!ptr_set_up)
23961	{
23962	  NOT_INUSE (ptr_regno);
23963	  emit_move_insn (ptr_reg, frame_reg_rtx);
23964	}
23965      ptr_off = -end_save;
23966      insn = rs6000_emit_savres_rtx (info, ptr_reg,
23967				     info->gp_save_offset + ptr_off,
23968				     info->lr_save_offset + ptr_off,
23969				     reg_mode, sel);
23970      rs6000_frame_related (insn, ptr_reg, sp_off - ptr_off,
23971			    NULL_RTX, NULL_RTX);
23972      if (lr)
23973	END_USE (0);
23974    }
23975  else if (!WORLD_SAVE_P (info) && (strategy & SAVRES_MULTIPLE))
23976    {
23977      rtvec p;
23978      int i;
23979      p = rtvec_alloc (32 - info->first_gp_reg_save);
23980      for (i = 0; i < 32 - info->first_gp_reg_save; i++)
23981	RTVEC_ELT (p, i)
23982	  = gen_frame_store (gen_rtx_REG (reg_mode, info->first_gp_reg_save + i),
23983			     frame_reg_rtx,
23984			     info->gp_save_offset + frame_off + reg_size * i);
23985      insn = emit_insn (gen_rtx_PARALLEL (VOIDmode, p));
23986      rs6000_frame_related (insn, frame_reg_rtx, sp_off - frame_off,
23987			    NULL_RTX, NULL_RTX);
23988    }
23989  else if (!WORLD_SAVE_P (info))
23990    {
23991      int i;
23992      for (i = 0; i < 32 - info->first_gp_reg_save; i++)
23993	if (rs6000_reg_live_or_pic_offset_p (info->first_gp_reg_save + i))
23994	  emit_frame_save (frame_reg_rtx, reg_mode,
23995			   info->first_gp_reg_save + i,
23996			   info->gp_save_offset + frame_off + reg_size * i,
23997			   sp_off - frame_off);
23998    }
23999
24000  if (crtl->calls_eh_return)
24001    {
24002      unsigned int i;
24003      rtvec p;
24004
24005      for (i = 0; ; ++i)
24006	{
24007	  unsigned int regno = EH_RETURN_DATA_REGNO (i);
24008	  if (regno == INVALID_REGNUM)
24009	    break;
24010	}
24011
24012      p = rtvec_alloc (i);
24013
24014      for (i = 0; ; ++i)
24015	{
24016	  unsigned int regno = EH_RETURN_DATA_REGNO (i);
24017	  if (regno == INVALID_REGNUM)
24018	    break;
24019
24020	  insn
24021	    = gen_frame_store (gen_rtx_REG (reg_mode, regno),
24022			       sp_reg_rtx,
24023			       info->ehrd_offset + sp_off + reg_size * (int) i);
24024	  RTVEC_ELT (p, i) = insn;
24025	  RTX_FRAME_RELATED_P (insn) = 1;
24026	}
24027
24028      insn = emit_insn (gen_blockage ());
24029      RTX_FRAME_RELATED_P (insn) = 1;
24030      add_reg_note (insn, REG_FRAME_RELATED_EXPR, gen_rtx_PARALLEL (VOIDmode, p));
24031    }
24032
24033  /* In AIX ABI we need to make sure r2 is really saved.  */
24034  if (TARGET_AIX && crtl->calls_eh_return)
24035    {
24036      rtx tmp_reg, tmp_reg_si, hi, lo, compare_result, toc_save_done, jump;
24037      rtx save_insn, join_insn, note;
24038      long toc_restore_insn;
24039
24040      tmp_reg = gen_rtx_REG (Pmode, 11);
24041      tmp_reg_si = gen_rtx_REG (SImode, 11);
24042      if (using_static_chain_p)
24043	{
24044	  START_USE (0);
24045	  emit_move_insn (gen_rtx_REG (Pmode, 0), tmp_reg);
24046	}
24047      else
24048	START_USE (11);
24049      emit_move_insn (tmp_reg, gen_rtx_REG (Pmode, LR_REGNO));
24050      /* Peek at instruction to which this function returns.  If it's
24051	 restoring r2, then we know we've already saved r2.  We can't
24052	 unconditionally save r2 because the value we have will already
24053	 be updated if we arrived at this function via a plt call or
24054	 toc adjusting stub.  */
24055      emit_move_insn (tmp_reg_si, gen_rtx_MEM (SImode, tmp_reg));
24056      toc_restore_insn = ((TARGET_32BIT ? 0x80410000 : 0xE8410000)
24057			  + RS6000_TOC_SAVE_SLOT);
24058      hi = gen_int_mode (toc_restore_insn & ~0xffff, SImode);
24059      emit_insn (gen_xorsi3 (tmp_reg_si, tmp_reg_si, hi));
24060      compare_result = gen_rtx_REG (CCUNSmode, CR0_REGNO);
24061      validate_condition_mode (EQ, CCUNSmode);
24062      lo = gen_int_mode (toc_restore_insn & 0xffff, SImode);
24063      emit_insn (gen_rtx_SET (VOIDmode, compare_result,
24064			      gen_rtx_COMPARE (CCUNSmode, tmp_reg_si, lo)));
24065      toc_save_done = gen_label_rtx ();
24066      jump = gen_rtx_IF_THEN_ELSE (VOIDmode,
24067				   gen_rtx_EQ (VOIDmode, compare_result,
24068					       const0_rtx),
24069				   gen_rtx_LABEL_REF (VOIDmode, toc_save_done),
24070				   pc_rtx);
24071      jump = emit_jump_insn (gen_rtx_SET (VOIDmode, pc_rtx, jump));
24072      JUMP_LABEL (jump) = toc_save_done;
24073      LABEL_NUSES (toc_save_done) += 1;
24074
24075      save_insn = emit_frame_save (frame_reg_rtx, reg_mode,
24076				   TOC_REGNUM, frame_off + RS6000_TOC_SAVE_SLOT,
24077				   sp_off - frame_off);
24078
24079      emit_label (toc_save_done);
24080
24081      /* ??? If we leave SAVE_INSN as marked as saving R2, then we'll
24082	 have a CFG that has different saves along different paths.
24083	 Move the note to a dummy blockage insn, which describes that
24084	 R2 is unconditionally saved after the label.  */
24085      /* ??? An alternate representation might be a special insn pattern
24086	 containing both the branch and the store.  That might let the
24087	 code that minimizes the number of DW_CFA_advance opcodes better
24088	 freedom in placing the annotations.  */
24089      note = find_reg_note (save_insn, REG_FRAME_RELATED_EXPR, NULL);
24090      if (note)
24091	remove_note (save_insn, note);
24092      else
24093	note = alloc_reg_note (REG_FRAME_RELATED_EXPR,
24094			       copy_rtx (PATTERN (save_insn)), NULL_RTX);
24095      RTX_FRAME_RELATED_P (save_insn) = 0;
24096
24097      join_insn = emit_insn (gen_blockage ());
24098      REG_NOTES (join_insn) = note;
24099      RTX_FRAME_RELATED_P (join_insn) = 1;
24100
24101      if (using_static_chain_p)
24102	{
24103	  emit_move_insn (tmp_reg, gen_rtx_REG (Pmode, 0));
24104	  END_USE (0);
24105	}
24106      else
24107	END_USE (11);
24108    }
24109
24110  /* Save CR if we use any that must be preserved.  */
24111  if (!WORLD_SAVE_P (info) && info->cr_save_p)
24112    {
24113      rtx addr = gen_rtx_PLUS (Pmode, frame_reg_rtx,
24114			       GEN_INT (info->cr_save_offset + frame_off));
24115      rtx mem = gen_frame_mem (SImode, addr);
24116
24117      /* If we didn't copy cr before, do so now using r0.  */
24118      if (cr_save_rtx == NULL_RTX)
24119	{
24120	  START_USE (0);
24121	  cr_save_rtx = gen_rtx_REG (SImode, 0);
24122	  rs6000_emit_move_from_cr (cr_save_rtx);
24123	}
24124
24125      /* Saving CR requires a two-instruction sequence: one instruction
24126	 to move the CR to a general-purpose register, and a second
24127	 instruction that stores the GPR to memory.
24128
24129	 We do not emit any DWARF CFI records for the first of these,
24130	 because we cannot properly represent the fact that CR is saved in
24131	 a register.  One reason is that we cannot express that multiple
24132	 CR fields are saved; another reason is that on 64-bit, the size
24133	 of the CR register in DWARF (4 bytes) differs from the size of
24134	 a general-purpose register.
24135
24136	 This means if any intervening instruction were to clobber one of
24137	 the call-saved CR fields, we'd have incorrect CFI.  To prevent
24138	 this from happening, we mark the store to memory as a use of
24139	 those CR fields, which prevents any such instruction from being
24140	 scheduled in between the two instructions.  */
24141      rtx crsave_v[9];
24142      int n_crsave = 0;
24143      int i;
24144
24145      crsave_v[n_crsave++] = gen_rtx_SET (VOIDmode, mem, cr_save_rtx);
24146      for (i = 0; i < 8; i++)
24147	if (save_reg_p (CR0_REGNO + i))
24148	  crsave_v[n_crsave++]
24149	    = gen_rtx_USE (VOIDmode, gen_rtx_REG (CCmode, CR0_REGNO + i));
24150
24151      insn = emit_insn (gen_rtx_PARALLEL (VOIDmode,
24152					  gen_rtvec_v (n_crsave, crsave_v)));
24153      END_USE (REGNO (cr_save_rtx));
24154
24155      /* Now, there's no way that dwarf2out_frame_debug_expr is going to
24156	 understand '(unspec:SI [(reg:CC 68) ...] UNSPEC_MOVESI_FROM_CR)',
24157	 so we need to construct a frame expression manually.  */
24158      RTX_FRAME_RELATED_P (insn) = 1;
24159
24160      /* Update address to be stack-pointer relative, like
24161	 rs6000_frame_related would do.  */
24162      addr = gen_rtx_PLUS (Pmode, gen_rtx_REG (Pmode, STACK_POINTER_REGNUM),
24163			   GEN_INT (info->cr_save_offset + sp_off));
24164      mem = gen_frame_mem (SImode, addr);
24165
24166      if (DEFAULT_ABI == ABI_ELFv2)
24167	{
24168	  /* In the ELFv2 ABI we generate separate CFI records for each
24169	     CR field that was actually saved.  They all point to the
24170	     same 32-bit stack slot.  */
24171	  rtx crframe[8];
24172	  int n_crframe = 0;
24173
24174	  for (i = 0; i < 8; i++)
24175	    if (save_reg_p (CR0_REGNO + i))
24176	      {
24177		crframe[n_crframe]
24178		  = gen_rtx_SET (VOIDmode, mem,
24179				 gen_rtx_REG (SImode, CR0_REGNO + i));
24180
24181		RTX_FRAME_RELATED_P (crframe[n_crframe]) = 1;
24182		n_crframe++;
24183	     }
24184
24185	  add_reg_note (insn, REG_FRAME_RELATED_EXPR,
24186			gen_rtx_PARALLEL (VOIDmode,
24187					  gen_rtvec_v (n_crframe, crframe)));
24188	}
24189      else
24190	{
24191	  /* In other ABIs, by convention, we use a single CR regnum to
24192	     represent the fact that all call-saved CR fields are saved.
24193	     We use CR2_REGNO to be compatible with gcc-2.95 on Linux.  */
24194	  rtx set = gen_rtx_SET (VOIDmode, mem,
24195				 gen_rtx_REG (SImode, CR2_REGNO));
24196	  add_reg_note (insn, REG_FRAME_RELATED_EXPR, set);
24197	}
24198    }
24199
24200  /* In the ELFv2 ABI we need to save all call-saved CR fields into
24201     *separate* slots if the routine calls __builtin_eh_return, so
24202     that they can be independently restored by the unwinder.  */
24203  if (DEFAULT_ABI == ABI_ELFv2 && crtl->calls_eh_return)
24204    {
24205      int i, cr_off = info->ehcr_offset;
24206      rtx crsave;
24207
24208      /* ??? We might get better performance by using multiple mfocrf
24209	 instructions.  */
24210      crsave = gen_rtx_REG (SImode, 0);
24211      emit_insn (gen_movesi_from_cr (crsave));
24212
24213      for (i = 0; i < 8; i++)
24214	if (!call_used_regs[CR0_REGNO + i])
24215	  {
24216	    rtvec p = rtvec_alloc (2);
24217	    RTVEC_ELT (p, 0)
24218	      = gen_frame_store (crsave, frame_reg_rtx, cr_off + frame_off);
24219	    RTVEC_ELT (p, 1)
24220	      = gen_rtx_USE (VOIDmode, gen_rtx_REG (CCmode, CR0_REGNO + i));
24221
24222	    insn = emit_insn (gen_rtx_PARALLEL (VOIDmode, p));
24223
24224	    RTX_FRAME_RELATED_P (insn) = 1;
24225	    add_reg_note (insn, REG_FRAME_RELATED_EXPR,
24226			  gen_frame_store (gen_rtx_REG (SImode, CR0_REGNO + i),
24227					   sp_reg_rtx, cr_off + sp_off));
24228
24229	    cr_off += reg_size;
24230	  }
24231    }
24232
24233  /* Update stack and set back pointer unless this is V.4,
24234     for which it was done previously.  */
24235  if (!WORLD_SAVE_P (info) && info->push_p
24236      && !(DEFAULT_ABI == ABI_V4 || crtl->calls_eh_return))
24237    {
24238      rtx ptr_reg = NULL;
24239      int ptr_off = 0;
24240
24241      /* If saving altivec regs we need to be able to address all save
24242	 locations using a 16-bit offset.  */
24243      if ((strategy & SAVE_INLINE_VRS) == 0
24244	  || (info->altivec_size != 0
24245	      && (info->altivec_save_offset + info->altivec_size - 16
24246		  + info->total_size - frame_off) > 32767)
24247	  || (info->vrsave_size != 0
24248	      && (info->vrsave_save_offset
24249		  + info->total_size - frame_off) > 32767))
24250	{
24251	  int sel = SAVRES_SAVE | SAVRES_VR;
24252	  unsigned ptr_regno = ptr_regno_for_savres (sel);
24253
24254	  if (using_static_chain_p
24255	      && ptr_regno == STATIC_CHAIN_REGNUM)
24256	    ptr_regno = 12;
24257	  if (REGNO (frame_reg_rtx) != ptr_regno)
24258	    START_USE (ptr_regno);
24259	  ptr_reg = gen_rtx_REG (Pmode, ptr_regno);
24260	  frame_reg_rtx = ptr_reg;
24261	  ptr_off = info->altivec_save_offset + info->altivec_size;
24262	  frame_off = -ptr_off;
24263	}
24264      else if (REGNO (frame_reg_rtx) == 1)
24265	frame_off = info->total_size;
24266      rs6000_emit_allocate_stack (info->total_size, ptr_reg, ptr_off);
24267      sp_off = info->total_size;
24268      if (frame_reg_rtx != sp_reg_rtx)
24269	rs6000_emit_stack_tie (frame_reg_rtx, false);
24270    }
24271
24272  /* Set frame pointer, if needed.  */
24273  if (frame_pointer_needed)
24274    {
24275      insn = emit_move_insn (gen_rtx_REG (Pmode, HARD_FRAME_POINTER_REGNUM),
24276			     sp_reg_rtx);
24277      RTX_FRAME_RELATED_P (insn) = 1;
24278    }
24279
24280  /* Save AltiVec registers if needed.  Save here because the red zone does
24281     not always include AltiVec registers.  */
24282  if (!WORLD_SAVE_P (info) && TARGET_ALTIVEC_ABI
24283      && info->altivec_size != 0 && (strategy & SAVE_INLINE_VRS) == 0)
24284    {
24285      int end_save = info->altivec_save_offset + info->altivec_size;
24286      int ptr_off;
24287      /* Oddly, the vector save/restore functions point r0 at the end
24288	 of the save area, then use r11 or r12 to load offsets for
24289	 [reg+reg] addressing.  */
24290      rtx ptr_reg = gen_rtx_REG (Pmode, 0);
24291      int scratch_regno = ptr_regno_for_savres (SAVRES_SAVE | SAVRES_VR);
24292      rtx scratch_reg = gen_rtx_REG (Pmode, scratch_regno);
24293
24294      gcc_checking_assert (scratch_regno == 11 || scratch_regno == 12);
24295      NOT_INUSE (0);
24296      if (end_save + frame_off != 0)
24297	{
24298	  rtx offset = GEN_INT (end_save + frame_off);
24299
24300	  emit_insn (gen_add3_insn (ptr_reg, frame_reg_rtx, offset));
24301	}
24302      else
24303	emit_move_insn (ptr_reg, frame_reg_rtx);
24304
24305      ptr_off = -end_save;
24306      insn = rs6000_emit_savres_rtx (info, scratch_reg,
24307				     info->altivec_save_offset + ptr_off,
24308				     0, V4SImode, SAVRES_SAVE | SAVRES_VR);
24309      rs6000_frame_related (insn, scratch_reg, sp_off - ptr_off,
24310			    NULL_RTX, NULL_RTX);
24311      if (REGNO (frame_reg_rtx) == REGNO (scratch_reg))
24312	{
24313	  /* The oddity mentioned above clobbered our frame reg.  */
24314	  emit_move_insn (frame_reg_rtx, ptr_reg);
24315	  frame_off = ptr_off;
24316	}
24317    }
24318  else if (!WORLD_SAVE_P (info) && TARGET_ALTIVEC_ABI
24319	   && info->altivec_size != 0)
24320    {
24321      int i;
24322
24323      for (i = info->first_altivec_reg_save; i <= LAST_ALTIVEC_REGNO; ++i)
24324	if (info->vrsave_mask & ALTIVEC_REG_BIT (i))
24325	  {
24326	    rtx areg, savereg, mem;
24327	    int offset;
24328
24329	    offset = (info->altivec_save_offset + frame_off
24330		      + 16 * (i - info->first_altivec_reg_save));
24331
24332	    savereg = gen_rtx_REG (V4SImode, i);
24333
24334	    NOT_INUSE (0);
24335	    areg = gen_rtx_REG (Pmode, 0);
24336	    emit_move_insn (areg, GEN_INT (offset));
24337
24338	    /* AltiVec addressing mode is [reg+reg].  */
24339	    mem = gen_frame_mem (V4SImode,
24340				 gen_rtx_PLUS (Pmode, frame_reg_rtx, areg));
24341
24342	    /* Rather than emitting a generic move, force use of the stvx
24343	       instruction, which we always want.  In particular we don't
24344	       want xxpermdi/stxvd2x for little endian.  */
24345	    insn = emit_insn (gen_altivec_stvx_v4si_internal (mem, savereg));
24346
24347	    rs6000_frame_related (insn, frame_reg_rtx, sp_off - frame_off,
24348				  areg, GEN_INT (offset));
24349	  }
24350    }
24351
24352  /* VRSAVE is a bit vector representing which AltiVec registers
24353     are used.  The OS uses this to determine which vector
24354     registers to save on a context switch.  We need to save
24355     VRSAVE on the stack frame, add whatever AltiVec registers we
24356     used in this function, and do the corresponding magic in the
24357     epilogue.  */
24358
24359  if (!WORLD_SAVE_P (info)
24360      && TARGET_ALTIVEC
24361      && TARGET_ALTIVEC_VRSAVE
24362      && info->vrsave_mask != 0)
24363    {
24364      rtx reg, vrsave;
24365      int offset;
24366      int save_regno;
24367
24368      /* Get VRSAVE onto a GPR.  Note that ABI_V4 and ABI_DARWIN might
24369	 be using r12 as frame_reg_rtx and r11 as the static chain
24370	 pointer for nested functions.  */
24371      save_regno = 12;
24372      if ((DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
24373	  && !using_static_chain_p)
24374	save_regno = 11;
24375      else if (REGNO (frame_reg_rtx) == 12)
24376	{
24377	  save_regno = 11;
24378	  if (using_static_chain_p)
24379	    save_regno = 0;
24380	}
24381
24382      NOT_INUSE (save_regno);
24383      reg = gen_rtx_REG (SImode, save_regno);
24384      vrsave = gen_rtx_REG (SImode, VRSAVE_REGNO);
24385      if (TARGET_MACHO)
24386	emit_insn (gen_get_vrsave_internal (reg));
24387      else
24388	emit_insn (gen_rtx_SET (VOIDmode, reg, vrsave));
24389
24390      /* Save VRSAVE.  */
24391      offset = info->vrsave_save_offset + frame_off;
24392      insn = emit_insn (gen_frame_store (reg, frame_reg_rtx, offset));
24393
24394      /* Include the registers in the mask.  */
24395      emit_insn (gen_iorsi3 (reg, reg, GEN_INT ((int) info->vrsave_mask)));
24396
24397      insn = emit_insn (generate_set_vrsave (reg, info, 0));
24398    }
24399
24400  /* If we are using RS6000_PIC_OFFSET_TABLE_REGNUM, we need to set it up.  */
24401  if (!TARGET_SINGLE_PIC_BASE
24402      && ((TARGET_TOC && TARGET_MINIMAL_TOC && get_pool_size () != 0)
24403	  || (DEFAULT_ABI == ABI_V4
24404	      && (flag_pic == 1 || (flag_pic && TARGET_SECURE_PLT))
24405	      && df_regs_ever_live_p (RS6000_PIC_OFFSET_TABLE_REGNUM))))
24406    {
24407      /* If emit_load_toc_table will use the link register, we need to save
24408	 it.  We use R12 for this purpose because emit_load_toc_table
24409	 can use register 0.  This allows us to use a plain 'blr' to return
24410	 from the procedure more often.  */
24411      int save_LR_around_toc_setup = (TARGET_ELF
24412				      && DEFAULT_ABI == ABI_V4
24413				      && flag_pic
24414				      && ! info->lr_save_p
24415				      && EDGE_COUNT (EXIT_BLOCK_PTR_FOR_FN (cfun)->preds) > 0);
24416      if (save_LR_around_toc_setup)
24417	{
24418	  rtx lr = gen_rtx_REG (Pmode, LR_REGNO);
24419	  rtx tmp = gen_rtx_REG (Pmode, 12);
24420
24421	  insn = emit_move_insn (tmp, lr);
24422	  RTX_FRAME_RELATED_P (insn) = 1;
24423
24424	  rs6000_emit_load_toc_table (TRUE);
24425
24426	  insn = emit_move_insn (lr, tmp);
24427	  add_reg_note (insn, REG_CFA_RESTORE, lr);
24428	  RTX_FRAME_RELATED_P (insn) = 1;
24429	}
24430      else
24431	rs6000_emit_load_toc_table (TRUE);
24432    }
24433
24434#if TARGET_MACHO
24435  if (!TARGET_SINGLE_PIC_BASE
24436      && DEFAULT_ABI == ABI_DARWIN
24437      && flag_pic && crtl->uses_pic_offset_table)
24438    {
24439      rtx lr = gen_rtx_REG (Pmode, LR_REGNO);
24440      rtx src = gen_rtx_SYMBOL_REF (Pmode, MACHOPIC_FUNCTION_BASE_NAME);
24441
24442      /* Save and restore LR locally around this call (in R0).  */
24443      if (!info->lr_save_p)
24444	emit_move_insn (gen_rtx_REG (Pmode, 0), lr);
24445
24446      emit_insn (gen_load_macho_picbase (src));
24447
24448      emit_move_insn (gen_rtx_REG (Pmode,
24449				   RS6000_PIC_OFFSET_TABLE_REGNUM),
24450		      lr);
24451
24452      if (!info->lr_save_p)
24453	emit_move_insn (lr, gen_rtx_REG (Pmode, 0));
24454    }
24455#endif
24456
24457  /* If we need to, save the TOC register after doing the stack setup.
24458     Do not emit eh frame info for this save.  The unwinder wants info,
24459     conceptually attached to instructions in this function, about
24460     register values in the caller of this function.  This R2 may have
24461     already been changed from the value in the caller.
24462     We don't attempt to write accurate DWARF EH frame info for R2
24463     because code emitted by gcc for a (non-pointer) function call
24464     doesn't save and restore R2.  Instead, R2 is managed out-of-line
24465     by a linker generated plt call stub when the function resides in
24466     a shared library.  This behaviour is costly to describe in DWARF,
24467     both in terms of the size of DWARF info and the time taken in the
24468     unwinder to interpret it.  R2 changes, apart from the
24469     calls_eh_return case earlier in this function, are handled by
24470     linux-unwind.h frob_update_context.  */
24471  if (rs6000_save_toc_in_prologue_p ())
24472    {
24473      rtx reg = gen_rtx_REG (reg_mode, TOC_REGNUM);
24474      emit_insn (gen_frame_store (reg, sp_reg_rtx, RS6000_TOC_SAVE_SLOT));
24475    }
24476}
24477
24478/* Output .extern statements for the save/restore routines we use.  */
24479
24480static void
24481rs6000_output_savres_externs (FILE *file)
24482{
24483  rs6000_stack_t *info = rs6000_stack_info ();
24484
24485  if (TARGET_DEBUG_STACK)
24486    debug_stack_info (info);
24487
24488  /* Write .extern for any function we will call to save and restore
24489     fp values.  */
24490  if (info->first_fp_reg_save < 64
24491      && !TARGET_MACHO
24492      && !TARGET_ELF)
24493    {
24494      char *name;
24495      int regno = info->first_fp_reg_save - 32;
24496
24497      if ((info->savres_strategy & SAVE_INLINE_FPRS) == 0)
24498	{
24499	  bool lr = (info->savres_strategy & SAVE_NOINLINE_FPRS_SAVES_LR) != 0;
24500	  int sel = SAVRES_SAVE | SAVRES_FPR | (lr ? SAVRES_LR : 0);
24501	  name = rs6000_savres_routine_name (info, regno, sel);
24502	  fprintf (file, "\t.extern %s\n", name);
24503	}
24504      if ((info->savres_strategy & REST_INLINE_FPRS) == 0)
24505	{
24506	  bool lr = (info->savres_strategy
24507		     & REST_NOINLINE_FPRS_DOESNT_RESTORE_LR) == 0;
24508	  int sel = SAVRES_FPR | (lr ? SAVRES_LR : 0);
24509	  name = rs6000_savres_routine_name (info, regno, sel);
24510	  fprintf (file, "\t.extern %s\n", name);
24511	}
24512    }
24513}
24514
24515/* Write function prologue.  */
24516
24517static void
24518rs6000_output_function_prologue (FILE *file,
24519				 HOST_WIDE_INT size ATTRIBUTE_UNUSED)
24520{
24521  if (!cfun->is_thunk)
24522    rs6000_output_savres_externs (file);
24523
24524  /* ELFv2 ABI r2 setup code and local entry point.  This must follow
24525     immediately after the global entry point label.  */
24526  if (DEFAULT_ABI == ABI_ELFv2 && cfun->machine->r2_setup_needed)
24527    {
24528      const char *name = XSTR (XEXP (DECL_RTL (current_function_decl), 0), 0);
24529
24530      fprintf (file, "0:\taddis 2,12,.TOC.-0b@ha\n");
24531      fprintf (file, "\taddi 2,2,.TOC.-0b@l\n");
24532
24533      fputs ("\t.localentry\t", file);
24534      assemble_name (file, name);
24535      fputs (",.-", file);
24536      assemble_name (file, name);
24537      fputs ("\n", file);
24538    }
24539
24540  /* Output -mprofile-kernel code.  This needs to be done here instead of
24541     in output_function_profile since it must go after the ELFv2 ABI
24542     local entry point.  */
24543  if (TARGET_PROFILE_KERNEL && crtl->profile)
24544    {
24545      gcc_assert (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2);
24546      gcc_assert (!TARGET_32BIT);
24547
24548      asm_fprintf (file, "\tmflr %s\n", reg_names[0]);
24549      asm_fprintf (file, "\tstd %s,16(%s)\n", reg_names[0], reg_names[1]);
24550
24551      /* In the ELFv2 ABI we have no compiler stack word.  It must be
24552	 the resposibility of _mcount to preserve the static chain
24553	 register if required.  */
24554      if (DEFAULT_ABI != ABI_ELFv2
24555	  && cfun->static_chain_decl != NULL)
24556	{
24557	  asm_fprintf (file, "\tstd %s,24(%s)\n",
24558		       reg_names[STATIC_CHAIN_REGNUM], reg_names[1]);
24559	  fprintf (file, "\tbl %s\n", RS6000_MCOUNT);
24560	  asm_fprintf (file, "\tld %s,24(%s)\n",
24561		       reg_names[STATIC_CHAIN_REGNUM], reg_names[1]);
24562	}
24563      else
24564	fprintf (file, "\tbl %s\n", RS6000_MCOUNT);
24565    }
24566
24567  rs6000_pic_labelno++;
24568}
24569
24570/* Non-zero if vmx regs are restored before the frame pop, zero if
24571   we restore after the pop when possible.  */
24572#define ALWAYS_RESTORE_ALTIVEC_BEFORE_POP 0
24573
24574/* Restoring cr is a two step process: loading a reg from the frame
24575   save, then moving the reg to cr.  For ABI_V4 we must let the
24576   unwinder know that the stack location is no longer valid at or
24577   before the stack deallocation, but we can't emit a cfa_restore for
24578   cr at the stack deallocation like we do for other registers.
24579   The trouble is that it is possible for the move to cr to be
24580   scheduled after the stack deallocation.  So say exactly where cr
24581   is located on each of the two insns.  */
24582
24583static rtx
24584load_cr_save (int regno, rtx frame_reg_rtx, int offset, bool exit_func)
24585{
24586  rtx mem = gen_frame_mem_offset (SImode, frame_reg_rtx, offset);
24587  rtx reg = gen_rtx_REG (SImode, regno);
24588  rtx_insn *insn = emit_move_insn (reg, mem);
24589
24590  if (!exit_func && DEFAULT_ABI == ABI_V4)
24591    {
24592      rtx cr = gen_rtx_REG (SImode, CR2_REGNO);
24593      rtx set = gen_rtx_SET (VOIDmode, reg, cr);
24594
24595      add_reg_note (insn, REG_CFA_REGISTER, set);
24596      RTX_FRAME_RELATED_P (insn) = 1;
24597    }
24598  return reg;
24599}
24600
24601/* Reload CR from REG.  */
24602
24603static void
24604restore_saved_cr (rtx reg, int using_mfcr_multiple, bool exit_func)
24605{
24606  int count = 0;
24607  int i;
24608
24609  if (using_mfcr_multiple)
24610    {
24611      for (i = 0; i < 8; i++)
24612	if (save_reg_p (CR0_REGNO + i))
24613	  count++;
24614      gcc_assert (count);
24615    }
24616
24617  if (using_mfcr_multiple && count > 1)
24618    {
24619      rtx_insn *insn;
24620      rtvec p;
24621      int ndx;
24622
24623      p = rtvec_alloc (count);
24624
24625      ndx = 0;
24626      for (i = 0; i < 8; i++)
24627	if (save_reg_p (CR0_REGNO + i))
24628	  {
24629	    rtvec r = rtvec_alloc (2);
24630	    RTVEC_ELT (r, 0) = reg;
24631	    RTVEC_ELT (r, 1) = GEN_INT (1 << (7-i));
24632	    RTVEC_ELT (p, ndx) =
24633	      gen_rtx_SET (VOIDmode, gen_rtx_REG (CCmode, CR0_REGNO + i),
24634			   gen_rtx_UNSPEC (CCmode, r, UNSPEC_MOVESI_TO_CR));
24635	    ndx++;
24636	  }
24637      insn = emit_insn (gen_rtx_PARALLEL (VOIDmode, p));
24638      gcc_assert (ndx == count);
24639
24640      /* For the ELFv2 ABI we generate a CFA_RESTORE for each
24641	 CR field separately.  */
24642      if (!exit_func && DEFAULT_ABI == ABI_ELFv2 && flag_shrink_wrap)
24643	{
24644	  for (i = 0; i < 8; i++)
24645	    if (save_reg_p (CR0_REGNO + i))
24646	      add_reg_note (insn, REG_CFA_RESTORE,
24647			    gen_rtx_REG (SImode, CR0_REGNO + i));
24648
24649	  RTX_FRAME_RELATED_P (insn) = 1;
24650	}
24651    }
24652  else
24653    for (i = 0; i < 8; i++)
24654      if (save_reg_p (CR0_REGNO + i))
24655	{
24656	  rtx insn = emit_insn (gen_movsi_to_cr_one
24657				 (gen_rtx_REG (CCmode, CR0_REGNO + i), reg));
24658
24659	  /* For the ELFv2 ABI we generate a CFA_RESTORE for each
24660	     CR field separately, attached to the insn that in fact
24661	     restores this particular CR field.  */
24662	  if (!exit_func && DEFAULT_ABI == ABI_ELFv2 && flag_shrink_wrap)
24663	    {
24664	      add_reg_note (insn, REG_CFA_RESTORE,
24665			    gen_rtx_REG (SImode, CR0_REGNO + i));
24666
24667	      RTX_FRAME_RELATED_P (insn) = 1;
24668	    }
24669	}
24670
24671  /* For other ABIs, we just generate a single CFA_RESTORE for CR2.  */
24672  if (!exit_func && DEFAULT_ABI != ABI_ELFv2
24673      && (DEFAULT_ABI == ABI_V4 || flag_shrink_wrap))
24674    {
24675      rtx_insn *insn = get_last_insn ();
24676      rtx cr = gen_rtx_REG (SImode, CR2_REGNO);
24677
24678      add_reg_note (insn, REG_CFA_RESTORE, cr);
24679      RTX_FRAME_RELATED_P (insn) = 1;
24680    }
24681}
24682
24683/* Like cr, the move to lr instruction can be scheduled after the
24684   stack deallocation, but unlike cr, its stack frame save is still
24685   valid.  So we only need to emit the cfa_restore on the correct
24686   instruction.  */
24687
24688static void
24689load_lr_save (int regno, rtx frame_reg_rtx, int offset)
24690{
24691  rtx mem = gen_frame_mem_offset (Pmode, frame_reg_rtx, offset);
24692  rtx reg = gen_rtx_REG (Pmode, regno);
24693
24694  emit_move_insn (reg, mem);
24695}
24696
24697static void
24698restore_saved_lr (int regno, bool exit_func)
24699{
24700  rtx reg = gen_rtx_REG (Pmode, regno);
24701  rtx lr = gen_rtx_REG (Pmode, LR_REGNO);
24702  rtx_insn *insn = emit_move_insn (lr, reg);
24703
24704  if (!exit_func && flag_shrink_wrap)
24705    {
24706      add_reg_note (insn, REG_CFA_RESTORE, lr);
24707      RTX_FRAME_RELATED_P (insn) = 1;
24708    }
24709}
24710
24711static rtx
24712add_crlr_cfa_restore (const rs6000_stack_t *info, rtx cfa_restores)
24713{
24714  if (DEFAULT_ABI == ABI_ELFv2)
24715    {
24716      int i;
24717      for (i = 0; i < 8; i++)
24718	if (save_reg_p (CR0_REGNO + i))
24719	  {
24720	    rtx cr = gen_rtx_REG (SImode, CR0_REGNO + i);
24721	    cfa_restores = alloc_reg_note (REG_CFA_RESTORE, cr,
24722					   cfa_restores);
24723	  }
24724    }
24725  else if (info->cr_save_p)
24726    cfa_restores = alloc_reg_note (REG_CFA_RESTORE,
24727				   gen_rtx_REG (SImode, CR2_REGNO),
24728				   cfa_restores);
24729
24730  if (info->lr_save_p)
24731    cfa_restores = alloc_reg_note (REG_CFA_RESTORE,
24732				   gen_rtx_REG (Pmode, LR_REGNO),
24733				   cfa_restores);
24734  return cfa_restores;
24735}
24736
24737/* Return true if OFFSET from stack pointer can be clobbered by signals.
24738   V.4 doesn't have any stack cushion, AIX ABIs have 220 or 288 bytes
24739   below stack pointer not cloberred by signals.  */
24740
24741static inline bool
24742offset_below_red_zone_p (HOST_WIDE_INT offset)
24743{
24744  return offset < (DEFAULT_ABI == ABI_V4
24745		   ? 0
24746		   : TARGET_32BIT ? -220 : -288);
24747}
24748
24749/* Append CFA_RESTORES to any existing REG_NOTES on the last insn.  */
24750
24751static void
24752emit_cfa_restores (rtx cfa_restores)
24753{
24754  rtx_insn *insn = get_last_insn ();
24755  rtx *loc = &REG_NOTES (insn);
24756
24757  while (*loc)
24758    loc = &XEXP (*loc, 1);
24759  *loc = cfa_restores;
24760  RTX_FRAME_RELATED_P (insn) = 1;
24761}
24762
24763/* Emit function epilogue as insns.  */
24764
24765void
24766rs6000_emit_epilogue (int sibcall)
24767{
24768  rs6000_stack_t *info;
24769  int restoring_GPRs_inline;
24770  int restoring_FPRs_inline;
24771  int using_load_multiple;
24772  int using_mtcr_multiple;
24773  int use_backchain_to_restore_sp;
24774  int restore_lr;
24775  int strategy;
24776  HOST_WIDE_INT frame_off = 0;
24777  rtx sp_reg_rtx = gen_rtx_REG (Pmode, 1);
24778  rtx frame_reg_rtx = sp_reg_rtx;
24779  rtx cfa_restores = NULL_RTX;
24780  rtx insn;
24781  rtx cr_save_reg = NULL_RTX;
24782  machine_mode reg_mode = Pmode;
24783  int reg_size = TARGET_32BIT ? 4 : 8;
24784  int i;
24785  bool exit_func;
24786  unsigned ptr_regno;
24787
24788  info = rs6000_stack_info ();
24789
24790  if (TARGET_SPE_ABI && info->spe_64bit_regs_used != 0)
24791    {
24792      reg_mode = V2SImode;
24793      reg_size = 8;
24794    }
24795
24796  strategy = info->savres_strategy;
24797  using_load_multiple = strategy & SAVRES_MULTIPLE;
24798  restoring_FPRs_inline = sibcall || (strategy & REST_INLINE_FPRS);
24799  restoring_GPRs_inline = sibcall || (strategy & REST_INLINE_GPRS);
24800  using_mtcr_multiple = (rs6000_cpu == PROCESSOR_PPC601
24801			 || rs6000_cpu == PROCESSOR_PPC603
24802			 || rs6000_cpu == PROCESSOR_PPC750
24803			 || optimize_size);
24804  /* Restore via the backchain when we have a large frame, since this
24805     is more efficient than an addis, addi pair.  The second condition
24806     here will not trigger at the moment;  We don't actually need a
24807     frame pointer for alloca, but the generic parts of the compiler
24808     give us one anyway.  */
24809  use_backchain_to_restore_sp = (info->total_size > 32767 - info->lr_save_offset
24810				 || (cfun->calls_alloca
24811				     && !frame_pointer_needed));
24812  restore_lr = (info->lr_save_p
24813		&& (restoring_FPRs_inline
24814		    || (strategy & REST_NOINLINE_FPRS_DOESNT_RESTORE_LR))
24815		&& (restoring_GPRs_inline
24816		    || info->first_fp_reg_save < 64));
24817
24818  if (WORLD_SAVE_P (info))
24819    {
24820      int i, j;
24821      char rname[30];
24822      const char *alloc_rname;
24823      rtvec p;
24824
24825      /* eh_rest_world_r10 will return to the location saved in the LR
24826	 stack slot (which is not likely to be our caller.)
24827	 Input: R10 -- stack adjustment.  Clobbers R0, R11, R12, R7, R8.
24828	 rest_world is similar, except any R10 parameter is ignored.
24829	 The exception-handling stuff that was here in 2.95 is no
24830	 longer necessary.  */
24831
24832      p = rtvec_alloc (9
24833		       + 1
24834		       + 32 - info->first_gp_reg_save
24835		       + LAST_ALTIVEC_REGNO + 1 - info->first_altivec_reg_save
24836		       + 63 + 1 - info->first_fp_reg_save);
24837
24838      strcpy (rname, ((crtl->calls_eh_return) ?
24839		      "*eh_rest_world_r10" : "*rest_world"));
24840      alloc_rname = ggc_strdup (rname);
24841
24842      j = 0;
24843      RTVEC_ELT (p, j++) = ret_rtx;
24844      RTVEC_ELT (p, j++) = gen_rtx_USE (VOIDmode,
24845					gen_rtx_REG (Pmode,
24846						     LR_REGNO));
24847      RTVEC_ELT (p, j++)
24848	= gen_rtx_USE (VOIDmode, gen_rtx_SYMBOL_REF (Pmode, alloc_rname));
24849      /* The instruction pattern requires a clobber here;
24850	 it is shared with the restVEC helper. */
24851      RTVEC_ELT (p, j++)
24852	= gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (Pmode, 11));
24853
24854      {
24855	/* CR register traditionally saved as CR2.  */
24856	rtx reg = gen_rtx_REG (SImode, CR2_REGNO);
24857	RTVEC_ELT (p, j++)
24858	  = gen_frame_load (reg, frame_reg_rtx, info->cr_save_offset);
24859	if (flag_shrink_wrap)
24860	  {
24861	    cfa_restores = alloc_reg_note (REG_CFA_RESTORE,
24862					   gen_rtx_REG (Pmode, LR_REGNO),
24863					   cfa_restores);
24864	    cfa_restores = alloc_reg_note (REG_CFA_RESTORE, reg, cfa_restores);
24865	  }
24866      }
24867
24868      for (i = 0; i < 32 - info->first_gp_reg_save; i++)
24869	{
24870	  rtx reg = gen_rtx_REG (reg_mode, info->first_gp_reg_save + i);
24871	  RTVEC_ELT (p, j++)
24872	    = gen_frame_load (reg,
24873			      frame_reg_rtx, info->gp_save_offset + reg_size * i);
24874	  if (flag_shrink_wrap)
24875	    cfa_restores = alloc_reg_note (REG_CFA_RESTORE, reg, cfa_restores);
24876	}
24877      for (i = 0; info->first_altivec_reg_save + i <= LAST_ALTIVEC_REGNO; i++)
24878	{
24879	  rtx reg = gen_rtx_REG (V4SImode, info->first_altivec_reg_save + i);
24880	  RTVEC_ELT (p, j++)
24881	    = gen_frame_load (reg,
24882			      frame_reg_rtx, info->altivec_save_offset + 16 * i);
24883	  if (flag_shrink_wrap)
24884	    cfa_restores = alloc_reg_note (REG_CFA_RESTORE, reg, cfa_restores);
24885	}
24886      for (i = 0; info->first_fp_reg_save + i <= 63; i++)
24887	{
24888	  rtx reg = gen_rtx_REG ((TARGET_HARD_FLOAT && TARGET_DOUBLE_FLOAT
24889				  ? DFmode : SFmode),
24890				 info->first_fp_reg_save + i);
24891	  RTVEC_ELT (p, j++)
24892	    = gen_frame_load (reg, frame_reg_rtx, info->fp_save_offset + 8 * i);
24893	  if (flag_shrink_wrap)
24894	    cfa_restores = alloc_reg_note (REG_CFA_RESTORE, reg, cfa_restores);
24895	}
24896      RTVEC_ELT (p, j++)
24897	= gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (Pmode, 0));
24898      RTVEC_ELT (p, j++)
24899	= gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (SImode, 12));
24900      RTVEC_ELT (p, j++)
24901	= gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (SImode, 7));
24902      RTVEC_ELT (p, j++)
24903	= gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (SImode, 8));
24904      RTVEC_ELT (p, j++)
24905	= gen_rtx_USE (VOIDmode, gen_rtx_REG (SImode, 10));
24906      insn = emit_jump_insn (gen_rtx_PARALLEL (VOIDmode, p));
24907
24908      if (flag_shrink_wrap)
24909	{
24910	  REG_NOTES (insn) = cfa_restores;
24911	  add_reg_note (insn, REG_CFA_DEF_CFA, sp_reg_rtx);
24912	  RTX_FRAME_RELATED_P (insn) = 1;
24913	}
24914      return;
24915    }
24916
24917  /* frame_reg_rtx + frame_off points to the top of this stack frame.  */
24918  if (info->push_p)
24919    frame_off = info->total_size;
24920
24921  /* Restore AltiVec registers if we must do so before adjusting the
24922     stack.  */
24923  if (TARGET_ALTIVEC_ABI
24924      && info->altivec_size != 0
24925      && (ALWAYS_RESTORE_ALTIVEC_BEFORE_POP
24926	  || (DEFAULT_ABI != ABI_V4
24927	      && offset_below_red_zone_p (info->altivec_save_offset))))
24928    {
24929      int i;
24930      int scratch_regno = ptr_regno_for_savres (SAVRES_VR);
24931
24932      gcc_checking_assert (scratch_regno == 11 || scratch_regno == 12);
24933      if (use_backchain_to_restore_sp)
24934	{
24935	  int frame_regno = 11;
24936
24937	  if ((strategy & REST_INLINE_VRS) == 0)
24938	    {
24939	      /* Of r11 and r12, select the one not clobbered by an
24940		 out-of-line restore function for the frame register.  */
24941	      frame_regno = 11 + 12 - scratch_regno;
24942	    }
24943	  frame_reg_rtx = gen_rtx_REG (Pmode, frame_regno);
24944	  emit_move_insn (frame_reg_rtx,
24945			  gen_rtx_MEM (Pmode, sp_reg_rtx));
24946	  frame_off = 0;
24947	}
24948      else if (frame_pointer_needed)
24949	frame_reg_rtx = hard_frame_pointer_rtx;
24950
24951      if ((strategy & REST_INLINE_VRS) == 0)
24952	{
24953	  int end_save = info->altivec_save_offset + info->altivec_size;
24954	  int ptr_off;
24955	  rtx ptr_reg = gen_rtx_REG (Pmode, 0);
24956	  rtx scratch_reg = gen_rtx_REG (Pmode, scratch_regno);
24957
24958	  if (end_save + frame_off != 0)
24959	    {
24960	      rtx offset = GEN_INT (end_save + frame_off);
24961
24962	      emit_insn (gen_add3_insn (ptr_reg, frame_reg_rtx, offset));
24963	    }
24964	  else
24965	    emit_move_insn (ptr_reg, frame_reg_rtx);
24966
24967	  ptr_off = -end_save;
24968	  insn = rs6000_emit_savres_rtx (info, scratch_reg,
24969					 info->altivec_save_offset + ptr_off,
24970					 0, V4SImode, SAVRES_VR);
24971	}
24972      else
24973	{
24974	  for (i = info->first_altivec_reg_save; i <= LAST_ALTIVEC_REGNO; ++i)
24975	    if (info->vrsave_mask & ALTIVEC_REG_BIT (i))
24976	      {
24977		rtx addr, areg, mem, reg;
24978
24979		areg = gen_rtx_REG (Pmode, 0);
24980		emit_move_insn
24981		  (areg, GEN_INT (info->altivec_save_offset
24982				  + frame_off
24983				  + 16 * (i - info->first_altivec_reg_save)));
24984
24985		/* AltiVec addressing mode is [reg+reg].  */
24986		addr = gen_rtx_PLUS (Pmode, frame_reg_rtx, areg);
24987		mem = gen_frame_mem (V4SImode, addr);
24988
24989		reg = gen_rtx_REG (V4SImode, i);
24990		/* Rather than emitting a generic move, force use of the
24991		   lvx instruction, which we always want.  In particular
24992		   we don't want lxvd2x/xxpermdi for little endian.  */
24993		(void) emit_insn (gen_altivec_lvx_v4si_internal (reg, mem));
24994	      }
24995	}
24996
24997      for (i = info->first_altivec_reg_save; i <= LAST_ALTIVEC_REGNO; ++i)
24998	if (((strategy & REST_INLINE_VRS) == 0
24999	     || (info->vrsave_mask & ALTIVEC_REG_BIT (i)) != 0)
25000	    && (flag_shrink_wrap
25001		|| (offset_below_red_zone_p
25002		    (info->altivec_save_offset
25003		     + 16 * (i - info->first_altivec_reg_save)))))
25004	  {
25005	    rtx reg = gen_rtx_REG (V4SImode, i);
25006	    cfa_restores = alloc_reg_note (REG_CFA_RESTORE, reg, cfa_restores);
25007	  }
25008    }
25009
25010  /* Restore VRSAVE if we must do so before adjusting the stack.  */
25011  if (TARGET_ALTIVEC
25012      && TARGET_ALTIVEC_VRSAVE
25013      && info->vrsave_mask != 0
25014      && (ALWAYS_RESTORE_ALTIVEC_BEFORE_POP
25015	  || (DEFAULT_ABI != ABI_V4
25016	      && offset_below_red_zone_p (info->vrsave_save_offset))))
25017    {
25018      rtx reg;
25019
25020      if (frame_reg_rtx == sp_reg_rtx)
25021	{
25022	  if (use_backchain_to_restore_sp)
25023	    {
25024	      frame_reg_rtx = gen_rtx_REG (Pmode, 11);
25025	      emit_move_insn (frame_reg_rtx,
25026			      gen_rtx_MEM (Pmode, sp_reg_rtx));
25027	      frame_off = 0;
25028	    }
25029	  else if (frame_pointer_needed)
25030	    frame_reg_rtx = hard_frame_pointer_rtx;
25031	}
25032
25033      reg = gen_rtx_REG (SImode, 12);
25034      emit_insn (gen_frame_load (reg, frame_reg_rtx,
25035				 info->vrsave_save_offset + frame_off));
25036
25037      emit_insn (generate_set_vrsave (reg, info, 1));
25038    }
25039
25040  insn = NULL_RTX;
25041  /* If we have a large stack frame, restore the old stack pointer
25042     using the backchain.  */
25043  if (use_backchain_to_restore_sp)
25044    {
25045      if (frame_reg_rtx == sp_reg_rtx)
25046	{
25047	  /* Under V.4, don't reset the stack pointer until after we're done
25048	     loading the saved registers.  */
25049	  if (DEFAULT_ABI == ABI_V4)
25050	    frame_reg_rtx = gen_rtx_REG (Pmode, 11);
25051
25052	  insn = emit_move_insn (frame_reg_rtx,
25053				 gen_rtx_MEM (Pmode, sp_reg_rtx));
25054	  frame_off = 0;
25055	}
25056      else if (ALWAYS_RESTORE_ALTIVEC_BEFORE_POP
25057	       && DEFAULT_ABI == ABI_V4)
25058	/* frame_reg_rtx has been set up by the altivec restore.  */
25059	;
25060      else
25061	{
25062	  insn = emit_move_insn (sp_reg_rtx, frame_reg_rtx);
25063	  frame_reg_rtx = sp_reg_rtx;
25064	}
25065    }
25066  /* If we have a frame pointer, we can restore the old stack pointer
25067     from it.  */
25068  else if (frame_pointer_needed)
25069    {
25070      frame_reg_rtx = sp_reg_rtx;
25071      if (DEFAULT_ABI == ABI_V4)
25072	frame_reg_rtx = gen_rtx_REG (Pmode, 11);
25073      /* Prevent reordering memory accesses against stack pointer restore.  */
25074      else if (cfun->calls_alloca
25075	       || offset_below_red_zone_p (-info->total_size))
25076	rs6000_emit_stack_tie (frame_reg_rtx, true);
25077
25078      insn = emit_insn (gen_add3_insn (frame_reg_rtx, hard_frame_pointer_rtx,
25079				       GEN_INT (info->total_size)));
25080      frame_off = 0;
25081    }
25082  else if (info->push_p
25083	   && DEFAULT_ABI != ABI_V4
25084	   && !crtl->calls_eh_return)
25085    {
25086      /* Prevent reordering memory accesses against stack pointer restore.  */
25087      if (cfun->calls_alloca
25088	  || offset_below_red_zone_p (-info->total_size))
25089	rs6000_emit_stack_tie (frame_reg_rtx, false);
25090      insn = emit_insn (gen_add3_insn (sp_reg_rtx, sp_reg_rtx,
25091				       GEN_INT (info->total_size)));
25092      frame_off = 0;
25093    }
25094  if (insn && frame_reg_rtx == sp_reg_rtx)
25095    {
25096      if (cfa_restores)
25097	{
25098	  REG_NOTES (insn) = cfa_restores;
25099	  cfa_restores = NULL_RTX;
25100	}
25101      add_reg_note (insn, REG_CFA_DEF_CFA, sp_reg_rtx);
25102      RTX_FRAME_RELATED_P (insn) = 1;
25103    }
25104
25105  /* Restore AltiVec registers if we have not done so already.  */
25106  if (!ALWAYS_RESTORE_ALTIVEC_BEFORE_POP
25107      && TARGET_ALTIVEC_ABI
25108      && info->altivec_size != 0
25109      && (DEFAULT_ABI == ABI_V4
25110	  || !offset_below_red_zone_p (info->altivec_save_offset)))
25111    {
25112      int i;
25113
25114      if ((strategy & REST_INLINE_VRS) == 0)
25115	{
25116	  int end_save = info->altivec_save_offset + info->altivec_size;
25117	  int ptr_off;
25118	  rtx ptr_reg = gen_rtx_REG (Pmode, 0);
25119	  int scratch_regno = ptr_regno_for_savres (SAVRES_VR);
25120	  rtx scratch_reg = gen_rtx_REG (Pmode, scratch_regno);
25121
25122	  if (end_save + frame_off != 0)
25123	    {
25124	      rtx offset = GEN_INT (end_save + frame_off);
25125
25126	      emit_insn (gen_add3_insn (ptr_reg, frame_reg_rtx, offset));
25127	    }
25128	  else
25129	    emit_move_insn (ptr_reg, frame_reg_rtx);
25130
25131	  ptr_off = -end_save;
25132	  insn = rs6000_emit_savres_rtx (info, scratch_reg,
25133					 info->altivec_save_offset + ptr_off,
25134					 0, V4SImode, SAVRES_VR);
25135	  if (REGNO (frame_reg_rtx) == REGNO (scratch_reg))
25136	    {
25137	      /* Frame reg was clobbered by out-of-line save.  Restore it
25138		 from ptr_reg, and if we are calling out-of-line gpr or
25139		 fpr restore set up the correct pointer and offset.  */
25140	      unsigned newptr_regno = 1;
25141	      if (!restoring_GPRs_inline)
25142		{
25143		  bool lr = info->gp_save_offset + info->gp_size == 0;
25144		  int sel = SAVRES_GPR | (lr ? SAVRES_LR : 0);
25145		  newptr_regno = ptr_regno_for_savres (sel);
25146		  end_save = info->gp_save_offset + info->gp_size;
25147		}
25148	      else if (!restoring_FPRs_inline)
25149		{
25150		  bool lr = !(strategy & REST_NOINLINE_FPRS_DOESNT_RESTORE_LR);
25151		  int sel = SAVRES_FPR | (lr ? SAVRES_LR : 0);
25152		  newptr_regno = ptr_regno_for_savres (sel);
25153		  end_save = info->fp_save_offset + info->fp_size;
25154		}
25155
25156	      if (newptr_regno != 1 && REGNO (frame_reg_rtx) != newptr_regno)
25157		frame_reg_rtx = gen_rtx_REG (Pmode, newptr_regno);
25158
25159	      if (end_save + ptr_off != 0)
25160		{
25161		  rtx offset = GEN_INT (end_save + ptr_off);
25162
25163		  frame_off = -end_save;
25164		  if (TARGET_32BIT)
25165		    emit_insn (gen_addsi3_carry (frame_reg_rtx,
25166						 ptr_reg, offset));
25167		  else
25168		    emit_insn (gen_adddi3_carry (frame_reg_rtx,
25169						 ptr_reg, offset));
25170		}
25171	      else
25172		{
25173		  frame_off = ptr_off;
25174		  emit_move_insn (frame_reg_rtx, ptr_reg);
25175		}
25176	    }
25177	}
25178      else
25179	{
25180	  for (i = info->first_altivec_reg_save; i <= LAST_ALTIVEC_REGNO; ++i)
25181	    if (info->vrsave_mask & ALTIVEC_REG_BIT (i))
25182	      {
25183		rtx addr, areg, mem, reg;
25184
25185		areg = gen_rtx_REG (Pmode, 0);
25186		emit_move_insn
25187		  (areg, GEN_INT (info->altivec_save_offset
25188				  + frame_off
25189				  + 16 * (i - info->first_altivec_reg_save)));
25190
25191		/* AltiVec addressing mode is [reg+reg].  */
25192		addr = gen_rtx_PLUS (Pmode, frame_reg_rtx, areg);
25193		mem = gen_frame_mem (V4SImode, addr);
25194
25195		reg = gen_rtx_REG (V4SImode, i);
25196		/* Rather than emitting a generic move, force use of the
25197		   lvx instruction, which we always want.  In particular
25198		   we don't want lxvd2x/xxpermdi for little endian.  */
25199		(void) emit_insn (gen_altivec_lvx_v4si_internal (reg, mem));
25200	      }
25201	}
25202
25203      for (i = info->first_altivec_reg_save; i <= LAST_ALTIVEC_REGNO; ++i)
25204	if (((strategy & REST_INLINE_VRS) == 0
25205	     || (info->vrsave_mask & ALTIVEC_REG_BIT (i)) != 0)
25206	    && (DEFAULT_ABI == ABI_V4 || flag_shrink_wrap))
25207	  {
25208	    rtx reg = gen_rtx_REG (V4SImode, i);
25209	    cfa_restores = alloc_reg_note (REG_CFA_RESTORE, reg, cfa_restores);
25210	  }
25211    }
25212
25213  /* Restore VRSAVE if we have not done so already.  */
25214  if (!ALWAYS_RESTORE_ALTIVEC_BEFORE_POP
25215      && TARGET_ALTIVEC
25216      && TARGET_ALTIVEC_VRSAVE
25217      && info->vrsave_mask != 0
25218      && (DEFAULT_ABI == ABI_V4
25219	  || !offset_below_red_zone_p (info->vrsave_save_offset)))
25220    {
25221      rtx reg;
25222
25223      reg = gen_rtx_REG (SImode, 12);
25224      emit_insn (gen_frame_load (reg, frame_reg_rtx,
25225				 info->vrsave_save_offset + frame_off));
25226
25227      emit_insn (generate_set_vrsave (reg, info, 1));
25228    }
25229
25230  /* If we exit by an out-of-line restore function on ABI_V4 then that
25231     function will deallocate the stack, so we don't need to worry
25232     about the unwinder restoring cr from an invalid stack frame
25233     location.  */
25234  exit_func = (!restoring_FPRs_inline
25235	       || (!restoring_GPRs_inline
25236		   && info->first_fp_reg_save == 64));
25237
25238  /* In the ELFv2 ABI we need to restore all call-saved CR fields from
25239     *separate* slots if the routine calls __builtin_eh_return, so
25240     that they can be independently restored by the unwinder.  */
25241  if (DEFAULT_ABI == ABI_ELFv2 && crtl->calls_eh_return)
25242    {
25243      int i, cr_off = info->ehcr_offset;
25244
25245      for (i = 0; i < 8; i++)
25246	if (!call_used_regs[CR0_REGNO + i])
25247	  {
25248	    rtx reg = gen_rtx_REG (SImode, 0);
25249	    emit_insn (gen_frame_load (reg, frame_reg_rtx,
25250				       cr_off + frame_off));
25251
25252	    insn = emit_insn (gen_movsi_to_cr_one
25253				(gen_rtx_REG (CCmode, CR0_REGNO + i), reg));
25254
25255	    if (!exit_func && flag_shrink_wrap)
25256	      {
25257		add_reg_note (insn, REG_CFA_RESTORE,
25258			      gen_rtx_REG (SImode, CR0_REGNO + i));
25259
25260		RTX_FRAME_RELATED_P (insn) = 1;
25261	      }
25262
25263	    cr_off += reg_size;
25264	  }
25265    }
25266
25267  /* Get the old lr if we saved it.  If we are restoring registers
25268     out-of-line, then the out-of-line routines can do this for us.  */
25269  if (restore_lr && restoring_GPRs_inline)
25270    load_lr_save (0, frame_reg_rtx, info->lr_save_offset + frame_off);
25271
25272  /* Get the old cr if we saved it.  */
25273  if (info->cr_save_p)
25274    {
25275      unsigned cr_save_regno = 12;
25276
25277      if (!restoring_GPRs_inline)
25278	{
25279	  /* Ensure we don't use the register used by the out-of-line
25280	     gpr register restore below.  */
25281	  bool lr = info->gp_save_offset + info->gp_size == 0;
25282	  int sel = SAVRES_GPR | (lr ? SAVRES_LR : 0);
25283	  int gpr_ptr_regno = ptr_regno_for_savres (sel);
25284
25285	  if (gpr_ptr_regno == 12)
25286	    cr_save_regno = 11;
25287	  gcc_checking_assert (REGNO (frame_reg_rtx) != cr_save_regno);
25288	}
25289      else if (REGNO (frame_reg_rtx) == 12)
25290	cr_save_regno = 11;
25291
25292      cr_save_reg = load_cr_save (cr_save_regno, frame_reg_rtx,
25293				  info->cr_save_offset + frame_off,
25294				  exit_func);
25295    }
25296
25297  /* Set LR here to try to overlap restores below.  */
25298  if (restore_lr && restoring_GPRs_inline)
25299    restore_saved_lr (0, exit_func);
25300
25301  /* Load exception handler data registers, if needed.  */
25302  if (crtl->calls_eh_return)
25303    {
25304      unsigned int i, regno;
25305
25306      if (TARGET_AIX)
25307	{
25308	  rtx reg = gen_rtx_REG (reg_mode, 2);
25309	  emit_insn (gen_frame_load (reg, frame_reg_rtx,
25310				     frame_off + RS6000_TOC_SAVE_SLOT));
25311	}
25312
25313      for (i = 0; ; ++i)
25314	{
25315	  rtx mem;
25316
25317	  regno = EH_RETURN_DATA_REGNO (i);
25318	  if (regno == INVALID_REGNUM)
25319	    break;
25320
25321	  /* Note: possible use of r0 here to address SPE regs.  */
25322	  mem = gen_frame_mem_offset (reg_mode, frame_reg_rtx,
25323				      info->ehrd_offset + frame_off
25324				      + reg_size * (int) i);
25325
25326	  emit_move_insn (gen_rtx_REG (reg_mode, regno), mem);
25327	}
25328    }
25329
25330  /* Restore GPRs.  This is done as a PARALLEL if we are using
25331     the load-multiple instructions.  */
25332  if (TARGET_SPE_ABI
25333      && info->spe_64bit_regs_used
25334      && info->first_gp_reg_save != 32)
25335    {
25336      /* Determine whether we can address all of the registers that need
25337	 to be saved with an offset from frame_reg_rtx that fits in
25338	 the small const field for SPE memory instructions.  */
25339      int spe_regs_addressable
25340	= (SPE_CONST_OFFSET_OK (info->spe_gp_save_offset + frame_off
25341				+ reg_size * (32 - info->first_gp_reg_save - 1))
25342	   && restoring_GPRs_inline);
25343
25344      if (!spe_regs_addressable)
25345	{
25346	  int ool_adjust = 0;
25347	  rtx old_frame_reg_rtx = frame_reg_rtx;
25348	  /* Make r11 point to the start of the SPE save area.  We worried about
25349	     not clobbering it when we were saving registers in the prologue.
25350	     There's no need to worry here because the static chain is passed
25351	     anew to every function.  */
25352
25353	  if (!restoring_GPRs_inline)
25354	    ool_adjust = 8 * (info->first_gp_reg_save - FIRST_SAVED_GP_REGNO);
25355	  frame_reg_rtx = gen_rtx_REG (Pmode, 11);
25356	  emit_insn (gen_addsi3 (frame_reg_rtx, old_frame_reg_rtx,
25357				 GEN_INT (info->spe_gp_save_offset
25358					  + frame_off
25359					  - ool_adjust)));
25360	  /* Keep the invariant that frame_reg_rtx + frame_off points
25361	     at the top of the stack frame.  */
25362	  frame_off = -info->spe_gp_save_offset + ool_adjust;
25363	}
25364
25365      if (restoring_GPRs_inline)
25366	{
25367	  HOST_WIDE_INT spe_offset = info->spe_gp_save_offset + frame_off;
25368
25369	  for (i = 0; i < 32 - info->first_gp_reg_save; i++)
25370	    if (rs6000_reg_live_or_pic_offset_p (info->first_gp_reg_save + i))
25371	      {
25372		rtx offset, addr, mem, reg;
25373
25374		/* We're doing all this to ensure that the immediate offset
25375		   fits into the immediate field of 'evldd'.  */
25376		gcc_assert (SPE_CONST_OFFSET_OK (spe_offset + reg_size * i));
25377
25378		offset = GEN_INT (spe_offset + reg_size * i);
25379		addr = gen_rtx_PLUS (Pmode, frame_reg_rtx, offset);
25380		mem = gen_rtx_MEM (V2SImode, addr);
25381		reg = gen_rtx_REG (reg_mode, info->first_gp_reg_save + i);
25382
25383		emit_move_insn (reg, mem);
25384	      }
25385	}
25386      else
25387	rs6000_emit_savres_rtx (info, frame_reg_rtx,
25388				info->spe_gp_save_offset + frame_off,
25389				info->lr_save_offset + frame_off,
25390				reg_mode,
25391				SAVRES_GPR | SAVRES_LR);
25392    }
25393  else if (!restoring_GPRs_inline)
25394    {
25395      /* We are jumping to an out-of-line function.  */
25396      rtx ptr_reg;
25397      int end_save = info->gp_save_offset + info->gp_size;
25398      bool can_use_exit = end_save == 0;
25399      int sel = SAVRES_GPR | (can_use_exit ? SAVRES_LR : 0);
25400      int ptr_off;
25401
25402      /* Emit stack reset code if we need it.  */
25403      ptr_regno = ptr_regno_for_savres (sel);
25404      ptr_reg = gen_rtx_REG (Pmode, ptr_regno);
25405      if (can_use_exit)
25406	rs6000_emit_stack_reset (info, frame_reg_rtx, frame_off, ptr_regno);
25407      else if (end_save + frame_off != 0)
25408	emit_insn (gen_add3_insn (ptr_reg, frame_reg_rtx,
25409				  GEN_INT (end_save + frame_off)));
25410      else if (REGNO (frame_reg_rtx) != ptr_regno)
25411	emit_move_insn (ptr_reg, frame_reg_rtx);
25412      if (REGNO (frame_reg_rtx) == ptr_regno)
25413	frame_off = -end_save;
25414
25415      if (can_use_exit && info->cr_save_p)
25416	restore_saved_cr (cr_save_reg, using_mtcr_multiple, true);
25417
25418      ptr_off = -end_save;
25419      rs6000_emit_savres_rtx (info, ptr_reg,
25420			      info->gp_save_offset + ptr_off,
25421			      info->lr_save_offset + ptr_off,
25422			      reg_mode, sel);
25423    }
25424  else if (using_load_multiple)
25425    {
25426      rtvec p;
25427      p = rtvec_alloc (32 - info->first_gp_reg_save);
25428      for (i = 0; i < 32 - info->first_gp_reg_save; i++)
25429	RTVEC_ELT (p, i)
25430	  = gen_frame_load (gen_rtx_REG (reg_mode, info->first_gp_reg_save + i),
25431			    frame_reg_rtx,
25432			    info->gp_save_offset + frame_off + reg_size * i);
25433      emit_insn (gen_rtx_PARALLEL (VOIDmode, p));
25434    }
25435  else
25436    {
25437      for (i = 0; i < 32 - info->first_gp_reg_save; i++)
25438	if (rs6000_reg_live_or_pic_offset_p (info->first_gp_reg_save + i))
25439	  emit_insn (gen_frame_load
25440		     (gen_rtx_REG (reg_mode, info->first_gp_reg_save + i),
25441		      frame_reg_rtx,
25442		      info->gp_save_offset + frame_off + reg_size * i));
25443    }
25444
25445  if (DEFAULT_ABI == ABI_V4 || flag_shrink_wrap)
25446    {
25447      /* If the frame pointer was used then we can't delay emitting
25448	 a REG_CFA_DEF_CFA note.  This must happen on the insn that
25449	 restores the frame pointer, r31.  We may have already emitted
25450	 a REG_CFA_DEF_CFA note, but that's OK;  A duplicate is
25451	 discarded by dwarf2cfi.c/dwarf2out.c, and in any case would
25452	 be harmless if emitted.  */
25453      if (frame_pointer_needed)
25454	{
25455	  insn = get_last_insn ();
25456	  add_reg_note (insn, REG_CFA_DEF_CFA,
25457			plus_constant (Pmode, frame_reg_rtx, frame_off));
25458	  RTX_FRAME_RELATED_P (insn) = 1;
25459	}
25460
25461      /* Set up cfa_restores.  We always need these when
25462	 shrink-wrapping.  If not shrink-wrapping then we only need
25463	 the cfa_restore when the stack location is no longer valid.
25464	 The cfa_restores must be emitted on or before the insn that
25465	 invalidates the stack, and of course must not be emitted
25466	 before the insn that actually does the restore.  The latter
25467	 is why it is a bad idea to emit the cfa_restores as a group
25468	 on the last instruction here that actually does a restore:
25469	 That insn may be reordered with respect to others doing
25470	 restores.  */
25471      if (flag_shrink_wrap
25472	  && !restoring_GPRs_inline
25473	  && info->first_fp_reg_save == 64)
25474	cfa_restores = add_crlr_cfa_restore (info, cfa_restores);
25475
25476      for (i = info->first_gp_reg_save; i < 32; i++)
25477	if (!restoring_GPRs_inline
25478	    || using_load_multiple
25479	    || rs6000_reg_live_or_pic_offset_p (i))
25480	  {
25481	    rtx reg = gen_rtx_REG (reg_mode, i);
25482
25483	    cfa_restores = alloc_reg_note (REG_CFA_RESTORE, reg, cfa_restores);
25484	  }
25485    }
25486
25487  if (!restoring_GPRs_inline
25488      && info->first_fp_reg_save == 64)
25489    {
25490      /* We are jumping to an out-of-line function.  */
25491      if (cfa_restores)
25492	emit_cfa_restores (cfa_restores);
25493      return;
25494    }
25495
25496  if (restore_lr && !restoring_GPRs_inline)
25497    {
25498      load_lr_save (0, frame_reg_rtx, info->lr_save_offset + frame_off);
25499      restore_saved_lr (0, exit_func);
25500    }
25501
25502  /* Restore fpr's if we need to do it without calling a function.  */
25503  if (restoring_FPRs_inline)
25504    for (i = 0; i < 64 - info->first_fp_reg_save; i++)
25505      if (save_reg_p (info->first_fp_reg_save + i))
25506	{
25507	  rtx reg = gen_rtx_REG ((TARGET_HARD_FLOAT && TARGET_DOUBLE_FLOAT
25508				  ? DFmode : SFmode),
25509				 info->first_fp_reg_save + i);
25510	  emit_insn (gen_frame_load (reg, frame_reg_rtx,
25511				     info->fp_save_offset + frame_off + 8 * i));
25512	  if (DEFAULT_ABI == ABI_V4 || flag_shrink_wrap)
25513	    cfa_restores = alloc_reg_note (REG_CFA_RESTORE, reg, cfa_restores);
25514	}
25515
25516  /* If we saved cr, restore it here.  Just those that were used.  */
25517  if (info->cr_save_p)
25518    restore_saved_cr (cr_save_reg, using_mtcr_multiple, exit_func);
25519
25520  /* If this is V.4, unwind the stack pointer after all of the loads
25521     have been done, or set up r11 if we are restoring fp out of line.  */
25522  ptr_regno = 1;
25523  if (!restoring_FPRs_inline)
25524    {
25525      bool lr = (strategy & REST_NOINLINE_FPRS_DOESNT_RESTORE_LR) == 0;
25526      int sel = SAVRES_FPR | (lr ? SAVRES_LR : 0);
25527      ptr_regno = ptr_regno_for_savres (sel);
25528    }
25529
25530  insn = rs6000_emit_stack_reset (info, frame_reg_rtx, frame_off, ptr_regno);
25531  if (REGNO (frame_reg_rtx) == ptr_regno)
25532    frame_off = 0;
25533
25534  if (insn && restoring_FPRs_inline)
25535    {
25536      if (cfa_restores)
25537	{
25538	  REG_NOTES (insn) = cfa_restores;
25539	  cfa_restores = NULL_RTX;
25540	}
25541      add_reg_note (insn, REG_CFA_DEF_CFA, sp_reg_rtx);
25542      RTX_FRAME_RELATED_P (insn) = 1;
25543    }
25544
25545  if (crtl->calls_eh_return)
25546    {
25547      rtx sa = EH_RETURN_STACKADJ_RTX;
25548      emit_insn (gen_add3_insn (sp_reg_rtx, sp_reg_rtx, sa));
25549    }
25550
25551  if (!sibcall)
25552    {
25553      rtvec p;
25554      bool lr = (strategy & REST_NOINLINE_FPRS_DOESNT_RESTORE_LR) == 0;
25555      if (! restoring_FPRs_inline)
25556	{
25557	  p = rtvec_alloc (4 + 64 - info->first_fp_reg_save);
25558	  RTVEC_ELT (p, 0) = ret_rtx;
25559	}
25560      else
25561	{
25562	  if (cfa_restores)
25563	    {
25564	      /* We can't hang the cfa_restores off a simple return,
25565		 since the shrink-wrap code sometimes uses an existing
25566		 return.  This means there might be a path from
25567		 pre-prologue code to this return, and dwarf2cfi code
25568		 wants the eh_frame unwinder state to be the same on
25569		 all paths to any point.  So we need to emit the
25570		 cfa_restores before the return.  For -m64 we really
25571		 don't need epilogue cfa_restores at all, except for
25572		 this irritating dwarf2cfi with shrink-wrap
25573		 requirement;  The stack red-zone means eh_frame info
25574		 from the prologue telling the unwinder to restore
25575		 from the stack is perfectly good right to the end of
25576		 the function.  */
25577	      emit_insn (gen_blockage ());
25578	      emit_cfa_restores (cfa_restores);
25579	      cfa_restores = NULL_RTX;
25580	    }
25581	  p = rtvec_alloc (2);
25582	  RTVEC_ELT (p, 0) = simple_return_rtx;
25583	}
25584
25585      RTVEC_ELT (p, 1) = ((restoring_FPRs_inline || !lr)
25586			  ? gen_rtx_USE (VOIDmode,
25587					 gen_rtx_REG (Pmode, LR_REGNO))
25588			  : gen_rtx_CLOBBER (VOIDmode,
25589					     gen_rtx_REG (Pmode, LR_REGNO)));
25590
25591      /* If we have to restore more than two FP registers, branch to the
25592	 restore function.  It will return to our caller.  */
25593      if (! restoring_FPRs_inline)
25594	{
25595	  int i;
25596	  int reg;
25597	  rtx sym;
25598
25599	  if (flag_shrink_wrap)
25600	    cfa_restores = add_crlr_cfa_restore (info, cfa_restores);
25601
25602	  sym = rs6000_savres_routine_sym (info,
25603					   SAVRES_FPR | (lr ? SAVRES_LR : 0));
25604	  RTVEC_ELT (p, 2) = gen_rtx_USE (VOIDmode, sym);
25605	  reg = (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)? 1 : 11;
25606	  RTVEC_ELT (p, 3) = gen_rtx_USE (VOIDmode, gen_rtx_REG (Pmode, reg));
25607
25608	  for (i = 0; i < 64 - info->first_fp_reg_save; i++)
25609	    {
25610	      rtx reg = gen_rtx_REG (DFmode, info->first_fp_reg_save + i);
25611
25612	      RTVEC_ELT (p, i + 4)
25613		= gen_frame_load (reg, sp_reg_rtx, info->fp_save_offset + 8 * i);
25614	      if (flag_shrink_wrap)
25615		cfa_restores = alloc_reg_note (REG_CFA_RESTORE, reg,
25616					       cfa_restores);
25617	    }
25618	}
25619
25620      emit_jump_insn (gen_rtx_PARALLEL (VOIDmode, p));
25621    }
25622
25623  if (cfa_restores)
25624    {
25625      if (sibcall)
25626	/* Ensure the cfa_restores are hung off an insn that won't
25627	   be reordered above other restores.  */
25628	emit_insn (gen_blockage ());
25629
25630      emit_cfa_restores (cfa_restores);
25631    }
25632}
25633
25634/* Write function epilogue.  */
25635
25636static void
25637rs6000_output_function_epilogue (FILE *file,
25638				 HOST_WIDE_INT size ATTRIBUTE_UNUSED)
25639{
25640#if TARGET_MACHO
25641  macho_branch_islands ();
25642  /* Mach-O doesn't support labels at the end of objects, so if
25643     it looks like we might want one, insert a NOP.  */
25644  {
25645    rtx_insn *insn = get_last_insn ();
25646    rtx_insn *deleted_debug_label = NULL;
25647    while (insn
25648	   && NOTE_P (insn)
25649	   && NOTE_KIND (insn) != NOTE_INSN_DELETED_LABEL)
25650      {
25651	/* Don't insert a nop for NOTE_INSN_DELETED_DEBUG_LABEL
25652	   notes only, instead set their CODE_LABEL_NUMBER to -1,
25653	   otherwise there would be code generation differences
25654	   in between -g and -g0.  */
25655	if (NOTE_P (insn) && NOTE_KIND (insn) == NOTE_INSN_DELETED_DEBUG_LABEL)
25656	  deleted_debug_label = insn;
25657	insn = PREV_INSN (insn);
25658      }
25659    if (insn
25660	&& (LABEL_P (insn)
25661	    || (NOTE_P (insn)
25662		&& NOTE_KIND (insn) == NOTE_INSN_DELETED_LABEL)))
25663      fputs ("\tnop\n", file);
25664    else if (deleted_debug_label)
25665      for (insn = deleted_debug_label; insn; insn = NEXT_INSN (insn))
25666	if (NOTE_KIND (insn) == NOTE_INSN_DELETED_DEBUG_LABEL)
25667	  CODE_LABEL_NUMBER (insn) = -1;
25668  }
25669#endif
25670
25671  /* Output a traceback table here.  See /usr/include/sys/debug.h for info
25672     on its format.
25673
25674     We don't output a traceback table if -finhibit-size-directive was
25675     used.  The documentation for -finhibit-size-directive reads
25676     ``don't output a @code{.size} assembler directive, or anything
25677     else that would cause trouble if the function is split in the
25678     middle, and the two halves are placed at locations far apart in
25679     memory.''  The traceback table has this property, since it
25680     includes the offset from the start of the function to the
25681     traceback table itself.
25682
25683     System V.4 Powerpc's (and the embedded ABI derived from it) use a
25684     different traceback table.  */
25685  if ((DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
25686      && ! flag_inhibit_size_directive
25687      && rs6000_traceback != traceback_none && !cfun->is_thunk)
25688    {
25689      const char *fname = NULL;
25690      const char *language_string = lang_hooks.name;
25691      int fixed_parms = 0, float_parms = 0, parm_info = 0;
25692      int i;
25693      int optional_tbtab;
25694      rs6000_stack_t *info = rs6000_stack_info ();
25695
25696      if (rs6000_traceback == traceback_full)
25697	optional_tbtab = 1;
25698      else if (rs6000_traceback == traceback_part)
25699	optional_tbtab = 0;
25700      else
25701	optional_tbtab = !optimize_size && !TARGET_ELF;
25702
25703      if (optional_tbtab)
25704	{
25705	  fname = XSTR (XEXP (DECL_RTL (current_function_decl), 0), 0);
25706	  while (*fname == '.')	/* V.4 encodes . in the name */
25707	    fname++;
25708
25709	  /* Need label immediately before tbtab, so we can compute
25710	     its offset from the function start.  */
25711	  ASM_OUTPUT_INTERNAL_LABEL_PREFIX (file, "LT");
25712	  ASM_OUTPUT_LABEL (file, fname);
25713	}
25714
25715      /* The .tbtab pseudo-op can only be used for the first eight
25716	 expressions, since it can't handle the possibly variable
25717	 length fields that follow.  However, if you omit the optional
25718	 fields, the assembler outputs zeros for all optional fields
25719	 anyways, giving each variable length field is minimum length
25720	 (as defined in sys/debug.h).  Thus we can not use the .tbtab
25721	 pseudo-op at all.  */
25722
25723      /* An all-zero word flags the start of the tbtab, for debuggers
25724	 that have to find it by searching forward from the entry
25725	 point or from the current pc.  */
25726      fputs ("\t.long 0\n", file);
25727
25728      /* Tbtab format type.  Use format type 0.  */
25729      fputs ("\t.byte 0,", file);
25730
25731      /* Language type.  Unfortunately, there does not seem to be any
25732	 official way to discover the language being compiled, so we
25733	 use language_string.
25734	 C is 0.  Fortran is 1.  Pascal is 2.  Ada is 3.  C++ is 9.
25735	 Java is 13.  Objective-C is 14.  Objective-C++ isn't assigned
25736	 a number, so for now use 9.  LTO, Go and JIT aren't assigned numbers
25737	 either, so for now use 0.  */
25738      if (lang_GNU_C ()
25739	  || ! strcmp (language_string, "GNU GIMPLE")
25740	  || ! strcmp (language_string, "GNU Go")
25741	  || ! strcmp (language_string, "libgccjit"))
25742	i = 0;
25743      else if (! strcmp (language_string, "GNU F77")
25744	       || lang_GNU_Fortran ())
25745	i = 1;
25746      else if (! strcmp (language_string, "GNU Pascal"))
25747	i = 2;
25748      else if (! strcmp (language_string, "GNU Ada"))
25749	i = 3;
25750      else if (lang_GNU_CXX ()
25751	       || ! strcmp (language_string, "GNU Objective-C++"))
25752	i = 9;
25753      else if (! strcmp (language_string, "GNU Java"))
25754	i = 13;
25755      else if (! strcmp (language_string, "GNU Objective-C"))
25756	i = 14;
25757      else
25758	gcc_unreachable ();
25759      fprintf (file, "%d,", i);
25760
25761      /* 8 single bit fields: global linkage (not set for C extern linkage,
25762	 apparently a PL/I convention?), out-of-line epilogue/prologue, offset
25763	 from start of procedure stored in tbtab, internal function, function
25764	 has controlled storage, function has no toc, function uses fp,
25765	 function logs/aborts fp operations.  */
25766      /* Assume that fp operations are used if any fp reg must be saved.  */
25767      fprintf (file, "%d,",
25768	       (optional_tbtab << 5) | ((info->first_fp_reg_save != 64) << 1));
25769
25770      /* 6 bitfields: function is interrupt handler, name present in
25771	 proc table, function calls alloca, on condition directives
25772	 (controls stack walks, 3 bits), saves condition reg, saves
25773	 link reg.  */
25774      /* The `function calls alloca' bit seems to be set whenever reg 31 is
25775	 set up as a frame pointer, even when there is no alloca call.  */
25776      fprintf (file, "%d,",
25777	       ((optional_tbtab << 6)
25778		| ((optional_tbtab & frame_pointer_needed) << 5)
25779		| (info->cr_save_p << 1)
25780		| (info->lr_save_p)));
25781
25782      /* 3 bitfields: saves backchain, fixup code, number of fpr saved
25783	 (6 bits).  */
25784      fprintf (file, "%d,",
25785	       (info->push_p << 7) | (64 - info->first_fp_reg_save));
25786
25787      /* 2 bitfields: spare bits (2 bits), number of gpr saved (6 bits).  */
25788      fprintf (file, "%d,", (32 - first_reg_to_save ()));
25789
25790      if (optional_tbtab)
25791	{
25792	  /* Compute the parameter info from the function decl argument
25793	     list.  */
25794	  tree decl;
25795	  int next_parm_info_bit = 31;
25796
25797	  for (decl = DECL_ARGUMENTS (current_function_decl);
25798	       decl; decl = DECL_CHAIN (decl))
25799	    {
25800	      rtx parameter = DECL_INCOMING_RTL (decl);
25801	      machine_mode mode = GET_MODE (parameter);
25802
25803	      if (GET_CODE (parameter) == REG)
25804		{
25805		  if (SCALAR_FLOAT_MODE_P (mode))
25806		    {
25807		      int bits;
25808
25809		      float_parms++;
25810
25811		      switch (mode)
25812			{
25813			case SFmode:
25814			case SDmode:
25815			  bits = 0x2;
25816			  break;
25817
25818			case DFmode:
25819			case DDmode:
25820			case TFmode:
25821			case TDmode:
25822			  bits = 0x3;
25823			  break;
25824
25825			default:
25826			  gcc_unreachable ();
25827			}
25828
25829		      /* If only one bit will fit, don't or in this entry.  */
25830		      if (next_parm_info_bit > 0)
25831			parm_info |= (bits << (next_parm_info_bit - 1));
25832		      next_parm_info_bit -= 2;
25833		    }
25834		  else
25835		    {
25836		      fixed_parms += ((GET_MODE_SIZE (mode)
25837				       + (UNITS_PER_WORD - 1))
25838				      / UNITS_PER_WORD);
25839		      next_parm_info_bit -= 1;
25840		    }
25841		}
25842	    }
25843	}
25844
25845      /* Number of fixed point parameters.  */
25846      /* This is actually the number of words of fixed point parameters; thus
25847	 an 8 byte struct counts as 2; and thus the maximum value is 8.  */
25848      fprintf (file, "%d,", fixed_parms);
25849
25850      /* 2 bitfields: number of floating point parameters (7 bits), parameters
25851	 all on stack.  */
25852      /* This is actually the number of fp registers that hold parameters;
25853	 and thus the maximum value is 13.  */
25854      /* Set parameters on stack bit if parameters are not in their original
25855	 registers, regardless of whether they are on the stack?  Xlc
25856	 seems to set the bit when not optimizing.  */
25857      fprintf (file, "%d\n", ((float_parms << 1) | (! optimize)));
25858
25859      if (! optional_tbtab)
25860	return;
25861
25862      /* Optional fields follow.  Some are variable length.  */
25863
25864      /* Parameter types, left adjusted bit fields: 0 fixed, 10 single float,
25865	 11 double float.  */
25866      /* There is an entry for each parameter in a register, in the order that
25867	 they occur in the parameter list.  Any intervening arguments on the
25868	 stack are ignored.  If the list overflows a long (max possible length
25869	 34 bits) then completely leave off all elements that don't fit.  */
25870      /* Only emit this long if there was at least one parameter.  */
25871      if (fixed_parms || float_parms)
25872	fprintf (file, "\t.long %d\n", parm_info);
25873
25874      /* Offset from start of code to tb table.  */
25875      fputs ("\t.long ", file);
25876      ASM_OUTPUT_INTERNAL_LABEL_PREFIX (file, "LT");
25877      RS6000_OUTPUT_BASENAME (file, fname);
25878      putc ('-', file);
25879      rs6000_output_function_entry (file, fname);
25880      putc ('\n', file);
25881
25882      /* Interrupt handler mask.  */
25883      /* Omit this long, since we never set the interrupt handler bit
25884	 above.  */
25885
25886      /* Number of CTL (controlled storage) anchors.  */
25887      /* Omit this long, since the has_ctl bit is never set above.  */
25888
25889      /* Displacement into stack of each CTL anchor.  */
25890      /* Omit this list of longs, because there are no CTL anchors.  */
25891
25892      /* Length of function name.  */
25893      if (*fname == '*')
25894	++fname;
25895      fprintf (file, "\t.short %d\n", (int) strlen (fname));
25896
25897      /* Function name.  */
25898      assemble_string (fname, strlen (fname));
25899
25900      /* Register for alloca automatic storage; this is always reg 31.
25901	 Only emit this if the alloca bit was set above.  */
25902      if (frame_pointer_needed)
25903	fputs ("\t.byte 31\n", file);
25904
25905      fputs ("\t.align 2\n", file);
25906    }
25907}
25908
25909/* A C compound statement that outputs the assembler code for a thunk
25910   function, used to implement C++ virtual function calls with
25911   multiple inheritance.  The thunk acts as a wrapper around a virtual
25912   function, adjusting the implicit object parameter before handing
25913   control off to the real function.
25914
25915   First, emit code to add the integer DELTA to the location that
25916   contains the incoming first argument.  Assume that this argument
25917   contains a pointer, and is the one used to pass the `this' pointer
25918   in C++.  This is the incoming argument *before* the function
25919   prologue, e.g. `%o0' on a sparc.  The addition must preserve the
25920   values of all other incoming arguments.
25921
25922   After the addition, emit code to jump to FUNCTION, which is a
25923   `FUNCTION_DECL'.  This is a direct pure jump, not a call, and does
25924   not touch the return address.  Hence returning from FUNCTION will
25925   return to whoever called the current `thunk'.
25926
25927   The effect must be as if FUNCTION had been called directly with the
25928   adjusted first argument.  This macro is responsible for emitting
25929   all of the code for a thunk function; output_function_prologue()
25930   and output_function_epilogue() are not invoked.
25931
25932   The THUNK_FNDECL is redundant.  (DELTA and FUNCTION have already
25933   been extracted from it.)  It might possibly be useful on some
25934   targets, but probably not.
25935
25936   If you do not define this macro, the target-independent code in the
25937   C++ frontend will generate a less efficient heavyweight thunk that
25938   calls FUNCTION instead of jumping to it.  The generic approach does
25939   not support varargs.  */
25940
25941static void
25942rs6000_output_mi_thunk (FILE *file, tree thunk_fndecl ATTRIBUTE_UNUSED,
25943			HOST_WIDE_INT delta, HOST_WIDE_INT vcall_offset,
25944			tree function)
25945{
25946  rtx this_rtx, funexp;
25947  rtx_insn *insn;
25948
25949  reload_completed = 1;
25950  epilogue_completed = 1;
25951
25952  /* Mark the end of the (empty) prologue.  */
25953  emit_note (NOTE_INSN_PROLOGUE_END);
25954
25955  /* Find the "this" pointer.  If the function returns a structure,
25956     the structure return pointer is in r3.  */
25957  if (aggregate_value_p (TREE_TYPE (TREE_TYPE (function)), function))
25958    this_rtx = gen_rtx_REG (Pmode, 4);
25959  else
25960    this_rtx = gen_rtx_REG (Pmode, 3);
25961
25962  /* Apply the constant offset, if required.  */
25963  if (delta)
25964    emit_insn (gen_add3_insn (this_rtx, this_rtx, GEN_INT (delta)));
25965
25966  /* Apply the offset from the vtable, if required.  */
25967  if (vcall_offset)
25968    {
25969      rtx vcall_offset_rtx = GEN_INT (vcall_offset);
25970      rtx tmp = gen_rtx_REG (Pmode, 12);
25971
25972      emit_move_insn (tmp, gen_rtx_MEM (Pmode, this_rtx));
25973      if (((unsigned HOST_WIDE_INT) vcall_offset) + 0x8000 >= 0x10000)
25974	{
25975	  emit_insn (gen_add3_insn (tmp, tmp, vcall_offset_rtx));
25976	  emit_move_insn (tmp, gen_rtx_MEM (Pmode, tmp));
25977	}
25978      else
25979	{
25980	  rtx loc = gen_rtx_PLUS (Pmode, tmp, vcall_offset_rtx);
25981
25982	  emit_move_insn (tmp, gen_rtx_MEM (Pmode, loc));
25983	}
25984      emit_insn (gen_add3_insn (this_rtx, this_rtx, tmp));
25985    }
25986
25987  /* Generate a tail call to the target function.  */
25988  if (!TREE_USED (function))
25989    {
25990      assemble_external (function);
25991      TREE_USED (function) = 1;
25992    }
25993  funexp = XEXP (DECL_RTL (function), 0);
25994  funexp = gen_rtx_MEM (FUNCTION_MODE, funexp);
25995
25996#if TARGET_MACHO
25997  if (MACHOPIC_INDIRECT)
25998    funexp = machopic_indirect_call_target (funexp);
25999#endif
26000
26001  /* gen_sibcall expects reload to convert scratch pseudo to LR so we must
26002     generate sibcall RTL explicitly.  */
26003  insn = emit_call_insn (
26004	   gen_rtx_PARALLEL (VOIDmode,
26005	     gen_rtvec (4,
26006			gen_rtx_CALL (VOIDmode,
26007				      funexp, const0_rtx),
26008			gen_rtx_USE (VOIDmode, const0_rtx),
26009			gen_rtx_USE (VOIDmode,
26010				     gen_rtx_REG (SImode,
26011						  LR_REGNO)),
26012			simple_return_rtx)));
26013  SIBLING_CALL_P (insn) = 1;
26014  emit_barrier ();
26015
26016  /* Ensure we have a global entry point for the thunk.   ??? We could
26017     avoid that if the target routine doesn't need a global entry point,
26018     but we do not know whether this is the case at this point.  */
26019  if (DEFAULT_ABI == ABI_ELFv2)
26020    cfun->machine->r2_setup_needed = true;
26021
26022  /* Run just enough of rest_of_compilation to get the insns emitted.
26023     There's not really enough bulk here to make other passes such as
26024     instruction scheduling worth while.  Note that use_thunk calls
26025     assemble_start_function and assemble_end_function.  */
26026  insn = get_insns ();
26027  shorten_branches (insn);
26028  final_start_function (insn, file, 1);
26029  final (insn, file, 1);
26030  final_end_function ();
26031
26032  reload_completed = 0;
26033  epilogue_completed = 0;
26034}
26035
26036/* A quick summary of the various types of 'constant-pool tables'
26037   under PowerPC:
26038
26039   Target	Flags		Name		One table per
26040   AIX		(none)		AIX TOC		object file
26041   AIX		-mfull-toc	AIX TOC		object file
26042   AIX		-mminimal-toc	AIX minimal TOC	translation unit
26043   SVR4/EABI	(none)		SVR4 SDATA	object file
26044   SVR4/EABI	-fpic		SVR4 pic	object file
26045   SVR4/EABI	-fPIC		SVR4 PIC	translation unit
26046   SVR4/EABI	-mrelocatable	EABI TOC	function
26047   SVR4/EABI	-maix		AIX TOC		object file
26048   SVR4/EABI	-maix -mminimal-toc
26049				AIX minimal TOC	translation unit
26050
26051   Name			Reg.	Set by	entries	      contains:
26052					made by	 addrs?	fp?	sum?
26053
26054   AIX TOC		2	crt0	as	 Y	option	option
26055   AIX minimal TOC	30	prolog	gcc	 Y	Y	option
26056   SVR4 SDATA		13	crt0	gcc	 N	Y	N
26057   SVR4 pic		30	prolog	ld	 Y	not yet	N
26058   SVR4 PIC		30	prolog	gcc	 Y	option	option
26059   EABI TOC		30	prolog	gcc	 Y	option	option
26060
26061*/
26062
26063/* Hash functions for the hash table.  */
26064
26065static unsigned
26066rs6000_hash_constant (rtx k)
26067{
26068  enum rtx_code code = GET_CODE (k);
26069  machine_mode mode = GET_MODE (k);
26070  unsigned result = (code << 3) ^ mode;
26071  const char *format;
26072  int flen, fidx;
26073
26074  format = GET_RTX_FORMAT (code);
26075  flen = strlen (format);
26076  fidx = 0;
26077
26078  switch (code)
26079    {
26080    case LABEL_REF:
26081      return result * 1231 + (unsigned) INSN_UID (XEXP (k, 0));
26082
26083    case CONST_WIDE_INT:
26084      {
26085	int i;
26086	flen = CONST_WIDE_INT_NUNITS (k);
26087	for (i = 0; i < flen; i++)
26088	  result = result * 613 + CONST_WIDE_INT_ELT (k, i);
26089	return result;
26090      }
26091
26092    case CONST_DOUBLE:
26093      if (mode != VOIDmode)
26094	return real_hash (CONST_DOUBLE_REAL_VALUE (k)) * result;
26095      flen = 2;
26096      break;
26097
26098    case CODE_LABEL:
26099      fidx = 3;
26100      break;
26101
26102    default:
26103      break;
26104    }
26105
26106  for (; fidx < flen; fidx++)
26107    switch (format[fidx])
26108      {
26109      case 's':
26110	{
26111	  unsigned i, len;
26112	  const char *str = XSTR (k, fidx);
26113	  len = strlen (str);
26114	  result = result * 613 + len;
26115	  for (i = 0; i < len; i++)
26116	    result = result * 613 + (unsigned) str[i];
26117	  break;
26118	}
26119      case 'u':
26120      case 'e':
26121	result = result * 1231 + rs6000_hash_constant (XEXP (k, fidx));
26122	break;
26123      case 'i':
26124      case 'n':
26125	result = result * 613 + (unsigned) XINT (k, fidx);
26126	break;
26127      case 'w':
26128	if (sizeof (unsigned) >= sizeof (HOST_WIDE_INT))
26129	  result = result * 613 + (unsigned) XWINT (k, fidx);
26130	else
26131	  {
26132	    size_t i;
26133	    for (i = 0; i < sizeof (HOST_WIDE_INT) / sizeof (unsigned); i++)
26134	      result = result * 613 + (unsigned) (XWINT (k, fidx)
26135						  >> CHAR_BIT * i);
26136	  }
26137	break;
26138      case '0':
26139	break;
26140      default:
26141	gcc_unreachable ();
26142      }
26143
26144  return result;
26145}
26146
26147hashval_t
26148toc_hasher::hash (toc_hash_struct *thc)
26149{
26150  return rs6000_hash_constant (thc->key) ^ thc->key_mode;
26151}
26152
26153/* Compare H1 and H2 for equivalence.  */
26154
26155bool
26156toc_hasher::equal (toc_hash_struct *h1, toc_hash_struct *h2)
26157{
26158  rtx r1 = h1->key;
26159  rtx r2 = h2->key;
26160
26161  if (h1->key_mode != h2->key_mode)
26162    return 0;
26163
26164  return rtx_equal_p (r1, r2);
26165}
26166
26167/* These are the names given by the C++ front-end to vtables, and
26168   vtable-like objects.  Ideally, this logic should not be here;
26169   instead, there should be some programmatic way of inquiring as
26170   to whether or not an object is a vtable.  */
26171
26172#define VTABLE_NAME_P(NAME)				\
26173  (strncmp ("_vt.", name, strlen ("_vt.")) == 0		\
26174  || strncmp ("_ZTV", name, strlen ("_ZTV")) == 0	\
26175  || strncmp ("_ZTT", name, strlen ("_ZTT")) == 0	\
26176  || strncmp ("_ZTI", name, strlen ("_ZTI")) == 0	\
26177  || strncmp ("_ZTC", name, strlen ("_ZTC")) == 0)
26178
26179#ifdef NO_DOLLAR_IN_LABEL
26180/* Return a GGC-allocated character string translating dollar signs in
26181   input NAME to underscores.  Used by XCOFF ASM_OUTPUT_LABELREF.  */
26182
26183const char *
26184rs6000_xcoff_strip_dollar (const char *name)
26185{
26186  char *strip, *p;
26187  const char *q;
26188  size_t len;
26189
26190  q = (const char *) strchr (name, '$');
26191
26192  if (q == 0 || q == name)
26193    return name;
26194
26195  len = strlen (name);
26196  strip = XALLOCAVEC (char, len + 1);
26197  strcpy (strip, name);
26198  p = strip + (q - name);
26199  while (p)
26200    {
26201      *p = '_';
26202      p = strchr (p + 1, '$');
26203    }
26204
26205  return ggc_alloc_string (strip, len);
26206}
26207#endif
26208
26209void
26210rs6000_output_symbol_ref (FILE *file, rtx x)
26211{
26212  /* Currently C++ toc references to vtables can be emitted before it
26213     is decided whether the vtable is public or private.  If this is
26214     the case, then the linker will eventually complain that there is
26215     a reference to an unknown section.  Thus, for vtables only,
26216     we emit the TOC reference to reference the symbol and not the
26217     section.  */
26218  const char *name = XSTR (x, 0);
26219
26220  tree decl = SYMBOL_REF_DECL (x);
26221  if (decl /* sync condition with assemble_external () */
26222      && DECL_P (decl) && DECL_EXTERNAL (decl) && TREE_PUBLIC (decl)
26223      && (TREE_CODE (decl) == VAR_DECL
26224	  || TREE_CODE (decl) == FUNCTION_DECL)
26225      && name[strlen (name) - 1] != ']')
26226    {
26227      name = concat (name,
26228		     (TREE_CODE (decl) == FUNCTION_DECL
26229		      ? "[DS]" : "[UA]"),
26230		     NULL);
26231      XSTR (x, 0) = name;
26232    }
26233
26234  if (VTABLE_NAME_P (name))
26235    {
26236      RS6000_OUTPUT_BASENAME (file, name);
26237    }
26238  else
26239    assemble_name (file, name);
26240}
26241
26242/* Output a TOC entry.  We derive the entry name from what is being
26243   written.  */
26244
26245void
26246output_toc (FILE *file, rtx x, int labelno, machine_mode mode)
26247{
26248  char buf[256];
26249  const char *name = buf;
26250  rtx base = x;
26251  HOST_WIDE_INT offset = 0;
26252
26253  gcc_assert (!TARGET_NO_TOC);
26254
26255  /* When the linker won't eliminate them, don't output duplicate
26256     TOC entries (this happens on AIX if there is any kind of TOC,
26257     and on SVR4 under -fPIC or -mrelocatable).  Don't do this for
26258     CODE_LABELs.  */
26259  if (TARGET_TOC && GET_CODE (x) != LABEL_REF)
26260    {
26261      struct toc_hash_struct *h;
26262
26263      /* Create toc_hash_table.  This can't be done at TARGET_OPTION_OVERRIDE
26264	 time because GGC is not initialized at that point.  */
26265      if (toc_hash_table == NULL)
26266	toc_hash_table = hash_table<toc_hasher>::create_ggc (1021);
26267
26268      h = ggc_alloc<toc_hash_struct> ();
26269      h->key = x;
26270      h->key_mode = mode;
26271      h->labelno = labelno;
26272
26273      toc_hash_struct **found = toc_hash_table->find_slot (h, INSERT);
26274      if (*found == NULL)
26275	*found = h;
26276      else  /* This is indeed a duplicate.
26277	       Set this label equal to that label.  */
26278	{
26279	  fputs ("\t.set ", file);
26280	  ASM_OUTPUT_INTERNAL_LABEL_PREFIX (file, "LC");
26281	  fprintf (file, "%d,", labelno);
26282	  ASM_OUTPUT_INTERNAL_LABEL_PREFIX (file, "LC");
26283	  fprintf (file, "%d\n", ((*found)->labelno));
26284
26285#ifdef HAVE_AS_TLS
26286	  if (TARGET_XCOFF && GET_CODE (x) == SYMBOL_REF
26287	      && (SYMBOL_REF_TLS_MODEL (x) == TLS_MODEL_GLOBAL_DYNAMIC
26288		  || SYMBOL_REF_TLS_MODEL (x) == TLS_MODEL_LOCAL_DYNAMIC))
26289	    {
26290	      fputs ("\t.set ", file);
26291	      ASM_OUTPUT_INTERNAL_LABEL_PREFIX (file, "LCM");
26292	      fprintf (file, "%d,", labelno);
26293	      ASM_OUTPUT_INTERNAL_LABEL_PREFIX (file, "LCM");
26294	      fprintf (file, "%d\n", ((*found)->labelno));
26295	    }
26296#endif
26297	  return;
26298	}
26299    }
26300
26301  /* If we're going to put a double constant in the TOC, make sure it's
26302     aligned properly when strict alignment is on.  */
26303  if ((CONST_DOUBLE_P (x) || CONST_WIDE_INT_P (x))
26304      && STRICT_ALIGNMENT
26305      && GET_MODE_BITSIZE (mode) >= 64
26306      && ! (TARGET_NO_FP_IN_TOC && ! TARGET_MINIMAL_TOC)) {
26307    ASM_OUTPUT_ALIGN (file, 3);
26308  }
26309
26310  (*targetm.asm_out.internal_label) (file, "LC", labelno);
26311
26312  /* Handle FP constants specially.  Note that if we have a minimal
26313     TOC, things we put here aren't actually in the TOC, so we can allow
26314     FP constants.  */
26315  if (GET_CODE (x) == CONST_DOUBLE &&
26316      (GET_MODE (x) == TFmode || GET_MODE (x) == TDmode))
26317    {
26318      REAL_VALUE_TYPE rv;
26319      long k[4];
26320
26321      REAL_VALUE_FROM_CONST_DOUBLE (rv, x);
26322      if (DECIMAL_FLOAT_MODE_P (GET_MODE (x)))
26323	REAL_VALUE_TO_TARGET_DECIMAL128 (rv, k);
26324      else
26325	REAL_VALUE_TO_TARGET_LONG_DOUBLE (rv, k);
26326
26327      if (TARGET_64BIT)
26328	{
26329	  if (TARGET_ELF || TARGET_MINIMAL_TOC)
26330	    fputs (DOUBLE_INT_ASM_OP, file);
26331	  else
26332	    fprintf (file, "\t.tc FT_%lx_%lx_%lx_%lx[TC],",
26333		     k[0] & 0xffffffff, k[1] & 0xffffffff,
26334		     k[2] & 0xffffffff, k[3] & 0xffffffff);
26335	  fprintf (file, "0x%lx%08lx,0x%lx%08lx\n",
26336		   k[WORDS_BIG_ENDIAN ? 0 : 1] & 0xffffffff,
26337		   k[WORDS_BIG_ENDIAN ? 1 : 0] & 0xffffffff,
26338		   k[WORDS_BIG_ENDIAN ? 2 : 3] & 0xffffffff,
26339		   k[WORDS_BIG_ENDIAN ? 3 : 2] & 0xffffffff);
26340	  return;
26341	}
26342      else
26343	{
26344	  if (TARGET_ELF || TARGET_MINIMAL_TOC)
26345	    fputs ("\t.long ", file);
26346	  else
26347	    fprintf (file, "\t.tc FT_%lx_%lx_%lx_%lx[TC],",
26348		     k[0] & 0xffffffff, k[1] & 0xffffffff,
26349		     k[2] & 0xffffffff, k[3] & 0xffffffff);
26350	  fprintf (file, "0x%lx,0x%lx,0x%lx,0x%lx\n",
26351		   k[0] & 0xffffffff, k[1] & 0xffffffff,
26352		   k[2] & 0xffffffff, k[3] & 0xffffffff);
26353	  return;
26354	}
26355    }
26356  else if (GET_CODE (x) == CONST_DOUBLE &&
26357	   (GET_MODE (x) == DFmode || GET_MODE (x) == DDmode))
26358    {
26359      REAL_VALUE_TYPE rv;
26360      long k[2];
26361
26362      REAL_VALUE_FROM_CONST_DOUBLE (rv, x);
26363
26364      if (DECIMAL_FLOAT_MODE_P (GET_MODE (x)))
26365	REAL_VALUE_TO_TARGET_DECIMAL64 (rv, k);
26366      else
26367	REAL_VALUE_TO_TARGET_DOUBLE (rv, k);
26368
26369      if (TARGET_64BIT)
26370	{
26371	  if (TARGET_ELF || TARGET_MINIMAL_TOC)
26372	    fputs (DOUBLE_INT_ASM_OP, file);
26373	  else
26374	    fprintf (file, "\t.tc FD_%lx_%lx[TC],",
26375		     k[0] & 0xffffffff, k[1] & 0xffffffff);
26376	  fprintf (file, "0x%lx%08lx\n",
26377		   k[WORDS_BIG_ENDIAN ? 0 : 1] & 0xffffffff,
26378		   k[WORDS_BIG_ENDIAN ? 1 : 0] & 0xffffffff);
26379	  return;
26380	}
26381      else
26382	{
26383	  if (TARGET_ELF || TARGET_MINIMAL_TOC)
26384	    fputs ("\t.long ", file);
26385	  else
26386	    fprintf (file, "\t.tc FD_%lx_%lx[TC],",
26387		     k[0] & 0xffffffff, k[1] & 0xffffffff);
26388	  fprintf (file, "0x%lx,0x%lx\n",
26389		   k[0] & 0xffffffff, k[1] & 0xffffffff);
26390	  return;
26391	}
26392    }
26393  else if (GET_CODE (x) == CONST_DOUBLE &&
26394	   (GET_MODE (x) == SFmode || GET_MODE (x) == SDmode))
26395    {
26396      REAL_VALUE_TYPE rv;
26397      long l;
26398
26399      REAL_VALUE_FROM_CONST_DOUBLE (rv, x);
26400      if (DECIMAL_FLOAT_MODE_P (GET_MODE (x)))
26401	REAL_VALUE_TO_TARGET_DECIMAL32 (rv, l);
26402      else
26403	REAL_VALUE_TO_TARGET_SINGLE (rv, l);
26404
26405      if (TARGET_64BIT)
26406	{
26407	  if (TARGET_ELF || TARGET_MINIMAL_TOC)
26408	    fputs (DOUBLE_INT_ASM_OP, file);
26409	  else
26410	    fprintf (file, "\t.tc FS_%lx[TC],", l & 0xffffffff);
26411	  if (WORDS_BIG_ENDIAN)
26412	    fprintf (file, "0x%lx00000000\n", l & 0xffffffff);
26413	  else
26414	    fprintf (file, "0x%lx\n", l & 0xffffffff);
26415	  return;
26416	}
26417      else
26418	{
26419	  if (TARGET_ELF || TARGET_MINIMAL_TOC)
26420	    fputs ("\t.long ", file);
26421	  else
26422	    fprintf (file, "\t.tc FS_%lx[TC],", l & 0xffffffff);
26423	  fprintf (file, "0x%lx\n", l & 0xffffffff);
26424	  return;
26425	}
26426    }
26427  else if (GET_MODE (x) == VOIDmode && GET_CODE (x) == CONST_INT)
26428    {
26429      unsigned HOST_WIDE_INT low;
26430      HOST_WIDE_INT high;
26431
26432      low = INTVAL (x) & 0xffffffff;
26433      high = (HOST_WIDE_INT) INTVAL (x) >> 32;
26434
26435      /* TOC entries are always Pmode-sized, so when big-endian
26436	 smaller integer constants in the TOC need to be padded.
26437	 (This is still a win over putting the constants in
26438	 a separate constant pool, because then we'd have
26439	 to have both a TOC entry _and_ the actual constant.)
26440
26441	 For a 32-bit target, CONST_INT values are loaded and shifted
26442	 entirely within `low' and can be stored in one TOC entry.  */
26443
26444      /* It would be easy to make this work, but it doesn't now.  */
26445      gcc_assert (!TARGET_64BIT || POINTER_SIZE >= GET_MODE_BITSIZE (mode));
26446
26447      if (WORDS_BIG_ENDIAN && POINTER_SIZE > GET_MODE_BITSIZE (mode))
26448	{
26449	  low |= high << 32;
26450	  low <<= POINTER_SIZE - GET_MODE_BITSIZE (mode);
26451	  high = (HOST_WIDE_INT) low >> 32;
26452	  low &= 0xffffffff;
26453	}
26454
26455      if (TARGET_64BIT)
26456	{
26457	  if (TARGET_ELF || TARGET_MINIMAL_TOC)
26458	    fputs (DOUBLE_INT_ASM_OP, file);
26459	  else
26460	    fprintf (file, "\t.tc ID_%lx_%lx[TC],",
26461		     (long) high & 0xffffffff, (long) low & 0xffffffff);
26462	  fprintf (file, "0x%lx%08lx\n",
26463		   (long) high & 0xffffffff, (long) low & 0xffffffff);
26464	  return;
26465	}
26466      else
26467	{
26468	  if (POINTER_SIZE < GET_MODE_BITSIZE (mode))
26469	    {
26470	      if (TARGET_ELF || TARGET_MINIMAL_TOC)
26471		fputs ("\t.long ", file);
26472	      else
26473		fprintf (file, "\t.tc ID_%lx_%lx[TC],",
26474			 (long) high & 0xffffffff, (long) low & 0xffffffff);
26475	      fprintf (file, "0x%lx,0x%lx\n",
26476		       (long) high & 0xffffffff, (long) low & 0xffffffff);
26477	    }
26478	  else
26479	    {
26480	      if (TARGET_ELF || TARGET_MINIMAL_TOC)
26481		fputs ("\t.long ", file);
26482	      else
26483		fprintf (file, "\t.tc IS_%lx[TC],", (long) low & 0xffffffff);
26484	      fprintf (file, "0x%lx\n", (long) low & 0xffffffff);
26485	    }
26486	  return;
26487	}
26488    }
26489
26490  if (GET_CODE (x) == CONST)
26491    {
26492      gcc_assert (GET_CODE (XEXP (x, 0)) == PLUS
26493		  && GET_CODE (XEXP (XEXP (x, 0), 1)) == CONST_INT);
26494
26495      base = XEXP (XEXP (x, 0), 0);
26496      offset = INTVAL (XEXP (XEXP (x, 0), 1));
26497    }
26498
26499  switch (GET_CODE (base))
26500    {
26501    case SYMBOL_REF:
26502      name = XSTR (base, 0);
26503      break;
26504
26505    case LABEL_REF:
26506      ASM_GENERATE_INTERNAL_LABEL (buf, "L",
26507				   CODE_LABEL_NUMBER (XEXP (base, 0)));
26508      break;
26509
26510    case CODE_LABEL:
26511      ASM_GENERATE_INTERNAL_LABEL (buf, "L", CODE_LABEL_NUMBER (base));
26512      break;
26513
26514    default:
26515      gcc_unreachable ();
26516    }
26517
26518  if (TARGET_ELF || TARGET_MINIMAL_TOC)
26519    fputs (TARGET_32BIT ? "\t.long " : DOUBLE_INT_ASM_OP, file);
26520  else
26521    {
26522      fputs ("\t.tc ", file);
26523      RS6000_OUTPUT_BASENAME (file, name);
26524
26525      if (offset < 0)
26526	fprintf (file, ".N" HOST_WIDE_INT_PRINT_UNSIGNED, - offset);
26527      else if (offset)
26528	fprintf (file, ".P" HOST_WIDE_INT_PRINT_UNSIGNED, offset);
26529
26530      /* Mark large TOC symbols on AIX with [TE] so they are mapped
26531	 after other TOC symbols, reducing overflow of small TOC access
26532	 to [TC] symbols.  */
26533      fputs (TARGET_XCOFF && TARGET_CMODEL != CMODEL_SMALL
26534	     ? "[TE]," : "[TC],", file);
26535    }
26536
26537  /* Currently C++ toc references to vtables can be emitted before it
26538     is decided whether the vtable is public or private.  If this is
26539     the case, then the linker will eventually complain that there is
26540     a TOC reference to an unknown section.  Thus, for vtables only,
26541     we emit the TOC reference to reference the symbol and not the
26542     section.  */
26543  if (VTABLE_NAME_P (name))
26544    {
26545      RS6000_OUTPUT_BASENAME (file, name);
26546      if (offset < 0)
26547	fprintf (file, HOST_WIDE_INT_PRINT_DEC, offset);
26548      else if (offset > 0)
26549	fprintf (file, "+" HOST_WIDE_INT_PRINT_DEC, offset);
26550    }
26551  else
26552    output_addr_const (file, x);
26553
26554#if HAVE_AS_TLS
26555  if (TARGET_XCOFF && GET_CODE (base) == SYMBOL_REF
26556      && SYMBOL_REF_TLS_MODEL (base) != 0)
26557    {
26558      if (SYMBOL_REF_TLS_MODEL (base) == TLS_MODEL_LOCAL_EXEC)
26559	fputs ("@le", file);
26560      else if (SYMBOL_REF_TLS_MODEL (base) == TLS_MODEL_INITIAL_EXEC)
26561	fputs ("@ie", file);
26562      /* Use global-dynamic for local-dynamic.  */
26563      else if (SYMBOL_REF_TLS_MODEL (base) == TLS_MODEL_GLOBAL_DYNAMIC
26564	       || SYMBOL_REF_TLS_MODEL (base) == TLS_MODEL_LOCAL_DYNAMIC)
26565	{
26566	  putc ('\n', file);
26567	  (*targetm.asm_out.internal_label) (file, "LCM", labelno);
26568	  fputs ("\t.tc .", file);
26569	  RS6000_OUTPUT_BASENAME (file, name);
26570	  fputs ("[TC],", file);
26571	  output_addr_const (file, x);
26572	  fputs ("@m", file);
26573	}
26574    }
26575#endif
26576
26577  putc ('\n', file);
26578}
26579
26580/* Output an assembler pseudo-op to write an ASCII string of N characters
26581   starting at P to FILE.
26582
26583   On the RS/6000, we have to do this using the .byte operation and
26584   write out special characters outside the quoted string.
26585   Also, the assembler is broken; very long strings are truncated,
26586   so we must artificially break them up early.  */
26587
26588void
26589output_ascii (FILE *file, const char *p, int n)
26590{
26591  char c;
26592  int i, count_string;
26593  const char *for_string = "\t.byte \"";
26594  const char *for_decimal = "\t.byte ";
26595  const char *to_close = NULL;
26596
26597  count_string = 0;
26598  for (i = 0; i < n; i++)
26599    {
26600      c = *p++;
26601      if (c >= ' ' && c < 0177)
26602	{
26603	  if (for_string)
26604	    fputs (for_string, file);
26605	  putc (c, file);
26606
26607	  /* Write two quotes to get one.  */
26608	  if (c == '"')
26609	    {
26610	      putc (c, file);
26611	      ++count_string;
26612	    }
26613
26614	  for_string = NULL;
26615	  for_decimal = "\"\n\t.byte ";
26616	  to_close = "\"\n";
26617	  ++count_string;
26618
26619	  if (count_string >= 512)
26620	    {
26621	      fputs (to_close, file);
26622
26623	      for_string = "\t.byte \"";
26624	      for_decimal = "\t.byte ";
26625	      to_close = NULL;
26626	      count_string = 0;
26627	    }
26628	}
26629      else
26630	{
26631	  if (for_decimal)
26632	    fputs (for_decimal, file);
26633	  fprintf (file, "%d", c);
26634
26635	  for_string = "\n\t.byte \"";
26636	  for_decimal = ", ";
26637	  to_close = "\n";
26638	  count_string = 0;
26639	}
26640    }
26641
26642  /* Now close the string if we have written one.  Then end the line.  */
26643  if (to_close)
26644    fputs (to_close, file);
26645}
26646
26647/* Generate a unique section name for FILENAME for a section type
26648   represented by SECTION_DESC.  Output goes into BUF.
26649
26650   SECTION_DESC can be any string, as long as it is different for each
26651   possible section type.
26652
26653   We name the section in the same manner as xlc.  The name begins with an
26654   underscore followed by the filename (after stripping any leading directory
26655   names) with the last period replaced by the string SECTION_DESC.  If
26656   FILENAME does not contain a period, SECTION_DESC is appended to the end of
26657   the name.  */
26658
26659void
26660rs6000_gen_section_name (char **buf, const char *filename,
26661			 const char *section_desc)
26662{
26663  const char *q, *after_last_slash, *last_period = 0;
26664  char *p;
26665  int len;
26666
26667  after_last_slash = filename;
26668  for (q = filename; *q; q++)
26669    {
26670      if (*q == '/')
26671	after_last_slash = q + 1;
26672      else if (*q == '.')
26673	last_period = q;
26674    }
26675
26676  len = strlen (after_last_slash) + strlen (section_desc) + 2;
26677  *buf = (char *) xmalloc (len);
26678
26679  p = *buf;
26680  *p++ = '_';
26681
26682  for (q = after_last_slash; *q; q++)
26683    {
26684      if (q == last_period)
26685	{
26686	  strcpy (p, section_desc);
26687	  p += strlen (section_desc);
26688	  break;
26689	}
26690
26691      else if (ISALNUM (*q))
26692	*p++ = *q;
26693    }
26694
26695  if (last_period == 0)
26696    strcpy (p, section_desc);
26697  else
26698    *p = '\0';
26699}
26700
26701/* Emit profile function.  */
26702
26703void
26704output_profile_hook (int labelno ATTRIBUTE_UNUSED)
26705{
26706  /* Non-standard profiling for kernels, which just saves LR then calls
26707     _mcount without worrying about arg saves.  The idea is to change
26708     the function prologue as little as possible as it isn't easy to
26709     account for arg save/restore code added just for _mcount.  */
26710  if (TARGET_PROFILE_KERNEL)
26711    return;
26712
26713  if (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
26714    {
26715#ifndef NO_PROFILE_COUNTERS
26716# define NO_PROFILE_COUNTERS 0
26717#endif
26718      if (NO_PROFILE_COUNTERS)
26719	emit_library_call (init_one_libfunc (RS6000_MCOUNT),
26720			   LCT_NORMAL, VOIDmode, 0);
26721      else
26722	{
26723	  char buf[30];
26724	  const char *label_name;
26725	  rtx fun;
26726
26727	  ASM_GENERATE_INTERNAL_LABEL (buf, "LP", labelno);
26728	  label_name = ggc_strdup ((*targetm.strip_name_encoding) (buf));
26729	  fun = gen_rtx_SYMBOL_REF (Pmode, label_name);
26730
26731	  emit_library_call (init_one_libfunc (RS6000_MCOUNT),
26732			     LCT_NORMAL, VOIDmode, 1, fun, Pmode);
26733	}
26734    }
26735  else if (DEFAULT_ABI == ABI_DARWIN)
26736    {
26737      const char *mcount_name = RS6000_MCOUNT;
26738      int caller_addr_regno = LR_REGNO;
26739
26740      /* Be conservative and always set this, at least for now.  */
26741      crtl->uses_pic_offset_table = 1;
26742
26743#if TARGET_MACHO
26744      /* For PIC code, set up a stub and collect the caller's address
26745	 from r0, which is where the prologue puts it.  */
26746      if (MACHOPIC_INDIRECT
26747	  && crtl->uses_pic_offset_table)
26748	caller_addr_regno = 0;
26749#endif
26750      emit_library_call (gen_rtx_SYMBOL_REF (Pmode, mcount_name),
26751			 LCT_NORMAL, VOIDmode, 1,
26752			 gen_rtx_REG (Pmode, caller_addr_regno), Pmode);
26753    }
26754}
26755
26756/* Write function profiler code.  */
26757
26758void
26759output_function_profiler (FILE *file, int labelno)
26760{
26761  char buf[100];
26762
26763  switch (DEFAULT_ABI)
26764    {
26765    default:
26766      gcc_unreachable ();
26767
26768    case ABI_V4:
26769      if (!TARGET_32BIT)
26770	{
26771	  warning (0, "no profiling of 64-bit code for this ABI");
26772	  return;
26773	}
26774      ASM_GENERATE_INTERNAL_LABEL (buf, "LP", labelno);
26775      fprintf (file, "\tmflr %s\n", reg_names[0]);
26776      if (NO_PROFILE_COUNTERS)
26777	{
26778	  asm_fprintf (file, "\tstw %s,4(%s)\n",
26779		       reg_names[0], reg_names[1]);
26780	}
26781      else if (TARGET_SECURE_PLT && flag_pic)
26782	{
26783	  if (TARGET_LINK_STACK)
26784	    {
26785	      char name[32];
26786	      get_ppc476_thunk_name (name);
26787	      asm_fprintf (file, "\tbl %s\n", name);
26788	    }
26789	  else
26790	    asm_fprintf (file, "\tbcl 20,31,1f\n1:\n");
26791	  asm_fprintf (file, "\tstw %s,4(%s)\n",
26792		       reg_names[0], reg_names[1]);
26793	  asm_fprintf (file, "\tmflr %s\n", reg_names[12]);
26794	  asm_fprintf (file, "\taddis %s,%s,",
26795		       reg_names[12], reg_names[12]);
26796	  assemble_name (file, buf);
26797	  asm_fprintf (file, "-1b@ha\n\tla %s,", reg_names[0]);
26798	  assemble_name (file, buf);
26799	  asm_fprintf (file, "-1b@l(%s)\n", reg_names[12]);
26800	}
26801      else if (flag_pic == 1)
26802	{
26803	  fputs ("\tbl _GLOBAL_OFFSET_TABLE_@local-4\n", file);
26804	  asm_fprintf (file, "\tstw %s,4(%s)\n",
26805		       reg_names[0], reg_names[1]);
26806	  asm_fprintf (file, "\tmflr %s\n", reg_names[12]);
26807	  asm_fprintf (file, "\tlwz %s,", reg_names[0]);
26808	  assemble_name (file, buf);
26809	  asm_fprintf (file, "@got(%s)\n", reg_names[12]);
26810	}
26811      else if (flag_pic > 1)
26812	{
26813	  asm_fprintf (file, "\tstw %s,4(%s)\n",
26814		       reg_names[0], reg_names[1]);
26815	  /* Now, we need to get the address of the label.  */
26816	  if (TARGET_LINK_STACK)
26817	    {
26818	      char name[32];
26819	      get_ppc476_thunk_name (name);
26820	      asm_fprintf (file, "\tbl %s\n\tb 1f\n\t.long ", name);
26821	      assemble_name (file, buf);
26822	      fputs ("-.\n1:", file);
26823	      asm_fprintf (file, "\tmflr %s\n", reg_names[11]);
26824	      asm_fprintf (file, "\taddi %s,%s,4\n",
26825			   reg_names[11], reg_names[11]);
26826	    }
26827	  else
26828	    {
26829	      fputs ("\tbcl 20,31,1f\n\t.long ", file);
26830	      assemble_name (file, buf);
26831	      fputs ("-.\n1:", file);
26832	      asm_fprintf (file, "\tmflr %s\n", reg_names[11]);
26833	    }
26834	  asm_fprintf (file, "\tlwz %s,0(%s)\n",
26835		       reg_names[0], reg_names[11]);
26836	  asm_fprintf (file, "\tadd %s,%s,%s\n",
26837		       reg_names[0], reg_names[0], reg_names[11]);
26838	}
26839      else
26840	{
26841	  asm_fprintf (file, "\tlis %s,", reg_names[12]);
26842	  assemble_name (file, buf);
26843	  fputs ("@ha\n", file);
26844	  asm_fprintf (file, "\tstw %s,4(%s)\n",
26845		       reg_names[0], reg_names[1]);
26846	  asm_fprintf (file, "\tla %s,", reg_names[0]);
26847	  assemble_name (file, buf);
26848	  asm_fprintf (file, "@l(%s)\n", reg_names[12]);
26849	}
26850
26851      /* ABI_V4 saves the static chain reg with ASM_OUTPUT_REG_PUSH.  */
26852      fprintf (file, "\tbl %s%s\n",
26853	       RS6000_MCOUNT, flag_pic ? "@plt" : "");
26854      break;
26855
26856    case ABI_AIX:
26857    case ABI_ELFv2:
26858    case ABI_DARWIN:
26859      /* Don't do anything, done in output_profile_hook ().  */
26860      break;
26861    }
26862}
26863
26864
26865
26866/* The following variable value is the last issued insn.  */
26867
26868static rtx last_scheduled_insn;
26869
26870/* The following variable helps to balance issuing of load and
26871   store instructions */
26872
26873static int load_store_pendulum;
26874
26875/* Power4 load update and store update instructions are cracked into a
26876   load or store and an integer insn which are executed in the same cycle.
26877   Branches have their own dispatch slot which does not count against the
26878   GCC issue rate, but it changes the program flow so there are no other
26879   instructions to issue in this cycle.  */
26880
26881static int
26882rs6000_variable_issue_1 (rtx_insn *insn, int more)
26883{
26884  last_scheduled_insn = insn;
26885  if (GET_CODE (PATTERN (insn)) == USE
26886      || GET_CODE (PATTERN (insn)) == CLOBBER)
26887    {
26888      cached_can_issue_more = more;
26889      return cached_can_issue_more;
26890    }
26891
26892  if (insn_terminates_group_p (insn, current_group))
26893    {
26894      cached_can_issue_more = 0;
26895      return cached_can_issue_more;
26896    }
26897
26898  /* If no reservation, but reach here */
26899  if (recog_memoized (insn) < 0)
26900    return more;
26901
26902  if (rs6000_sched_groups)
26903    {
26904      if (is_microcoded_insn (insn))
26905        cached_can_issue_more = 0;
26906      else if (is_cracked_insn (insn))
26907        cached_can_issue_more = more > 2 ? more - 2 : 0;
26908      else
26909        cached_can_issue_more = more - 1;
26910
26911      return cached_can_issue_more;
26912    }
26913
26914  if (rs6000_cpu_attr == CPU_CELL && is_nonpipeline_insn (insn))
26915    return 0;
26916
26917  cached_can_issue_more = more - 1;
26918  return cached_can_issue_more;
26919}
26920
26921static int
26922rs6000_variable_issue (FILE *stream, int verbose, rtx_insn *insn, int more)
26923{
26924  int r = rs6000_variable_issue_1 (insn, more);
26925  if (verbose)
26926    fprintf (stream, "// rs6000_variable_issue (more = %d) = %d\n", more, r);
26927  return r;
26928}
26929
26930/* Adjust the cost of a scheduling dependency.  Return the new cost of
26931   a dependency LINK or INSN on DEP_INSN.  COST is the current cost.  */
26932
26933static int
26934rs6000_adjust_cost (rtx_insn *insn, rtx link, rtx_insn *dep_insn, int cost)
26935{
26936  enum attr_type attr_type;
26937
26938  if (! recog_memoized (insn))
26939    return 0;
26940
26941  switch (REG_NOTE_KIND (link))
26942    {
26943    case REG_DEP_TRUE:
26944      {
26945        /* Data dependency; DEP_INSN writes a register that INSN reads
26946	   some cycles later.  */
26947
26948	/* Separate a load from a narrower, dependent store.  */
26949	if (rs6000_sched_groups
26950	    && GET_CODE (PATTERN (insn)) == SET
26951	    && GET_CODE (PATTERN (dep_insn)) == SET
26952	    && GET_CODE (XEXP (PATTERN (insn), 1)) == MEM
26953	    && GET_CODE (XEXP (PATTERN (dep_insn), 0)) == MEM
26954	    && (GET_MODE_SIZE (GET_MODE (XEXP (PATTERN (insn), 1)))
26955		> GET_MODE_SIZE (GET_MODE (XEXP (PATTERN (dep_insn), 0)))))
26956	  return cost + 14;
26957
26958        attr_type = get_attr_type (insn);
26959
26960        switch (attr_type)
26961          {
26962          case TYPE_JMPREG:
26963            /* Tell the first scheduling pass about the latency between
26964               a mtctr and bctr (and mtlr and br/blr).  The first
26965               scheduling pass will not know about this latency since
26966               the mtctr instruction, which has the latency associated
26967               to it, will be generated by reload.  */
26968            return 4;
26969          case TYPE_BRANCH:
26970            /* Leave some extra cycles between a compare and its
26971               dependent branch, to inhibit expensive mispredicts.  */
26972            if ((rs6000_cpu_attr == CPU_PPC603
26973                 || rs6000_cpu_attr == CPU_PPC604
26974                 || rs6000_cpu_attr == CPU_PPC604E
26975                 || rs6000_cpu_attr == CPU_PPC620
26976                 || rs6000_cpu_attr == CPU_PPC630
26977                 || rs6000_cpu_attr == CPU_PPC750
26978                 || rs6000_cpu_attr == CPU_PPC7400
26979                 || rs6000_cpu_attr == CPU_PPC7450
26980                 || rs6000_cpu_attr == CPU_PPCE5500
26981                 || rs6000_cpu_attr == CPU_PPCE6500
26982                 || rs6000_cpu_attr == CPU_POWER4
26983                 || rs6000_cpu_attr == CPU_POWER5
26984		 || rs6000_cpu_attr == CPU_POWER7
26985		 || rs6000_cpu_attr == CPU_POWER8
26986                 || rs6000_cpu_attr == CPU_CELL)
26987                && recog_memoized (dep_insn)
26988                && (INSN_CODE (dep_insn) >= 0))
26989
26990              switch (get_attr_type (dep_insn))
26991                {
26992                case TYPE_CMP:
26993                case TYPE_FPCOMPARE:
26994                case TYPE_CR_LOGICAL:
26995                case TYPE_DELAYED_CR:
26996		  return cost + 2;
26997                case TYPE_EXTS:
26998                case TYPE_MUL:
26999		  if (get_attr_dot (dep_insn) == DOT_YES)
27000		    return cost + 2;
27001		  else
27002		    break;
27003                case TYPE_SHIFT:
27004		  if (get_attr_dot (dep_insn) == DOT_YES
27005		      && get_attr_var_shift (dep_insn) == VAR_SHIFT_NO)
27006		    return cost + 2;
27007		  else
27008		    break;
27009		default:
27010		  break;
27011		}
27012            break;
27013
27014          case TYPE_STORE:
27015          case TYPE_FPSTORE:
27016            if ((rs6000_cpu == PROCESSOR_POWER6)
27017                && recog_memoized (dep_insn)
27018                && (INSN_CODE (dep_insn) >= 0))
27019              {
27020
27021                if (GET_CODE (PATTERN (insn)) != SET)
27022                  /* If this happens, we have to extend this to schedule
27023                     optimally.  Return default for now.  */
27024                  return cost;
27025
27026                /* Adjust the cost for the case where the value written
27027                   by a fixed point operation is used as the address
27028                   gen value on a store. */
27029                switch (get_attr_type (dep_insn))
27030                  {
27031                  case TYPE_LOAD:
27032                  case TYPE_CNTLZ:
27033                    {
27034                      if (! store_data_bypass_p (dep_insn, insn))
27035                        return get_attr_sign_extend (dep_insn)
27036                               == SIGN_EXTEND_YES ? 6 : 4;
27037                      break;
27038                    }
27039                  case TYPE_SHIFT:
27040                    {
27041                      if (! store_data_bypass_p (dep_insn, insn))
27042                        return get_attr_var_shift (dep_insn) == VAR_SHIFT_YES ?
27043                               6 : 3;
27044                      break;
27045		    }
27046                  case TYPE_INTEGER:
27047                  case TYPE_ADD:
27048                  case TYPE_LOGICAL:
27049                  case TYPE_EXTS:
27050                  case TYPE_INSERT:
27051                    {
27052                      if (! store_data_bypass_p (dep_insn, insn))
27053                        return 3;
27054                      break;
27055                    }
27056                  case TYPE_STORE:
27057                  case TYPE_FPLOAD:
27058                  case TYPE_FPSTORE:
27059                    {
27060                      if (get_attr_update (dep_insn) == UPDATE_YES
27061                          && ! store_data_bypass_p (dep_insn, insn))
27062                        return 3;
27063                      break;
27064                    }
27065                  case TYPE_MUL:
27066                    {
27067                      if (! store_data_bypass_p (dep_insn, insn))
27068                        return 17;
27069                      break;
27070                    }
27071                  case TYPE_DIV:
27072                    {
27073                      if (! store_data_bypass_p (dep_insn, insn))
27074                        return get_attr_size (dep_insn) == SIZE_32 ? 45 : 57;
27075                      break;
27076                    }
27077                  default:
27078                    break;
27079                  }
27080              }
27081	    break;
27082
27083          case TYPE_LOAD:
27084            if ((rs6000_cpu == PROCESSOR_POWER6)
27085                && recog_memoized (dep_insn)
27086                && (INSN_CODE (dep_insn) >= 0))
27087              {
27088
27089                /* Adjust the cost for the case where the value written
27090                   by a fixed point instruction is used within the address
27091                   gen portion of a subsequent load(u)(x) */
27092                switch (get_attr_type (dep_insn))
27093                  {
27094                  case TYPE_LOAD:
27095                  case TYPE_CNTLZ:
27096                    {
27097                      if (set_to_load_agen (dep_insn, insn))
27098                        return get_attr_sign_extend (dep_insn)
27099                               == SIGN_EXTEND_YES ? 6 : 4;
27100                      break;
27101                    }
27102                  case TYPE_SHIFT:
27103                    {
27104                      if (set_to_load_agen (dep_insn, insn))
27105                        return get_attr_var_shift (dep_insn) == VAR_SHIFT_YES ?
27106                               6 : 3;
27107                      break;
27108		    }
27109                  case TYPE_INTEGER:
27110                  case TYPE_ADD:
27111                  case TYPE_LOGICAL:
27112                  case TYPE_EXTS:
27113                  case TYPE_INSERT:
27114                    {
27115                      if (set_to_load_agen (dep_insn, insn))
27116                        return 3;
27117                      break;
27118                    }
27119                  case TYPE_STORE:
27120                  case TYPE_FPLOAD:
27121                  case TYPE_FPSTORE:
27122                    {
27123                      if (get_attr_update (dep_insn) == UPDATE_YES
27124                          && set_to_load_agen (dep_insn, insn))
27125                        return 3;
27126                      break;
27127                    }
27128                  case TYPE_MUL:
27129                    {
27130                      if (set_to_load_agen (dep_insn, insn))
27131                        return 17;
27132                      break;
27133                    }
27134                  case TYPE_DIV:
27135                    {
27136                      if (set_to_load_agen (dep_insn, insn))
27137                        return get_attr_size (dep_insn) == SIZE_32 ? 45 : 57;
27138                      break;
27139                    }
27140                  default:
27141                    break;
27142                  }
27143              }
27144            break;
27145
27146          case TYPE_FPLOAD:
27147            if ((rs6000_cpu == PROCESSOR_POWER6)
27148                && get_attr_update (insn) == UPDATE_NO
27149                && recog_memoized (dep_insn)
27150                && (INSN_CODE (dep_insn) >= 0)
27151                && (get_attr_type (dep_insn) == TYPE_MFFGPR))
27152              return 2;
27153
27154          default:
27155            break;
27156          }
27157
27158	/* Fall out to return default cost.  */
27159      }
27160      break;
27161
27162    case REG_DEP_OUTPUT:
27163      /* Output dependency; DEP_INSN writes a register that INSN writes some
27164	 cycles later.  */
27165      if ((rs6000_cpu == PROCESSOR_POWER6)
27166          && recog_memoized (dep_insn)
27167          && (INSN_CODE (dep_insn) >= 0))
27168        {
27169          attr_type = get_attr_type (insn);
27170
27171          switch (attr_type)
27172            {
27173            case TYPE_FP:
27174              if (get_attr_type (dep_insn) == TYPE_FP)
27175                return 1;
27176              break;
27177            case TYPE_FPLOAD:
27178              if (get_attr_update (insn) == UPDATE_NO
27179                  && get_attr_type (dep_insn) == TYPE_MFFGPR)
27180                return 2;
27181              break;
27182            default:
27183              break;
27184            }
27185        }
27186    case REG_DEP_ANTI:
27187      /* Anti dependency; DEP_INSN reads a register that INSN writes some
27188	 cycles later.  */
27189      return 0;
27190
27191    default:
27192      gcc_unreachable ();
27193    }
27194
27195  return cost;
27196}
27197
27198/* Debug version of rs6000_adjust_cost.  */
27199
27200static int
27201rs6000_debug_adjust_cost (rtx_insn *insn, rtx link, rtx_insn *dep_insn,
27202			  int cost)
27203{
27204  int ret = rs6000_adjust_cost (insn, link, dep_insn, cost);
27205
27206  if (ret != cost)
27207    {
27208      const char *dep;
27209
27210      switch (REG_NOTE_KIND (link))
27211	{
27212	default:	     dep = "unknown depencency"; break;
27213	case REG_DEP_TRUE:   dep = "data dependency";	 break;
27214	case REG_DEP_OUTPUT: dep = "output dependency";  break;
27215	case REG_DEP_ANTI:   dep = "anti depencency";	 break;
27216	}
27217
27218      fprintf (stderr,
27219	       "\nrs6000_adjust_cost, final cost = %d, orig cost = %d, "
27220	       "%s, insn:\n", ret, cost, dep);
27221
27222      debug_rtx (insn);
27223    }
27224
27225  return ret;
27226}
27227
27228/* The function returns a true if INSN is microcoded.
27229   Return false otherwise.  */
27230
27231static bool
27232is_microcoded_insn (rtx_insn *insn)
27233{
27234  if (!insn || !NONDEBUG_INSN_P (insn)
27235      || GET_CODE (PATTERN (insn)) == USE
27236      || GET_CODE (PATTERN (insn)) == CLOBBER)
27237    return false;
27238
27239  if (rs6000_cpu_attr == CPU_CELL)
27240    return get_attr_cell_micro (insn) == CELL_MICRO_ALWAYS;
27241
27242  if (rs6000_sched_groups
27243      && (rs6000_cpu == PROCESSOR_POWER4 || rs6000_cpu == PROCESSOR_POWER5))
27244    {
27245      enum attr_type type = get_attr_type (insn);
27246      if ((type == TYPE_LOAD
27247	   && get_attr_update (insn) == UPDATE_YES
27248	   && get_attr_sign_extend (insn) == SIGN_EXTEND_YES)
27249	  || ((type == TYPE_LOAD || type == TYPE_STORE)
27250	      && get_attr_update (insn) == UPDATE_YES
27251	      && get_attr_indexed (insn) == INDEXED_YES)
27252	  || type == TYPE_MFCR)
27253	return true;
27254    }
27255
27256  return false;
27257}
27258
27259/* The function returns true if INSN is cracked into 2 instructions
27260   by the processor (and therefore occupies 2 issue slots).  */
27261
27262static bool
27263is_cracked_insn (rtx_insn *insn)
27264{
27265  if (!insn || !NONDEBUG_INSN_P (insn)
27266      || GET_CODE (PATTERN (insn)) == USE
27267      || GET_CODE (PATTERN (insn)) == CLOBBER)
27268    return false;
27269
27270  if (rs6000_sched_groups
27271      && (rs6000_cpu == PROCESSOR_POWER4 || rs6000_cpu == PROCESSOR_POWER5))
27272    {
27273      enum attr_type type = get_attr_type (insn);
27274      if ((type == TYPE_LOAD
27275	   && get_attr_sign_extend (insn) == SIGN_EXTEND_YES
27276	   && get_attr_update (insn) == UPDATE_NO)
27277	  || (type == TYPE_LOAD
27278	      && get_attr_sign_extend (insn) == SIGN_EXTEND_NO
27279	      && get_attr_update (insn) == UPDATE_YES
27280	      && get_attr_indexed (insn) == INDEXED_NO)
27281	  || (type == TYPE_STORE
27282	      && get_attr_update (insn) == UPDATE_YES
27283	      && get_attr_indexed (insn) == INDEXED_NO)
27284	  || ((type == TYPE_FPLOAD || type == TYPE_FPSTORE)
27285	      && get_attr_update (insn) == UPDATE_YES)
27286	  || type == TYPE_DELAYED_CR
27287	  || (type == TYPE_EXTS
27288	      && get_attr_dot (insn) == DOT_YES)
27289	  || (type == TYPE_SHIFT
27290	      && get_attr_dot (insn) == DOT_YES
27291	      && get_attr_var_shift (insn) == VAR_SHIFT_NO)
27292	  || (type == TYPE_MUL
27293	      && get_attr_dot (insn) == DOT_YES)
27294	  || type == TYPE_DIV
27295	  || (type == TYPE_INSERT
27296	      && get_attr_size (insn) == SIZE_32))
27297	return true;
27298    }
27299
27300  return false;
27301}
27302
27303/* The function returns true if INSN can be issued only from
27304   the branch slot.  */
27305
27306static bool
27307is_branch_slot_insn (rtx_insn *insn)
27308{
27309  if (!insn || !NONDEBUG_INSN_P (insn)
27310      || GET_CODE (PATTERN (insn)) == USE
27311      || GET_CODE (PATTERN (insn)) == CLOBBER)
27312    return false;
27313
27314  if (rs6000_sched_groups)
27315    {
27316      enum attr_type type = get_attr_type (insn);
27317      if (type == TYPE_BRANCH || type == TYPE_JMPREG)
27318	return true;
27319      return false;
27320    }
27321
27322  return false;
27323}
27324
27325/* The function returns true if out_inst sets a value that is
27326   used in the address generation computation of in_insn */
27327static bool
27328set_to_load_agen (rtx_insn *out_insn, rtx_insn *in_insn)
27329{
27330  rtx out_set, in_set;
27331
27332  /* For performance reasons, only handle the simple case where
27333     both loads are a single_set. */
27334  out_set = single_set (out_insn);
27335  if (out_set)
27336    {
27337      in_set = single_set (in_insn);
27338      if (in_set)
27339        return reg_mentioned_p (SET_DEST (out_set), SET_SRC (in_set));
27340    }
27341
27342  return false;
27343}
27344
27345/* Try to determine base/offset/size parts of the given MEM.
27346   Return true if successful, false if all the values couldn't
27347   be determined.
27348
27349   This function only looks for REG or REG+CONST address forms.
27350   REG+REG address form will return false. */
27351
27352static bool
27353get_memref_parts (rtx mem, rtx *base, HOST_WIDE_INT *offset,
27354		  HOST_WIDE_INT *size)
27355{
27356  rtx addr_rtx;
27357  if MEM_SIZE_KNOWN_P (mem)
27358    *size = MEM_SIZE (mem);
27359  else
27360    return false;
27361
27362  addr_rtx = (XEXP (mem, 0));
27363  if (GET_CODE (addr_rtx) == PRE_MODIFY)
27364    addr_rtx = XEXP (addr_rtx, 1);
27365
27366  *offset = 0;
27367  while (GET_CODE (addr_rtx) == PLUS
27368	 && CONST_INT_P (XEXP (addr_rtx, 1)))
27369    {
27370      *offset += INTVAL (XEXP (addr_rtx, 1));
27371      addr_rtx = XEXP (addr_rtx, 0);
27372    }
27373  if (!REG_P (addr_rtx))
27374    return false;
27375
27376  *base = addr_rtx;
27377  return true;
27378}
27379
27380/* The function returns true if the target storage location of
27381   mem1 is adjacent to the target storage location of mem2 */
27382/* Return 1 if memory locations are adjacent.  */
27383
27384static bool
27385adjacent_mem_locations (rtx mem1, rtx mem2)
27386{
27387  rtx reg1, reg2;
27388  HOST_WIDE_INT off1, size1, off2, size2;
27389
27390  if (get_memref_parts (mem1, &reg1, &off1, &size1)
27391      && get_memref_parts (mem2, &reg2, &off2, &size2))
27392    return ((REGNO (reg1) == REGNO (reg2))
27393	    && ((off1 + size1 == off2)
27394		|| (off2 + size2 == off1)));
27395
27396  return false;
27397}
27398
27399/* This function returns true if it can be determined that the two MEM
27400   locations overlap by at least 1 byte based on base reg/offset/size. */
27401
27402static bool
27403mem_locations_overlap (rtx mem1, rtx mem2)
27404{
27405  rtx reg1, reg2;
27406  HOST_WIDE_INT off1, size1, off2, size2;
27407
27408  if (get_memref_parts (mem1, &reg1, &off1, &size1)
27409      && get_memref_parts (mem2, &reg2, &off2, &size2))
27410    return ((REGNO (reg1) == REGNO (reg2))
27411	    && (((off1 <= off2) && (off1 + size1 > off2))
27412		|| ((off2 <= off1) && (off2 + size2 > off1))));
27413
27414  return false;
27415}
27416
27417/* A C statement (sans semicolon) to update the integer scheduling
27418   priority INSN_PRIORITY (INSN). Increase the priority to execute the
27419   INSN earlier, reduce the priority to execute INSN later.  Do not
27420   define this macro if you do not need to adjust the scheduling
27421   priorities of insns.  */
27422
27423static int
27424rs6000_adjust_priority (rtx_insn *insn ATTRIBUTE_UNUSED, int priority)
27425{
27426  rtx load_mem, str_mem;
27427  /* On machines (like the 750) which have asymmetric integer units,
27428     where one integer unit can do multiply and divides and the other
27429     can't, reduce the priority of multiply/divide so it is scheduled
27430     before other integer operations.  */
27431
27432#if 0
27433  if (! INSN_P (insn))
27434    return priority;
27435
27436  if (GET_CODE (PATTERN (insn)) == USE)
27437    return priority;
27438
27439  switch (rs6000_cpu_attr) {
27440  case CPU_PPC750:
27441    switch (get_attr_type (insn))
27442      {
27443      default:
27444	break;
27445
27446      case TYPE_MUL:
27447      case TYPE_DIV:
27448	fprintf (stderr, "priority was %#x (%d) before adjustment\n",
27449		 priority, priority);
27450	if (priority >= 0 && priority < 0x01000000)
27451	  priority >>= 3;
27452	break;
27453      }
27454  }
27455#endif
27456
27457  if (insn_must_be_first_in_group (insn)
27458      && reload_completed
27459      && current_sched_info->sched_max_insns_priority
27460      && rs6000_sched_restricted_insns_priority)
27461    {
27462
27463      /* Prioritize insns that can be dispatched only in the first
27464	 dispatch slot.  */
27465      if (rs6000_sched_restricted_insns_priority == 1)
27466	/* Attach highest priority to insn. This means that in
27467	   haifa-sched.c:ready_sort(), dispatch-slot restriction considerations
27468	   precede 'priority' (critical path) considerations.  */
27469	return current_sched_info->sched_max_insns_priority;
27470      else if (rs6000_sched_restricted_insns_priority == 2)
27471	/* Increase priority of insn by a minimal amount. This means that in
27472	   haifa-sched.c:ready_sort(), only 'priority' (critical path)
27473	   considerations precede dispatch-slot restriction considerations.  */
27474	return (priority + 1);
27475    }
27476
27477  if (rs6000_cpu == PROCESSOR_POWER6
27478      && ((load_store_pendulum == -2 && is_load_insn (insn, &load_mem))
27479          || (load_store_pendulum == 2 && is_store_insn (insn, &str_mem))))
27480    /* Attach highest priority to insn if the scheduler has just issued two
27481       stores and this instruction is a load, or two loads and this instruction
27482       is a store. Power6 wants loads and stores scheduled alternately
27483       when possible */
27484    return current_sched_info->sched_max_insns_priority;
27485
27486  return priority;
27487}
27488
27489/* Return true if the instruction is nonpipelined on the Cell. */
27490static bool
27491is_nonpipeline_insn (rtx_insn *insn)
27492{
27493  enum attr_type type;
27494  if (!insn || !NONDEBUG_INSN_P (insn)
27495      || GET_CODE (PATTERN (insn)) == USE
27496      || GET_CODE (PATTERN (insn)) == CLOBBER)
27497    return false;
27498
27499  type = get_attr_type (insn);
27500  if (type == TYPE_MUL
27501      || type == TYPE_DIV
27502      || type == TYPE_SDIV
27503      || type == TYPE_DDIV
27504      || type == TYPE_SSQRT
27505      || type == TYPE_DSQRT
27506      || type == TYPE_MFCR
27507      || type == TYPE_MFCRF
27508      || type == TYPE_MFJMPR)
27509    {
27510      return true;
27511    }
27512  return false;
27513}
27514
27515
27516/* Return how many instructions the machine can issue per cycle.  */
27517
27518static int
27519rs6000_issue_rate (void)
27520{
27521  /* Unless scheduling for register pressure, use issue rate of 1 for
27522     first scheduling pass to decrease degradation.  */
27523  if (!reload_completed && !flag_sched_pressure)
27524    return 1;
27525
27526  switch (rs6000_cpu_attr) {
27527  case CPU_RS64A:
27528  case CPU_PPC601: /* ? */
27529  case CPU_PPC7450:
27530    return 3;
27531  case CPU_PPC440:
27532  case CPU_PPC603:
27533  case CPU_PPC750:
27534  case CPU_PPC7400:
27535  case CPU_PPC8540:
27536  case CPU_PPC8548:
27537  case CPU_CELL:
27538  case CPU_PPCE300C2:
27539  case CPU_PPCE300C3:
27540  case CPU_PPCE500MC:
27541  case CPU_PPCE500MC64:
27542  case CPU_PPCE5500:
27543  case CPU_PPCE6500:
27544  case CPU_TITAN:
27545    return 2;
27546  case CPU_PPC476:
27547  case CPU_PPC604:
27548  case CPU_PPC604E:
27549  case CPU_PPC620:
27550  case CPU_PPC630:
27551    return 4;
27552  case CPU_POWER4:
27553  case CPU_POWER5:
27554  case CPU_POWER6:
27555  case CPU_POWER7:
27556    return 5;
27557  case CPU_POWER8:
27558    return 7;
27559  default:
27560    return 1;
27561  }
27562}
27563
27564/* Return how many instructions to look ahead for better insn
27565   scheduling.  */
27566
27567static int
27568rs6000_use_sched_lookahead (void)
27569{
27570  switch (rs6000_cpu_attr)
27571    {
27572    case CPU_PPC8540:
27573    case CPU_PPC8548:
27574      return 4;
27575
27576    case CPU_CELL:
27577      return (reload_completed ? 8 : 0);
27578
27579    default:
27580      return 0;
27581    }
27582}
27583
27584/* We are choosing insn from the ready queue.  Return zero if INSN can be
27585   chosen.  */
27586static int
27587rs6000_use_sched_lookahead_guard (rtx_insn *insn, int ready_index)
27588{
27589  if (ready_index == 0)
27590    return 0;
27591
27592  if (rs6000_cpu_attr != CPU_CELL)
27593    return 0;
27594
27595  gcc_assert (insn != NULL_RTX && INSN_P (insn));
27596
27597  if (!reload_completed
27598      || is_nonpipeline_insn (insn)
27599      || is_microcoded_insn (insn))
27600    return 1;
27601
27602  return 0;
27603}
27604
27605/* Determine if PAT refers to memory. If so, set MEM_REF to the MEM rtx
27606   and return true.  */
27607
27608static bool
27609find_mem_ref (rtx pat, rtx *mem_ref)
27610{
27611  const char * fmt;
27612  int i, j;
27613
27614  /* stack_tie does not produce any real memory traffic.  */
27615  if (tie_operand (pat, VOIDmode))
27616    return false;
27617
27618  if (GET_CODE (pat) == MEM)
27619    {
27620      *mem_ref = pat;
27621      return true;
27622    }
27623
27624  /* Recursively process the pattern.  */
27625  fmt = GET_RTX_FORMAT (GET_CODE (pat));
27626
27627  for (i = GET_RTX_LENGTH (GET_CODE (pat)) - 1; i >= 0; i--)
27628    {
27629      if (fmt[i] == 'e')
27630	{
27631	  if (find_mem_ref (XEXP (pat, i), mem_ref))
27632	    return true;
27633	}
27634      else if (fmt[i] == 'E')
27635	for (j = XVECLEN (pat, i) - 1; j >= 0; j--)
27636	  {
27637	    if (find_mem_ref (XVECEXP (pat, i, j), mem_ref))
27638	      return true;
27639	  }
27640    }
27641
27642  return false;
27643}
27644
27645/* Determine if PAT is a PATTERN of a load insn.  */
27646
27647static bool
27648is_load_insn1 (rtx pat, rtx *load_mem)
27649{
27650  if (!pat || pat == NULL_RTX)
27651    return false;
27652
27653  if (GET_CODE (pat) == SET)
27654    return find_mem_ref (SET_SRC (pat), load_mem);
27655
27656  if (GET_CODE (pat) == PARALLEL)
27657    {
27658      int i;
27659
27660      for (i = 0; i < XVECLEN (pat, 0); i++)
27661	if (is_load_insn1 (XVECEXP (pat, 0, i), load_mem))
27662	  return true;
27663    }
27664
27665  return false;
27666}
27667
27668/* Determine if INSN loads from memory.  */
27669
27670static bool
27671is_load_insn (rtx insn, rtx *load_mem)
27672{
27673  if (!insn || !INSN_P (insn))
27674    return false;
27675
27676  if (CALL_P (insn))
27677    return false;
27678
27679  return is_load_insn1 (PATTERN (insn), load_mem);
27680}
27681
27682/* Determine if PAT is a PATTERN of a store insn.  */
27683
27684static bool
27685is_store_insn1 (rtx pat, rtx *str_mem)
27686{
27687  if (!pat || pat == NULL_RTX)
27688    return false;
27689
27690  if (GET_CODE (pat) == SET)
27691    return find_mem_ref (SET_DEST (pat), str_mem);
27692
27693  if (GET_CODE (pat) == PARALLEL)
27694    {
27695      int i;
27696
27697      for (i = 0; i < XVECLEN (pat, 0); i++)
27698	if (is_store_insn1 (XVECEXP (pat, 0, i), str_mem))
27699	  return true;
27700    }
27701
27702  return false;
27703}
27704
27705/* Determine if INSN stores to memory.  */
27706
27707static bool
27708is_store_insn (rtx insn, rtx *str_mem)
27709{
27710  if (!insn || !INSN_P (insn))
27711    return false;
27712
27713  return is_store_insn1 (PATTERN (insn), str_mem);
27714}
27715
27716/* Returns whether the dependence between INSN and NEXT is considered
27717   costly by the given target.  */
27718
27719static bool
27720rs6000_is_costly_dependence (dep_t dep, int cost, int distance)
27721{
27722  rtx insn;
27723  rtx next;
27724  rtx load_mem, str_mem;
27725
27726  /* If the flag is not enabled - no dependence is considered costly;
27727     allow all dependent insns in the same group.
27728     This is the most aggressive option.  */
27729  if (rs6000_sched_costly_dep == no_dep_costly)
27730    return false;
27731
27732  /* If the flag is set to 1 - a dependence is always considered costly;
27733     do not allow dependent instructions in the same group.
27734     This is the most conservative option.  */
27735  if (rs6000_sched_costly_dep == all_deps_costly)
27736    return true;
27737
27738  insn = DEP_PRO (dep);
27739  next = DEP_CON (dep);
27740
27741  if (rs6000_sched_costly_dep == store_to_load_dep_costly
27742      && is_load_insn (next, &load_mem)
27743      && is_store_insn (insn, &str_mem))
27744    /* Prevent load after store in the same group.  */
27745    return true;
27746
27747  if (rs6000_sched_costly_dep == true_store_to_load_dep_costly
27748      && is_load_insn (next, &load_mem)
27749      && is_store_insn (insn, &str_mem)
27750      && DEP_TYPE (dep) == REG_DEP_TRUE
27751      && mem_locations_overlap(str_mem, load_mem))
27752     /* Prevent load after store in the same group if it is a true
27753	dependence.  */
27754     return true;
27755
27756  /* The flag is set to X; dependences with latency >= X are considered costly,
27757     and will not be scheduled in the same group.  */
27758  if (rs6000_sched_costly_dep <= max_dep_latency
27759      && ((cost - distance) >= (int)rs6000_sched_costly_dep))
27760    return true;
27761
27762  return false;
27763}
27764
27765/* Return the next insn after INSN that is found before TAIL is reached,
27766   skipping any "non-active" insns - insns that will not actually occupy
27767   an issue slot.  Return NULL_RTX if such an insn is not found.  */
27768
27769static rtx_insn *
27770get_next_active_insn (rtx_insn *insn, rtx_insn *tail)
27771{
27772  if (insn == NULL_RTX || insn == tail)
27773    return NULL;
27774
27775  while (1)
27776    {
27777      insn = NEXT_INSN (insn);
27778      if (insn == NULL_RTX || insn == tail)
27779	return NULL;
27780
27781      if (CALL_P (insn)
27782	  || JUMP_P (insn) || JUMP_TABLE_DATA_P (insn)
27783	  || (NONJUMP_INSN_P (insn)
27784	      && GET_CODE (PATTERN (insn)) != USE
27785	      && GET_CODE (PATTERN (insn)) != CLOBBER
27786	      && INSN_CODE (insn) != CODE_FOR_stack_tie))
27787	break;
27788    }
27789  return insn;
27790}
27791
27792/* We are about to begin issuing insns for this clock cycle. */
27793
27794static int
27795rs6000_sched_reorder (FILE *dump ATTRIBUTE_UNUSED, int sched_verbose,
27796                        rtx_insn **ready ATTRIBUTE_UNUSED,
27797                        int *pn_ready ATTRIBUTE_UNUSED,
27798		        int clock_var ATTRIBUTE_UNUSED)
27799{
27800  int n_ready = *pn_ready;
27801
27802  if (sched_verbose)
27803    fprintf (dump, "// rs6000_sched_reorder :\n");
27804
27805  /* Reorder the ready list, if the second to last ready insn
27806     is a nonepipeline insn.  */
27807  if (rs6000_cpu_attr == CPU_CELL && n_ready > 1)
27808  {
27809    if (is_nonpipeline_insn (ready[n_ready - 1])
27810        && (recog_memoized (ready[n_ready - 2]) > 0))
27811      /* Simply swap first two insns.  */
27812      std::swap (ready[n_ready - 1], ready[n_ready - 2]);
27813  }
27814
27815  if (rs6000_cpu == PROCESSOR_POWER6)
27816    load_store_pendulum = 0;
27817
27818  return rs6000_issue_rate ();
27819}
27820
27821/* Like rs6000_sched_reorder, but called after issuing each insn.  */
27822
27823static int
27824rs6000_sched_reorder2 (FILE *dump, int sched_verbose, rtx_insn **ready,
27825		         int *pn_ready, int clock_var ATTRIBUTE_UNUSED)
27826{
27827  if (sched_verbose)
27828    fprintf (dump, "// rs6000_sched_reorder2 :\n");
27829
27830  /* For Power6, we need to handle some special cases to try and keep the
27831     store queue from overflowing and triggering expensive flushes.
27832
27833     This code monitors how load and store instructions are being issued
27834     and skews the ready list one way or the other to increase the likelihood
27835     that a desired instruction is issued at the proper time.
27836
27837     A couple of things are done.  First, we maintain a "load_store_pendulum"
27838     to track the current state of load/store issue.
27839
27840       - If the pendulum is at zero, then no loads or stores have been
27841         issued in the current cycle so we do nothing.
27842
27843       - If the pendulum is 1, then a single load has been issued in this
27844         cycle and we attempt to locate another load in the ready list to
27845         issue with it.
27846
27847       - If the pendulum is -2, then two stores have already been
27848         issued in this cycle, so we increase the priority of the first load
27849         in the ready list to increase it's likelihood of being chosen first
27850         in the next cycle.
27851
27852       - If the pendulum is -1, then a single store has been issued in this
27853         cycle and we attempt to locate another store in the ready list to
27854         issue with it, preferring a store to an adjacent memory location to
27855         facilitate store pairing in the store queue.
27856
27857       - If the pendulum is 2, then two loads have already been
27858         issued in this cycle, so we increase the priority of the first store
27859         in the ready list to increase it's likelihood of being chosen first
27860         in the next cycle.
27861
27862       - If the pendulum < -2 or > 2, then do nothing.
27863
27864       Note: This code covers the most common scenarios.  There exist non
27865             load/store instructions which make use of the LSU and which
27866             would need to be accounted for to strictly model the behavior
27867             of the machine.  Those instructions are currently unaccounted
27868             for to help minimize compile time overhead of this code.
27869   */
27870  if (rs6000_cpu == PROCESSOR_POWER6 && last_scheduled_insn)
27871    {
27872      int pos;
27873      int i;
27874      rtx_insn *tmp;
27875      rtx load_mem, str_mem;
27876
27877      if (is_store_insn (last_scheduled_insn, &str_mem))
27878        /* Issuing a store, swing the load_store_pendulum to the left */
27879        load_store_pendulum--;
27880      else if (is_load_insn (last_scheduled_insn, &load_mem))
27881        /* Issuing a load, swing the load_store_pendulum to the right */
27882        load_store_pendulum++;
27883      else
27884        return cached_can_issue_more;
27885
27886      /* If the pendulum is balanced, or there is only one instruction on
27887         the ready list, then all is well, so return. */
27888      if ((load_store_pendulum == 0) || (*pn_ready <= 1))
27889        return cached_can_issue_more;
27890
27891      if (load_store_pendulum == 1)
27892        {
27893          /* A load has been issued in this cycle.  Scan the ready list
27894             for another load to issue with it */
27895          pos = *pn_ready-1;
27896
27897          while (pos >= 0)
27898            {
27899              if (is_load_insn (ready[pos], &load_mem))
27900                {
27901                  /* Found a load.  Move it to the head of the ready list,
27902                     and adjust it's priority so that it is more likely to
27903                     stay there */
27904                  tmp = ready[pos];
27905                  for (i=pos; i<*pn_ready-1; i++)
27906                    ready[i] = ready[i + 1];
27907                  ready[*pn_ready-1] = tmp;
27908
27909                  if (!sel_sched_p () && INSN_PRIORITY_KNOWN (tmp))
27910                    INSN_PRIORITY (tmp)++;
27911                  break;
27912                }
27913              pos--;
27914            }
27915        }
27916      else if (load_store_pendulum == -2)
27917        {
27918          /* Two stores have been issued in this cycle.  Increase the
27919             priority of the first load in the ready list to favor it for
27920             issuing in the next cycle. */
27921          pos = *pn_ready-1;
27922
27923          while (pos >= 0)
27924            {
27925              if (is_load_insn (ready[pos], &load_mem)
27926                  && !sel_sched_p ()
27927		  && INSN_PRIORITY_KNOWN (ready[pos]))
27928                {
27929                  INSN_PRIORITY (ready[pos])++;
27930
27931                  /* Adjust the pendulum to account for the fact that a load
27932                     was found and increased in priority.  This is to prevent
27933                     increasing the priority of multiple loads */
27934                  load_store_pendulum--;
27935
27936                  break;
27937                }
27938              pos--;
27939            }
27940        }
27941      else if (load_store_pendulum == -1)
27942        {
27943          /* A store has been issued in this cycle.  Scan the ready list for
27944             another store to issue with it, preferring a store to an adjacent
27945             memory location */
27946          int first_store_pos = -1;
27947
27948          pos = *pn_ready-1;
27949
27950          while (pos >= 0)
27951            {
27952              if (is_store_insn (ready[pos], &str_mem))
27953                {
27954		  rtx str_mem2;
27955                  /* Maintain the index of the first store found on the
27956                     list */
27957                  if (first_store_pos == -1)
27958                    first_store_pos = pos;
27959
27960                  if (is_store_insn (last_scheduled_insn, &str_mem2)
27961                      && adjacent_mem_locations (str_mem, str_mem2))
27962                    {
27963                      /* Found an adjacent store.  Move it to the head of the
27964                         ready list, and adjust it's priority so that it is
27965                         more likely to stay there */
27966                      tmp = ready[pos];
27967                      for (i=pos; i<*pn_ready-1; i++)
27968                        ready[i] = ready[i + 1];
27969                      ready[*pn_ready-1] = tmp;
27970
27971                      if (!sel_sched_p () && INSN_PRIORITY_KNOWN (tmp))
27972                        INSN_PRIORITY (tmp)++;
27973
27974                      first_store_pos = -1;
27975
27976                      break;
27977                    };
27978                }
27979              pos--;
27980            }
27981
27982          if (first_store_pos >= 0)
27983            {
27984              /* An adjacent store wasn't found, but a non-adjacent store was,
27985                 so move the non-adjacent store to the front of the ready
27986                 list, and adjust its priority so that it is more likely to
27987                 stay there. */
27988              tmp = ready[first_store_pos];
27989              for (i=first_store_pos; i<*pn_ready-1; i++)
27990                ready[i] = ready[i + 1];
27991              ready[*pn_ready-1] = tmp;
27992              if (!sel_sched_p () && INSN_PRIORITY_KNOWN (tmp))
27993                INSN_PRIORITY (tmp)++;
27994            }
27995        }
27996      else if (load_store_pendulum == 2)
27997       {
27998           /* Two loads have been issued in this cycle.  Increase the priority
27999              of the first store in the ready list to favor it for issuing in
28000              the next cycle. */
28001          pos = *pn_ready-1;
28002
28003          while (pos >= 0)
28004            {
28005              if (is_store_insn (ready[pos], &str_mem)
28006                  && !sel_sched_p ()
28007		  && INSN_PRIORITY_KNOWN (ready[pos]))
28008                {
28009                  INSN_PRIORITY (ready[pos])++;
28010
28011                  /* Adjust the pendulum to account for the fact that a store
28012                     was found and increased in priority.  This is to prevent
28013                     increasing the priority of multiple stores */
28014                  load_store_pendulum++;
28015
28016                  break;
28017                }
28018              pos--;
28019            }
28020        }
28021    }
28022
28023  return cached_can_issue_more;
28024}
28025
28026/* Return whether the presence of INSN causes a dispatch group termination
28027   of group WHICH_GROUP.
28028
28029   If WHICH_GROUP == current_group, this function will return true if INSN
28030   causes the termination of the current group (i.e, the dispatch group to
28031   which INSN belongs). This means that INSN will be the last insn in the
28032   group it belongs to.
28033
28034   If WHICH_GROUP == previous_group, this function will return true if INSN
28035   causes the termination of the previous group (i.e, the dispatch group that
28036   precedes the group to which INSN belongs).  This means that INSN will be
28037   the first insn in the group it belongs to).  */
28038
28039static bool
28040insn_terminates_group_p (rtx_insn *insn, enum group_termination which_group)
28041{
28042  bool first, last;
28043
28044  if (! insn)
28045    return false;
28046
28047  first = insn_must_be_first_in_group (insn);
28048  last = insn_must_be_last_in_group (insn);
28049
28050  if (first && last)
28051    return true;
28052
28053  if (which_group == current_group)
28054    return last;
28055  else if (which_group == previous_group)
28056    return first;
28057
28058  return false;
28059}
28060
28061
28062static bool
28063insn_must_be_first_in_group (rtx_insn *insn)
28064{
28065  enum attr_type type;
28066
28067  if (!insn
28068      || NOTE_P (insn)
28069      || DEBUG_INSN_P (insn)
28070      || GET_CODE (PATTERN (insn)) == USE
28071      || GET_CODE (PATTERN (insn)) == CLOBBER)
28072    return false;
28073
28074  switch (rs6000_cpu)
28075    {
28076    case PROCESSOR_POWER5:
28077      if (is_cracked_insn (insn))
28078        return true;
28079    case PROCESSOR_POWER4:
28080      if (is_microcoded_insn (insn))
28081        return true;
28082
28083      if (!rs6000_sched_groups)
28084        return false;
28085
28086      type = get_attr_type (insn);
28087
28088      switch (type)
28089        {
28090        case TYPE_MFCR:
28091        case TYPE_MFCRF:
28092        case TYPE_MTCR:
28093        case TYPE_DELAYED_CR:
28094        case TYPE_CR_LOGICAL:
28095        case TYPE_MTJMPR:
28096        case TYPE_MFJMPR:
28097        case TYPE_DIV:
28098        case TYPE_LOAD_L:
28099        case TYPE_STORE_C:
28100        case TYPE_ISYNC:
28101        case TYPE_SYNC:
28102          return true;
28103        default:
28104          break;
28105        }
28106      break;
28107    case PROCESSOR_POWER6:
28108      type = get_attr_type (insn);
28109
28110      switch (type)
28111        {
28112        case TYPE_EXTS:
28113        case TYPE_CNTLZ:
28114        case TYPE_TRAP:
28115        case TYPE_MUL:
28116        case TYPE_INSERT:
28117        case TYPE_FPCOMPARE:
28118        case TYPE_MFCR:
28119        case TYPE_MTCR:
28120        case TYPE_MFJMPR:
28121        case TYPE_MTJMPR:
28122        case TYPE_ISYNC:
28123        case TYPE_SYNC:
28124        case TYPE_LOAD_L:
28125        case TYPE_STORE_C:
28126          return true;
28127        case TYPE_SHIFT:
28128          if (get_attr_dot (insn) == DOT_NO
28129              || get_attr_var_shift (insn) == VAR_SHIFT_NO)
28130            return true;
28131          else
28132            break;
28133        case TYPE_DIV:
28134          if (get_attr_size (insn) == SIZE_32)
28135            return true;
28136          else
28137            break;
28138        case TYPE_LOAD:
28139        case TYPE_STORE:
28140        case TYPE_FPLOAD:
28141        case TYPE_FPSTORE:
28142          if (get_attr_update (insn) == UPDATE_YES)
28143            return true;
28144          else
28145            break;
28146        default:
28147          break;
28148        }
28149      break;
28150    case PROCESSOR_POWER7:
28151      type = get_attr_type (insn);
28152
28153      switch (type)
28154        {
28155        case TYPE_CR_LOGICAL:
28156        case TYPE_MFCR:
28157        case TYPE_MFCRF:
28158        case TYPE_MTCR:
28159        case TYPE_DIV:
28160        case TYPE_ISYNC:
28161        case TYPE_LOAD_L:
28162        case TYPE_STORE_C:
28163        case TYPE_MFJMPR:
28164        case TYPE_MTJMPR:
28165          return true;
28166        case TYPE_MUL:
28167        case TYPE_SHIFT:
28168        case TYPE_EXTS:
28169          if (get_attr_dot (insn) == DOT_YES)
28170            return true;
28171          else
28172            break;
28173        case TYPE_LOAD:
28174          if (get_attr_sign_extend (insn) == SIGN_EXTEND_YES
28175              || get_attr_update (insn) == UPDATE_YES)
28176            return true;
28177          else
28178            break;
28179        case TYPE_STORE:
28180        case TYPE_FPLOAD:
28181        case TYPE_FPSTORE:
28182          if (get_attr_update (insn) == UPDATE_YES)
28183            return true;
28184          else
28185            break;
28186        default:
28187          break;
28188        }
28189      break;
28190    case PROCESSOR_POWER8:
28191      type = get_attr_type (insn);
28192
28193      switch (type)
28194        {
28195        case TYPE_CR_LOGICAL:
28196        case TYPE_DELAYED_CR:
28197        case TYPE_MFCR:
28198        case TYPE_MFCRF:
28199        case TYPE_MTCR:
28200        case TYPE_SYNC:
28201        case TYPE_ISYNC:
28202        case TYPE_LOAD_L:
28203        case TYPE_STORE_C:
28204        case TYPE_VECSTORE:
28205        case TYPE_MFJMPR:
28206        case TYPE_MTJMPR:
28207          return true;
28208        case TYPE_SHIFT:
28209        case TYPE_EXTS:
28210        case TYPE_MUL:
28211          if (get_attr_dot (insn) == DOT_YES)
28212            return true;
28213          else
28214            break;
28215        case TYPE_LOAD:
28216          if (get_attr_sign_extend (insn) == SIGN_EXTEND_YES
28217              || get_attr_update (insn) == UPDATE_YES)
28218            return true;
28219          else
28220            break;
28221        case TYPE_STORE:
28222          if (get_attr_update (insn) == UPDATE_YES
28223              && get_attr_indexed (insn) == INDEXED_YES)
28224            return true;
28225          else
28226            break;
28227        default:
28228          break;
28229        }
28230      break;
28231    default:
28232      break;
28233    }
28234
28235  return false;
28236}
28237
28238static bool
28239insn_must_be_last_in_group (rtx_insn *insn)
28240{
28241  enum attr_type type;
28242
28243  if (!insn
28244      || NOTE_P (insn)
28245      || DEBUG_INSN_P (insn)
28246      || GET_CODE (PATTERN (insn)) == USE
28247      || GET_CODE (PATTERN (insn)) == CLOBBER)
28248    return false;
28249
28250  switch (rs6000_cpu) {
28251  case PROCESSOR_POWER4:
28252  case PROCESSOR_POWER5:
28253    if (is_microcoded_insn (insn))
28254      return true;
28255
28256    if (is_branch_slot_insn (insn))
28257      return true;
28258
28259    break;
28260  case PROCESSOR_POWER6:
28261    type = get_attr_type (insn);
28262
28263    switch (type)
28264      {
28265      case TYPE_EXTS:
28266      case TYPE_CNTLZ:
28267      case TYPE_TRAP:
28268      case TYPE_MUL:
28269      case TYPE_FPCOMPARE:
28270      case TYPE_MFCR:
28271      case TYPE_MTCR:
28272      case TYPE_MFJMPR:
28273      case TYPE_MTJMPR:
28274      case TYPE_ISYNC:
28275      case TYPE_SYNC:
28276      case TYPE_LOAD_L:
28277      case TYPE_STORE_C:
28278        return true;
28279      case TYPE_SHIFT:
28280        if (get_attr_dot (insn) == DOT_NO
28281            || get_attr_var_shift (insn) == VAR_SHIFT_NO)
28282          return true;
28283        else
28284          break;
28285      case TYPE_DIV:
28286        if (get_attr_size (insn) == SIZE_32)
28287          return true;
28288        else
28289          break;
28290      default:
28291        break;
28292    }
28293    break;
28294  case PROCESSOR_POWER7:
28295    type = get_attr_type (insn);
28296
28297    switch (type)
28298      {
28299      case TYPE_ISYNC:
28300      case TYPE_SYNC:
28301      case TYPE_LOAD_L:
28302      case TYPE_STORE_C:
28303        return true;
28304      case TYPE_LOAD:
28305        if (get_attr_sign_extend (insn) == SIGN_EXTEND_YES
28306            && get_attr_update (insn) == UPDATE_YES)
28307          return true;
28308        else
28309          break;
28310      case TYPE_STORE:
28311        if (get_attr_update (insn) == UPDATE_YES
28312            && get_attr_indexed (insn) == INDEXED_YES)
28313          return true;
28314        else
28315          break;
28316      default:
28317        break;
28318    }
28319    break;
28320  case PROCESSOR_POWER8:
28321    type = get_attr_type (insn);
28322
28323    switch (type)
28324      {
28325      case TYPE_MFCR:
28326      case TYPE_MTCR:
28327      case TYPE_ISYNC:
28328      case TYPE_SYNC:
28329      case TYPE_LOAD_L:
28330      case TYPE_STORE_C:
28331        return true;
28332      case TYPE_LOAD:
28333        if (get_attr_sign_extend (insn) == SIGN_EXTEND_YES
28334            && get_attr_update (insn) == UPDATE_YES)
28335          return true;
28336        else
28337          break;
28338      case TYPE_STORE:
28339        if (get_attr_update (insn) == UPDATE_YES
28340            && get_attr_indexed (insn) == INDEXED_YES)
28341          return true;
28342        else
28343          break;
28344      default:
28345        break;
28346    }
28347    break;
28348  default:
28349    break;
28350  }
28351
28352  return false;
28353}
28354
28355/* Return true if it is recommended to keep NEXT_INSN "far" (in a separate
28356   dispatch group) from the insns in GROUP_INSNS.  Return false otherwise.  */
28357
28358static bool
28359is_costly_group (rtx *group_insns, rtx next_insn)
28360{
28361  int i;
28362  int issue_rate = rs6000_issue_rate ();
28363
28364  for (i = 0; i < issue_rate; i++)
28365    {
28366      sd_iterator_def sd_it;
28367      dep_t dep;
28368      rtx insn = group_insns[i];
28369
28370      if (!insn)
28371	continue;
28372
28373      FOR_EACH_DEP (insn, SD_LIST_RES_FORW, sd_it, dep)
28374	{
28375	  rtx next = DEP_CON (dep);
28376
28377	  if (next == next_insn
28378	      && rs6000_is_costly_dependence (dep, dep_cost (dep), 0))
28379	    return true;
28380	}
28381    }
28382
28383  return false;
28384}
28385
28386/* Utility of the function redefine_groups.
28387   Check if it is too costly to schedule NEXT_INSN together with GROUP_INSNS
28388   in the same dispatch group.  If so, insert nops before NEXT_INSN, in order
28389   to keep it "far" (in a separate group) from GROUP_INSNS, following
28390   one of the following schemes, depending on the value of the flag
28391   -minsert_sched_nops = X:
28392   (1) X == sched_finish_regroup_exact: insert exactly as many nops as needed
28393       in order to force NEXT_INSN into a separate group.
28394   (2) X < sched_finish_regroup_exact: insert exactly X nops.
28395   GROUP_END, CAN_ISSUE_MORE and GROUP_COUNT record the state after nop
28396   insertion (has a group just ended, how many vacant issue slots remain in the
28397   last group, and how many dispatch groups were encountered so far).  */
28398
28399static int
28400force_new_group (int sched_verbose, FILE *dump, rtx *group_insns,
28401		 rtx_insn *next_insn, bool *group_end, int can_issue_more,
28402		 int *group_count)
28403{
28404  rtx nop;
28405  bool force;
28406  int issue_rate = rs6000_issue_rate ();
28407  bool end = *group_end;
28408  int i;
28409
28410  if (next_insn == NULL_RTX || DEBUG_INSN_P (next_insn))
28411    return can_issue_more;
28412
28413  if (rs6000_sched_insert_nops > sched_finish_regroup_exact)
28414    return can_issue_more;
28415
28416  force = is_costly_group (group_insns, next_insn);
28417  if (!force)
28418    return can_issue_more;
28419
28420  if (sched_verbose > 6)
28421    fprintf (dump,"force: group count = %d, can_issue_more = %d\n",
28422	     *group_count ,can_issue_more);
28423
28424  if (rs6000_sched_insert_nops == sched_finish_regroup_exact)
28425    {
28426      if (*group_end)
28427	can_issue_more = 0;
28428
28429      /* Since only a branch can be issued in the last issue_slot, it is
28430	 sufficient to insert 'can_issue_more - 1' nops if next_insn is not
28431	 a branch. If next_insn is a branch, we insert 'can_issue_more' nops;
28432	 in this case the last nop will start a new group and the branch
28433	 will be forced to the new group.  */
28434      if (can_issue_more && !is_branch_slot_insn (next_insn))
28435	can_issue_more--;
28436
28437      /* Do we have a special group ending nop? */
28438      if (rs6000_cpu_attr == CPU_POWER6 || rs6000_cpu_attr == CPU_POWER7
28439	  || rs6000_cpu_attr == CPU_POWER8)
28440	{
28441	  nop = gen_group_ending_nop ();
28442	  emit_insn_before (nop, next_insn);
28443	  can_issue_more = 0;
28444	}
28445      else
28446	while (can_issue_more > 0)
28447	  {
28448	    nop = gen_nop ();
28449	    emit_insn_before (nop, next_insn);
28450	    can_issue_more--;
28451	  }
28452
28453      *group_end = true;
28454      return 0;
28455    }
28456
28457  if (rs6000_sched_insert_nops < sched_finish_regroup_exact)
28458    {
28459      int n_nops = rs6000_sched_insert_nops;
28460
28461      /* Nops can't be issued from the branch slot, so the effective
28462	 issue_rate for nops is 'issue_rate - 1'.  */
28463      if (can_issue_more == 0)
28464	can_issue_more = issue_rate;
28465      can_issue_more--;
28466      if (can_issue_more == 0)
28467	{
28468	  can_issue_more = issue_rate - 1;
28469	  (*group_count)++;
28470	  end = true;
28471	  for (i = 0; i < issue_rate; i++)
28472	    {
28473	      group_insns[i] = 0;
28474	    }
28475	}
28476
28477      while (n_nops > 0)
28478	{
28479	  nop = gen_nop ();
28480	  emit_insn_before (nop, next_insn);
28481	  if (can_issue_more == issue_rate - 1) /* new group begins */
28482	    end = false;
28483	  can_issue_more--;
28484	  if (can_issue_more == 0)
28485	    {
28486	      can_issue_more = issue_rate - 1;
28487	      (*group_count)++;
28488	      end = true;
28489	      for (i = 0; i < issue_rate; i++)
28490		{
28491		  group_insns[i] = 0;
28492		}
28493	    }
28494	  n_nops--;
28495	}
28496
28497      /* Scale back relative to 'issue_rate' (instead of 'issue_rate - 1').  */
28498      can_issue_more++;
28499
28500      /* Is next_insn going to start a new group?  */
28501      *group_end
28502	= (end
28503	   || (can_issue_more == 1 && !is_branch_slot_insn (next_insn))
28504	   || (can_issue_more <= 2 && is_cracked_insn (next_insn))
28505	   || (can_issue_more < issue_rate &&
28506	       insn_terminates_group_p (next_insn, previous_group)));
28507      if (*group_end && end)
28508	(*group_count)--;
28509
28510      if (sched_verbose > 6)
28511	fprintf (dump, "done force: group count = %d, can_issue_more = %d\n",
28512		 *group_count, can_issue_more);
28513      return can_issue_more;
28514    }
28515
28516  return can_issue_more;
28517}
28518
28519/* This function tries to synch the dispatch groups that the compiler "sees"
28520   with the dispatch groups that the processor dispatcher is expected to
28521   form in practice.  It tries to achieve this synchronization by forcing the
28522   estimated processor grouping on the compiler (as opposed to the function
28523   'pad_goups' which tries to force the scheduler's grouping on the processor).
28524
28525   The function scans the insn sequence between PREV_HEAD_INSN and TAIL and
28526   examines the (estimated) dispatch groups that will be formed by the processor
28527   dispatcher.  It marks these group boundaries to reflect the estimated
28528   processor grouping, overriding the grouping that the scheduler had marked.
28529   Depending on the value of the flag '-minsert-sched-nops' this function can
28530   force certain insns into separate groups or force a certain distance between
28531   them by inserting nops, for example, if there exists a "costly dependence"
28532   between the insns.
28533
28534   The function estimates the group boundaries that the processor will form as
28535   follows:  It keeps track of how many vacant issue slots are available after
28536   each insn.  A subsequent insn will start a new group if one of the following
28537   4 cases applies:
28538   - no more vacant issue slots remain in the current dispatch group.
28539   - only the last issue slot, which is the branch slot, is vacant, but the next
28540     insn is not a branch.
28541   - only the last 2 or less issue slots, including the branch slot, are vacant,
28542     which means that a cracked insn (which occupies two issue slots) can't be
28543     issued in this group.
28544   - less than 'issue_rate' slots are vacant, and the next insn always needs to
28545     start a new group.  */
28546
28547static int
28548redefine_groups (FILE *dump, int sched_verbose, rtx_insn *prev_head_insn,
28549		 rtx_insn *tail)
28550{
28551  rtx_insn *insn, *next_insn;
28552  int issue_rate;
28553  int can_issue_more;
28554  int slot, i;
28555  bool group_end;
28556  int group_count = 0;
28557  rtx *group_insns;
28558
28559  /* Initialize.  */
28560  issue_rate = rs6000_issue_rate ();
28561  group_insns = XALLOCAVEC (rtx, issue_rate);
28562  for (i = 0; i < issue_rate; i++)
28563    {
28564      group_insns[i] = 0;
28565    }
28566  can_issue_more = issue_rate;
28567  slot = 0;
28568  insn = get_next_active_insn (prev_head_insn, tail);
28569  group_end = false;
28570
28571  while (insn != NULL_RTX)
28572    {
28573      slot = (issue_rate - can_issue_more);
28574      group_insns[slot] = insn;
28575      can_issue_more =
28576	rs6000_variable_issue (dump, sched_verbose, insn, can_issue_more);
28577      if (insn_terminates_group_p (insn, current_group))
28578	can_issue_more = 0;
28579
28580      next_insn = get_next_active_insn (insn, tail);
28581      if (next_insn == NULL_RTX)
28582	return group_count + 1;
28583
28584      /* Is next_insn going to start a new group?  */
28585      group_end
28586	= (can_issue_more == 0
28587	   || (can_issue_more == 1 && !is_branch_slot_insn (next_insn))
28588	   || (can_issue_more <= 2 && is_cracked_insn (next_insn))
28589	   || (can_issue_more < issue_rate &&
28590	       insn_terminates_group_p (next_insn, previous_group)));
28591
28592      can_issue_more = force_new_group (sched_verbose, dump, group_insns,
28593					next_insn, &group_end, can_issue_more,
28594					&group_count);
28595
28596      if (group_end)
28597	{
28598	  group_count++;
28599	  can_issue_more = 0;
28600	  for (i = 0; i < issue_rate; i++)
28601	    {
28602	      group_insns[i] = 0;
28603	    }
28604	}
28605
28606      if (GET_MODE (next_insn) == TImode && can_issue_more)
28607	PUT_MODE (next_insn, VOIDmode);
28608      else if (!can_issue_more && GET_MODE (next_insn) != TImode)
28609	PUT_MODE (next_insn, TImode);
28610
28611      insn = next_insn;
28612      if (can_issue_more == 0)
28613	can_issue_more = issue_rate;
28614    } /* while */
28615
28616  return group_count;
28617}
28618
28619/* Scan the insn sequence between PREV_HEAD_INSN and TAIL and examine the
28620   dispatch group boundaries that the scheduler had marked.  Pad with nops
28621   any dispatch groups which have vacant issue slots, in order to force the
28622   scheduler's grouping on the processor dispatcher.  The function
28623   returns the number of dispatch groups found.  */
28624
28625static int
28626pad_groups (FILE *dump, int sched_verbose, rtx_insn *prev_head_insn,
28627	    rtx_insn *tail)
28628{
28629  rtx_insn *insn, *next_insn;
28630  rtx nop;
28631  int issue_rate;
28632  int can_issue_more;
28633  int group_end;
28634  int group_count = 0;
28635
28636  /* Initialize issue_rate.  */
28637  issue_rate = rs6000_issue_rate ();
28638  can_issue_more = issue_rate;
28639
28640  insn = get_next_active_insn (prev_head_insn, tail);
28641  next_insn = get_next_active_insn (insn, tail);
28642
28643  while (insn != NULL_RTX)
28644    {
28645      can_issue_more =
28646      	rs6000_variable_issue (dump, sched_verbose, insn, can_issue_more);
28647
28648      group_end = (next_insn == NULL_RTX || GET_MODE (next_insn) == TImode);
28649
28650      if (next_insn == NULL_RTX)
28651	break;
28652
28653      if (group_end)
28654	{
28655	  /* If the scheduler had marked group termination at this location
28656	     (between insn and next_insn), and neither insn nor next_insn will
28657	     force group termination, pad the group with nops to force group
28658	     termination.  */
28659	  if (can_issue_more
28660	      && (rs6000_sched_insert_nops == sched_finish_pad_groups)
28661	      && !insn_terminates_group_p (insn, current_group)
28662	      && !insn_terminates_group_p (next_insn, previous_group))
28663	    {
28664	      if (!is_branch_slot_insn (next_insn))
28665		can_issue_more--;
28666
28667	      while (can_issue_more)
28668		{
28669		  nop = gen_nop ();
28670		  emit_insn_before (nop, next_insn);
28671		  can_issue_more--;
28672		}
28673	    }
28674
28675	  can_issue_more = issue_rate;
28676	  group_count++;
28677	}
28678
28679      insn = next_insn;
28680      next_insn = get_next_active_insn (insn, tail);
28681    }
28682
28683  return group_count;
28684}
28685
28686/* We're beginning a new block.  Initialize data structures as necessary.  */
28687
28688static void
28689rs6000_sched_init (FILE *dump ATTRIBUTE_UNUSED,
28690		     int sched_verbose ATTRIBUTE_UNUSED,
28691		     int max_ready ATTRIBUTE_UNUSED)
28692{
28693  last_scheduled_insn = NULL_RTX;
28694  load_store_pendulum = 0;
28695}
28696
28697/* The following function is called at the end of scheduling BB.
28698   After reload, it inserts nops at insn group bundling.  */
28699
28700static void
28701rs6000_sched_finish (FILE *dump, int sched_verbose)
28702{
28703  int n_groups;
28704
28705  if (sched_verbose)
28706    fprintf (dump, "=== Finishing schedule.\n");
28707
28708  if (reload_completed && rs6000_sched_groups)
28709    {
28710      /* Do not run sched_finish hook when selective scheduling enabled.  */
28711      if (sel_sched_p ())
28712	return;
28713
28714      if (rs6000_sched_insert_nops == sched_finish_none)
28715	return;
28716
28717      if (rs6000_sched_insert_nops == sched_finish_pad_groups)
28718	n_groups = pad_groups (dump, sched_verbose,
28719			       current_sched_info->prev_head,
28720			       current_sched_info->next_tail);
28721      else
28722	n_groups = redefine_groups (dump, sched_verbose,
28723				    current_sched_info->prev_head,
28724				    current_sched_info->next_tail);
28725
28726      if (sched_verbose >= 6)
28727	{
28728    	  fprintf (dump, "ngroups = %d\n", n_groups);
28729	  print_rtl (dump, current_sched_info->prev_head);
28730	  fprintf (dump, "Done finish_sched\n");
28731	}
28732    }
28733}
28734
28735struct _rs6000_sched_context
28736{
28737  short cached_can_issue_more;
28738  rtx last_scheduled_insn;
28739  int load_store_pendulum;
28740};
28741
28742typedef struct _rs6000_sched_context rs6000_sched_context_def;
28743typedef rs6000_sched_context_def *rs6000_sched_context_t;
28744
28745/* Allocate store for new scheduling context.  */
28746static void *
28747rs6000_alloc_sched_context (void)
28748{
28749  return xmalloc (sizeof (rs6000_sched_context_def));
28750}
28751
28752/* If CLEAN_P is true then initializes _SC with clean data,
28753   and from the global context otherwise.  */
28754static void
28755rs6000_init_sched_context (void *_sc, bool clean_p)
28756{
28757  rs6000_sched_context_t sc = (rs6000_sched_context_t) _sc;
28758
28759  if (clean_p)
28760    {
28761      sc->cached_can_issue_more = 0;
28762      sc->last_scheduled_insn = NULL_RTX;
28763      sc->load_store_pendulum = 0;
28764    }
28765  else
28766    {
28767      sc->cached_can_issue_more = cached_can_issue_more;
28768      sc->last_scheduled_insn = last_scheduled_insn;
28769      sc->load_store_pendulum = load_store_pendulum;
28770    }
28771}
28772
28773/* Sets the global scheduling context to the one pointed to by _SC.  */
28774static void
28775rs6000_set_sched_context (void *_sc)
28776{
28777  rs6000_sched_context_t sc = (rs6000_sched_context_t) _sc;
28778
28779  gcc_assert (sc != NULL);
28780
28781  cached_can_issue_more = sc->cached_can_issue_more;
28782  last_scheduled_insn = sc->last_scheduled_insn;
28783  load_store_pendulum = sc->load_store_pendulum;
28784}
28785
28786/* Free _SC.  */
28787static void
28788rs6000_free_sched_context (void *_sc)
28789{
28790  gcc_assert (_sc != NULL);
28791
28792  free (_sc);
28793}
28794
28795
28796/* Length in units of the trampoline for entering a nested function.  */
28797
28798int
28799rs6000_trampoline_size (void)
28800{
28801  int ret = 0;
28802
28803  switch (DEFAULT_ABI)
28804    {
28805    default:
28806      gcc_unreachable ();
28807
28808    case ABI_AIX:
28809      ret = (TARGET_32BIT) ? 12 : 24;
28810      break;
28811
28812    case ABI_ELFv2:
28813      gcc_assert (!TARGET_32BIT);
28814      ret = 32;
28815      break;
28816
28817    case ABI_DARWIN:
28818    case ABI_V4:
28819      ret = (TARGET_32BIT) ? 40 : 48;
28820      break;
28821    }
28822
28823  return ret;
28824}
28825
28826/* Emit RTL insns to initialize the variable parts of a trampoline.
28827   FNADDR is an RTX for the address of the function's pure code.
28828   CXT is an RTX for the static chain value for the function.  */
28829
28830static void
28831rs6000_trampoline_init (rtx m_tramp, tree fndecl, rtx cxt)
28832{
28833  int regsize = (TARGET_32BIT) ? 4 : 8;
28834  rtx fnaddr = XEXP (DECL_RTL (fndecl), 0);
28835  rtx ctx_reg = force_reg (Pmode, cxt);
28836  rtx addr = force_reg (Pmode, XEXP (m_tramp, 0));
28837
28838  switch (DEFAULT_ABI)
28839    {
28840    default:
28841      gcc_unreachable ();
28842
28843    /* Under AIX, just build the 3 word function descriptor */
28844    case ABI_AIX:
28845      {
28846	rtx fnmem, fn_reg, toc_reg;
28847
28848	if (!TARGET_POINTERS_TO_NESTED_FUNCTIONS)
28849	  error ("You cannot take the address of a nested function if you use "
28850		 "the -mno-pointers-to-nested-functions option.");
28851
28852	fnmem = gen_const_mem (Pmode, force_reg (Pmode, fnaddr));
28853	fn_reg = gen_reg_rtx (Pmode);
28854	toc_reg = gen_reg_rtx (Pmode);
28855
28856  /* Macro to shorten the code expansions below.  */
28857# define MEM_PLUS(MEM, OFFSET) adjust_address (MEM, Pmode, OFFSET)
28858
28859	m_tramp = replace_equiv_address (m_tramp, addr);
28860
28861	emit_move_insn (fn_reg, MEM_PLUS (fnmem, 0));
28862	emit_move_insn (toc_reg, MEM_PLUS (fnmem, regsize));
28863	emit_move_insn (MEM_PLUS (m_tramp, 0), fn_reg);
28864	emit_move_insn (MEM_PLUS (m_tramp, regsize), toc_reg);
28865	emit_move_insn (MEM_PLUS (m_tramp, 2*regsize), ctx_reg);
28866
28867# undef MEM_PLUS
28868      }
28869      break;
28870
28871    /* Under V.4/eabi/darwin, __trampoline_setup does the real work.  */
28872    case ABI_ELFv2:
28873    case ABI_DARWIN:
28874    case ABI_V4:
28875      emit_library_call (gen_rtx_SYMBOL_REF (Pmode, "__trampoline_setup"),
28876			 LCT_NORMAL, VOIDmode, 4,
28877			 addr, Pmode,
28878			 GEN_INT (rs6000_trampoline_size ()), SImode,
28879			 fnaddr, Pmode,
28880			 ctx_reg, Pmode);
28881      break;
28882    }
28883}
28884
28885
28886/* Returns TRUE iff the target attribute indicated by ATTR_ID takes a plain
28887   identifier as an argument, so the front end shouldn't look it up.  */
28888
28889static bool
28890rs6000_attribute_takes_identifier_p (const_tree attr_id)
28891{
28892  return is_attribute_p ("altivec", attr_id);
28893}
28894
28895/* Handle the "altivec" attribute.  The attribute may have
28896   arguments as follows:
28897
28898	__attribute__((altivec(vector__)))
28899	__attribute__((altivec(pixel__)))	(always followed by 'unsigned short')
28900	__attribute__((altivec(bool__)))	(always followed by 'unsigned')
28901
28902  and may appear more than once (e.g., 'vector bool char') in a
28903  given declaration.  */
28904
28905static tree
28906rs6000_handle_altivec_attribute (tree *node,
28907				 tree name ATTRIBUTE_UNUSED,
28908				 tree args,
28909				 int flags ATTRIBUTE_UNUSED,
28910				 bool *no_add_attrs)
28911{
28912  tree type = *node, result = NULL_TREE;
28913  machine_mode mode;
28914  int unsigned_p;
28915  char altivec_type
28916    = ((args && TREE_CODE (args) == TREE_LIST && TREE_VALUE (args)
28917	&& TREE_CODE (TREE_VALUE (args)) == IDENTIFIER_NODE)
28918       ? *IDENTIFIER_POINTER (TREE_VALUE (args))
28919       : '?');
28920
28921  while (POINTER_TYPE_P (type)
28922	 || TREE_CODE (type) == FUNCTION_TYPE
28923	 || TREE_CODE (type) == METHOD_TYPE
28924	 || TREE_CODE (type) == ARRAY_TYPE)
28925    type = TREE_TYPE (type);
28926
28927  mode = TYPE_MODE (type);
28928
28929  /* Check for invalid AltiVec type qualifiers.  */
28930  if (type == long_double_type_node)
28931    error ("use of %<long double%> in AltiVec types is invalid");
28932  else if (type == boolean_type_node)
28933    error ("use of boolean types in AltiVec types is invalid");
28934  else if (TREE_CODE (type) == COMPLEX_TYPE)
28935    error ("use of %<complex%> in AltiVec types is invalid");
28936  else if (DECIMAL_FLOAT_MODE_P (mode))
28937    error ("use of decimal floating point types in AltiVec types is invalid");
28938  else if (!TARGET_VSX)
28939    {
28940      if (type == long_unsigned_type_node || type == long_integer_type_node)
28941	{
28942	  if (TARGET_64BIT)
28943	    error ("use of %<long%> in AltiVec types is invalid for "
28944		   "64-bit code without -mvsx");
28945	  else if (rs6000_warn_altivec_long)
28946	    warning (0, "use of %<long%> in AltiVec types is deprecated; "
28947		     "use %<int%>");
28948	}
28949      else if (type == long_long_unsigned_type_node
28950	       || type == long_long_integer_type_node)
28951	error ("use of %<long long%> in AltiVec types is invalid without "
28952	       "-mvsx");
28953      else if (type == double_type_node)
28954	error ("use of %<double%> in AltiVec types is invalid without -mvsx");
28955    }
28956
28957  switch (altivec_type)
28958    {
28959    case 'v':
28960      unsigned_p = TYPE_UNSIGNED (type);
28961      switch (mode)
28962	{
28963	case TImode:
28964	  result = (unsigned_p ? unsigned_V1TI_type_node : V1TI_type_node);
28965	  break;
28966	case DImode:
28967	  result = (unsigned_p ? unsigned_V2DI_type_node : V2DI_type_node);
28968	  break;
28969	case SImode:
28970	  result = (unsigned_p ? unsigned_V4SI_type_node : V4SI_type_node);
28971	  break;
28972	case HImode:
28973	  result = (unsigned_p ? unsigned_V8HI_type_node : V8HI_type_node);
28974	  break;
28975	case QImode:
28976	  result = (unsigned_p ? unsigned_V16QI_type_node : V16QI_type_node);
28977	  break;
28978	case SFmode: result = V4SF_type_node; break;
28979	case DFmode: result = V2DF_type_node; break;
28980	  /* If the user says 'vector int bool', we may be handed the 'bool'
28981	     attribute _before_ the 'vector' attribute, and so select the
28982	     proper type in the 'b' case below.  */
28983	case V4SImode: case V8HImode: case V16QImode: case V4SFmode:
28984	case V2DImode: case V2DFmode:
28985	  result = type;
28986	default: break;
28987	}
28988      break;
28989    case 'b':
28990      switch (mode)
28991	{
28992	case DImode: case V2DImode: result = bool_V2DI_type_node; break;
28993	case SImode: case V4SImode: result = bool_V4SI_type_node; break;
28994	case HImode: case V8HImode: result = bool_V8HI_type_node; break;
28995	case QImode: case V16QImode: result = bool_V16QI_type_node;
28996	default: break;
28997	}
28998      break;
28999    case 'p':
29000      switch (mode)
29001	{
29002	case V8HImode: result = pixel_V8HI_type_node;
29003	default: break;
29004	}
29005    default: break;
29006    }
29007
29008  /* Propagate qualifiers attached to the element type
29009     onto the vector type.  */
29010  if (result && result != type && TYPE_QUALS (type))
29011    result = build_qualified_type (result, TYPE_QUALS (type));
29012
29013  *no_add_attrs = true;  /* No need to hang on to the attribute.  */
29014
29015  if (result)
29016    *node = lang_hooks.types.reconstruct_complex_type (*node, result);
29017
29018  return NULL_TREE;
29019}
29020
29021/* AltiVec defines four built-in scalar types that serve as vector
29022   elements; we must teach the compiler how to mangle them.  */
29023
29024static const char *
29025rs6000_mangle_type (const_tree type)
29026{
29027  type = TYPE_MAIN_VARIANT (type);
29028
29029  if (TREE_CODE (type) != VOID_TYPE && TREE_CODE (type) != BOOLEAN_TYPE
29030      && TREE_CODE (type) != INTEGER_TYPE && TREE_CODE (type) != REAL_TYPE)
29031    return NULL;
29032
29033  if (type == bool_char_type_node) return "U6__boolc";
29034  if (type == bool_short_type_node) return "U6__bools";
29035  if (type == pixel_type_node) return "u7__pixel";
29036  if (type == bool_int_type_node) return "U6__booli";
29037  if (type == bool_long_type_node) return "U6__booll";
29038
29039  /* Mangle IBM extended float long double as `g' (__float128) on
29040     powerpc*-linux where long-double-64 previously was the default.  */
29041  if (TYPE_MAIN_VARIANT (type) == long_double_type_node
29042      && TARGET_ELF
29043      && TARGET_LONG_DOUBLE_128
29044      && !TARGET_IEEEQUAD)
29045    return "g";
29046
29047  /* For all other types, use normal C++ mangling.  */
29048  return NULL;
29049}
29050
29051/* Handle a "longcall" or "shortcall" attribute; arguments as in
29052   struct attribute_spec.handler.  */
29053
29054static tree
29055rs6000_handle_longcall_attribute (tree *node, tree name,
29056				  tree args ATTRIBUTE_UNUSED,
29057				  int flags ATTRIBUTE_UNUSED,
29058				  bool *no_add_attrs)
29059{
29060  if (TREE_CODE (*node) != FUNCTION_TYPE
29061      && TREE_CODE (*node) != FIELD_DECL
29062      && TREE_CODE (*node) != TYPE_DECL)
29063    {
29064      warning (OPT_Wattributes, "%qE attribute only applies to functions",
29065	       name);
29066      *no_add_attrs = true;
29067    }
29068
29069  return NULL_TREE;
29070}
29071
29072/* Set longcall attributes on all functions declared when
29073   rs6000_default_long_calls is true.  */
29074static void
29075rs6000_set_default_type_attributes (tree type)
29076{
29077  if (rs6000_default_long_calls
29078      && (TREE_CODE (type) == FUNCTION_TYPE
29079	  || TREE_CODE (type) == METHOD_TYPE))
29080    TYPE_ATTRIBUTES (type) = tree_cons (get_identifier ("longcall"),
29081					NULL_TREE,
29082					TYPE_ATTRIBUTES (type));
29083
29084#if TARGET_MACHO
29085  darwin_set_default_type_attributes (type);
29086#endif
29087}
29088
29089/* Return a reference suitable for calling a function with the
29090   longcall attribute.  */
29091
29092rtx
29093rs6000_longcall_ref (rtx call_ref)
29094{
29095  const char *call_name;
29096  tree node;
29097
29098  if (GET_CODE (call_ref) != SYMBOL_REF)
29099    return call_ref;
29100
29101  /* System V adds '.' to the internal name, so skip them.  */
29102  call_name = XSTR (call_ref, 0);
29103  if (*call_name == '.')
29104    {
29105      while (*call_name == '.')
29106	call_name++;
29107
29108      node = get_identifier (call_name);
29109      call_ref = gen_rtx_SYMBOL_REF (VOIDmode, IDENTIFIER_POINTER (node));
29110    }
29111
29112  return force_reg (Pmode, call_ref);
29113}
29114
29115#ifndef TARGET_USE_MS_BITFIELD_LAYOUT
29116#define TARGET_USE_MS_BITFIELD_LAYOUT 0
29117#endif
29118
29119/* Handle a "ms_struct" or "gcc_struct" attribute; arguments as in
29120   struct attribute_spec.handler.  */
29121static tree
29122rs6000_handle_struct_attribute (tree *node, tree name,
29123				tree args ATTRIBUTE_UNUSED,
29124				int flags ATTRIBUTE_UNUSED, bool *no_add_attrs)
29125{
29126  tree *type = NULL;
29127  if (DECL_P (*node))
29128    {
29129      if (TREE_CODE (*node) == TYPE_DECL)
29130        type = &TREE_TYPE (*node);
29131    }
29132  else
29133    type = node;
29134
29135  if (!(type && (TREE_CODE (*type) == RECORD_TYPE
29136                 || TREE_CODE (*type) == UNION_TYPE)))
29137    {
29138      warning (OPT_Wattributes, "%qE attribute ignored", name);
29139      *no_add_attrs = true;
29140    }
29141
29142  else if ((is_attribute_p ("ms_struct", name)
29143            && lookup_attribute ("gcc_struct", TYPE_ATTRIBUTES (*type)))
29144           || ((is_attribute_p ("gcc_struct", name)
29145                && lookup_attribute ("ms_struct", TYPE_ATTRIBUTES (*type)))))
29146    {
29147      warning (OPT_Wattributes, "%qE incompatible attribute ignored",
29148               name);
29149      *no_add_attrs = true;
29150    }
29151
29152  return NULL_TREE;
29153}
29154
29155static bool
29156rs6000_ms_bitfield_layout_p (const_tree record_type)
29157{
29158  return (TARGET_USE_MS_BITFIELD_LAYOUT &&
29159          !lookup_attribute ("gcc_struct", TYPE_ATTRIBUTES (record_type)))
29160    || lookup_attribute ("ms_struct", TYPE_ATTRIBUTES (record_type));
29161}
29162
29163#ifdef USING_ELFOS_H
29164
29165/* A get_unnamed_section callback, used for switching to toc_section.  */
29166
29167static void
29168rs6000_elf_output_toc_section_asm_op (const void *data ATTRIBUTE_UNUSED)
29169{
29170  if ((DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
29171      && TARGET_MINIMAL_TOC
29172      && !TARGET_RELOCATABLE)
29173    {
29174      if (!toc_initialized)
29175	{
29176	  toc_initialized = 1;
29177	  fprintf (asm_out_file, "%s\n", TOC_SECTION_ASM_OP);
29178	  (*targetm.asm_out.internal_label) (asm_out_file, "LCTOC", 0);
29179	  fprintf (asm_out_file, "\t.tc ");
29180	  ASM_OUTPUT_INTERNAL_LABEL_PREFIX (asm_out_file, "LCTOC1[TC],");
29181	  ASM_OUTPUT_INTERNAL_LABEL_PREFIX (asm_out_file, "LCTOC1");
29182	  fprintf (asm_out_file, "\n");
29183
29184	  fprintf (asm_out_file, "%s\n", MINIMAL_TOC_SECTION_ASM_OP);
29185	  ASM_OUTPUT_INTERNAL_LABEL_PREFIX (asm_out_file, "LCTOC1");
29186	  fprintf (asm_out_file, " = .+32768\n");
29187	}
29188      else
29189	fprintf (asm_out_file, "%s\n", MINIMAL_TOC_SECTION_ASM_OP);
29190    }
29191  else if ((DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
29192	   && !TARGET_RELOCATABLE)
29193    fprintf (asm_out_file, "%s\n", TOC_SECTION_ASM_OP);
29194  else
29195    {
29196      fprintf (asm_out_file, "%s\n", MINIMAL_TOC_SECTION_ASM_OP);
29197      if (!toc_initialized)
29198	{
29199	  ASM_OUTPUT_INTERNAL_LABEL_PREFIX (asm_out_file, "LCTOC1");
29200	  fprintf (asm_out_file, " = .+32768\n");
29201	  toc_initialized = 1;
29202	}
29203    }
29204}
29205
29206/* Implement TARGET_ASM_INIT_SECTIONS.  */
29207
29208static void
29209rs6000_elf_asm_init_sections (void)
29210{
29211  toc_section
29212    = get_unnamed_section (0, rs6000_elf_output_toc_section_asm_op, NULL);
29213
29214  sdata2_section
29215    = get_unnamed_section (SECTION_WRITE, output_section_asm_op,
29216			   SDATA2_SECTION_ASM_OP);
29217}
29218
29219/* Implement TARGET_SELECT_RTX_SECTION.  */
29220
29221static section *
29222rs6000_elf_select_rtx_section (machine_mode mode, rtx x,
29223			       unsigned HOST_WIDE_INT align)
29224{
29225  if (ASM_OUTPUT_SPECIAL_POOL_ENTRY_P (x, mode))
29226    return toc_section;
29227  else
29228    return default_elf_select_rtx_section (mode, x, align);
29229}
29230
29231/* For a SYMBOL_REF, set generic flags and then perform some
29232   target-specific processing.
29233
29234   When the AIX ABI is requested on a non-AIX system, replace the
29235   function name with the real name (with a leading .) rather than the
29236   function descriptor name.  This saves a lot of overriding code to
29237   read the prefixes.  */
29238
29239static void rs6000_elf_encode_section_info (tree, rtx, int) ATTRIBUTE_UNUSED;
29240static void
29241rs6000_elf_encode_section_info (tree decl, rtx rtl, int first)
29242{
29243  default_encode_section_info (decl, rtl, first);
29244
29245  if (first
29246      && TREE_CODE (decl) == FUNCTION_DECL
29247      && !TARGET_AIX
29248      && DEFAULT_ABI == ABI_AIX)
29249    {
29250      rtx sym_ref = XEXP (rtl, 0);
29251      size_t len = strlen (XSTR (sym_ref, 0));
29252      char *str = XALLOCAVEC (char, len + 2);
29253      str[0] = '.';
29254      memcpy (str + 1, XSTR (sym_ref, 0), len + 1);
29255      XSTR (sym_ref, 0) = ggc_alloc_string (str, len + 1);
29256    }
29257}
29258
29259static inline bool
29260compare_section_name (const char *section, const char *templ)
29261{
29262  int len;
29263
29264  len = strlen (templ);
29265  return (strncmp (section, templ, len) == 0
29266	  && (section[len] == 0 || section[len] == '.'));
29267}
29268
29269bool
29270rs6000_elf_in_small_data_p (const_tree decl)
29271{
29272  if (rs6000_sdata == SDATA_NONE)
29273    return false;
29274
29275  /* We want to merge strings, so we never consider them small data.  */
29276  if (TREE_CODE (decl) == STRING_CST)
29277    return false;
29278
29279  /* Functions are never in the small data area.  */
29280  if (TREE_CODE (decl) == FUNCTION_DECL)
29281    return false;
29282
29283  if (TREE_CODE (decl) == VAR_DECL && DECL_SECTION_NAME (decl))
29284    {
29285      const char *section = DECL_SECTION_NAME (decl);
29286      if (compare_section_name (section, ".sdata")
29287	  || compare_section_name (section, ".sdata2")
29288	  || compare_section_name (section, ".gnu.linkonce.s")
29289	  || compare_section_name (section, ".sbss")
29290	  || compare_section_name (section, ".sbss2")
29291	  || compare_section_name (section, ".gnu.linkonce.sb")
29292	  || strcmp (section, ".PPC.EMB.sdata0") == 0
29293	  || strcmp (section, ".PPC.EMB.sbss0") == 0)
29294	return true;
29295    }
29296  else
29297    {
29298      HOST_WIDE_INT size = int_size_in_bytes (TREE_TYPE (decl));
29299
29300      if (size > 0
29301	  && size <= g_switch_value
29302	  /* If it's not public, and we're not going to reference it there,
29303	     there's no need to put it in the small data section.  */
29304	  && (rs6000_sdata != SDATA_DATA || TREE_PUBLIC (decl)))
29305	return true;
29306    }
29307
29308  return false;
29309}
29310
29311#endif /* USING_ELFOS_H */
29312
29313/* Implement TARGET_USE_BLOCKS_FOR_CONSTANT_P.  */
29314
29315static bool
29316rs6000_use_blocks_for_constant_p (machine_mode mode, const_rtx x)
29317{
29318  return !ASM_OUTPUT_SPECIAL_POOL_ENTRY_P (x, mode);
29319}
29320
29321/* Do not place thread-local symbols refs in the object blocks.  */
29322
29323static bool
29324rs6000_use_blocks_for_decl_p (const_tree decl)
29325{
29326  return !DECL_THREAD_LOCAL_P (decl);
29327}
29328
29329/* Return a REG that occurs in ADDR with coefficient 1.
29330   ADDR can be effectively incremented by incrementing REG.
29331
29332   r0 is special and we must not select it as an address
29333   register by this routine since our caller will try to
29334   increment the returned register via an "la" instruction.  */
29335
29336rtx
29337find_addr_reg (rtx addr)
29338{
29339  while (GET_CODE (addr) == PLUS)
29340    {
29341      if (GET_CODE (XEXP (addr, 0)) == REG
29342	  && REGNO (XEXP (addr, 0)) != 0)
29343	addr = XEXP (addr, 0);
29344      else if (GET_CODE (XEXP (addr, 1)) == REG
29345	       && REGNO (XEXP (addr, 1)) != 0)
29346	addr = XEXP (addr, 1);
29347      else if (CONSTANT_P (XEXP (addr, 0)))
29348	addr = XEXP (addr, 1);
29349      else if (CONSTANT_P (XEXP (addr, 1)))
29350	addr = XEXP (addr, 0);
29351      else
29352	gcc_unreachable ();
29353    }
29354  gcc_assert (GET_CODE (addr) == REG && REGNO (addr) != 0);
29355  return addr;
29356}
29357
29358void
29359rs6000_fatal_bad_address (rtx op)
29360{
29361  fatal_insn ("bad address", op);
29362}
29363
29364#if TARGET_MACHO
29365
29366typedef struct branch_island_d {
29367  tree function_name;
29368  tree label_name;
29369  int line_number;
29370} branch_island;
29371
29372
29373static vec<branch_island, va_gc> *branch_islands;
29374
29375/* Remember to generate a branch island for far calls to the given
29376   function.  */
29377
29378static void
29379add_compiler_branch_island (tree label_name, tree function_name,
29380			    int line_number)
29381{
29382  branch_island bi = {function_name, label_name, line_number};
29383  vec_safe_push (branch_islands, bi);
29384}
29385
29386/* Generate far-jump branch islands for everything recorded in
29387   branch_islands.  Invoked immediately after the last instruction of
29388   the epilogue has been emitted; the branch islands must be appended
29389   to, and contiguous with, the function body.  Mach-O stubs are
29390   generated in machopic_output_stub().  */
29391
29392static void
29393macho_branch_islands (void)
29394{
29395  char tmp_buf[512];
29396
29397  while (!vec_safe_is_empty (branch_islands))
29398    {
29399      branch_island *bi = &branch_islands->last ();
29400      const char *label = IDENTIFIER_POINTER (bi->label_name);
29401      const char *name = IDENTIFIER_POINTER (bi->function_name);
29402      char name_buf[512];
29403      /* Cheap copy of the details from the Darwin ASM_OUTPUT_LABELREF().  */
29404      if (name[0] == '*' || name[0] == '&')
29405	strcpy (name_buf, name+1);
29406      else
29407	{
29408	  name_buf[0] = '_';
29409	  strcpy (name_buf+1, name);
29410	}
29411      strcpy (tmp_buf, "\n");
29412      strcat (tmp_buf, label);
29413#if defined (DBX_DEBUGGING_INFO) || defined (XCOFF_DEBUGGING_INFO)
29414      if (write_symbols == DBX_DEBUG || write_symbols == XCOFF_DEBUG)
29415	dbxout_stabd (N_SLINE, bi->line_number);
29416#endif /* DBX_DEBUGGING_INFO || XCOFF_DEBUGGING_INFO */
29417      if (flag_pic)
29418	{
29419	  if (TARGET_LINK_STACK)
29420	    {
29421	      char name[32];
29422	      get_ppc476_thunk_name (name);
29423	      strcat (tmp_buf, ":\n\tmflr r0\n\tbl ");
29424	      strcat (tmp_buf, name);
29425	      strcat (tmp_buf, "\n");
29426	      strcat (tmp_buf, label);
29427	      strcat (tmp_buf, "_pic:\n\tmflr r11\n");
29428	    }
29429	  else
29430	    {
29431	      strcat (tmp_buf, ":\n\tmflr r0\n\tbcl 20,31,");
29432	      strcat (tmp_buf, label);
29433	      strcat (tmp_buf, "_pic\n");
29434	      strcat (tmp_buf, label);
29435	      strcat (tmp_buf, "_pic:\n\tmflr r11\n");
29436	    }
29437
29438	  strcat (tmp_buf, "\taddis r11,r11,ha16(");
29439	  strcat (tmp_buf, name_buf);
29440	  strcat (tmp_buf, " - ");
29441	  strcat (tmp_buf, label);
29442	  strcat (tmp_buf, "_pic)\n");
29443
29444	  strcat (tmp_buf, "\tmtlr r0\n");
29445
29446	  strcat (tmp_buf, "\taddi r12,r11,lo16(");
29447	  strcat (tmp_buf, name_buf);
29448	  strcat (tmp_buf, " - ");
29449	  strcat (tmp_buf, label);
29450	  strcat (tmp_buf, "_pic)\n");
29451
29452	  strcat (tmp_buf, "\tmtctr r12\n\tbctr\n");
29453	}
29454      else
29455	{
29456	  strcat (tmp_buf, ":\nlis r12,hi16(");
29457	  strcat (tmp_buf, name_buf);
29458	  strcat (tmp_buf, ")\n\tori r12,r12,lo16(");
29459	  strcat (tmp_buf, name_buf);
29460	  strcat (tmp_buf, ")\n\tmtctr r12\n\tbctr");
29461	}
29462      output_asm_insn (tmp_buf, 0);
29463#if defined (DBX_DEBUGGING_INFO) || defined (XCOFF_DEBUGGING_INFO)
29464      if (write_symbols == DBX_DEBUG || write_symbols == XCOFF_DEBUG)
29465	dbxout_stabd (N_SLINE, bi->line_number);
29466#endif /* DBX_DEBUGGING_INFO || XCOFF_DEBUGGING_INFO */
29467      branch_islands->pop ();
29468    }
29469}
29470
29471/* NO_PREVIOUS_DEF checks in the link list whether the function name is
29472   already there or not.  */
29473
29474static int
29475no_previous_def (tree function_name)
29476{
29477  branch_island *bi;
29478  unsigned ix;
29479
29480  FOR_EACH_VEC_SAFE_ELT (branch_islands, ix, bi)
29481    if (function_name == bi->function_name)
29482      return 0;
29483  return 1;
29484}
29485
29486/* GET_PREV_LABEL gets the label name from the previous definition of
29487   the function.  */
29488
29489static tree
29490get_prev_label (tree function_name)
29491{
29492  branch_island *bi;
29493  unsigned ix;
29494
29495  FOR_EACH_VEC_SAFE_ELT (branch_islands, ix, bi)
29496    if (function_name == bi->function_name)
29497      return bi->label_name;
29498  return NULL_TREE;
29499}
29500
29501/* INSN is either a function call or a millicode call.  It may have an
29502   unconditional jump in its delay slot.
29503
29504   CALL_DEST is the routine we are calling.  */
29505
29506char *
29507output_call (rtx_insn *insn, rtx *operands, int dest_operand_number,
29508	     int cookie_operand_number)
29509{
29510  static char buf[256];
29511  if (darwin_emit_branch_islands
29512      && GET_CODE (operands[dest_operand_number]) == SYMBOL_REF
29513      && (INTVAL (operands[cookie_operand_number]) & CALL_LONG))
29514    {
29515      tree labelname;
29516      tree funname = get_identifier (XSTR (operands[dest_operand_number], 0));
29517
29518      if (no_previous_def (funname))
29519	{
29520	  rtx label_rtx = gen_label_rtx ();
29521	  char *label_buf, temp_buf[256];
29522	  ASM_GENERATE_INTERNAL_LABEL (temp_buf, "L",
29523				       CODE_LABEL_NUMBER (label_rtx));
29524	  label_buf = temp_buf[0] == '*' ? temp_buf + 1 : temp_buf;
29525	  labelname = get_identifier (label_buf);
29526	  add_compiler_branch_island (labelname, funname, insn_line (insn));
29527	}
29528      else
29529	labelname = get_prev_label (funname);
29530
29531      /* "jbsr foo, L42" is Mach-O for "Link as 'bl foo' if a 'bl'
29532	 instruction will reach 'foo', otherwise link as 'bl L42'".
29533	 "L42" should be a 'branch island', that will do a far jump to
29534	 'foo'.  Branch islands are generated in
29535	 macho_branch_islands().  */
29536      sprintf (buf, "jbsr %%z%d,%.246s",
29537	       dest_operand_number, IDENTIFIER_POINTER (labelname));
29538    }
29539  else
29540    sprintf (buf, "bl %%z%d", dest_operand_number);
29541  return buf;
29542}
29543
29544/* Generate PIC and indirect symbol stubs.  */
29545
29546void
29547machopic_output_stub (FILE *file, const char *symb, const char *stub)
29548{
29549  unsigned int length;
29550  char *symbol_name, *lazy_ptr_name;
29551  char *local_label_0;
29552  static int label = 0;
29553
29554  /* Lose our funky encoding stuff so it doesn't contaminate the stub.  */
29555  symb = (*targetm.strip_name_encoding) (symb);
29556
29557
29558  length = strlen (symb);
29559  symbol_name = XALLOCAVEC (char, length + 32);
29560  GEN_SYMBOL_NAME_FOR_SYMBOL (symbol_name, symb, length);
29561
29562  lazy_ptr_name = XALLOCAVEC (char, length + 32);
29563  GEN_LAZY_PTR_NAME_FOR_SYMBOL (lazy_ptr_name, symb, length);
29564
29565  if (flag_pic == 2)
29566    switch_to_section (darwin_sections[machopic_picsymbol_stub1_section]);
29567  else
29568    switch_to_section (darwin_sections[machopic_symbol_stub1_section]);
29569
29570  if (flag_pic == 2)
29571    {
29572      fprintf (file, "\t.align 5\n");
29573
29574      fprintf (file, "%s:\n", stub);
29575      fprintf (file, "\t.indirect_symbol %s\n", symbol_name);
29576
29577      label++;
29578      local_label_0 = XALLOCAVEC (char, sizeof ("\"L00000000000$spb\""));
29579      sprintf (local_label_0, "\"L%011d$spb\"", label);
29580
29581      fprintf (file, "\tmflr r0\n");
29582      if (TARGET_LINK_STACK)
29583	{
29584	  char name[32];
29585	  get_ppc476_thunk_name (name);
29586	  fprintf (file, "\tbl %s\n", name);
29587	  fprintf (file, "%s:\n\tmflr r11\n", local_label_0);
29588	}
29589      else
29590	{
29591	  fprintf (file, "\tbcl 20,31,%s\n", local_label_0);
29592	  fprintf (file, "%s:\n\tmflr r11\n", local_label_0);
29593	}
29594      fprintf (file, "\taddis r11,r11,ha16(%s-%s)\n",
29595	       lazy_ptr_name, local_label_0);
29596      fprintf (file, "\tmtlr r0\n");
29597      fprintf (file, "\t%s r12,lo16(%s-%s)(r11)\n",
29598	       (TARGET_64BIT ? "ldu" : "lwzu"),
29599	       lazy_ptr_name, local_label_0);
29600      fprintf (file, "\tmtctr r12\n");
29601      fprintf (file, "\tbctr\n");
29602    }
29603  else
29604    {
29605      fprintf (file, "\t.align 4\n");
29606
29607      fprintf (file, "%s:\n", stub);
29608      fprintf (file, "\t.indirect_symbol %s\n", symbol_name);
29609
29610      fprintf (file, "\tlis r11,ha16(%s)\n", lazy_ptr_name);
29611      fprintf (file, "\t%s r12,lo16(%s)(r11)\n",
29612	       (TARGET_64BIT ? "ldu" : "lwzu"),
29613	       lazy_ptr_name);
29614      fprintf (file, "\tmtctr r12\n");
29615      fprintf (file, "\tbctr\n");
29616    }
29617
29618  switch_to_section (darwin_sections[machopic_lazy_symbol_ptr_section]);
29619  fprintf (file, "%s:\n", lazy_ptr_name);
29620  fprintf (file, "\t.indirect_symbol %s\n", symbol_name);
29621  fprintf (file, "%sdyld_stub_binding_helper\n",
29622	   (TARGET_64BIT ? DOUBLE_INT_ASM_OP : "\t.long\t"));
29623}
29624
29625/* Legitimize PIC addresses.  If the address is already
29626   position-independent, we return ORIG.  Newly generated
29627   position-independent addresses go into a reg.  This is REG if non
29628   zero, otherwise we allocate register(s) as necessary.  */
29629
29630#define SMALL_INT(X) ((UINTVAL (X) + 0x8000) < 0x10000)
29631
29632rtx
29633rs6000_machopic_legitimize_pic_address (rtx orig, machine_mode mode,
29634					rtx reg)
29635{
29636  rtx base, offset;
29637
29638  if (reg == NULL && ! reload_in_progress && ! reload_completed)
29639    reg = gen_reg_rtx (Pmode);
29640
29641  if (GET_CODE (orig) == CONST)
29642    {
29643      rtx reg_temp;
29644
29645      if (GET_CODE (XEXP (orig, 0)) == PLUS
29646	  && XEXP (XEXP (orig, 0), 0) == pic_offset_table_rtx)
29647	return orig;
29648
29649      gcc_assert (GET_CODE (XEXP (orig, 0)) == PLUS);
29650
29651      /* Use a different reg for the intermediate value, as
29652	 it will be marked UNCHANGING.  */
29653      reg_temp = !can_create_pseudo_p () ? reg : gen_reg_rtx (Pmode);
29654      base = rs6000_machopic_legitimize_pic_address (XEXP (XEXP (orig, 0), 0),
29655						     Pmode, reg_temp);
29656      offset =
29657	rs6000_machopic_legitimize_pic_address (XEXP (XEXP (orig, 0), 1),
29658						Pmode, reg);
29659
29660      if (GET_CODE (offset) == CONST_INT)
29661	{
29662	  if (SMALL_INT (offset))
29663	    return plus_constant (Pmode, base, INTVAL (offset));
29664	  else if (! reload_in_progress && ! reload_completed)
29665	    offset = force_reg (Pmode, offset);
29666	  else
29667	    {
29668 	      rtx mem = force_const_mem (Pmode, orig);
29669	      return machopic_legitimize_pic_address (mem, Pmode, reg);
29670	    }
29671	}
29672      return gen_rtx_PLUS (Pmode, base, offset);
29673    }
29674
29675  /* Fall back on generic machopic code.  */
29676  return machopic_legitimize_pic_address (orig, mode, reg);
29677}
29678
29679/* Output a .machine directive for the Darwin assembler, and call
29680   the generic start_file routine.  */
29681
29682static void
29683rs6000_darwin_file_start (void)
29684{
29685  static const struct
29686  {
29687    const char *arg;
29688    const char *name;
29689    HOST_WIDE_INT if_set;
29690  } mapping[] = {
29691    { "ppc64", "ppc64", MASK_64BIT },
29692    { "970", "ppc970", MASK_PPC_GPOPT | MASK_MFCRF | MASK_POWERPC64 },
29693    { "power4", "ppc970", 0 },
29694    { "G5", "ppc970", 0 },
29695    { "7450", "ppc7450", 0 },
29696    { "7400", "ppc7400", MASK_ALTIVEC },
29697    { "G4", "ppc7400", 0 },
29698    { "750", "ppc750", 0 },
29699    { "740", "ppc750", 0 },
29700    { "G3", "ppc750", 0 },
29701    { "604e", "ppc604e", 0 },
29702    { "604", "ppc604", 0 },
29703    { "603e", "ppc603", 0 },
29704    { "603", "ppc603", 0 },
29705    { "601", "ppc601", 0 },
29706    { NULL, "ppc", 0 } };
29707  const char *cpu_id = "";
29708  size_t i;
29709
29710  rs6000_file_start ();
29711  darwin_file_start ();
29712
29713  /* Determine the argument to -mcpu=.  Default to G3 if not specified.  */
29714
29715  if (rs6000_default_cpu != 0 && rs6000_default_cpu[0] != '\0')
29716    cpu_id = rs6000_default_cpu;
29717
29718  if (global_options_set.x_rs6000_cpu_index)
29719    cpu_id = processor_target_table[rs6000_cpu_index].name;
29720
29721  /* Look through the mapping array.  Pick the first name that either
29722     matches the argument, has a bit set in IF_SET that is also set
29723     in the target flags, or has a NULL name.  */
29724
29725  i = 0;
29726  while (mapping[i].arg != NULL
29727	 && strcmp (mapping[i].arg, cpu_id) != 0
29728	 && (mapping[i].if_set & rs6000_isa_flags) == 0)
29729    i++;
29730
29731  fprintf (asm_out_file, "\t.machine %s\n", mapping[i].name);
29732}
29733
29734#endif /* TARGET_MACHO */
29735
29736#if TARGET_ELF
29737static int
29738rs6000_elf_reloc_rw_mask (void)
29739{
29740  if (flag_pic)
29741    return 3;
29742  else if (DEFAULT_ABI == ABI_AIX || DEFAULT_ABI == ABI_ELFv2)
29743    return 2;
29744  else
29745    return 0;
29746}
29747
29748/* Record an element in the table of global constructors.  SYMBOL is
29749   a SYMBOL_REF of the function to be called; PRIORITY is a number
29750   between 0 and MAX_INIT_PRIORITY.
29751
29752   This differs from default_named_section_asm_out_constructor in
29753   that we have special handling for -mrelocatable.  */
29754
29755static void rs6000_elf_asm_out_constructor (rtx, int) ATTRIBUTE_UNUSED;
29756static void
29757rs6000_elf_asm_out_constructor (rtx symbol, int priority)
29758{
29759  const char *section = ".ctors";
29760  char buf[16];
29761
29762  if (priority != DEFAULT_INIT_PRIORITY)
29763    {
29764      sprintf (buf, ".ctors.%.5u",
29765	       /* Invert the numbering so the linker puts us in the proper
29766		  order; constructors are run from right to left, and the
29767		  linker sorts in increasing order.  */
29768	       MAX_INIT_PRIORITY - priority);
29769      section = buf;
29770    }
29771
29772  switch_to_section (get_section (section, SECTION_WRITE, NULL));
29773  assemble_align (POINTER_SIZE);
29774
29775  if (TARGET_RELOCATABLE)
29776    {
29777      fputs ("\t.long (", asm_out_file);
29778      output_addr_const (asm_out_file, symbol);
29779      fputs (")@fixup\n", asm_out_file);
29780    }
29781  else
29782    assemble_integer (symbol, POINTER_SIZE / BITS_PER_UNIT, POINTER_SIZE, 1);
29783}
29784
29785static void rs6000_elf_asm_out_destructor (rtx, int) ATTRIBUTE_UNUSED;
29786static void
29787rs6000_elf_asm_out_destructor (rtx symbol, int priority)
29788{
29789  const char *section = ".dtors";
29790  char buf[16];
29791
29792  if (priority != DEFAULT_INIT_PRIORITY)
29793    {
29794      sprintf (buf, ".dtors.%.5u",
29795	       /* Invert the numbering so the linker puts us in the proper
29796		  order; constructors are run from right to left, and the
29797		  linker sorts in increasing order.  */
29798	       MAX_INIT_PRIORITY - priority);
29799      section = buf;
29800    }
29801
29802  switch_to_section (get_section (section, SECTION_WRITE, NULL));
29803  assemble_align (POINTER_SIZE);
29804
29805  if (TARGET_RELOCATABLE)
29806    {
29807      fputs ("\t.long (", asm_out_file);
29808      output_addr_const (asm_out_file, symbol);
29809      fputs (")@fixup\n", asm_out_file);
29810    }
29811  else
29812    assemble_integer (symbol, POINTER_SIZE / BITS_PER_UNIT, POINTER_SIZE, 1);
29813}
29814
29815void
29816rs6000_elf_declare_function_name (FILE *file, const char *name, tree decl)
29817{
29818  if (TARGET_64BIT && DEFAULT_ABI != ABI_ELFv2)
29819    {
29820      fputs ("\t.section\t\".opd\",\"aw\"\n\t.align 3\n", file);
29821      ASM_OUTPUT_LABEL (file, name);
29822      fputs (DOUBLE_INT_ASM_OP, file);
29823      rs6000_output_function_entry (file, name);
29824      fputs (",.TOC.@tocbase,0\n\t.previous\n", file);
29825      if (DOT_SYMBOLS)
29826	{
29827	  fputs ("\t.size\t", file);
29828	  assemble_name (file, name);
29829	  fputs (",24\n\t.type\t.", file);
29830	  assemble_name (file, name);
29831	  fputs (",@function\n", file);
29832	  if (TREE_PUBLIC (decl) && ! DECL_WEAK (decl))
29833	    {
29834	      fputs ("\t.globl\t.", file);
29835	      assemble_name (file, name);
29836	      putc ('\n', file);
29837	    }
29838	}
29839      else
29840	ASM_OUTPUT_TYPE_DIRECTIVE (file, name, "function");
29841      ASM_DECLARE_RESULT (file, DECL_RESULT (decl));
29842      rs6000_output_function_entry (file, name);
29843      fputs (":\n", file);
29844      return;
29845    }
29846
29847  if (TARGET_RELOCATABLE
29848      && !TARGET_SECURE_PLT
29849      && (get_pool_size () != 0 || crtl->profile)
29850      && uses_TOC ())
29851    {
29852      char buf[256];
29853
29854      (*targetm.asm_out.internal_label) (file, "LCL", rs6000_pic_labelno);
29855
29856      ASM_GENERATE_INTERNAL_LABEL (buf, "LCTOC", 1);
29857      fprintf (file, "\t.long ");
29858      assemble_name (file, buf);
29859      putc ('-', file);
29860      ASM_GENERATE_INTERNAL_LABEL (buf, "LCF", rs6000_pic_labelno);
29861      assemble_name (file, buf);
29862      putc ('\n', file);
29863    }
29864
29865  ASM_OUTPUT_TYPE_DIRECTIVE (file, name, "function");
29866  ASM_DECLARE_RESULT (file, DECL_RESULT (decl));
29867
29868  if (DEFAULT_ABI == ABI_AIX)
29869    {
29870      const char *desc_name, *orig_name;
29871
29872      orig_name = (*targetm.strip_name_encoding) (name);
29873      desc_name = orig_name;
29874      while (*desc_name == '.')
29875	desc_name++;
29876
29877      if (TREE_PUBLIC (decl))
29878	fprintf (file, "\t.globl %s\n", desc_name);
29879
29880      fprintf (file, "%s\n", MINIMAL_TOC_SECTION_ASM_OP);
29881      fprintf (file, "%s:\n", desc_name);
29882      fprintf (file, "\t.long %s\n", orig_name);
29883      fputs ("\t.long _GLOBAL_OFFSET_TABLE_\n", file);
29884      fputs ("\t.long 0\n", file);
29885      fprintf (file, "\t.previous\n");
29886    }
29887  ASM_OUTPUT_LABEL (file, name);
29888}
29889
29890static void rs6000_elf_file_end (void) ATTRIBUTE_UNUSED;
29891static void
29892rs6000_elf_file_end (void)
29893{
29894#ifdef HAVE_AS_GNU_ATTRIBUTE
29895  if (TARGET_32BIT && DEFAULT_ABI == ABI_V4)
29896    {
29897      if (rs6000_passes_float)
29898	fprintf (asm_out_file, "\t.gnu_attribute 4, %d\n",
29899		 ((TARGET_HARD_FLOAT && TARGET_FPRS && TARGET_DOUBLE_FLOAT) ? 1
29900		  : (TARGET_HARD_FLOAT && TARGET_FPRS && TARGET_SINGLE_FLOAT) ? 3
29901		  : 2));
29902      if (rs6000_passes_vector)
29903	fprintf (asm_out_file, "\t.gnu_attribute 8, %d\n",
29904		 (TARGET_ALTIVEC_ABI ? 2
29905		  : TARGET_SPE_ABI ? 3
29906		  : 1));
29907      if (rs6000_returns_struct)
29908	fprintf (asm_out_file, "\t.gnu_attribute 12, %d\n",
29909		 aix_struct_return ? 2 : 1);
29910    }
29911#endif
29912#if defined (POWERPC_LINUX) || defined (POWERPC_FREEBSD)
29913  if (TARGET_32BIT || DEFAULT_ABI == ABI_ELFv2)
29914    file_end_indicate_exec_stack ();
29915#endif
29916}
29917#endif
29918
29919#if TARGET_XCOFF
29920static void
29921rs6000_xcoff_asm_output_anchor (rtx symbol)
29922{
29923  char buffer[100];
29924
29925  sprintf (buffer, "$ + " HOST_WIDE_INT_PRINT_DEC,
29926	   SYMBOL_REF_BLOCK_OFFSET (symbol));
29927  fprintf (asm_out_file, "%s", SET_ASM_OP);
29928  RS6000_OUTPUT_BASENAME (asm_out_file, XSTR (symbol, 0));
29929  fprintf (asm_out_file, ",");
29930  RS6000_OUTPUT_BASENAME (asm_out_file, buffer);
29931  fprintf (asm_out_file, "\n");
29932}
29933
29934static void
29935rs6000_xcoff_asm_globalize_label (FILE *stream, const char *name)
29936{
29937  fputs (GLOBAL_ASM_OP, stream);
29938  RS6000_OUTPUT_BASENAME (stream, name);
29939  putc ('\n', stream);
29940}
29941
29942/* A get_unnamed_decl callback, used for read-only sections.  PTR
29943   points to the section string variable.  */
29944
29945static void
29946rs6000_xcoff_output_readonly_section_asm_op (const void *directive)
29947{
29948  fprintf (asm_out_file, "\t.csect %s[RO],%s\n",
29949	   *(const char *const *) directive,
29950	   XCOFF_CSECT_DEFAULT_ALIGNMENT_STR);
29951}
29952
29953/* Likewise for read-write sections.  */
29954
29955static void
29956rs6000_xcoff_output_readwrite_section_asm_op (const void *directive)
29957{
29958  fprintf (asm_out_file, "\t.csect %s[RW],%s\n",
29959	   *(const char *const *) directive,
29960	   XCOFF_CSECT_DEFAULT_ALIGNMENT_STR);
29961}
29962
29963static void
29964rs6000_xcoff_output_tls_section_asm_op (const void *directive)
29965{
29966  fprintf (asm_out_file, "\t.csect %s[TL],%s\n",
29967	   *(const char *const *) directive,
29968	   XCOFF_CSECT_DEFAULT_ALIGNMENT_STR);
29969}
29970
29971/* A get_unnamed_section callback, used for switching to toc_section.  */
29972
29973static void
29974rs6000_xcoff_output_toc_section_asm_op (const void *data ATTRIBUTE_UNUSED)
29975{
29976  if (TARGET_MINIMAL_TOC)
29977    {
29978      /* toc_section is always selected at least once from
29979	 rs6000_xcoff_file_start, so this is guaranteed to
29980	 always be defined once and only once in each file.  */
29981      if (!toc_initialized)
29982	{
29983	  fputs ("\t.toc\nLCTOC..1:\n", asm_out_file);
29984	  fputs ("\t.tc toc_table[TC],toc_table[RW]\n", asm_out_file);
29985	  toc_initialized = 1;
29986	}
29987      fprintf (asm_out_file, "\t.csect toc_table[RW]%s\n",
29988	       (TARGET_32BIT ? "" : ",3"));
29989    }
29990  else
29991    fputs ("\t.toc\n", asm_out_file);
29992}
29993
29994/* Implement TARGET_ASM_INIT_SECTIONS.  */
29995
29996static void
29997rs6000_xcoff_asm_init_sections (void)
29998{
29999  read_only_data_section
30000    = get_unnamed_section (0, rs6000_xcoff_output_readonly_section_asm_op,
30001			   &xcoff_read_only_section_name);
30002
30003  private_data_section
30004    = get_unnamed_section (SECTION_WRITE,
30005			   rs6000_xcoff_output_readwrite_section_asm_op,
30006			   &xcoff_private_data_section_name);
30007
30008  tls_data_section
30009    = get_unnamed_section (SECTION_TLS,
30010			   rs6000_xcoff_output_tls_section_asm_op,
30011			   &xcoff_tls_data_section_name);
30012
30013  tls_private_data_section
30014    = get_unnamed_section (SECTION_TLS,
30015			   rs6000_xcoff_output_tls_section_asm_op,
30016			   &xcoff_private_data_section_name);
30017
30018  read_only_private_data_section
30019    = get_unnamed_section (0, rs6000_xcoff_output_readonly_section_asm_op,
30020			   &xcoff_private_data_section_name);
30021
30022  toc_section
30023    = get_unnamed_section (0, rs6000_xcoff_output_toc_section_asm_op, NULL);
30024
30025  readonly_data_section = read_only_data_section;
30026  exception_section = data_section;
30027}
30028
30029static int
30030rs6000_xcoff_reloc_rw_mask (void)
30031{
30032  return 3;
30033}
30034
30035static void
30036rs6000_xcoff_asm_named_section (const char *name, unsigned int flags,
30037				tree decl ATTRIBUTE_UNUSED)
30038{
30039  int smclass;
30040  static const char * const suffix[4] = { "PR", "RO", "RW", "TL" };
30041
30042  if (flags & SECTION_CODE)
30043    smclass = 0;
30044  else if (flags & SECTION_TLS)
30045    smclass = 3;
30046  else if (flags & SECTION_WRITE)
30047    smclass = 2;
30048  else
30049    smclass = 1;
30050
30051  fprintf (asm_out_file, "\t.csect %s%s[%s],%u\n",
30052	   (flags & SECTION_CODE) ? "." : "",
30053	   name, suffix[smclass], flags & SECTION_ENTSIZE);
30054}
30055
30056#define IN_NAMED_SECTION(DECL) \
30057  ((TREE_CODE (DECL) == FUNCTION_DECL || TREE_CODE (DECL) == VAR_DECL) \
30058   && DECL_SECTION_NAME (DECL) != NULL)
30059
30060static section *
30061rs6000_xcoff_select_section (tree decl, int reloc,
30062			     unsigned HOST_WIDE_INT align)
30063{
30064  /* Place variables with alignment stricter than BIGGEST_ALIGNMENT into
30065     named section.  */
30066  if (align > BIGGEST_ALIGNMENT)
30067    {
30068      resolve_unique_section (decl, reloc, true);
30069      if (IN_NAMED_SECTION (decl))
30070	return get_named_section (decl, NULL, reloc);
30071    }
30072
30073  if (decl_readonly_section (decl, reloc))
30074    {
30075      if (TREE_PUBLIC (decl))
30076	return read_only_data_section;
30077      else
30078	return read_only_private_data_section;
30079    }
30080  else
30081    {
30082#if HAVE_AS_TLS
30083      if (TREE_CODE (decl) == VAR_DECL && DECL_THREAD_LOCAL_P (decl))
30084	{
30085	  if (TREE_PUBLIC (decl))
30086	    return tls_data_section;
30087	  else if (bss_initializer_p (decl))
30088	    {
30089	      /* Convert to COMMON to emit in BSS.  */
30090	      DECL_COMMON (decl) = 1;
30091	      return tls_comm_section;
30092	    }
30093	  else
30094	    return tls_private_data_section;
30095	}
30096      else
30097#endif
30098	if (TREE_PUBLIC (decl))
30099	return data_section;
30100      else
30101	return private_data_section;
30102    }
30103}
30104
30105static void
30106rs6000_xcoff_unique_section (tree decl, int reloc ATTRIBUTE_UNUSED)
30107{
30108  const char *name;
30109
30110  /* Use select_section for private data and uninitialized data with
30111     alignment <= BIGGEST_ALIGNMENT.  */
30112  if (!TREE_PUBLIC (decl)
30113      || DECL_COMMON (decl)
30114      || (DECL_INITIAL (decl) == NULL_TREE
30115	  && DECL_ALIGN (decl) <= BIGGEST_ALIGNMENT)
30116      || DECL_INITIAL (decl) == error_mark_node
30117      || (flag_zero_initialized_in_bss
30118	  && initializer_zerop (DECL_INITIAL (decl))))
30119    return;
30120
30121  name = IDENTIFIER_POINTER (DECL_ASSEMBLER_NAME (decl));
30122  name = (*targetm.strip_name_encoding) (name);
30123  set_decl_section_name (decl, name);
30124}
30125
30126/* Select section for constant in constant pool.
30127
30128   On RS/6000, all constants are in the private read-only data area.
30129   However, if this is being placed in the TOC it must be output as a
30130   toc entry.  */
30131
30132static section *
30133rs6000_xcoff_select_rtx_section (machine_mode mode, rtx x,
30134				 unsigned HOST_WIDE_INT align ATTRIBUTE_UNUSED)
30135{
30136  if (ASM_OUTPUT_SPECIAL_POOL_ENTRY_P (x, mode))
30137    return toc_section;
30138  else
30139    return read_only_private_data_section;
30140}
30141
30142/* Remove any trailing [DS] or the like from the symbol name.  */
30143
30144static const char *
30145rs6000_xcoff_strip_name_encoding (const char *name)
30146{
30147  size_t len;
30148  if (*name == '*')
30149    name++;
30150  len = strlen (name);
30151  if (name[len - 1] == ']')
30152    return ggc_alloc_string (name, len - 4);
30153  else
30154    return name;
30155}
30156
30157/* Section attributes.  AIX is always PIC.  */
30158
30159static unsigned int
30160rs6000_xcoff_section_type_flags (tree decl, const char *name, int reloc)
30161{
30162  unsigned int align;
30163  unsigned int flags = default_section_type_flags (decl, name, reloc);
30164
30165  /* Align to at least UNIT size.  */
30166  if ((flags & SECTION_CODE) != 0 || !decl || !DECL_P (decl))
30167    align = MIN_UNITS_PER_WORD;
30168  else
30169    /* Increase alignment of large objects if not already stricter.  */
30170    align = MAX ((DECL_ALIGN (decl) / BITS_PER_UNIT),
30171		 int_size_in_bytes (TREE_TYPE (decl)) > MIN_UNITS_PER_WORD
30172		 ? UNITS_PER_FP_WORD : MIN_UNITS_PER_WORD);
30173
30174  return flags | (exact_log2 (align) & SECTION_ENTSIZE);
30175}
30176
30177/* Output at beginning of assembler file.
30178
30179   Initialize the section names for the RS/6000 at this point.
30180
30181   Specify filename, including full path, to assembler.
30182
30183   We want to go into the TOC section so at least one .toc will be emitted.
30184   Also, in order to output proper .bs/.es pairs, we need at least one static
30185   [RW] section emitted.
30186
30187   Finally, declare mcount when profiling to make the assembler happy.  */
30188
30189static void
30190rs6000_xcoff_file_start (void)
30191{
30192  rs6000_gen_section_name (&xcoff_bss_section_name,
30193			   main_input_filename, ".bss_");
30194  rs6000_gen_section_name (&xcoff_private_data_section_name,
30195			   main_input_filename, ".rw_");
30196  rs6000_gen_section_name (&xcoff_read_only_section_name,
30197			   main_input_filename, ".ro_");
30198  rs6000_gen_section_name (&xcoff_tls_data_section_name,
30199			   main_input_filename, ".tls_");
30200  rs6000_gen_section_name (&xcoff_tbss_section_name,
30201			   main_input_filename, ".tbss_[UL]");
30202
30203  fputs ("\t.file\t", asm_out_file);
30204  output_quoted_string (asm_out_file, main_input_filename);
30205  fputc ('\n', asm_out_file);
30206  if (write_symbols != NO_DEBUG)
30207    switch_to_section (private_data_section);
30208  switch_to_section (text_section);
30209  if (profile_flag)
30210    fprintf (asm_out_file, "\t.extern %s\n", RS6000_MCOUNT);
30211  rs6000_file_start ();
30212}
30213
30214/* Output at end of assembler file.
30215   On the RS/6000, referencing data should automatically pull in text.  */
30216
30217static void
30218rs6000_xcoff_file_end (void)
30219{
30220  switch_to_section (text_section);
30221  fputs ("_section_.text:\n", asm_out_file);
30222  switch_to_section (data_section);
30223  fputs (TARGET_32BIT
30224	 ? "\t.long _section_.text\n" : "\t.llong _section_.text\n",
30225	 asm_out_file);
30226}
30227
30228struct declare_alias_data
30229{
30230  FILE *file;
30231  bool function_descriptor;
30232};
30233
30234/* Declare alias N.  A helper function for for_node_and_aliases.  */
30235
30236static bool
30237rs6000_declare_alias (struct symtab_node *n, void *d)
30238{
30239  struct declare_alias_data *data = (struct declare_alias_data *)d;
30240  /* Main symbol is output specially, because varasm machinery does part of
30241     the job for us - we do not need to declare .globl/lglobs and such.  */
30242  if (!n->alias || n->weakref)
30243    return false;
30244
30245  if (lookup_attribute ("ifunc", DECL_ATTRIBUTES (n->decl)))
30246    return false;
30247
30248  /* Prevent assemble_alias from trying to use .set pseudo operation
30249     that does not behave as expected by the middle-end.  */
30250  TREE_ASM_WRITTEN (n->decl) = true;
30251
30252  const char *name = IDENTIFIER_POINTER (DECL_ASSEMBLER_NAME (n->decl));
30253  char *buffer = (char *) alloca (strlen (name) + 2);
30254  char *p;
30255  int dollar_inside = 0;
30256
30257  strcpy (buffer, name);
30258  p = strchr (buffer, '$');
30259  while (p) {
30260    *p = '_';
30261    dollar_inside++;
30262    p = strchr (p + 1, '$');
30263  }
30264  if (TREE_PUBLIC (n->decl))
30265    {
30266      if (!RS6000_WEAK || !DECL_WEAK (n->decl))
30267	{
30268          if (dollar_inside) {
30269	      if (data->function_descriptor)
30270                fprintf(data->file, "\t.rename .%s,\".%s\"\n", buffer, name);
30271	      fprintf(data->file, "\t.rename %s,\"%s\"\n", buffer, name);
30272	    }
30273	  if (data->function_descriptor)
30274	    {
30275	      fputs ("\t.globl .", data->file);
30276	      RS6000_OUTPUT_BASENAME (data->file, buffer);
30277	      putc ('\n', data->file);
30278	    }
30279	  fputs ("\t.globl ", data->file);
30280	  RS6000_OUTPUT_BASENAME (data->file, buffer);
30281	  putc ('\n', data->file);
30282	}
30283#ifdef ASM_WEAKEN_DECL
30284      else if (DECL_WEAK (n->decl) && !data->function_descriptor)
30285	ASM_WEAKEN_DECL (data->file, n->decl, name, NULL);
30286#endif
30287    }
30288  else
30289    {
30290      if (dollar_inside)
30291	{
30292	  if (data->function_descriptor)
30293            fprintf(data->file, "\t.rename .%s,\".%s\"\n", buffer, name);
30294	  fprintf(data->file, "\t.rename %s,\"%s\"\n", buffer, name);
30295	}
30296      if (data->function_descriptor)
30297	{
30298	  fputs ("\t.lglobl .", data->file);
30299	  RS6000_OUTPUT_BASENAME (data->file, buffer);
30300	  putc ('\n', data->file);
30301	}
30302      fputs ("\t.lglobl ", data->file);
30303      RS6000_OUTPUT_BASENAME (data->file, buffer);
30304      putc ('\n', data->file);
30305    }
30306  if (data->function_descriptor)
30307    fputs (".", data->file);
30308  RS6000_OUTPUT_BASENAME (data->file, buffer);
30309  fputs (":\n", data->file);
30310  return false;
30311}
30312
30313/* This macro produces the initial definition of a function name.
30314   On the RS/6000, we need to place an extra '.' in the function name and
30315   output the function descriptor.
30316   Dollar signs are converted to underscores.
30317
30318   The csect for the function will have already been created when
30319   text_section was selected.  We do have to go back to that csect, however.
30320
30321   The third and fourth parameters to the .function pseudo-op (16 and 044)
30322   are placeholders which no longer have any use.
30323
30324   Because AIX assembler's .set command has unexpected semantics, we output
30325   all aliases as alternative labels in front of the definition.  */
30326
30327void
30328rs6000_xcoff_declare_function_name (FILE *file, const char *name, tree decl)
30329{
30330  char *buffer = (char *) alloca (strlen (name) + 1);
30331  char *p;
30332  int dollar_inside = 0;
30333  struct declare_alias_data data = {file, false};
30334
30335  strcpy (buffer, name);
30336  p = strchr (buffer, '$');
30337  while (p) {
30338    *p = '_';
30339    dollar_inside++;
30340    p = strchr (p + 1, '$');
30341  }
30342  if (TREE_PUBLIC (decl))
30343    {
30344      if (!RS6000_WEAK || !DECL_WEAK (decl))
30345	{
30346          if (dollar_inside) {
30347              fprintf(file, "\t.rename .%s,\".%s\"\n", buffer, name);
30348              fprintf(file, "\t.rename %s,\"%s\"\n", buffer, name);
30349	    }
30350	  fputs ("\t.globl .", file);
30351	  RS6000_OUTPUT_BASENAME (file, buffer);
30352	  putc ('\n', file);
30353	}
30354    }
30355  else
30356    {
30357      if (dollar_inside) {
30358          fprintf(file, "\t.rename .%s,\".%s\"\n", buffer, name);
30359          fprintf(file, "\t.rename %s,\"%s\"\n", buffer, name);
30360	}
30361      fputs ("\t.lglobl .", file);
30362      RS6000_OUTPUT_BASENAME (file, buffer);
30363      putc ('\n', file);
30364    }
30365  fputs ("\t.csect ", file);
30366  RS6000_OUTPUT_BASENAME (file, buffer);
30367  fputs (TARGET_32BIT ? "[DS]\n" : "[DS],3\n", file);
30368  RS6000_OUTPUT_BASENAME (file, buffer);
30369  fputs (":\n", file);
30370  symtab_node::get (decl)->call_for_symbol_and_aliases (rs6000_declare_alias, &data, true);
30371  fputs (TARGET_32BIT ? "\t.long ." : "\t.llong .", file);
30372  RS6000_OUTPUT_BASENAME (file, buffer);
30373  fputs (", TOC[tc0], 0\n", file);
30374  in_section = NULL;
30375  switch_to_section (function_section (decl));
30376  putc ('.', file);
30377  RS6000_OUTPUT_BASENAME (file, buffer);
30378  fputs (":\n", file);
30379  data.function_descriptor = true;
30380  symtab_node::get (decl)->call_for_symbol_and_aliases (rs6000_declare_alias, &data, true);
30381  if (write_symbols != NO_DEBUG && !DECL_IGNORED_P (decl))
30382    xcoffout_declare_function (file, decl, buffer);
30383  return;
30384}
30385
30386/* This macro produces the initial definition of a object (variable) name.
30387   Because AIX assembler's .set command has unexpected semantics, we output
30388   all aliases as alternative labels in front of the definition.  */
30389
30390void
30391rs6000_xcoff_declare_object_name (FILE *file, const char *name, tree decl)
30392{
30393  struct declare_alias_data data = {file, false};
30394  RS6000_OUTPUT_BASENAME (file, name);
30395  fputs (":\n", file);
30396  symtab_node::get (decl)->call_for_symbol_and_aliases (rs6000_declare_alias, &data, true);
30397}
30398
30399#ifdef HAVE_AS_TLS
30400static void
30401rs6000_xcoff_encode_section_info (tree decl, rtx rtl, int first)
30402{
30403  rtx symbol;
30404  int flags;
30405
30406  default_encode_section_info (decl, rtl, first);
30407
30408  /* Careful not to prod global register variables.  */
30409  if (!MEM_P (rtl))
30410    return;
30411  symbol = XEXP (rtl, 0);
30412  if (GET_CODE (symbol) != SYMBOL_REF)
30413    return;
30414
30415  flags = SYMBOL_REF_FLAGS (symbol);
30416
30417  if (TREE_CODE (decl) == VAR_DECL && DECL_THREAD_LOCAL_P (decl))
30418    flags &= ~SYMBOL_FLAG_HAS_BLOCK_INFO;
30419
30420  SYMBOL_REF_FLAGS (symbol) = flags;
30421}
30422#endif /* HAVE_AS_TLS */
30423#endif /* TARGET_XCOFF */
30424
30425/* Compute a (partial) cost for rtx X.  Return true if the complete
30426   cost has been computed, and false if subexpressions should be
30427   scanned.  In either case, *TOTAL contains the cost result.  */
30428
30429static bool
30430rs6000_rtx_costs (rtx x, int code, int outer_code, int opno ATTRIBUTE_UNUSED,
30431		  int *total, bool speed)
30432{
30433  machine_mode mode = GET_MODE (x);
30434
30435  switch (code)
30436    {
30437      /* On the RS/6000, if it is valid in the insn, it is free.  */
30438    case CONST_INT:
30439      if (((outer_code == SET
30440	    || outer_code == PLUS
30441	    || outer_code == MINUS)
30442	   && (satisfies_constraint_I (x)
30443	       || satisfies_constraint_L (x)))
30444	  || (outer_code == AND
30445	      && (satisfies_constraint_K (x)
30446		  || (mode == SImode
30447		      ? satisfies_constraint_L (x)
30448		      : satisfies_constraint_J (x))
30449		  || mask_operand (x, mode)
30450		  || (mode == DImode
30451		      && mask64_operand (x, DImode))))
30452	  || ((outer_code == IOR || outer_code == XOR)
30453	      && (satisfies_constraint_K (x)
30454		  || (mode == SImode
30455		      ? satisfies_constraint_L (x)
30456		      : satisfies_constraint_J (x))))
30457	  || outer_code == ASHIFT
30458	  || outer_code == ASHIFTRT
30459	  || outer_code == LSHIFTRT
30460	  || outer_code == ROTATE
30461	  || outer_code == ROTATERT
30462	  || outer_code == ZERO_EXTRACT
30463	  || (outer_code == MULT
30464	      && satisfies_constraint_I (x))
30465	  || ((outer_code == DIV || outer_code == UDIV
30466	       || outer_code == MOD || outer_code == UMOD)
30467	      && exact_log2 (INTVAL (x)) >= 0)
30468	  || (outer_code == COMPARE
30469	      && (satisfies_constraint_I (x)
30470		  || satisfies_constraint_K (x)))
30471	  || ((outer_code == EQ || outer_code == NE)
30472	      && (satisfies_constraint_I (x)
30473		  || satisfies_constraint_K (x)
30474		  || (mode == SImode
30475		      ? satisfies_constraint_L (x)
30476		      : satisfies_constraint_J (x))))
30477	  || (outer_code == GTU
30478	      && satisfies_constraint_I (x))
30479	  || (outer_code == LTU
30480	      && satisfies_constraint_P (x)))
30481	{
30482	  *total = 0;
30483	  return true;
30484	}
30485      else if ((outer_code == PLUS
30486		&& reg_or_add_cint_operand (x, VOIDmode))
30487	       || (outer_code == MINUS
30488		   && reg_or_sub_cint_operand (x, VOIDmode))
30489	       || ((outer_code == SET
30490		    || outer_code == IOR
30491		    || outer_code == XOR)
30492		   && (INTVAL (x)
30493		       & ~ (unsigned HOST_WIDE_INT) 0xffffffff) == 0))
30494	{
30495	  *total = COSTS_N_INSNS (1);
30496	  return true;
30497	}
30498      /* FALLTHRU */
30499
30500    case CONST_DOUBLE:
30501    case CONST_WIDE_INT:
30502    case CONST:
30503    case HIGH:
30504    case SYMBOL_REF:
30505    case MEM:
30506      /* When optimizing for size, MEM should be slightly more expensive
30507	 than generating address, e.g., (plus (reg) (const)).
30508	 L1 cache latency is about two instructions.  */
30509      *total = !speed ? COSTS_N_INSNS (1) + 1 : COSTS_N_INSNS (2);
30510      return true;
30511
30512    case LABEL_REF:
30513      *total = 0;
30514      return true;
30515
30516    case PLUS:
30517    case MINUS:
30518      if (FLOAT_MODE_P (mode))
30519	*total = rs6000_cost->fp;
30520      else
30521	*total = COSTS_N_INSNS (1);
30522      return false;
30523
30524    case MULT:
30525      if (GET_CODE (XEXP (x, 1)) == CONST_INT
30526	  && satisfies_constraint_I (XEXP (x, 1)))
30527	{
30528	  if (INTVAL (XEXP (x, 1)) >= -256
30529	      && INTVAL (XEXP (x, 1)) <= 255)
30530	    *total = rs6000_cost->mulsi_const9;
30531	  else
30532	    *total = rs6000_cost->mulsi_const;
30533	}
30534      else if (mode == SFmode)
30535	*total = rs6000_cost->fp;
30536      else if (FLOAT_MODE_P (mode))
30537	*total = rs6000_cost->dmul;
30538      else if (mode == DImode)
30539	*total = rs6000_cost->muldi;
30540      else
30541	*total = rs6000_cost->mulsi;
30542      return false;
30543
30544    case FMA:
30545      if (mode == SFmode)
30546	*total = rs6000_cost->fp;
30547      else
30548	*total = rs6000_cost->dmul;
30549      break;
30550
30551    case DIV:
30552    case MOD:
30553      if (FLOAT_MODE_P (mode))
30554	{
30555	  *total = mode == DFmode ? rs6000_cost->ddiv
30556				  : rs6000_cost->sdiv;
30557	  return false;
30558	}
30559      /* FALLTHRU */
30560
30561    case UDIV:
30562    case UMOD:
30563      if (GET_CODE (XEXP (x, 1)) == CONST_INT
30564	  && exact_log2 (INTVAL (XEXP (x, 1))) >= 0)
30565	{
30566	  if (code == DIV || code == MOD)
30567	    /* Shift, addze */
30568	    *total = COSTS_N_INSNS (2);
30569	  else
30570	    /* Shift */
30571	    *total = COSTS_N_INSNS (1);
30572	}
30573      else
30574	{
30575	  if (GET_MODE (XEXP (x, 1)) == DImode)
30576	    *total = rs6000_cost->divdi;
30577	  else
30578	    *total = rs6000_cost->divsi;
30579	}
30580      /* Add in shift and subtract for MOD. */
30581      if (code == MOD || code == UMOD)
30582	*total += COSTS_N_INSNS (2);
30583      return false;
30584
30585    case CTZ:
30586    case FFS:
30587      *total = COSTS_N_INSNS (4);
30588      return false;
30589
30590    case POPCOUNT:
30591      *total = COSTS_N_INSNS (TARGET_POPCNTD ? 1 : 6);
30592      return false;
30593
30594    case PARITY:
30595      *total = COSTS_N_INSNS (TARGET_CMPB ? 2 : 6);
30596      return false;
30597
30598    case NOT:
30599      if (outer_code == AND || outer_code == IOR || outer_code == XOR)
30600	{
30601	  *total = 0;
30602	  return false;
30603	}
30604      /* FALLTHRU */
30605
30606    case AND:
30607    case CLZ:
30608    case IOR:
30609    case XOR:
30610    case ZERO_EXTRACT:
30611      *total = COSTS_N_INSNS (1);
30612      return false;
30613
30614    case ASHIFT:
30615    case ASHIFTRT:
30616    case LSHIFTRT:
30617    case ROTATE:
30618    case ROTATERT:
30619      /* Handle mul_highpart.  */
30620      if (outer_code == TRUNCATE
30621	  && GET_CODE (XEXP (x, 0)) == MULT)
30622	{
30623	  if (mode == DImode)
30624	    *total = rs6000_cost->muldi;
30625	  else
30626	    *total = rs6000_cost->mulsi;
30627	  return true;
30628	}
30629      else if (outer_code == AND)
30630	*total = 0;
30631      else
30632	*total = COSTS_N_INSNS (1);
30633      return false;
30634
30635    case SIGN_EXTEND:
30636    case ZERO_EXTEND:
30637      if (GET_CODE (XEXP (x, 0)) == MEM)
30638	*total = 0;
30639      else
30640	*total = COSTS_N_INSNS (1);
30641      return false;
30642
30643    case COMPARE:
30644    case NEG:
30645    case ABS:
30646      if (!FLOAT_MODE_P (mode))
30647	{
30648	  *total = COSTS_N_INSNS (1);
30649	  return false;
30650	}
30651      /* FALLTHRU */
30652
30653    case FLOAT:
30654    case UNSIGNED_FLOAT:
30655    case FIX:
30656    case UNSIGNED_FIX:
30657    case FLOAT_TRUNCATE:
30658      *total = rs6000_cost->fp;
30659      return false;
30660
30661    case FLOAT_EXTEND:
30662      if (mode == DFmode)
30663	*total = rs6000_cost->sfdf_convert;
30664      else
30665	*total = rs6000_cost->fp;
30666      return false;
30667
30668    case UNSPEC:
30669      switch (XINT (x, 1))
30670	{
30671	case UNSPEC_FRSP:
30672	  *total = rs6000_cost->fp;
30673	  return true;
30674
30675	default:
30676	  break;
30677	}
30678      break;
30679
30680    case CALL:
30681    case IF_THEN_ELSE:
30682      if (!speed)
30683	{
30684	  *total = COSTS_N_INSNS (1);
30685	  return true;
30686	}
30687      else if (FLOAT_MODE_P (mode)
30688	       && TARGET_PPC_GFXOPT && TARGET_HARD_FLOAT && TARGET_FPRS)
30689	{
30690	  *total = rs6000_cost->fp;
30691	  return false;
30692	}
30693      break;
30694
30695    case NE:
30696    case EQ:
30697    case GTU:
30698    case LTU:
30699      /* Carry bit requires mode == Pmode.
30700	 NEG or PLUS already counted so only add one.  */
30701      if (mode == Pmode
30702	  && (outer_code == NEG || outer_code == PLUS))
30703	{
30704	  *total = COSTS_N_INSNS (1);
30705	  return true;
30706	}
30707      if (outer_code == SET)
30708	{
30709	  if (XEXP (x, 1) == const0_rtx)
30710	    {
30711	      if (TARGET_ISEL && !TARGET_MFCRF)
30712		*total = COSTS_N_INSNS (8);
30713	      else
30714		*total = COSTS_N_INSNS (2);
30715	      return true;
30716	    }
30717	  else
30718	    {
30719	      *total = COSTS_N_INSNS (3);
30720	      return false;
30721	    }
30722	}
30723      /* FALLTHRU */
30724
30725    case GT:
30726    case LT:
30727    case UNORDERED:
30728      if (outer_code == SET && (XEXP (x, 1) == const0_rtx))
30729	{
30730	  if (TARGET_ISEL && !TARGET_MFCRF)
30731	    *total = COSTS_N_INSNS (8);
30732	  else
30733	    *total = COSTS_N_INSNS (2);
30734	  return true;
30735	}
30736      /* CC COMPARE.  */
30737      if (outer_code == COMPARE)
30738	{
30739	  *total = 0;
30740	  return true;
30741	}
30742      break;
30743
30744    default:
30745      break;
30746    }
30747
30748  return false;
30749}
30750
30751/* Debug form of r6000_rtx_costs that is selected if -mdebug=cost.  */
30752
30753static bool
30754rs6000_debug_rtx_costs (rtx x, int code, int outer_code, int opno, int *total,
30755			bool speed)
30756{
30757  bool ret = rs6000_rtx_costs (x, code, outer_code, opno, total, speed);
30758
30759  fprintf (stderr,
30760	   "\nrs6000_rtx_costs, return = %s, code = %s, outer_code = %s, "
30761	   "opno = %d, total = %d, speed = %s, x:\n",
30762	   ret ? "complete" : "scan inner",
30763	   GET_RTX_NAME (code),
30764	   GET_RTX_NAME (outer_code),
30765	   opno,
30766	   *total,
30767	   speed ? "true" : "false");
30768
30769  debug_rtx (x);
30770
30771  return ret;
30772}
30773
30774/* Debug form of ADDRESS_COST that is selected if -mdebug=cost.  */
30775
30776static int
30777rs6000_debug_address_cost (rtx x, machine_mode mode,
30778			   addr_space_t as, bool speed)
30779{
30780  int ret = TARGET_ADDRESS_COST (x, mode, as, speed);
30781
30782  fprintf (stderr, "\nrs6000_address_cost, return = %d, speed = %s, x:\n",
30783	   ret, speed ? "true" : "false");
30784  debug_rtx (x);
30785
30786  return ret;
30787}
30788
30789
30790/* A C expression returning the cost of moving data from a register of class
30791   CLASS1 to one of CLASS2.  */
30792
30793static int
30794rs6000_register_move_cost (machine_mode mode,
30795			   reg_class_t from, reg_class_t to)
30796{
30797  int ret;
30798
30799  if (TARGET_DEBUG_COST)
30800    dbg_cost_ctrl++;
30801
30802  /*  Moves from/to GENERAL_REGS.  */
30803  if (reg_classes_intersect_p (to, GENERAL_REGS)
30804      || reg_classes_intersect_p (from, GENERAL_REGS))
30805    {
30806      reg_class_t rclass = from;
30807
30808      if (! reg_classes_intersect_p (to, GENERAL_REGS))
30809	rclass = to;
30810
30811      if (rclass == FLOAT_REGS || rclass == ALTIVEC_REGS || rclass == VSX_REGS)
30812	ret = (rs6000_memory_move_cost (mode, rclass, false)
30813	       + rs6000_memory_move_cost (mode, GENERAL_REGS, false));
30814
30815      /* It's more expensive to move CR_REGS than CR0_REGS because of the
30816	 shift.  */
30817      else if (rclass == CR_REGS)
30818	ret = 4;
30819
30820      /* For those processors that have slow LR/CTR moves, make them more
30821         expensive than memory in order to bias spills to memory .*/
30822      else if ((rs6000_cpu == PROCESSOR_POWER6
30823		|| rs6000_cpu == PROCESSOR_POWER7
30824		|| rs6000_cpu == PROCESSOR_POWER8)
30825	       && reg_classes_intersect_p (rclass, LINK_OR_CTR_REGS))
30826        ret = 6 * hard_regno_nregs[0][mode];
30827
30828      else
30829	/* A move will cost one instruction per GPR moved.  */
30830	ret = 2 * hard_regno_nregs[0][mode];
30831    }
30832
30833  /* If we have VSX, we can easily move between FPR or Altivec registers.  */
30834  else if (VECTOR_MEM_VSX_P (mode)
30835	   && reg_classes_intersect_p (to, VSX_REGS)
30836	   && reg_classes_intersect_p (from, VSX_REGS))
30837    ret = 2 * hard_regno_nregs[32][mode];
30838
30839  /* Moving between two similar registers is just one instruction.  */
30840  else if (reg_classes_intersect_p (to, from))
30841    ret = (mode == TFmode || mode == TDmode) ? 4 : 2;
30842
30843  /* Everything else has to go through GENERAL_REGS.  */
30844  else
30845    ret = (rs6000_register_move_cost (mode, GENERAL_REGS, to)
30846	   + rs6000_register_move_cost (mode, from, GENERAL_REGS));
30847
30848  if (TARGET_DEBUG_COST)
30849    {
30850      if (dbg_cost_ctrl == 1)
30851	fprintf (stderr,
30852		 "rs6000_register_move_cost:, ret=%d, mode=%s, from=%s, to=%s\n",
30853		 ret, GET_MODE_NAME (mode), reg_class_names[from],
30854		 reg_class_names[to]);
30855      dbg_cost_ctrl--;
30856    }
30857
30858  return ret;
30859}
30860
30861/* A C expressions returning the cost of moving data of MODE from a register to
30862   or from memory.  */
30863
30864static int
30865rs6000_memory_move_cost (machine_mode mode, reg_class_t rclass,
30866			 bool in ATTRIBUTE_UNUSED)
30867{
30868  int ret;
30869
30870  if (TARGET_DEBUG_COST)
30871    dbg_cost_ctrl++;
30872
30873  if (reg_classes_intersect_p (rclass, GENERAL_REGS))
30874    ret = 4 * hard_regno_nregs[0][mode];
30875  else if ((reg_classes_intersect_p (rclass, FLOAT_REGS)
30876	    || reg_classes_intersect_p (rclass, VSX_REGS)))
30877    ret = 4 * hard_regno_nregs[32][mode];
30878  else if (reg_classes_intersect_p (rclass, ALTIVEC_REGS))
30879    ret = 4 * hard_regno_nregs[FIRST_ALTIVEC_REGNO][mode];
30880  else
30881    ret = 4 + rs6000_register_move_cost (mode, rclass, GENERAL_REGS);
30882
30883  if (TARGET_DEBUG_COST)
30884    {
30885      if (dbg_cost_ctrl == 1)
30886	fprintf (stderr,
30887		 "rs6000_memory_move_cost: ret=%d, mode=%s, rclass=%s, in=%d\n",
30888		 ret, GET_MODE_NAME (mode), reg_class_names[rclass], in);
30889      dbg_cost_ctrl--;
30890    }
30891
30892  return ret;
30893}
30894
30895/* Returns a code for a target-specific builtin that implements
30896   reciprocal of the function, or NULL_TREE if not available.  */
30897
30898static tree
30899rs6000_builtin_reciprocal (unsigned int fn, bool md_fn,
30900			   bool sqrt ATTRIBUTE_UNUSED)
30901{
30902  if (optimize_insn_for_size_p ())
30903    return NULL_TREE;
30904
30905  if (md_fn)
30906    switch (fn)
30907      {
30908      case VSX_BUILTIN_XVSQRTDP:
30909	if (!RS6000_RECIP_AUTO_RSQRTE_P (V2DFmode))
30910	  return NULL_TREE;
30911
30912	return rs6000_builtin_decls[VSX_BUILTIN_RSQRT_2DF];
30913
30914      case VSX_BUILTIN_XVSQRTSP:
30915	if (!RS6000_RECIP_AUTO_RSQRTE_P (V4SFmode))
30916	  return NULL_TREE;
30917
30918	return rs6000_builtin_decls[VSX_BUILTIN_RSQRT_4SF];
30919
30920      default:
30921	return NULL_TREE;
30922      }
30923
30924  else
30925    switch (fn)
30926      {
30927      case BUILT_IN_SQRT:
30928	if (!RS6000_RECIP_AUTO_RSQRTE_P (DFmode))
30929	  return NULL_TREE;
30930
30931	return rs6000_builtin_decls[RS6000_BUILTIN_RSQRT];
30932
30933      case BUILT_IN_SQRTF:
30934	if (!RS6000_RECIP_AUTO_RSQRTE_P (SFmode))
30935	  return NULL_TREE;
30936
30937	return rs6000_builtin_decls[RS6000_BUILTIN_RSQRTF];
30938
30939      default:
30940	return NULL_TREE;
30941      }
30942}
30943
30944/* Load up a constant.  If the mode is a vector mode, splat the value across
30945   all of the vector elements.  */
30946
30947static rtx
30948rs6000_load_constant_and_splat (machine_mode mode, REAL_VALUE_TYPE dconst)
30949{
30950  rtx reg;
30951
30952  if (mode == SFmode || mode == DFmode)
30953    {
30954      rtx d = CONST_DOUBLE_FROM_REAL_VALUE (dconst, mode);
30955      reg = force_reg (mode, d);
30956    }
30957  else if (mode == V4SFmode)
30958    {
30959      rtx d = CONST_DOUBLE_FROM_REAL_VALUE (dconst, SFmode);
30960      rtvec v = gen_rtvec (4, d, d, d, d);
30961      reg = gen_reg_rtx (mode);
30962      rs6000_expand_vector_init (reg, gen_rtx_PARALLEL (mode, v));
30963    }
30964  else if (mode == V2DFmode)
30965    {
30966      rtx d = CONST_DOUBLE_FROM_REAL_VALUE (dconst, DFmode);
30967      rtvec v = gen_rtvec (2, d, d);
30968      reg = gen_reg_rtx (mode);
30969      rs6000_expand_vector_init (reg, gen_rtx_PARALLEL (mode, v));
30970    }
30971  else
30972    gcc_unreachable ();
30973
30974  return reg;
30975}
30976
30977/* Generate an FMA instruction.  */
30978
30979static void
30980rs6000_emit_madd (rtx target, rtx m1, rtx m2, rtx a)
30981{
30982  machine_mode mode = GET_MODE (target);
30983  rtx dst;
30984
30985  dst = expand_ternary_op (mode, fma_optab, m1, m2, a, target, 0);
30986  gcc_assert (dst != NULL);
30987
30988  if (dst != target)
30989    emit_move_insn (target, dst);
30990}
30991
30992/* Generate a FMSUB instruction: dst = fma(m1, m2, -a).  */
30993
30994static void
30995rs6000_emit_msub (rtx target, rtx m1, rtx m2, rtx a)
30996{
30997  machine_mode mode = GET_MODE (target);
30998  rtx dst;
30999
31000  /* Altivec does not support fms directly;
31001     generate in terms of fma in that case.  */
31002  if (optab_handler (fms_optab, mode) != CODE_FOR_nothing)
31003    dst = expand_ternary_op (mode, fms_optab, m1, m2, a, target, 0);
31004  else
31005    {
31006      a = expand_unop (mode, neg_optab, a, NULL_RTX, 0);
31007      dst = expand_ternary_op (mode, fma_optab, m1, m2, a, target, 0);
31008    }
31009  gcc_assert (dst != NULL);
31010
31011  if (dst != target)
31012    emit_move_insn (target, dst);
31013}
31014
31015/* Generate a FNMSUB instruction: dst = -fma(m1, m2, -a).  */
31016
31017static void
31018rs6000_emit_nmsub (rtx dst, rtx m1, rtx m2, rtx a)
31019{
31020  machine_mode mode = GET_MODE (dst);
31021  rtx r;
31022
31023  /* This is a tad more complicated, since the fnma_optab is for
31024     a different expression: fma(-m1, m2, a), which is the same
31025     thing except in the case of signed zeros.
31026
31027     Fortunately we know that if FMA is supported that FNMSUB is
31028     also supported in the ISA.  Just expand it directly.  */
31029
31030  gcc_assert (optab_handler (fma_optab, mode) != CODE_FOR_nothing);
31031
31032  r = gen_rtx_NEG (mode, a);
31033  r = gen_rtx_FMA (mode, m1, m2, r);
31034  r = gen_rtx_NEG (mode, r);
31035  emit_insn (gen_rtx_SET (VOIDmode, dst, r));
31036}
31037
31038/* Newton-Raphson approximation of floating point divide DST = N/D.  If NOTE_P,
31039   add a reg_note saying that this was a division.  Support both scalar and
31040   vector divide.  Assumes no trapping math and finite arguments.  */
31041
31042void
31043rs6000_emit_swdiv (rtx dst, rtx n, rtx d, bool note_p)
31044{
31045  machine_mode mode = GET_MODE (dst);
31046  rtx one, x0, e0, x1, xprev, eprev, xnext, enext, u, v;
31047  int i;
31048
31049  /* Low precision estimates guarantee 5 bits of accuracy.  High
31050     precision estimates guarantee 14 bits of accuracy.  SFmode
31051     requires 23 bits of accuracy.  DFmode requires 52 bits of
31052     accuracy.  Each pass at least doubles the accuracy, leading
31053     to the following.  */
31054  int passes = (TARGET_RECIP_PRECISION) ? 1 : 3;
31055  if (mode == DFmode || mode == V2DFmode)
31056    passes++;
31057
31058  enum insn_code code = optab_handler (smul_optab, mode);
31059  insn_gen_fn gen_mul = GEN_FCN (code);
31060
31061  gcc_assert (code != CODE_FOR_nothing);
31062
31063  one = rs6000_load_constant_and_splat (mode, dconst1);
31064
31065  /* x0 = 1./d estimate */
31066  x0 = gen_reg_rtx (mode);
31067  emit_insn (gen_rtx_SET (VOIDmode, x0,
31068			  gen_rtx_UNSPEC (mode, gen_rtvec (1, d),
31069					  UNSPEC_FRES)));
31070
31071  /* Each iteration but the last calculates x_(i+1) = x_i * (2 - d * x_i).  */
31072  if (passes > 1) {
31073
31074    /* e0 = 1. - d * x0  */
31075    e0 = gen_reg_rtx (mode);
31076    rs6000_emit_nmsub (e0, d, x0, one);
31077
31078    /* x1 = x0 + e0 * x0  */
31079    x1 = gen_reg_rtx (mode);
31080    rs6000_emit_madd (x1, e0, x0, x0);
31081
31082    for (i = 0, xprev = x1, eprev = e0; i < passes - 2;
31083	 ++i, xprev = xnext, eprev = enext) {
31084
31085      /* enext = eprev * eprev  */
31086      enext = gen_reg_rtx (mode);
31087      emit_insn (gen_mul (enext, eprev, eprev));
31088
31089      /* xnext = xprev + enext * xprev  */
31090      xnext = gen_reg_rtx (mode);
31091      rs6000_emit_madd (xnext, enext, xprev, xprev);
31092    }
31093
31094  } else
31095    xprev = x0;
31096
31097  /* The last iteration calculates x_(i+1) = n * x_i * (2 - d * x_i).  */
31098
31099  /* u = n * xprev  */
31100  u = gen_reg_rtx (mode);
31101  emit_insn (gen_mul (u, n, xprev));
31102
31103  /* v = n - (d * u)  */
31104  v = gen_reg_rtx (mode);
31105  rs6000_emit_nmsub (v, d, u, n);
31106
31107  /* dst = (v * xprev) + u  */
31108  rs6000_emit_madd (dst, v, xprev, u);
31109
31110  if (note_p)
31111    add_reg_note (get_last_insn (), REG_EQUAL, gen_rtx_DIV (mode, n, d));
31112}
31113
31114/* Newton-Raphson approximation of single/double-precision floating point
31115   rsqrt.  Assumes no trapping math and finite arguments.  */
31116
31117void
31118rs6000_emit_swrsqrt (rtx dst, rtx src)
31119{
31120  machine_mode mode = GET_MODE (src);
31121  rtx x0 = gen_reg_rtx (mode);
31122  rtx y = gen_reg_rtx (mode);
31123
31124  /* Low precision estimates guarantee 5 bits of accuracy.  High
31125     precision estimates guarantee 14 bits of accuracy.  SFmode
31126     requires 23 bits of accuracy.  DFmode requires 52 bits of
31127     accuracy.  Each pass at least doubles the accuracy, leading
31128     to the following.  */
31129  int passes = (TARGET_RECIP_PRECISION) ? 1 : 3;
31130  if (mode == DFmode || mode == V2DFmode)
31131    passes++;
31132
31133  REAL_VALUE_TYPE dconst3_2;
31134  int i;
31135  rtx halfthree;
31136  enum insn_code code = optab_handler (smul_optab, mode);
31137  insn_gen_fn gen_mul = GEN_FCN (code);
31138
31139  gcc_assert (code != CODE_FOR_nothing);
31140
31141  /* Load up the constant 1.5 either as a scalar, or as a vector.  */
31142  real_from_integer (&dconst3_2, VOIDmode, 3, SIGNED);
31143  SET_REAL_EXP (&dconst3_2, REAL_EXP (&dconst3_2) - 1);
31144
31145  halfthree = rs6000_load_constant_and_splat (mode, dconst3_2);
31146
31147  /* x0 = rsqrt estimate */
31148  emit_insn (gen_rtx_SET (VOIDmode, x0,
31149			  gen_rtx_UNSPEC (mode, gen_rtvec (1, src),
31150					  UNSPEC_RSQRT)));
31151
31152  /* y = 0.5 * src = 1.5 * src - src -> fewer constants */
31153  rs6000_emit_msub (y, src, halfthree, src);
31154
31155  for (i = 0; i < passes; i++)
31156    {
31157      rtx x1 = gen_reg_rtx (mode);
31158      rtx u = gen_reg_rtx (mode);
31159      rtx v = gen_reg_rtx (mode);
31160
31161      /* x1 = x0 * (1.5 - y * (x0 * x0)) */
31162      emit_insn (gen_mul (u, x0, x0));
31163      rs6000_emit_nmsub (v, y, u, halfthree);
31164      emit_insn (gen_mul (x1, x0, v));
31165      x0 = x1;
31166    }
31167
31168  emit_move_insn (dst, x0);
31169  return;
31170}
31171
31172/* Emit popcount intrinsic on TARGET_POPCNTB (Power5) and TARGET_POPCNTD
31173   (Power7) targets.  DST is the target, and SRC is the argument operand.  */
31174
31175void
31176rs6000_emit_popcount (rtx dst, rtx src)
31177{
31178  machine_mode mode = GET_MODE (dst);
31179  rtx tmp1, tmp2;
31180
31181  /* Use the PPC ISA 2.06 popcnt{w,d} instruction if we can.  */
31182  if (TARGET_POPCNTD)
31183    {
31184      if (mode == SImode)
31185	emit_insn (gen_popcntdsi2 (dst, src));
31186      else
31187	emit_insn (gen_popcntddi2 (dst, src));
31188      return;
31189    }
31190
31191  tmp1 = gen_reg_rtx (mode);
31192
31193  if (mode == SImode)
31194    {
31195      emit_insn (gen_popcntbsi2 (tmp1, src));
31196      tmp2 = expand_mult (SImode, tmp1, GEN_INT (0x01010101),
31197			   NULL_RTX, 0);
31198      tmp2 = force_reg (SImode, tmp2);
31199      emit_insn (gen_lshrsi3 (dst, tmp2, GEN_INT (24)));
31200    }
31201  else
31202    {
31203      emit_insn (gen_popcntbdi2 (tmp1, src));
31204      tmp2 = expand_mult (DImode, tmp1,
31205			  GEN_INT ((HOST_WIDE_INT)
31206				   0x01010101 << 32 | 0x01010101),
31207			  NULL_RTX, 0);
31208      tmp2 = force_reg (DImode, tmp2);
31209      emit_insn (gen_lshrdi3 (dst, tmp2, GEN_INT (56)));
31210    }
31211}
31212
31213
31214/* Emit parity intrinsic on TARGET_POPCNTB targets.  DST is the
31215   target, and SRC is the argument operand.  */
31216
31217void
31218rs6000_emit_parity (rtx dst, rtx src)
31219{
31220  machine_mode mode = GET_MODE (dst);
31221  rtx tmp;
31222
31223  tmp = gen_reg_rtx (mode);
31224
31225  /* Use the PPC ISA 2.05 prtyw/prtyd instruction if we can.  */
31226  if (TARGET_CMPB)
31227    {
31228      if (mode == SImode)
31229	{
31230	  emit_insn (gen_popcntbsi2 (tmp, src));
31231	  emit_insn (gen_paritysi2_cmpb (dst, tmp));
31232	}
31233      else
31234	{
31235	  emit_insn (gen_popcntbdi2 (tmp, src));
31236	  emit_insn (gen_paritydi2_cmpb (dst, tmp));
31237	}
31238      return;
31239    }
31240
31241  if (mode == SImode)
31242    {
31243      /* Is mult+shift >= shift+xor+shift+xor?  */
31244      if (rs6000_cost->mulsi_const >= COSTS_N_INSNS (3))
31245	{
31246	  rtx tmp1, tmp2, tmp3, tmp4;
31247
31248	  tmp1 = gen_reg_rtx (SImode);
31249	  emit_insn (gen_popcntbsi2 (tmp1, src));
31250
31251	  tmp2 = gen_reg_rtx (SImode);
31252	  emit_insn (gen_lshrsi3 (tmp2, tmp1, GEN_INT (16)));
31253	  tmp3 = gen_reg_rtx (SImode);
31254	  emit_insn (gen_xorsi3 (tmp3, tmp1, tmp2));
31255
31256	  tmp4 = gen_reg_rtx (SImode);
31257	  emit_insn (gen_lshrsi3 (tmp4, tmp3, GEN_INT (8)));
31258	  emit_insn (gen_xorsi3 (tmp, tmp3, tmp4));
31259	}
31260      else
31261	rs6000_emit_popcount (tmp, src);
31262      emit_insn (gen_andsi3 (dst, tmp, const1_rtx));
31263    }
31264  else
31265    {
31266      /* Is mult+shift >= shift+xor+shift+xor+shift+xor?  */
31267      if (rs6000_cost->muldi >= COSTS_N_INSNS (5))
31268	{
31269	  rtx tmp1, tmp2, tmp3, tmp4, tmp5, tmp6;
31270
31271	  tmp1 = gen_reg_rtx (DImode);
31272	  emit_insn (gen_popcntbdi2 (tmp1, src));
31273
31274	  tmp2 = gen_reg_rtx (DImode);
31275	  emit_insn (gen_lshrdi3 (tmp2, tmp1, GEN_INT (32)));
31276	  tmp3 = gen_reg_rtx (DImode);
31277	  emit_insn (gen_xordi3 (tmp3, tmp1, tmp2));
31278
31279	  tmp4 = gen_reg_rtx (DImode);
31280	  emit_insn (gen_lshrdi3 (tmp4, tmp3, GEN_INT (16)));
31281	  tmp5 = gen_reg_rtx (DImode);
31282	  emit_insn (gen_xordi3 (tmp5, tmp3, tmp4));
31283
31284	  tmp6 = gen_reg_rtx (DImode);
31285	  emit_insn (gen_lshrdi3 (tmp6, tmp5, GEN_INT (8)));
31286	  emit_insn (gen_xordi3 (tmp, tmp5, tmp6));
31287	}
31288      else
31289        rs6000_emit_popcount (tmp, src);
31290      emit_insn (gen_anddi3 (dst, tmp, const1_rtx));
31291    }
31292}
31293
31294/* Expand an Altivec constant permutation for little endian mode.
31295   There are two issues: First, the two input operands must be
31296   swapped so that together they form a double-wide array in LE
31297   order.  Second, the vperm instruction has surprising behavior
31298   in LE mode:  it interprets the elements of the source vectors
31299   in BE mode ("left to right") and interprets the elements of
31300   the destination vector in LE mode ("right to left").  To
31301   correct for this, we must subtract each element of the permute
31302   control vector from 31.
31303
31304   For example, suppose we want to concatenate vr10 = {0, 1, 2, 3}
31305   with vr11 = {4, 5, 6, 7} and extract {0, 2, 4, 6} using a vperm.
31306   We place {0,1,2,3,8,9,10,11,16,17,18,19,24,25,26,27} in vr12 to
31307   serve as the permute control vector.  Then, in BE mode,
31308
31309     vperm 9,10,11,12
31310
31311   places the desired result in vr9.  However, in LE mode the
31312   vector contents will be
31313
31314     vr10 = 00000003 00000002 00000001 00000000
31315     vr11 = 00000007 00000006 00000005 00000004
31316
31317   The result of the vperm using the same permute control vector is
31318
31319     vr9  = 05000000 07000000 01000000 03000000
31320
31321   That is, the leftmost 4 bytes of vr10 are interpreted as the
31322   source for the rightmost 4 bytes of vr9, and so on.
31323
31324   If we change the permute control vector to
31325
31326     vr12 = {31,20,29,28,23,22,21,20,15,14,13,12,7,6,5,4}
31327
31328   and issue
31329
31330     vperm 9,11,10,12
31331
31332   we get the desired
31333
31334   vr9  = 00000006 00000004 00000002 00000000.  */
31335
31336void
31337altivec_expand_vec_perm_const_le (rtx operands[4])
31338{
31339  unsigned int i;
31340  rtx perm[16];
31341  rtx constv, unspec;
31342  rtx target = operands[0];
31343  rtx op0 = operands[1];
31344  rtx op1 = operands[2];
31345  rtx sel = operands[3];
31346
31347  /* Unpack and adjust the constant selector.  */
31348  for (i = 0; i < 16; ++i)
31349    {
31350      rtx e = XVECEXP (sel, 0, i);
31351      unsigned int elt = 31 - (INTVAL (e) & 31);
31352      perm[i] = GEN_INT (elt);
31353    }
31354
31355  /* Expand to a permute, swapping the inputs and using the
31356     adjusted selector.  */
31357  if (!REG_P (op0))
31358    op0 = force_reg (V16QImode, op0);
31359  if (!REG_P (op1))
31360    op1 = force_reg (V16QImode, op1);
31361
31362  constv = gen_rtx_CONST_VECTOR (V16QImode, gen_rtvec_v (16, perm));
31363  constv = force_reg (V16QImode, constv);
31364  unspec = gen_rtx_UNSPEC (V16QImode, gen_rtvec (3, op1, op0, constv),
31365			   UNSPEC_VPERM);
31366  if (!REG_P (target))
31367    {
31368      rtx tmp = gen_reg_rtx (V16QImode);
31369      emit_move_insn (tmp, unspec);
31370      unspec = tmp;
31371    }
31372
31373  emit_move_insn (target, unspec);
31374}
31375
31376/* Similarly to altivec_expand_vec_perm_const_le, we must adjust the
31377   permute control vector.  But here it's not a constant, so we must
31378   generate a vector NAND or NOR to do the adjustment.  */
31379
31380void
31381altivec_expand_vec_perm_le (rtx operands[4])
31382{
31383  rtx notx, iorx, unspec;
31384  rtx target = operands[0];
31385  rtx op0 = operands[1];
31386  rtx op1 = operands[2];
31387  rtx sel = operands[3];
31388  rtx tmp = target;
31389  rtx norreg = gen_reg_rtx (V16QImode);
31390  machine_mode mode = GET_MODE (target);
31391
31392  /* Get everything in regs so the pattern matches.  */
31393  if (!REG_P (op0))
31394    op0 = force_reg (mode, op0);
31395  if (!REG_P (op1))
31396    op1 = force_reg (mode, op1);
31397  if (!REG_P (sel))
31398    sel = force_reg (V16QImode, sel);
31399  if (!REG_P (target))
31400    tmp = gen_reg_rtx (mode);
31401
31402  /* Invert the selector with a VNAND if available, else a VNOR.
31403     The VNAND is preferred for future fusion opportunities.  */
31404  notx = gen_rtx_NOT (V16QImode, sel);
31405  iorx = (TARGET_P8_VECTOR
31406	  ? gen_rtx_IOR (V16QImode, notx, notx)
31407	  : gen_rtx_AND (V16QImode, notx, notx));
31408  emit_insn (gen_rtx_SET (VOIDmode, norreg, iorx));
31409
31410  /* Permute with operands reversed and adjusted selector.  */
31411  unspec = gen_rtx_UNSPEC (mode, gen_rtvec (3, op1, op0, norreg),
31412			   UNSPEC_VPERM);
31413
31414  /* Copy into target, possibly by way of a register.  */
31415  if (!REG_P (target))
31416    {
31417      emit_move_insn (tmp, unspec);
31418      unspec = tmp;
31419    }
31420
31421  emit_move_insn (target, unspec);
31422}
31423
31424/* Expand an Altivec constant permutation.  Return true if we match
31425   an efficient implementation; false to fall back to VPERM.  */
31426
31427bool
31428altivec_expand_vec_perm_const (rtx operands[4])
31429{
31430  struct altivec_perm_insn {
31431    HOST_WIDE_INT mask;
31432    enum insn_code impl;
31433    unsigned char perm[16];
31434  };
31435  static const struct altivec_perm_insn patterns[] = {
31436    { OPTION_MASK_ALTIVEC, CODE_FOR_altivec_vpkuhum_direct,
31437      {  1,  3,  5,  7,  9, 11, 13, 15, 17, 19, 21, 23, 25, 27, 29, 31 } },
31438    { OPTION_MASK_ALTIVEC, CODE_FOR_altivec_vpkuwum_direct,
31439      {  2,  3,  6,  7, 10, 11, 14, 15, 18, 19, 22, 23, 26, 27, 30, 31 } },
31440    { OPTION_MASK_ALTIVEC,
31441      (BYTES_BIG_ENDIAN ? CODE_FOR_altivec_vmrghb_direct
31442       : CODE_FOR_altivec_vmrglb_direct),
31443      {  0, 16,  1, 17,  2, 18,  3, 19,  4, 20,  5, 21,  6, 22,  7, 23 } },
31444    { OPTION_MASK_ALTIVEC,
31445      (BYTES_BIG_ENDIAN ? CODE_FOR_altivec_vmrghh_direct
31446       : CODE_FOR_altivec_vmrglh_direct),
31447      {  0,  1, 16, 17,  2,  3, 18, 19,  4,  5, 20, 21,  6,  7, 22, 23 } },
31448    { OPTION_MASK_ALTIVEC,
31449      (BYTES_BIG_ENDIAN ? CODE_FOR_altivec_vmrghw_direct
31450       : CODE_FOR_altivec_vmrglw_direct),
31451      {  0,  1,  2,  3, 16, 17, 18, 19,  4,  5,  6,  7, 20, 21, 22, 23 } },
31452    { OPTION_MASK_ALTIVEC,
31453      (BYTES_BIG_ENDIAN ? CODE_FOR_altivec_vmrglb_direct
31454       : CODE_FOR_altivec_vmrghb_direct),
31455      {  8, 24,  9, 25, 10, 26, 11, 27, 12, 28, 13, 29, 14, 30, 15, 31 } },
31456    { OPTION_MASK_ALTIVEC,
31457      (BYTES_BIG_ENDIAN ? CODE_FOR_altivec_vmrglh_direct
31458       : CODE_FOR_altivec_vmrghh_direct),
31459      {  8,  9, 24, 25, 10, 11, 26, 27, 12, 13, 28, 29, 14, 15, 30, 31 } },
31460    { OPTION_MASK_ALTIVEC,
31461      (BYTES_BIG_ENDIAN ? CODE_FOR_altivec_vmrglw_direct
31462       : CODE_FOR_altivec_vmrghw_direct),
31463      {  8,  9, 10, 11, 24, 25, 26, 27, 12, 13, 14, 15, 28, 29, 30, 31 } },
31464    { OPTION_MASK_P8_VECTOR, CODE_FOR_p8_vmrgew,
31465      {  0,  1,  2,  3, 16, 17, 18, 19,  8,  9, 10, 11, 24, 25, 26, 27 } },
31466    { OPTION_MASK_P8_VECTOR, CODE_FOR_p8_vmrgow,
31467      {  4,  5,  6,  7, 20, 21, 22, 23, 12, 13, 14, 15, 28, 29, 30, 31 } }
31468  };
31469
31470  unsigned int i, j, elt, which;
31471  unsigned char perm[16];
31472  rtx target, op0, op1, sel, x;
31473  bool one_vec;
31474
31475  target = operands[0];
31476  op0 = operands[1];
31477  op1 = operands[2];
31478  sel = operands[3];
31479
31480  /* Unpack the constant selector.  */
31481  for (i = which = 0; i < 16; ++i)
31482    {
31483      rtx e = XVECEXP (sel, 0, i);
31484      elt = INTVAL (e) & 31;
31485      which |= (elt < 16 ? 1 : 2);
31486      perm[i] = elt;
31487    }
31488
31489  /* Simplify the constant selector based on operands.  */
31490  switch (which)
31491    {
31492    default:
31493      gcc_unreachable ();
31494
31495    case 3:
31496      one_vec = false;
31497      if (!rtx_equal_p (op0, op1))
31498	break;
31499      /* FALLTHRU */
31500
31501    case 2:
31502      for (i = 0; i < 16; ++i)
31503	perm[i] &= 15;
31504      op0 = op1;
31505      one_vec = true;
31506      break;
31507
31508    case 1:
31509      op1 = op0;
31510      one_vec = true;
31511      break;
31512    }
31513
31514  /* Look for splat patterns.  */
31515  if (one_vec)
31516    {
31517      elt = perm[0];
31518
31519      for (i = 0; i < 16; ++i)
31520	if (perm[i] != elt)
31521	  break;
31522      if (i == 16)
31523	{
31524          if (!BYTES_BIG_ENDIAN)
31525            elt = 15 - elt;
31526	  emit_insn (gen_altivec_vspltb_direct (target, op0, GEN_INT (elt)));
31527	  return true;
31528	}
31529
31530      if (elt % 2 == 0)
31531	{
31532	  for (i = 0; i < 16; i += 2)
31533	    if (perm[i] != elt || perm[i + 1] != elt + 1)
31534	      break;
31535	  if (i == 16)
31536	    {
31537	      int field = BYTES_BIG_ENDIAN ? elt / 2 : 7 - elt / 2;
31538	      x = gen_reg_rtx (V8HImode);
31539	      emit_insn (gen_altivec_vsplth_direct (x, gen_lowpart (V8HImode, op0),
31540						    GEN_INT (field)));
31541	      emit_move_insn (target, gen_lowpart (V16QImode, x));
31542	      return true;
31543	    }
31544	}
31545
31546      if (elt % 4 == 0)
31547	{
31548	  for (i = 0; i < 16; i += 4)
31549	    if (perm[i] != elt
31550		|| perm[i + 1] != elt + 1
31551		|| perm[i + 2] != elt + 2
31552		|| perm[i + 3] != elt + 3)
31553	      break;
31554	  if (i == 16)
31555	    {
31556	      int field = BYTES_BIG_ENDIAN ? elt / 4 : 3 - elt / 4;
31557	      x = gen_reg_rtx (V4SImode);
31558	      emit_insn (gen_altivec_vspltw_direct (x, gen_lowpart (V4SImode, op0),
31559						    GEN_INT (field)));
31560	      emit_move_insn (target, gen_lowpart (V16QImode, x));
31561	      return true;
31562	    }
31563	}
31564    }
31565
31566  /* Look for merge and pack patterns.  */
31567  for (j = 0; j < ARRAY_SIZE (patterns); ++j)
31568    {
31569      bool swapped;
31570
31571      if ((patterns[j].mask & rs6000_isa_flags) == 0)
31572	continue;
31573
31574      elt = patterns[j].perm[0];
31575      if (perm[0] == elt)
31576	swapped = false;
31577      else if (perm[0] == elt + 16)
31578	swapped = true;
31579      else
31580	continue;
31581      for (i = 1; i < 16; ++i)
31582	{
31583	  elt = patterns[j].perm[i];
31584	  if (swapped)
31585	    elt = (elt >= 16 ? elt - 16 : elt + 16);
31586	  else if (one_vec && elt >= 16)
31587	    elt -= 16;
31588	  if (perm[i] != elt)
31589	    break;
31590	}
31591      if (i == 16)
31592	{
31593	  enum insn_code icode = patterns[j].impl;
31594	  machine_mode omode = insn_data[icode].operand[0].mode;
31595	  machine_mode imode = insn_data[icode].operand[1].mode;
31596
31597	  /* For little-endian, don't use vpkuwum and vpkuhum if the
31598	     underlying vector type is not V4SI and V8HI, respectively.
31599	     For example, using vpkuwum with a V8HI picks up the even
31600	     halfwords (BE numbering) when the even halfwords (LE
31601	     numbering) are what we need.  */
31602	  if (!BYTES_BIG_ENDIAN
31603	      && icode == CODE_FOR_altivec_vpkuwum_direct
31604	      && ((GET_CODE (op0) == REG
31605		   && GET_MODE (op0) != V4SImode)
31606		  || (GET_CODE (op0) == SUBREG
31607		      && GET_MODE (XEXP (op0, 0)) != V4SImode)))
31608	    continue;
31609	  if (!BYTES_BIG_ENDIAN
31610	      && icode == CODE_FOR_altivec_vpkuhum_direct
31611	      && ((GET_CODE (op0) == REG
31612		   && GET_MODE (op0) != V8HImode)
31613		  || (GET_CODE (op0) == SUBREG
31614		      && GET_MODE (XEXP (op0, 0)) != V8HImode)))
31615	    continue;
31616
31617          /* For little-endian, the two input operands must be swapped
31618             (or swapped back) to ensure proper right-to-left numbering
31619             from 0 to 2N-1.  */
31620	  if (swapped ^ !BYTES_BIG_ENDIAN)
31621	    std::swap (op0, op1);
31622	  if (imode != V16QImode)
31623	    {
31624	      op0 = gen_lowpart (imode, op0);
31625	      op1 = gen_lowpart (imode, op1);
31626	    }
31627	  if (omode == V16QImode)
31628	    x = target;
31629	  else
31630	    x = gen_reg_rtx (omode);
31631	  emit_insn (GEN_FCN (icode) (x, op0, op1));
31632	  if (omode != V16QImode)
31633	    emit_move_insn (target, gen_lowpart (V16QImode, x));
31634	  return true;
31635	}
31636    }
31637
31638  if (!BYTES_BIG_ENDIAN)
31639    {
31640      altivec_expand_vec_perm_const_le (operands);
31641      return true;
31642    }
31643
31644  return false;
31645}
31646
31647/* Expand a Paired Single, VSX Permute Doubleword, or SPE constant permutation.
31648   Return true if we match an efficient implementation.  */
31649
31650static bool
31651rs6000_expand_vec_perm_const_1 (rtx target, rtx op0, rtx op1,
31652				unsigned char perm0, unsigned char perm1)
31653{
31654  rtx x;
31655
31656  /* If both selectors come from the same operand, fold to single op.  */
31657  if ((perm0 & 2) == (perm1 & 2))
31658    {
31659      if (perm0 & 2)
31660	op0 = op1;
31661      else
31662	op1 = op0;
31663    }
31664  /* If both operands are equal, fold to simpler permutation.  */
31665  if (rtx_equal_p (op0, op1))
31666    {
31667      perm0 = perm0 & 1;
31668      perm1 = (perm1 & 1) + 2;
31669    }
31670  /* If the first selector comes from the second operand, swap.  */
31671  else if (perm0 & 2)
31672    {
31673      if (perm1 & 2)
31674	return false;
31675      perm0 -= 2;
31676      perm1 += 2;
31677      std::swap (op0, op1);
31678    }
31679  /* If the second selector does not come from the second operand, fail.  */
31680  else if ((perm1 & 2) == 0)
31681    return false;
31682
31683  /* Success! */
31684  if (target != NULL)
31685    {
31686      machine_mode vmode, dmode;
31687      rtvec v;
31688
31689      vmode = GET_MODE (target);
31690      gcc_assert (GET_MODE_NUNITS (vmode) == 2);
31691      dmode = mode_for_vector (GET_MODE_INNER (vmode), 4);
31692      x = gen_rtx_VEC_CONCAT (dmode, op0, op1);
31693      v = gen_rtvec (2, GEN_INT (perm0), GEN_INT (perm1));
31694      x = gen_rtx_VEC_SELECT (vmode, x, gen_rtx_PARALLEL (VOIDmode, v));
31695      emit_insn (gen_rtx_SET (VOIDmode, target, x));
31696    }
31697  return true;
31698}
31699
31700bool
31701rs6000_expand_vec_perm_const (rtx operands[4])
31702{
31703  rtx target, op0, op1, sel;
31704  unsigned char perm0, perm1;
31705
31706  target = operands[0];
31707  op0 = operands[1];
31708  op1 = operands[2];
31709  sel = operands[3];
31710
31711  /* Unpack the constant selector.  */
31712  perm0 = INTVAL (XVECEXP (sel, 0, 0)) & 3;
31713  perm1 = INTVAL (XVECEXP (sel, 0, 1)) & 3;
31714
31715  return rs6000_expand_vec_perm_const_1 (target, op0, op1, perm0, perm1);
31716}
31717
31718/* Test whether a constant permutation is supported.  */
31719
31720static bool
31721rs6000_vectorize_vec_perm_const_ok (machine_mode vmode,
31722				    const unsigned char *sel)
31723{
31724  /* AltiVec (and thus VSX) can handle arbitrary permutations.  */
31725  if (TARGET_ALTIVEC)
31726    return true;
31727
31728  /* Check for ps_merge* or evmerge* insns.  */
31729  if ((TARGET_PAIRED_FLOAT && vmode == V2SFmode)
31730      || (TARGET_SPE && vmode == V2SImode))
31731    {
31732      rtx op0 = gen_raw_REG (vmode, LAST_VIRTUAL_REGISTER + 1);
31733      rtx op1 = gen_raw_REG (vmode, LAST_VIRTUAL_REGISTER + 2);
31734      return rs6000_expand_vec_perm_const_1 (NULL, op0, op1, sel[0], sel[1]);
31735    }
31736
31737  return false;
31738}
31739
31740/* A subroutine for rs6000_expand_extract_even & rs6000_expand_interleave.  */
31741
31742static void
31743rs6000_do_expand_vec_perm (rtx target, rtx op0, rtx op1,
31744			   machine_mode vmode, unsigned nelt, rtx perm[])
31745{
31746  machine_mode imode;
31747  rtx x;
31748
31749  imode = vmode;
31750  if (GET_MODE_CLASS (vmode) != MODE_VECTOR_INT)
31751    {
31752      imode = GET_MODE_INNER (vmode);
31753      imode = mode_for_size (GET_MODE_BITSIZE (imode), MODE_INT, 0);
31754      imode = mode_for_vector (imode, nelt);
31755    }
31756
31757  x = gen_rtx_CONST_VECTOR (imode, gen_rtvec_v (nelt, perm));
31758  x = expand_vec_perm (vmode, op0, op1, x, target);
31759  if (x != target)
31760    emit_move_insn (target, x);
31761}
31762
31763/* Expand an extract even operation.  */
31764
31765void
31766rs6000_expand_extract_even (rtx target, rtx op0, rtx op1)
31767{
31768  machine_mode vmode = GET_MODE (target);
31769  unsigned i, nelt = GET_MODE_NUNITS (vmode);
31770  rtx perm[16];
31771
31772  for (i = 0; i < nelt; i++)
31773    perm[i] = GEN_INT (i * 2);
31774
31775  rs6000_do_expand_vec_perm (target, op0, op1, vmode, nelt, perm);
31776}
31777
31778/* Expand a vector interleave operation.  */
31779
31780void
31781rs6000_expand_interleave (rtx target, rtx op0, rtx op1, bool highp)
31782{
31783  machine_mode vmode = GET_MODE (target);
31784  unsigned i, high, nelt = GET_MODE_NUNITS (vmode);
31785  rtx perm[16];
31786
31787  high = (highp ? 0 : nelt / 2);
31788  for (i = 0; i < nelt / 2; i++)
31789    {
31790      perm[i * 2] = GEN_INT (i + high);
31791      perm[i * 2 + 1] = GEN_INT (i + nelt + high);
31792    }
31793
31794  rs6000_do_expand_vec_perm (target, op0, op1, vmode, nelt, perm);
31795}
31796
31797/* Scale a V2DF vector SRC by two to the SCALE and place in TGT.  */
31798void
31799rs6000_scale_v2df (rtx tgt, rtx src, int scale)
31800{
31801  HOST_WIDE_INT hwi_scale (scale);
31802  REAL_VALUE_TYPE r_pow;
31803  rtvec v = rtvec_alloc (2);
31804  rtx elt;
31805  rtx scale_vec = gen_reg_rtx (V2DFmode);
31806  (void)real_powi (&r_pow, DFmode, &dconst2, hwi_scale);
31807  elt = CONST_DOUBLE_FROM_REAL_VALUE (r_pow, DFmode);
31808  RTVEC_ELT (v, 0) = elt;
31809  RTVEC_ELT (v, 1) = elt;
31810  rs6000_expand_vector_init (scale_vec, gen_rtx_PARALLEL (V2DFmode, v));
31811  emit_insn (gen_mulv2df3 (tgt, src, scale_vec));
31812}
31813
31814/* Return an RTX representing where to find the function value of a
31815   function returning MODE.  */
31816static rtx
31817rs6000_complex_function_value (machine_mode mode)
31818{
31819  unsigned int regno;
31820  rtx r1, r2;
31821  machine_mode inner = GET_MODE_INNER (mode);
31822  unsigned int inner_bytes = GET_MODE_SIZE (inner);
31823
31824  if (FLOAT_MODE_P (mode) && TARGET_HARD_FLOAT && TARGET_FPRS)
31825    regno = FP_ARG_RETURN;
31826  else
31827    {
31828      regno = GP_ARG_RETURN;
31829
31830      /* 32-bit is OK since it'll go in r3/r4.  */
31831      if (TARGET_32BIT && inner_bytes >= 4)
31832	return gen_rtx_REG (mode, regno);
31833    }
31834
31835  if (inner_bytes >= 8)
31836    return gen_rtx_REG (mode, regno);
31837
31838  r1 = gen_rtx_EXPR_LIST (inner, gen_rtx_REG (inner, regno),
31839			  const0_rtx);
31840  r2 = gen_rtx_EXPR_LIST (inner, gen_rtx_REG (inner, regno + 1),
31841			  GEN_INT (inner_bytes));
31842  return gen_rtx_PARALLEL (mode, gen_rtvec (2, r1, r2));
31843}
31844
31845/* Return an rtx describing a return value of MODE as a PARALLEL
31846   in N_ELTS registers, each of mode ELT_MODE, starting at REGNO,
31847   stride REG_STRIDE.  */
31848
31849static rtx
31850rs6000_parallel_return (machine_mode mode,
31851			int n_elts, machine_mode elt_mode,
31852			unsigned int regno, unsigned int reg_stride)
31853{
31854  rtx par = gen_rtx_PARALLEL (mode, rtvec_alloc (n_elts));
31855
31856  int i;
31857  for (i = 0; i < n_elts; i++)
31858    {
31859      rtx r = gen_rtx_REG (elt_mode, regno);
31860      rtx off = GEN_INT (i * GET_MODE_SIZE (elt_mode));
31861      XVECEXP (par, 0, i) = gen_rtx_EXPR_LIST (VOIDmode, r, off);
31862      regno += reg_stride;
31863    }
31864
31865  return par;
31866}
31867
31868/* Target hook for TARGET_FUNCTION_VALUE.
31869
31870   On the SPE, both FPs and vectors are returned in r3.
31871
31872   On RS/6000 an integer value is in r3 and a floating-point value is in
31873   fp1, unless -msoft-float.  */
31874
31875static rtx
31876rs6000_function_value (const_tree valtype,
31877		       const_tree fn_decl_or_type ATTRIBUTE_UNUSED,
31878		       bool outgoing ATTRIBUTE_UNUSED)
31879{
31880  machine_mode mode;
31881  unsigned int regno;
31882  machine_mode elt_mode;
31883  int n_elts;
31884
31885  /* Special handling for structs in darwin64.  */
31886  if (TARGET_MACHO
31887      && rs6000_darwin64_struct_check_p (TYPE_MODE (valtype), valtype))
31888    {
31889      CUMULATIVE_ARGS valcum;
31890      rtx valret;
31891
31892      valcum.words = 0;
31893      valcum.fregno = FP_ARG_MIN_REG;
31894      valcum.vregno = ALTIVEC_ARG_MIN_REG;
31895      /* Do a trial code generation as if this were going to be passed as
31896	 an argument; if any part goes in memory, we return NULL.  */
31897      valret = rs6000_darwin64_record_arg (&valcum, valtype, true, /* retval= */ true);
31898      if (valret)
31899	return valret;
31900      /* Otherwise fall through to standard ABI rules.  */
31901    }
31902
31903  mode = TYPE_MODE (valtype);
31904
31905  /* The ELFv2 ABI returns homogeneous VFP aggregates in registers.  */
31906  if (rs6000_discover_homogeneous_aggregate (mode, valtype, &elt_mode, &n_elts))
31907    {
31908      int first_reg, n_regs;
31909
31910      if (SCALAR_FLOAT_MODE_P (elt_mode))
31911	{
31912	  /* _Decimal128 must use even/odd register pairs.  */
31913	  first_reg = (elt_mode == TDmode) ? FP_ARG_RETURN + 1 : FP_ARG_RETURN;
31914	  n_regs = (GET_MODE_SIZE (elt_mode) + 7) >> 3;
31915	}
31916      else
31917	{
31918	  first_reg = ALTIVEC_ARG_RETURN;
31919	  n_regs = 1;
31920	}
31921
31922      return rs6000_parallel_return (mode, n_elts, elt_mode, first_reg, n_regs);
31923    }
31924
31925  /* Some return value types need be split in -mpowerpc64, 32bit ABI.  */
31926  if (TARGET_32BIT && TARGET_POWERPC64)
31927    switch (mode)
31928      {
31929      default:
31930	break;
31931      case DImode:
31932      case SCmode:
31933      case DCmode:
31934      case TCmode:
31935	int count = GET_MODE_SIZE (mode) / 4;
31936	return rs6000_parallel_return (mode, count, SImode, GP_ARG_RETURN, 1);
31937      }
31938
31939  if ((INTEGRAL_TYPE_P (valtype)
31940       && GET_MODE_BITSIZE (mode) < (TARGET_32BIT ? 32 : 64))
31941      || POINTER_TYPE_P (valtype))
31942    mode = TARGET_32BIT ? SImode : DImode;
31943
31944  if (DECIMAL_FLOAT_MODE_P (mode) && TARGET_HARD_FLOAT && TARGET_FPRS)
31945    /* _Decimal128 must use an even/odd register pair.  */
31946    regno = (mode == TDmode) ? FP_ARG_RETURN + 1 : FP_ARG_RETURN;
31947  else if (SCALAR_FLOAT_TYPE_P (valtype) && TARGET_HARD_FLOAT && TARGET_FPRS
31948	   && ((TARGET_SINGLE_FLOAT && (mode == SFmode)) || TARGET_DOUBLE_FLOAT))
31949    regno = FP_ARG_RETURN;
31950  else if (TREE_CODE (valtype) == COMPLEX_TYPE
31951	   && targetm.calls.split_complex_arg)
31952    return rs6000_complex_function_value (mode);
31953  /* VSX is a superset of Altivec and adds V2DImode/V2DFmode.  Since the same
31954     return register is used in both cases, and we won't see V2DImode/V2DFmode
31955     for pure altivec, combine the two cases.  */
31956  else if (TREE_CODE (valtype) == VECTOR_TYPE
31957	   && TARGET_ALTIVEC && TARGET_ALTIVEC_ABI
31958	   && ALTIVEC_OR_VSX_VECTOR_MODE (mode))
31959    regno = ALTIVEC_ARG_RETURN;
31960  else if (TARGET_E500_DOUBLE && TARGET_HARD_FLOAT
31961	   && (mode == DFmode || mode == DCmode
31962	       || mode == TFmode || mode == TCmode))
31963    return spe_build_register_parallel (mode, GP_ARG_RETURN);
31964  else
31965    regno = GP_ARG_RETURN;
31966
31967  return gen_rtx_REG (mode, regno);
31968}
31969
31970/* Define how to find the value returned by a library function
31971   assuming the value has mode MODE.  */
31972rtx
31973rs6000_libcall_value (machine_mode mode)
31974{
31975  unsigned int regno;
31976
31977  /* Long long return value need be split in -mpowerpc64, 32bit ABI.  */
31978  if (TARGET_32BIT && TARGET_POWERPC64 && mode == DImode)
31979    return rs6000_parallel_return (mode, 2, SImode, GP_ARG_RETURN, 1);
31980
31981  if (DECIMAL_FLOAT_MODE_P (mode) && TARGET_HARD_FLOAT && TARGET_FPRS)
31982    /* _Decimal128 must use an even/odd register pair.  */
31983    regno = (mode == TDmode) ? FP_ARG_RETURN + 1 : FP_ARG_RETURN;
31984  else if (SCALAR_FLOAT_MODE_P (mode)
31985	   && TARGET_HARD_FLOAT && TARGET_FPRS
31986           && ((TARGET_SINGLE_FLOAT && mode == SFmode) || TARGET_DOUBLE_FLOAT))
31987    regno = FP_ARG_RETURN;
31988  /* VSX is a superset of Altivec and adds V2DImode/V2DFmode.  Since the same
31989     return register is used in both cases, and we won't see V2DImode/V2DFmode
31990     for pure altivec, combine the two cases.  */
31991  else if (ALTIVEC_OR_VSX_VECTOR_MODE (mode)
31992	   && TARGET_ALTIVEC && TARGET_ALTIVEC_ABI)
31993    regno = ALTIVEC_ARG_RETURN;
31994  else if (COMPLEX_MODE_P (mode) && targetm.calls.split_complex_arg)
31995    return rs6000_complex_function_value (mode);
31996  else if (TARGET_E500_DOUBLE && TARGET_HARD_FLOAT
31997	   && (mode == DFmode || mode == DCmode
31998	       || mode == TFmode || mode == TCmode))
31999    return spe_build_register_parallel (mode, GP_ARG_RETURN);
32000  else
32001    regno = GP_ARG_RETURN;
32002
32003  return gen_rtx_REG (mode, regno);
32004}
32005
32006
32007/* Return true if we use LRA instead of reload pass.  */
32008static bool
32009rs6000_lra_p (void)
32010{
32011  return rs6000_lra_flag;
32012}
32013
32014/* Given FROM and TO register numbers, say whether this elimination is allowed.
32015   Frame pointer elimination is automatically handled.
32016
32017   For the RS/6000, if frame pointer elimination is being done, we would like
32018   to convert ap into fp, not sp.
32019
32020   We need r30 if -mminimal-toc was specified, and there are constant pool
32021   references.  */
32022
32023static bool
32024rs6000_can_eliminate (const int from, const int to)
32025{
32026  return (from == ARG_POINTER_REGNUM && to == STACK_POINTER_REGNUM
32027          ? ! frame_pointer_needed
32028          : from == RS6000_PIC_OFFSET_TABLE_REGNUM
32029            ? ! TARGET_MINIMAL_TOC || TARGET_NO_TOC || get_pool_size () == 0
32030            : true);
32031}
32032
32033/* Define the offset between two registers, FROM to be eliminated and its
32034   replacement TO, at the start of a routine.  */
32035HOST_WIDE_INT
32036rs6000_initial_elimination_offset (int from, int to)
32037{
32038  rs6000_stack_t *info = rs6000_stack_info ();
32039  HOST_WIDE_INT offset;
32040
32041  if (from == HARD_FRAME_POINTER_REGNUM && to == STACK_POINTER_REGNUM)
32042    offset = info->push_p ? 0 : -info->total_size;
32043  else if (from == FRAME_POINTER_REGNUM && to == STACK_POINTER_REGNUM)
32044    {
32045      offset = info->push_p ? 0 : -info->total_size;
32046      if (FRAME_GROWS_DOWNWARD)
32047	offset += info->fixed_size + info->vars_size + info->parm_size;
32048    }
32049  else if (from == FRAME_POINTER_REGNUM && to == HARD_FRAME_POINTER_REGNUM)
32050    offset = FRAME_GROWS_DOWNWARD
32051	     ? info->fixed_size + info->vars_size + info->parm_size
32052	     : 0;
32053  else if (from == ARG_POINTER_REGNUM && to == HARD_FRAME_POINTER_REGNUM)
32054    offset = info->total_size;
32055  else if (from == ARG_POINTER_REGNUM && to == STACK_POINTER_REGNUM)
32056    offset = info->push_p ? info->total_size : 0;
32057  else if (from == RS6000_PIC_OFFSET_TABLE_REGNUM)
32058    offset = 0;
32059  else
32060    gcc_unreachable ();
32061
32062  return offset;
32063}
32064
32065static rtx
32066rs6000_dwarf_register_span (rtx reg)
32067{
32068  rtx parts[8];
32069  int i, words;
32070  unsigned regno = REGNO (reg);
32071  machine_mode mode = GET_MODE (reg);
32072
32073  if (TARGET_SPE
32074      && regno < 32
32075      && (SPE_VECTOR_MODE (GET_MODE (reg))
32076	  || (TARGET_E500_DOUBLE && FLOAT_MODE_P (mode)
32077	      && mode != SFmode && mode != SDmode && mode != SCmode)))
32078    ;
32079  else
32080    return NULL_RTX;
32081
32082  regno = REGNO (reg);
32083
32084  /* The duality of the SPE register size wreaks all kinds of havoc.
32085     This is a way of distinguishing r0 in 32-bits from r0 in
32086     64-bits.  */
32087  words = (GET_MODE_SIZE (mode) + UNITS_PER_FP_WORD - 1) / UNITS_PER_FP_WORD;
32088  gcc_assert (words <= 4);
32089  for (i = 0; i < words; i++, regno++)
32090    {
32091      if (BYTES_BIG_ENDIAN)
32092	{
32093	  parts[2 * i] = gen_rtx_REG (SImode, regno + FIRST_SPE_HIGH_REGNO);
32094	  parts[2 * i + 1] = gen_rtx_REG (SImode, regno);
32095	}
32096      else
32097	{
32098	  parts[2 * i] = gen_rtx_REG (SImode, regno);
32099	  parts[2 * i + 1] = gen_rtx_REG (SImode, regno + FIRST_SPE_HIGH_REGNO);
32100	}
32101    }
32102
32103  return gen_rtx_PARALLEL (VOIDmode, gen_rtvec_v (words * 2, parts));
32104}
32105
32106/* Fill in sizes for SPE register high parts in table used by unwinder.  */
32107
32108static void
32109rs6000_init_dwarf_reg_sizes_extra (tree address)
32110{
32111  if (TARGET_SPE)
32112    {
32113      int i;
32114      machine_mode mode = TYPE_MODE (char_type_node);
32115      rtx addr = expand_expr (address, NULL_RTX, VOIDmode, EXPAND_NORMAL);
32116      rtx mem = gen_rtx_MEM (BLKmode, addr);
32117      rtx value = gen_int_mode (4, mode);
32118
32119      for (i = FIRST_SPE_HIGH_REGNO; i < LAST_SPE_HIGH_REGNO+1; i++)
32120	{
32121	  int column = DWARF_REG_TO_UNWIND_COLUMN
32122		(DWARF2_FRAME_REG_OUT (DWARF_FRAME_REGNUM (i), true));
32123	  HOST_WIDE_INT offset = column * GET_MODE_SIZE (mode);
32124
32125	  emit_move_insn (adjust_address (mem, mode, offset), value);
32126	}
32127    }
32128
32129  if (TARGET_MACHO && ! TARGET_ALTIVEC)
32130    {
32131      int i;
32132      machine_mode mode = TYPE_MODE (char_type_node);
32133      rtx addr = expand_expr (address, NULL_RTX, VOIDmode, EXPAND_NORMAL);
32134      rtx mem = gen_rtx_MEM (BLKmode, addr);
32135      rtx value = gen_int_mode (16, mode);
32136
32137      /* On Darwin, libgcc may be built to run on both G3 and G4/5.
32138	 The unwinder still needs to know the size of Altivec registers.  */
32139
32140      for (i = FIRST_ALTIVEC_REGNO; i < LAST_ALTIVEC_REGNO+1; i++)
32141	{
32142	  int column = DWARF_REG_TO_UNWIND_COLUMN
32143		(DWARF2_FRAME_REG_OUT (DWARF_FRAME_REGNUM (i), true));
32144	  HOST_WIDE_INT offset = column * GET_MODE_SIZE (mode);
32145
32146	  emit_move_insn (adjust_address (mem, mode, offset), value);
32147	}
32148    }
32149}
32150
32151/* Map internal gcc register numbers to debug format register numbers.
32152   FORMAT specifies the type of debug register number to use:
32153     0 -- debug information, except for frame-related sections
32154     1 -- DWARF .debug_frame section
32155     2 -- DWARF .eh_frame section  */
32156
32157unsigned int
32158rs6000_dbx_register_number (unsigned int regno, unsigned int format)
32159{
32160  /* We never use the GCC internal number for SPE high registers.
32161     Those are mapped to the 1200..1231 range for all debug formats.  */
32162  if (SPE_HIGH_REGNO_P (regno))
32163    return regno - FIRST_SPE_HIGH_REGNO + 1200;
32164
32165  /* Except for the above, we use the internal number for non-DWARF
32166     debug information, and also for .eh_frame.  */
32167  if ((format == 0 && write_symbols != DWARF2_DEBUG) || format == 2)
32168    return regno;
32169
32170  /* On some platforms, we use the standard DWARF register
32171     numbering for .debug_info and .debug_frame.  */
32172#ifdef RS6000_USE_DWARF_NUMBERING
32173  if (regno <= 63)
32174    return regno;
32175  if (regno == LR_REGNO)
32176    return 108;
32177  if (regno == CTR_REGNO)
32178    return 109;
32179  /* Special handling for CR for .debug_frame: rs6000_emit_prologue has
32180     translated any combination of CR2, CR3, CR4 saves to a save of CR2.
32181     The actual code emitted saves the whole of CR, so we map CR2_REGNO
32182     to the DWARF reg for CR.  */
32183  if (format == 1 && regno == CR2_REGNO)
32184    return 64;
32185  if (CR_REGNO_P (regno))
32186    return regno - CR0_REGNO + 86;
32187  if (regno == CA_REGNO)
32188    return 101;  /* XER */
32189  if (ALTIVEC_REGNO_P (regno))
32190    return regno - FIRST_ALTIVEC_REGNO + 1124;
32191  if (regno == VRSAVE_REGNO)
32192    return 356;
32193  if (regno == VSCR_REGNO)
32194    return 67;
32195  if (regno == SPE_ACC_REGNO)
32196    return 99;
32197  if (regno == SPEFSCR_REGNO)
32198    return 612;
32199#endif
32200  return regno;
32201}
32202
32203/* target hook eh_return_filter_mode */
32204static machine_mode
32205rs6000_eh_return_filter_mode (void)
32206{
32207  return TARGET_32BIT ? SImode : word_mode;
32208}
32209
32210/* Target hook for scalar_mode_supported_p.  */
32211static bool
32212rs6000_scalar_mode_supported_p (machine_mode mode)
32213{
32214  /* -m32 does not support TImode.  This is the default, from
32215     default_scalar_mode_supported_p.  For -m32 -mpowerpc64 we want the
32216     same ABI as for -m32.  But default_scalar_mode_supported_p allows
32217     integer modes of precision 2 * BITS_PER_WORD, which matches TImode
32218     for -mpowerpc64.  */
32219  if (TARGET_32BIT && mode == TImode)
32220    return false;
32221
32222  if (DECIMAL_FLOAT_MODE_P (mode))
32223    return default_decimal_float_supported_p ();
32224  else
32225    return default_scalar_mode_supported_p (mode);
32226}
32227
32228/* Target hook for vector_mode_supported_p.  */
32229static bool
32230rs6000_vector_mode_supported_p (machine_mode mode)
32231{
32232
32233  if (TARGET_PAIRED_FLOAT && PAIRED_VECTOR_MODE (mode))
32234    return true;
32235
32236  if (TARGET_SPE && SPE_VECTOR_MODE (mode))
32237    return true;
32238
32239  else if (VECTOR_MEM_ALTIVEC_OR_VSX_P (mode))
32240    return true;
32241
32242  else
32243    return false;
32244}
32245
32246/* Target hook for invalid_arg_for_unprototyped_fn. */
32247static const char *
32248invalid_arg_for_unprototyped_fn (const_tree typelist, const_tree funcdecl, const_tree val)
32249{
32250  return (!rs6000_darwin64_abi
32251	  && typelist == 0
32252          && TREE_CODE (TREE_TYPE (val)) == VECTOR_TYPE
32253          && (funcdecl == NULL_TREE
32254              || (TREE_CODE (funcdecl) == FUNCTION_DECL
32255                  && DECL_BUILT_IN_CLASS (funcdecl) != BUILT_IN_MD)))
32256	  ? N_("AltiVec argument passed to unprototyped function")
32257	  : NULL;
32258}
32259
32260/* For TARGET_SECURE_PLT 32-bit PIC code we can save PIC register
32261   setup by using __stack_chk_fail_local hidden function instead of
32262   calling __stack_chk_fail directly.  Otherwise it is better to call
32263   __stack_chk_fail directly.  */
32264
32265static tree ATTRIBUTE_UNUSED
32266rs6000_stack_protect_fail (void)
32267{
32268  return (DEFAULT_ABI == ABI_V4 && TARGET_SECURE_PLT && flag_pic)
32269	 ? default_hidden_stack_protect_fail ()
32270	 : default_external_stack_protect_fail ();
32271}
32272
32273void
32274rs6000_final_prescan_insn (rtx_insn *insn, rtx *operand ATTRIBUTE_UNUSED,
32275			   int num_operands ATTRIBUTE_UNUSED)
32276{
32277  if (rs6000_warn_cell_microcode)
32278    {
32279      const char *temp;
32280      int insn_code_number = recog_memoized (insn);
32281      location_t location = INSN_LOCATION (insn);
32282
32283      /* Punt on insns we cannot recognize.  */
32284      if (insn_code_number < 0)
32285	return;
32286
32287      temp = get_insn_template (insn_code_number, insn);
32288
32289      if (get_attr_cell_micro (insn) == CELL_MICRO_ALWAYS)
32290	warning_at (location, OPT_mwarn_cell_microcode,
32291		    "emitting microcode insn %s\t[%s] #%d",
32292		    temp, insn_data[INSN_CODE (insn)].name, INSN_UID (insn));
32293      else if (get_attr_cell_micro (insn) == CELL_MICRO_CONDITIONAL)
32294	warning_at (location, OPT_mwarn_cell_microcode,
32295		    "emitting conditional microcode insn %s\t[%s] #%d",
32296		    temp, insn_data[INSN_CODE (insn)].name, INSN_UID (insn));
32297    }
32298}
32299
32300/* Implement the TARGET_ASAN_SHADOW_OFFSET hook.  */
32301
32302#if TARGET_ELF
32303static unsigned HOST_WIDE_INT
32304rs6000_asan_shadow_offset (void)
32305{
32306  return (unsigned HOST_WIDE_INT) 1 << (TARGET_64BIT ? 41 : 29);
32307}
32308#endif
32309
32310/* Mask options that we want to support inside of attribute((target)) and
32311   #pragma GCC target operations.  Note, we do not include things like
32312   64/32-bit, endianess, hard/soft floating point, etc. that would have
32313   different calling sequences.  */
32314
32315struct rs6000_opt_mask {
32316  const char *name;		/* option name */
32317  HOST_WIDE_INT mask;		/* mask to set */
32318  bool invert;			/* invert sense of mask */
32319  bool valid_target;		/* option is a target option */
32320};
32321
32322static struct rs6000_opt_mask const rs6000_opt_masks[] =
32323{
32324  { "altivec",			OPTION_MASK_ALTIVEC,		false, true  },
32325  { "cmpb",			OPTION_MASK_CMPB,		false, true  },
32326  { "crypto",			OPTION_MASK_CRYPTO,		false, true  },
32327  { "direct-move",		OPTION_MASK_DIRECT_MOVE,	false, true  },
32328  { "dlmzb",			OPTION_MASK_DLMZB,		false, true  },
32329  { "efficient-unaligned-vsx",	OPTION_MASK_EFFICIENT_UNALIGNED_VSX,
32330								false, true  },
32331  { "fprnd",			OPTION_MASK_FPRND,		false, true  },
32332  { "hard-dfp",			OPTION_MASK_DFP,		false, true  },
32333  { "htm",			OPTION_MASK_HTM,		false, true  },
32334  { "isel",			OPTION_MASK_ISEL,		false, true  },
32335  { "mfcrf",			OPTION_MASK_MFCRF,		false, true  },
32336  { "mfpgpr",			OPTION_MASK_MFPGPR,		false, true  },
32337  { "mulhw",			OPTION_MASK_MULHW,		false, true  },
32338  { "multiple",			OPTION_MASK_MULTIPLE,		false, true  },
32339  { "popcntb",			OPTION_MASK_POPCNTB,		false, true  },
32340  { "popcntd",			OPTION_MASK_POPCNTD,		false, true  },
32341  { "power8-fusion",		OPTION_MASK_P8_FUSION,		false, true  },
32342  { "power8-fusion-sign",	OPTION_MASK_P8_FUSION_SIGN,	false, true  },
32343  { "power8-vector",		OPTION_MASK_P8_VECTOR,		false, true  },
32344  { "powerpc-gfxopt",		OPTION_MASK_PPC_GFXOPT,		false, true  },
32345  { "powerpc-gpopt",		OPTION_MASK_PPC_GPOPT,		false, true  },
32346  { "quad-memory",		OPTION_MASK_QUAD_MEMORY,	false, true  },
32347  { "quad-memory-atomic",	OPTION_MASK_QUAD_MEMORY_ATOMIC,	false, true  },
32348  { "recip-precision",		OPTION_MASK_RECIP_PRECISION,	false, true  },
32349  { "save-toc-indirect",	OPTION_MASK_SAVE_TOC_INDIRECT,	false, true  },
32350  { "string",			OPTION_MASK_STRING,		false, true  },
32351  { "update",			OPTION_MASK_NO_UPDATE,		true , true  },
32352  { "upper-regs-df",		OPTION_MASK_UPPER_REGS_DF,	false, true  },
32353  { "upper-regs-sf",		OPTION_MASK_UPPER_REGS_SF,	false, true  },
32354  { "vsx",			OPTION_MASK_VSX,		false, true  },
32355  { "vsx-timode",		OPTION_MASK_VSX_TIMODE,		false, true  },
32356#ifdef OPTION_MASK_64BIT
32357#if TARGET_AIX_OS
32358  { "aix64",			OPTION_MASK_64BIT,		false, false },
32359  { "aix32",			OPTION_MASK_64BIT,		true,  false },
32360#else
32361  { "64",			OPTION_MASK_64BIT,		false, false },
32362  { "32",			OPTION_MASK_64BIT,		true,  false },
32363#endif
32364#endif
32365#ifdef OPTION_MASK_EABI
32366  { "eabi",			OPTION_MASK_EABI,		false, false },
32367#endif
32368#ifdef OPTION_MASK_LITTLE_ENDIAN
32369  { "little",			OPTION_MASK_LITTLE_ENDIAN,	false, false },
32370  { "big",			OPTION_MASK_LITTLE_ENDIAN,	true,  false },
32371#endif
32372#ifdef OPTION_MASK_RELOCATABLE
32373  { "relocatable",		OPTION_MASK_RELOCATABLE,	false, false },
32374#endif
32375#ifdef OPTION_MASK_STRICT_ALIGN
32376  { "strict-align",		OPTION_MASK_STRICT_ALIGN,	false, false },
32377#endif
32378  { "soft-float",		OPTION_MASK_SOFT_FLOAT,		false, false },
32379  { "string",			OPTION_MASK_STRING,		false, false },
32380};
32381
32382/* Builtin mask mapping for printing the flags.  */
32383static struct rs6000_opt_mask const rs6000_builtin_mask_names[] =
32384{
32385  { "altivec",		 RS6000_BTM_ALTIVEC,	false, false },
32386  { "vsx",		 RS6000_BTM_VSX,	false, false },
32387  { "spe",		 RS6000_BTM_SPE,	false, false },
32388  { "paired",		 RS6000_BTM_PAIRED,	false, false },
32389  { "fre",		 RS6000_BTM_FRE,	false, false },
32390  { "fres",		 RS6000_BTM_FRES,	false, false },
32391  { "frsqrte",		 RS6000_BTM_FRSQRTE,	false, false },
32392  { "frsqrtes",		 RS6000_BTM_FRSQRTES,	false, false },
32393  { "popcntd",		 RS6000_BTM_POPCNTD,	false, false },
32394  { "cell",		 RS6000_BTM_CELL,	false, false },
32395  { "power8-vector",	 RS6000_BTM_P8_VECTOR,	false, false },
32396  { "crypto",		 RS6000_BTM_CRYPTO,	false, false },
32397  { "htm",		 RS6000_BTM_HTM,	false, false },
32398  { "hard-dfp",		 RS6000_BTM_DFP,	false, false },
32399  { "hard-float",	 RS6000_BTM_HARD_FLOAT,	false, false },
32400  { "long-double-128",	 RS6000_BTM_LDBL128,	false, false },
32401};
32402
32403/* Option variables that we want to support inside attribute((target)) and
32404   #pragma GCC target operations.  */
32405
32406struct rs6000_opt_var {
32407  const char *name;		/* option name */
32408  size_t global_offset;		/* offset of the option in global_options.  */
32409  size_t target_offset;		/* offset of the option in target optiosn.  */
32410};
32411
32412static struct rs6000_opt_var const rs6000_opt_vars[] =
32413{
32414  { "friz",
32415    offsetof (struct gcc_options, x_TARGET_FRIZ),
32416    offsetof (struct cl_target_option, x_TARGET_FRIZ), },
32417  { "avoid-indexed-addresses",
32418    offsetof (struct gcc_options, x_TARGET_AVOID_XFORM),
32419    offsetof (struct cl_target_option, x_TARGET_AVOID_XFORM) },
32420  { "paired",
32421    offsetof (struct gcc_options, x_rs6000_paired_float),
32422    offsetof (struct cl_target_option, x_rs6000_paired_float), },
32423  { "longcall",
32424    offsetof (struct gcc_options, x_rs6000_default_long_calls),
32425    offsetof (struct cl_target_option, x_rs6000_default_long_calls), },
32426  { "optimize-swaps",
32427    offsetof (struct gcc_options, x_rs6000_optimize_swaps),
32428    offsetof (struct cl_target_option, x_rs6000_optimize_swaps), },
32429  { "allow-movmisalign",
32430    offsetof (struct gcc_options, x_TARGET_ALLOW_MOVMISALIGN),
32431    offsetof (struct cl_target_option, x_TARGET_ALLOW_MOVMISALIGN), },
32432  { "allow-df-permute",
32433    offsetof (struct gcc_options, x_TARGET_ALLOW_DF_PERMUTE),
32434    offsetof (struct cl_target_option, x_TARGET_ALLOW_DF_PERMUTE), },
32435  { "sched-groups",
32436    offsetof (struct gcc_options, x_TARGET_SCHED_GROUPS),
32437    offsetof (struct cl_target_option, x_TARGET_SCHED_GROUPS), },
32438  { "always-hint",
32439    offsetof (struct gcc_options, x_TARGET_ALWAYS_HINT),
32440    offsetof (struct cl_target_option, x_TARGET_ALWAYS_HINT), },
32441  { "align-branch-targets",
32442    offsetof (struct gcc_options, x_TARGET_ALIGN_BRANCH_TARGETS),
32443    offsetof (struct cl_target_option, x_TARGET_ALIGN_BRANCH_TARGETS), },
32444  { "vectorize-builtins",
32445    offsetof (struct gcc_options, x_TARGET_VECTORIZE_BUILTINS),
32446    offsetof (struct cl_target_option, x_TARGET_VECTORIZE_BUILTINS), },
32447  { "tls-markers",
32448    offsetof (struct gcc_options, x_tls_markers),
32449    offsetof (struct cl_target_option, x_tls_markers), },
32450  { "sched-prolog",
32451    offsetof (struct gcc_options, x_TARGET_SCHED_PROLOG),
32452    offsetof (struct cl_target_option, x_TARGET_SCHED_PROLOG), },
32453  { "sched-epilog",
32454    offsetof (struct gcc_options, x_TARGET_SCHED_PROLOG),
32455    offsetof (struct cl_target_option, x_TARGET_SCHED_PROLOG), },
32456  { "gen-cell-microcode",
32457    offsetof (struct gcc_options, x_rs6000_gen_cell_microcode),
32458    offsetof (struct cl_target_option, x_rs6000_gen_cell_microcode), },
32459  { "warn-cell-microcode",
32460    offsetof (struct gcc_options, x_rs6000_warn_cell_microcode),
32461    offsetof (struct cl_target_option, x_rs6000_warn_cell_microcode), },
32462};
32463
32464/* Inner function to handle attribute((target("..."))) and #pragma GCC target
32465   parsing.  Return true if there were no errors.  */
32466
32467static bool
32468rs6000_inner_target_options (tree args, bool attr_p)
32469{
32470  bool ret = true;
32471
32472  if (args == NULL_TREE)
32473    ;
32474
32475  else if (TREE_CODE (args) == STRING_CST)
32476    {
32477      char *p = ASTRDUP (TREE_STRING_POINTER (args));
32478      char *q;
32479
32480      while ((q = strtok (p, ",")) != NULL)
32481	{
32482	  bool error_p = false;
32483	  bool not_valid_p = false;
32484	  const char *cpu_opt = NULL;
32485
32486	  p = NULL;
32487	  if (strncmp (q, "cpu=", 4) == 0)
32488	    {
32489	      int cpu_index = rs6000_cpu_name_lookup (q+4);
32490	      if (cpu_index >= 0)
32491		rs6000_cpu_index = cpu_index;
32492	      else
32493		{
32494		  error_p = true;
32495		  cpu_opt = q+4;
32496		}
32497	    }
32498	  else if (strncmp (q, "tune=", 5) == 0)
32499	    {
32500	      int tune_index = rs6000_cpu_name_lookup (q+5);
32501	      if (tune_index >= 0)
32502		rs6000_tune_index = tune_index;
32503	      else
32504		{
32505		  error_p = true;
32506		  cpu_opt = q+5;
32507		}
32508	    }
32509	  else
32510	    {
32511	      size_t i;
32512	      bool invert = false;
32513	      char *r = q;
32514
32515	      error_p = true;
32516	      if (strncmp (r, "no-", 3) == 0)
32517		{
32518		  invert = true;
32519		  r += 3;
32520		}
32521
32522	      for (i = 0; i < ARRAY_SIZE (rs6000_opt_masks); i++)
32523		if (strcmp (r, rs6000_opt_masks[i].name) == 0)
32524		  {
32525		    HOST_WIDE_INT mask = rs6000_opt_masks[i].mask;
32526
32527		    if (!rs6000_opt_masks[i].valid_target)
32528		      not_valid_p = true;
32529		    else
32530		      {
32531			error_p = false;
32532			rs6000_isa_flags_explicit |= mask;
32533
32534			/* VSX needs altivec, so -mvsx automagically sets
32535			   altivec and disables -mavoid-indexed-addresses.  */
32536			if (!invert)
32537			  {
32538			    if (mask == OPTION_MASK_VSX)
32539			      {
32540				mask |= OPTION_MASK_ALTIVEC;
32541				TARGET_AVOID_XFORM = 0;
32542			      }
32543			  }
32544
32545			if (rs6000_opt_masks[i].invert)
32546			  invert = !invert;
32547
32548			if (invert)
32549			  rs6000_isa_flags &= ~mask;
32550			else
32551			  rs6000_isa_flags |= mask;
32552		      }
32553		    break;
32554		  }
32555
32556	      if (error_p && !not_valid_p)
32557		{
32558		  for (i = 0; i < ARRAY_SIZE (rs6000_opt_vars); i++)
32559		    if (strcmp (r, rs6000_opt_vars[i].name) == 0)
32560		      {
32561			size_t j = rs6000_opt_vars[i].global_offset;
32562			*((int *) ((char *)&global_options + j)) = !invert;
32563			error_p = false;
32564			not_valid_p = false;
32565			break;
32566		      }
32567		}
32568	    }
32569
32570	  if (error_p)
32571	    {
32572	      const char *eprefix, *esuffix;
32573
32574	      ret = false;
32575	      if (attr_p)
32576		{
32577		  eprefix = "__attribute__((__target__(";
32578		  esuffix = ")))";
32579		}
32580	      else
32581		{
32582		  eprefix = "#pragma GCC target ";
32583		  esuffix = "";
32584		}
32585
32586	      if (cpu_opt)
32587		error ("invalid cpu \"%s\" for %s\"%s\"%s", cpu_opt, eprefix,
32588		       q, esuffix);
32589	      else if (not_valid_p)
32590		error ("%s\"%s\"%s is not allowed", eprefix, q, esuffix);
32591	      else
32592		error ("%s\"%s\"%s is invalid", eprefix, q, esuffix);
32593	    }
32594	}
32595    }
32596
32597  else if (TREE_CODE (args) == TREE_LIST)
32598    {
32599      do
32600	{
32601	  tree value = TREE_VALUE (args);
32602	  if (value)
32603	    {
32604	      bool ret2 = rs6000_inner_target_options (value, attr_p);
32605	      if (!ret2)
32606		ret = false;
32607	    }
32608	  args = TREE_CHAIN (args);
32609	}
32610      while (args != NULL_TREE);
32611    }
32612
32613  else
32614    gcc_unreachable ();
32615
32616  return ret;
32617}
32618
32619/* Print out the target options as a list for -mdebug=target.  */
32620
32621static void
32622rs6000_debug_target_options (tree args, const char *prefix)
32623{
32624  if (args == NULL_TREE)
32625    fprintf (stderr, "%s<NULL>", prefix);
32626
32627  else if (TREE_CODE (args) == STRING_CST)
32628    {
32629      char *p = ASTRDUP (TREE_STRING_POINTER (args));
32630      char *q;
32631
32632      while ((q = strtok (p, ",")) != NULL)
32633	{
32634	  p = NULL;
32635	  fprintf (stderr, "%s\"%s\"", prefix, q);
32636	  prefix = ", ";
32637	}
32638    }
32639
32640  else if (TREE_CODE (args) == TREE_LIST)
32641    {
32642      do
32643	{
32644	  tree value = TREE_VALUE (args);
32645	  if (value)
32646	    {
32647	      rs6000_debug_target_options (value, prefix);
32648	      prefix = ", ";
32649	    }
32650	  args = TREE_CHAIN (args);
32651	}
32652      while (args != NULL_TREE);
32653    }
32654
32655  else
32656    gcc_unreachable ();
32657
32658  return;
32659}
32660
32661
32662/* Hook to validate attribute((target("..."))).  */
32663
32664static bool
32665rs6000_valid_attribute_p (tree fndecl,
32666			  tree ARG_UNUSED (name),
32667			  tree args,
32668			  int flags)
32669{
32670  struct cl_target_option cur_target;
32671  bool ret;
32672  tree old_optimize = build_optimization_node (&global_options);
32673  tree new_target, new_optimize;
32674  tree func_optimize = DECL_FUNCTION_SPECIFIC_OPTIMIZATION (fndecl);
32675
32676  gcc_assert ((fndecl != NULL_TREE) && (args != NULL_TREE));
32677
32678  if (TARGET_DEBUG_TARGET)
32679    {
32680      tree tname = DECL_NAME (fndecl);
32681      fprintf (stderr, "\n==================== rs6000_valid_attribute_p:\n");
32682      if (tname)
32683	fprintf (stderr, "function: %.*s\n",
32684		 (int) IDENTIFIER_LENGTH (tname),
32685		 IDENTIFIER_POINTER (tname));
32686      else
32687	fprintf (stderr, "function: unknown\n");
32688
32689      fprintf (stderr, "args:");
32690      rs6000_debug_target_options (args, " ");
32691      fprintf (stderr, "\n");
32692
32693      if (flags)
32694	fprintf (stderr, "flags: 0x%x\n", flags);
32695
32696      fprintf (stderr, "--------------------\n");
32697    }
32698
32699  old_optimize = build_optimization_node (&global_options);
32700  func_optimize = DECL_FUNCTION_SPECIFIC_OPTIMIZATION (fndecl);
32701
32702  /* If the function changed the optimization levels as well as setting target
32703     options, start with the optimizations specified.  */
32704  if (func_optimize && func_optimize != old_optimize)
32705    cl_optimization_restore (&global_options,
32706			     TREE_OPTIMIZATION (func_optimize));
32707
32708  /* The target attributes may also change some optimization flags, so update
32709     the optimization options if necessary.  */
32710  cl_target_option_save (&cur_target, &global_options);
32711  rs6000_cpu_index = rs6000_tune_index = -1;
32712  ret = rs6000_inner_target_options (args, true);
32713
32714  /* Set up any additional state.  */
32715  if (ret)
32716    {
32717      ret = rs6000_option_override_internal (false);
32718      new_target = build_target_option_node (&global_options);
32719    }
32720  else
32721    new_target = NULL;
32722
32723  new_optimize = build_optimization_node (&global_options);
32724
32725  if (!new_target)
32726    ret = false;
32727
32728  else if (fndecl)
32729    {
32730      DECL_FUNCTION_SPECIFIC_TARGET (fndecl) = new_target;
32731
32732      if (old_optimize != new_optimize)
32733	DECL_FUNCTION_SPECIFIC_OPTIMIZATION (fndecl) = new_optimize;
32734    }
32735
32736  cl_target_option_restore (&global_options, &cur_target);
32737
32738  if (old_optimize != new_optimize)
32739    cl_optimization_restore (&global_options,
32740			     TREE_OPTIMIZATION (old_optimize));
32741
32742  return ret;
32743}
32744
32745
32746/* Hook to validate the current #pragma GCC target and set the state, and
32747   update the macros based on what was changed.  If ARGS is NULL, then
32748   POP_TARGET is used to reset the options.  */
32749
32750bool
32751rs6000_pragma_target_parse (tree args, tree pop_target)
32752{
32753  tree prev_tree = build_target_option_node (&global_options);
32754  tree cur_tree;
32755  struct cl_target_option *prev_opt, *cur_opt;
32756  HOST_WIDE_INT prev_flags, cur_flags, diff_flags;
32757  HOST_WIDE_INT prev_bumask, cur_bumask, diff_bumask;
32758
32759  if (TARGET_DEBUG_TARGET)
32760    {
32761      fprintf (stderr, "\n==================== rs6000_pragma_target_parse\n");
32762      fprintf (stderr, "args:");
32763      rs6000_debug_target_options (args, " ");
32764      fprintf (stderr, "\n");
32765
32766      if (pop_target)
32767	{
32768	  fprintf (stderr, "pop_target:\n");
32769	  debug_tree (pop_target);
32770	}
32771      else
32772	fprintf (stderr, "pop_target: <NULL>\n");
32773
32774      fprintf (stderr, "--------------------\n");
32775    }
32776
32777  if (! args)
32778    {
32779      cur_tree = ((pop_target)
32780		  ? pop_target
32781		  : target_option_default_node);
32782      cl_target_option_restore (&global_options,
32783				TREE_TARGET_OPTION (cur_tree));
32784    }
32785  else
32786    {
32787      rs6000_cpu_index = rs6000_tune_index = -1;
32788      if (!rs6000_inner_target_options (args, false)
32789	  || !rs6000_option_override_internal (false)
32790	  || (cur_tree = build_target_option_node (&global_options))
32791	     == NULL_TREE)
32792	{
32793	  if (TARGET_DEBUG_BUILTIN || TARGET_DEBUG_TARGET)
32794	    fprintf (stderr, "invalid pragma\n");
32795
32796	  return false;
32797	}
32798    }
32799
32800  target_option_current_node = cur_tree;
32801
32802  /* If we have the preprocessor linked in (i.e. C or C++ languages), possibly
32803     change the macros that are defined.  */
32804  if (rs6000_target_modify_macros_ptr)
32805    {
32806      prev_opt    = TREE_TARGET_OPTION (prev_tree);
32807      prev_bumask = prev_opt->x_rs6000_builtin_mask;
32808      prev_flags  = prev_opt->x_rs6000_isa_flags;
32809
32810      cur_opt     = TREE_TARGET_OPTION (cur_tree);
32811      cur_flags   = cur_opt->x_rs6000_isa_flags;
32812      cur_bumask  = cur_opt->x_rs6000_builtin_mask;
32813
32814      diff_bumask = (prev_bumask ^ cur_bumask);
32815      diff_flags  = (prev_flags ^ cur_flags);
32816
32817      if ((diff_flags != 0) || (diff_bumask != 0))
32818	{
32819	  /* Delete old macros.  */
32820	  rs6000_target_modify_macros_ptr (false,
32821					   prev_flags & diff_flags,
32822					   prev_bumask & diff_bumask);
32823
32824	  /* Define new macros.  */
32825	  rs6000_target_modify_macros_ptr (true,
32826					   cur_flags & diff_flags,
32827					   cur_bumask & diff_bumask);
32828	}
32829    }
32830
32831  return true;
32832}
32833
32834
32835/* Remember the last target of rs6000_set_current_function.  */
32836static GTY(()) tree rs6000_previous_fndecl;
32837
32838/* Establish appropriate back-end context for processing the function
32839   FNDECL.  The argument might be NULL to indicate processing at top
32840   level, outside of any function scope.  */
32841static void
32842rs6000_set_current_function (tree fndecl)
32843{
32844  tree old_tree = (rs6000_previous_fndecl
32845		   ? DECL_FUNCTION_SPECIFIC_TARGET (rs6000_previous_fndecl)
32846		   : NULL_TREE);
32847
32848  tree new_tree = (fndecl
32849		   ? DECL_FUNCTION_SPECIFIC_TARGET (fndecl)
32850		   : NULL_TREE);
32851
32852  if (TARGET_DEBUG_TARGET)
32853    {
32854      bool print_final = false;
32855      fprintf (stderr, "\n==================== rs6000_set_current_function");
32856
32857      if (fndecl)
32858	fprintf (stderr, ", fndecl %s (%p)",
32859		 (DECL_NAME (fndecl)
32860		  ? IDENTIFIER_POINTER (DECL_NAME (fndecl))
32861		  : "<unknown>"), (void *)fndecl);
32862
32863      if (rs6000_previous_fndecl)
32864	fprintf (stderr, ", prev_fndecl (%p)", (void *)rs6000_previous_fndecl);
32865
32866      fprintf (stderr, "\n");
32867      if (new_tree)
32868	{
32869	  fprintf (stderr, "\nnew fndecl target specific options:\n");
32870	  debug_tree (new_tree);
32871	  print_final = true;
32872	}
32873
32874      if (old_tree)
32875	{
32876	  fprintf (stderr, "\nold fndecl target specific options:\n");
32877	  debug_tree (old_tree);
32878	  print_final = true;
32879	}
32880
32881      if (print_final)
32882	fprintf (stderr, "--------------------\n");
32883    }
32884
32885  /* Only change the context if the function changes.  This hook is called
32886     several times in the course of compiling a function, and we don't want to
32887     slow things down too much or call target_reinit when it isn't safe.  */
32888  if (fndecl && fndecl != rs6000_previous_fndecl)
32889    {
32890      rs6000_previous_fndecl = fndecl;
32891      if (old_tree == new_tree)
32892	;
32893
32894      else if (new_tree && new_tree != target_option_default_node)
32895	{
32896	  cl_target_option_restore (&global_options,
32897				    TREE_TARGET_OPTION (new_tree));
32898	  if (TREE_TARGET_GLOBALS (new_tree))
32899	    restore_target_globals (TREE_TARGET_GLOBALS (new_tree));
32900	  else
32901	    TREE_TARGET_GLOBALS (new_tree)
32902	      = save_target_globals_default_opts ();
32903	}
32904
32905      else if (old_tree && old_tree != target_option_default_node)
32906	{
32907	  new_tree = target_option_current_node;
32908	  cl_target_option_restore (&global_options,
32909				    TREE_TARGET_OPTION (new_tree));
32910	  if (TREE_TARGET_GLOBALS (new_tree))
32911	    restore_target_globals (TREE_TARGET_GLOBALS (new_tree));
32912	  else if (new_tree == target_option_default_node)
32913	    restore_target_globals (&default_target_globals);
32914	  else
32915	    TREE_TARGET_GLOBALS (new_tree)
32916	      = save_target_globals_default_opts ();
32917	}
32918    }
32919}
32920
32921
32922/* Save the current options */
32923
32924static void
32925rs6000_function_specific_save (struct cl_target_option *ptr,
32926			       struct gcc_options *opts)
32927{
32928  ptr->x_rs6000_isa_flags = opts->x_rs6000_isa_flags;
32929  ptr->x_rs6000_isa_flags_explicit = opts->x_rs6000_isa_flags_explicit;
32930}
32931
32932/* Restore the current options */
32933
32934static void
32935rs6000_function_specific_restore (struct gcc_options *opts,
32936				  struct cl_target_option *ptr)
32937
32938{
32939  opts->x_rs6000_isa_flags = ptr->x_rs6000_isa_flags;
32940  opts->x_rs6000_isa_flags_explicit = ptr->x_rs6000_isa_flags_explicit;
32941  (void) rs6000_option_override_internal (false);
32942}
32943
32944/* Print the current options */
32945
32946static void
32947rs6000_function_specific_print (FILE *file, int indent,
32948				struct cl_target_option *ptr)
32949{
32950  rs6000_print_isa_options (file, indent, "Isa options set",
32951			    ptr->x_rs6000_isa_flags);
32952
32953  rs6000_print_isa_options (file, indent, "Isa options explicit",
32954			    ptr->x_rs6000_isa_flags_explicit);
32955}
32956
32957/* Helper function to print the current isa or misc options on a line.  */
32958
32959static void
32960rs6000_print_options_internal (FILE *file,
32961			       int indent,
32962			       const char *string,
32963			       HOST_WIDE_INT flags,
32964			       const char *prefix,
32965			       const struct rs6000_opt_mask *opts,
32966			       size_t num_elements)
32967{
32968  size_t i;
32969  size_t start_column = 0;
32970  size_t cur_column;
32971  size_t max_column = 76;
32972  const char *comma = "";
32973
32974  if (indent)
32975    start_column += fprintf (file, "%*s", indent, "");
32976
32977  if (!flags)
32978    {
32979      fprintf (stderr, DEBUG_FMT_S, string, "<none>");
32980      return;
32981    }
32982
32983  start_column += fprintf (stderr, DEBUG_FMT_WX, string, flags);
32984
32985  /* Print the various mask options.  */
32986  cur_column = start_column;
32987  for (i = 0; i < num_elements; i++)
32988    {
32989      if ((flags & opts[i].mask) != 0)
32990	{
32991	  const char *no_str = rs6000_opt_masks[i].invert ? "no-" : "";
32992	  size_t len = (strlen (comma)
32993			+ strlen (prefix)
32994			+ strlen (no_str)
32995			+ strlen (rs6000_opt_masks[i].name));
32996
32997	  cur_column += len;
32998	  if (cur_column > max_column)
32999	    {
33000	      fprintf (stderr, ", \\\n%*s", (int)start_column, "");
33001	      cur_column = start_column + len;
33002	      comma = "";
33003	    }
33004
33005	  fprintf (file, "%s%s%s%s", comma, prefix, no_str,
33006		   rs6000_opt_masks[i].name);
33007	  flags &= ~ opts[i].mask;
33008	  comma = ", ";
33009	}
33010    }
33011
33012  fputs ("\n", file);
33013}
33014
33015/* Helper function to print the current isa options on a line.  */
33016
33017static void
33018rs6000_print_isa_options (FILE *file, int indent, const char *string,
33019			  HOST_WIDE_INT flags)
33020{
33021  rs6000_print_options_internal (file, indent, string, flags, "-m",
33022				 &rs6000_opt_masks[0],
33023				 ARRAY_SIZE (rs6000_opt_masks));
33024}
33025
33026static void
33027rs6000_print_builtin_options (FILE *file, int indent, const char *string,
33028			      HOST_WIDE_INT flags)
33029{
33030  rs6000_print_options_internal (file, indent, string, flags, "",
33031				 &rs6000_builtin_mask_names[0],
33032				 ARRAY_SIZE (rs6000_builtin_mask_names));
33033}
33034
33035
33036/* Hook to determine if one function can safely inline another.  */
33037
33038static bool
33039rs6000_can_inline_p (tree caller, tree callee)
33040{
33041  bool ret = false;
33042  tree caller_tree = DECL_FUNCTION_SPECIFIC_TARGET (caller);
33043  tree callee_tree = DECL_FUNCTION_SPECIFIC_TARGET (callee);
33044
33045  /* If callee has no option attributes, then it is ok to inline.  */
33046  if (!callee_tree)
33047    ret = true;
33048
33049  /* If caller has no option attributes, but callee does then it is not ok to
33050     inline.  */
33051  else if (!caller_tree)
33052    ret = false;
33053
33054  else
33055    {
33056      struct cl_target_option *caller_opts = TREE_TARGET_OPTION (caller_tree);
33057      struct cl_target_option *callee_opts = TREE_TARGET_OPTION (callee_tree);
33058
33059      /* Callee's options should a subset of the caller's, i.e. a vsx function
33060	 can inline an altivec function but a non-vsx function can't inline a
33061	 vsx function.  */
33062      if ((caller_opts->x_rs6000_isa_flags & callee_opts->x_rs6000_isa_flags)
33063	  == callee_opts->x_rs6000_isa_flags)
33064	ret = true;
33065    }
33066
33067  if (TARGET_DEBUG_TARGET)
33068    fprintf (stderr, "rs6000_can_inline_p:, caller %s, callee %s, %s inline\n",
33069	     (DECL_NAME (caller)
33070	      ? IDENTIFIER_POINTER (DECL_NAME (caller))
33071	      : "<unknown>"),
33072	     (DECL_NAME (callee)
33073	      ? IDENTIFIER_POINTER (DECL_NAME (callee))
33074	      : "<unknown>"),
33075	     (ret ? "can" : "cannot"));
33076
33077  return ret;
33078}
33079
33080/* Allocate a stack temp and fixup the address so it meets the particular
33081   memory requirements (either offetable or REG+REG addressing).  */
33082
33083rtx
33084rs6000_allocate_stack_temp (machine_mode mode,
33085			    bool offsettable_p,
33086			    bool reg_reg_p)
33087{
33088  rtx stack = assign_stack_temp (mode, GET_MODE_SIZE (mode));
33089  rtx addr = XEXP (stack, 0);
33090  int strict_p = (reload_in_progress || reload_completed);
33091
33092  if (!legitimate_indirect_address_p (addr, strict_p))
33093    {
33094      if (offsettable_p
33095	  && !rs6000_legitimate_offset_address_p (mode, addr, strict_p, true))
33096	stack = replace_equiv_address (stack, copy_addr_to_reg (addr));
33097
33098      else if (reg_reg_p && !legitimate_indexed_address_p (addr, strict_p))
33099	stack = replace_equiv_address (stack, copy_addr_to_reg (addr));
33100    }
33101
33102  return stack;
33103}
33104
33105/* Given a memory reference, if it is not a reg or reg+reg addressing, convert
33106   to such a form to deal with memory reference instructions like STFIWX that
33107   only take reg+reg addressing.  */
33108
33109rtx
33110rs6000_address_for_fpconvert (rtx x)
33111{
33112  int strict_p = (reload_in_progress || reload_completed);
33113  rtx addr;
33114
33115  gcc_assert (MEM_P (x));
33116  addr = XEXP (x, 0);
33117  if (! legitimate_indirect_address_p (addr, strict_p)
33118      && ! legitimate_indexed_address_p (addr, strict_p))
33119    {
33120      if (GET_CODE (addr) == PRE_INC || GET_CODE (addr) == PRE_DEC)
33121	{
33122	  rtx reg = XEXP (addr, 0);
33123	  HOST_WIDE_INT size = GET_MODE_SIZE (GET_MODE (x));
33124	  rtx size_rtx = GEN_INT ((GET_CODE (addr) == PRE_DEC) ? -size : size);
33125	  gcc_assert (REG_P (reg));
33126	  emit_insn (gen_add3_insn (reg, reg, size_rtx));
33127	  addr = reg;
33128	}
33129      else if (GET_CODE (addr) == PRE_MODIFY)
33130	{
33131	  rtx reg = XEXP (addr, 0);
33132	  rtx expr = XEXP (addr, 1);
33133	  gcc_assert (REG_P (reg));
33134	  gcc_assert (GET_CODE (expr) == PLUS);
33135	  emit_insn (gen_add3_insn (reg, XEXP (expr, 0), XEXP (expr, 1)));
33136	  addr = reg;
33137	}
33138
33139      x = replace_equiv_address (x, copy_addr_to_reg (addr));
33140    }
33141
33142  return x;
33143}
33144
33145/* Given a memory reference, if it is not in the form for altivec memory
33146   reference instructions (i.e. reg or reg+reg addressing with AND of -16),
33147   convert to the altivec format.  */
33148
33149rtx
33150rs6000_address_for_altivec (rtx x)
33151{
33152  gcc_assert (MEM_P (x));
33153  if (!altivec_indexed_or_indirect_operand (x, GET_MODE (x)))
33154    {
33155      rtx addr = XEXP (x, 0);
33156      int strict_p = (reload_in_progress || reload_completed);
33157
33158      if (!legitimate_indexed_address_p (addr, strict_p)
33159	  && !legitimate_indirect_address_p (addr, strict_p))
33160	addr = copy_to_mode_reg (Pmode, addr);
33161
33162      addr = gen_rtx_AND (Pmode, addr, GEN_INT (-16));
33163      x = change_address (x, GET_MODE (x), addr);
33164    }
33165
33166  return x;
33167}
33168
33169/* Implement TARGET_LEGITIMATE_CONSTANT_P.
33170
33171   On the RS/6000, all integer constants are acceptable, most won't be valid
33172   for particular insns, though.  Only easy FP constants are acceptable.  */
33173
33174static bool
33175rs6000_legitimate_constant_p (machine_mode mode, rtx x)
33176{
33177  if (TARGET_ELF && tls_referenced_p (x))
33178    return false;
33179
33180  return ((GET_CODE (x) != CONST_DOUBLE && GET_CODE (x) != CONST_VECTOR)
33181	  || GET_MODE (x) == VOIDmode
33182	  || (TARGET_POWERPC64 && mode == DImode)
33183	  || easy_fp_constant (x, mode)
33184	  || easy_vector_constant (x, mode));
33185}
33186
33187
33188/* Return TRUE iff the sequence ending in LAST sets the static chain.  */
33189
33190static bool
33191chain_already_loaded (rtx_insn *last)
33192{
33193  for (; last != NULL; last = PREV_INSN (last))
33194    {
33195      if (NONJUMP_INSN_P (last))
33196	{
33197	  rtx patt = PATTERN (last);
33198
33199	  if (GET_CODE (patt) == SET)
33200	    {
33201	      rtx lhs = XEXP (patt, 0);
33202
33203	      if (REG_P (lhs) && REGNO (lhs) == STATIC_CHAIN_REGNUM)
33204		return true;
33205	    }
33206	}
33207    }
33208  return false;
33209}
33210
33211/* Expand code to perform a call under the AIX or ELFv2 ABI.  */
33212
33213void
33214rs6000_call_aix (rtx value, rtx func_desc, rtx flag, rtx cookie)
33215{
33216  const bool direct_call_p
33217    = GET_CODE (func_desc) == SYMBOL_REF && SYMBOL_REF_FUNCTION_P (func_desc);
33218  rtx toc_reg = gen_rtx_REG (Pmode, TOC_REGNUM);
33219  rtx toc_load = NULL_RTX;
33220  rtx toc_restore = NULL_RTX;
33221  rtx func_addr;
33222  rtx abi_reg = NULL_RTX;
33223  rtx call[4];
33224  int n_call;
33225  rtx insn;
33226
33227  /* Handle longcall attributes.  */
33228  if (INTVAL (cookie) & CALL_LONG)
33229    func_desc = rs6000_longcall_ref (func_desc);
33230
33231  /* Handle indirect calls.  */
33232  if (GET_CODE (func_desc) != SYMBOL_REF
33233      || (DEFAULT_ABI == ABI_AIX && !SYMBOL_REF_FUNCTION_P (func_desc)))
33234    {
33235      /* Save the TOC into its reserved slot before the call,
33236	 and prepare to restore it after the call.  */
33237      rtx stack_ptr = gen_rtx_REG (Pmode, STACK_POINTER_REGNUM);
33238      rtx stack_toc_offset = GEN_INT (RS6000_TOC_SAVE_SLOT);
33239      rtx stack_toc_mem = gen_frame_mem (Pmode,
33240					 gen_rtx_PLUS (Pmode, stack_ptr,
33241						       stack_toc_offset));
33242      rtx stack_toc_unspec = gen_rtx_UNSPEC (Pmode,
33243					     gen_rtvec (1, stack_toc_offset),
33244					     UNSPEC_TOCSLOT);
33245      toc_restore = gen_rtx_SET (VOIDmode, toc_reg, stack_toc_unspec);
33246
33247      /* Can we optimize saving the TOC in the prologue or
33248	 do we need to do it at every call?  */
33249      if (TARGET_SAVE_TOC_INDIRECT && !cfun->calls_alloca)
33250	cfun->machine->save_toc_in_prologue = true;
33251      else
33252	{
33253	  MEM_VOLATILE_P (stack_toc_mem) = 1;
33254	  emit_move_insn (stack_toc_mem, toc_reg);
33255	}
33256
33257      if (DEFAULT_ABI == ABI_ELFv2)
33258	{
33259	  /* A function pointer in the ELFv2 ABI is just a plain address, but
33260	     the ABI requires it to be loaded into r12 before the call.  */
33261	  func_addr = gen_rtx_REG (Pmode, 12);
33262	  emit_move_insn (func_addr, func_desc);
33263	  abi_reg = func_addr;
33264	}
33265      else
33266	{
33267	  /* A function pointer under AIX is a pointer to a data area whose
33268	     first word contains the actual address of the function, whose
33269	     second word contains a pointer to its TOC, and whose third word
33270	     contains a value to place in the static chain register (r11).
33271	     Note that if we load the static chain, our "trampoline" need
33272	     not have any executable code.  */
33273
33274	  /* Load up address of the actual function.  */
33275	  func_desc = force_reg (Pmode, func_desc);
33276	  func_addr = gen_reg_rtx (Pmode);
33277	  emit_move_insn (func_addr, gen_rtx_MEM (Pmode, func_desc));
33278
33279	  /* Prepare to load the TOC of the called function.  Note that the
33280	     TOC load must happen immediately before the actual call so
33281	     that unwinding the TOC registers works correctly.  See the
33282	     comment in frob_update_context.  */
33283	  rtx func_toc_offset = GEN_INT (GET_MODE_SIZE (Pmode));
33284	  rtx func_toc_mem = gen_rtx_MEM (Pmode,
33285					  gen_rtx_PLUS (Pmode, func_desc,
33286							func_toc_offset));
33287	  toc_load = gen_rtx_USE (VOIDmode, func_toc_mem);
33288
33289	  /* If we have a static chain, load it up.  But, if the call was
33290	     originally direct, the 3rd word has not been written since no
33291	     trampoline has been built, so we ought not to load it, lest we
33292	     override a static chain value.  */
33293	  if (!direct_call_p
33294	      && TARGET_POINTERS_TO_NESTED_FUNCTIONS
33295	      && !chain_already_loaded (crtl->emit.sequence_stack->last))
33296	    {
33297	      rtx sc_reg = gen_rtx_REG (Pmode, STATIC_CHAIN_REGNUM);
33298	      rtx func_sc_offset = GEN_INT (2 * GET_MODE_SIZE (Pmode));
33299	      rtx func_sc_mem = gen_rtx_MEM (Pmode,
33300					     gen_rtx_PLUS (Pmode, func_desc,
33301							   func_sc_offset));
33302	      emit_move_insn (sc_reg, func_sc_mem);
33303	      abi_reg = sc_reg;
33304	    }
33305	}
33306    }
33307  else
33308    {
33309      /* Direct calls use the TOC: for local calls, the callee will
33310	 assume the TOC register is set; for non-local calls, the
33311	 PLT stub needs the TOC register.  */
33312      abi_reg = toc_reg;
33313      func_addr = func_desc;
33314    }
33315
33316  /* Create the call.  */
33317  call[0] = gen_rtx_CALL (VOIDmode, gen_rtx_MEM (SImode, func_addr), flag);
33318  if (value != NULL_RTX)
33319    call[0] = gen_rtx_SET (VOIDmode, value, call[0]);
33320  n_call = 1;
33321
33322  if (toc_load)
33323    call[n_call++] = toc_load;
33324  if (toc_restore)
33325    call[n_call++] = toc_restore;
33326
33327  call[n_call++] = gen_rtx_CLOBBER (VOIDmode, gen_rtx_REG (Pmode, LR_REGNO));
33328
33329  insn = gen_rtx_PARALLEL (VOIDmode, gen_rtvec_v (n_call, call));
33330  insn = emit_call_insn (insn);
33331
33332  /* Mention all registers defined by the ABI to hold information
33333     as uses in CALL_INSN_FUNCTION_USAGE.  */
33334  if (abi_reg)
33335    use_reg (&CALL_INSN_FUNCTION_USAGE (insn), abi_reg);
33336}
33337
33338/* Expand code to perform a sibling call under the AIX or ELFv2 ABI.  */
33339
33340void
33341rs6000_sibcall_aix (rtx value, rtx func_desc, rtx flag, rtx cookie)
33342{
33343  rtx call[2];
33344  rtx insn;
33345
33346  gcc_assert (INTVAL (cookie) == 0);
33347
33348  /* Create the call.  */
33349  call[0] = gen_rtx_CALL (VOIDmode, gen_rtx_MEM (SImode, func_desc), flag);
33350  if (value != NULL_RTX)
33351    call[0] = gen_rtx_SET (VOIDmode, value, call[0]);
33352
33353  call[1] = simple_return_rtx;
33354
33355  insn = gen_rtx_PARALLEL (VOIDmode, gen_rtvec_v (2, call));
33356  insn = emit_call_insn (insn);
33357
33358  /* Note use of the TOC register.  */
33359  use_reg (&CALL_INSN_FUNCTION_USAGE (insn), gen_rtx_REG (Pmode, TOC_REGNUM));
33360  /* We need to also mark a use of the link register since the function we
33361     sibling-call to will use it to return to our caller.  */
33362  use_reg (&CALL_INSN_FUNCTION_USAGE (insn), gen_rtx_REG (Pmode, LR_REGNO));
33363}
33364
33365/* Return whether we need to always update the saved TOC pointer when we update
33366   the stack pointer.  */
33367
33368static bool
33369rs6000_save_toc_in_prologue_p (void)
33370{
33371  return (cfun && cfun->machine && cfun->machine->save_toc_in_prologue);
33372}
33373
33374#ifdef HAVE_GAS_HIDDEN
33375# define USE_HIDDEN_LINKONCE 1
33376#else
33377# define USE_HIDDEN_LINKONCE 0
33378#endif
33379
33380/* Fills in the label name that should be used for a 476 link stack thunk.  */
33381
33382void
33383get_ppc476_thunk_name (char name[32])
33384{
33385  gcc_assert (TARGET_LINK_STACK);
33386
33387  if (USE_HIDDEN_LINKONCE)
33388    sprintf (name, "__ppc476.get_thunk");
33389  else
33390    ASM_GENERATE_INTERNAL_LABEL (name, "LPPC476_", 0);
33391}
33392
33393/* This function emits the simple thunk routine that is used to preserve
33394   the link stack on the 476 cpu.  */
33395
33396static void rs6000_code_end (void) ATTRIBUTE_UNUSED;
33397static void
33398rs6000_code_end (void)
33399{
33400  char name[32];
33401  tree decl;
33402
33403  if (!TARGET_LINK_STACK)
33404    return;
33405
33406  get_ppc476_thunk_name (name);
33407
33408  decl = build_decl (BUILTINS_LOCATION, FUNCTION_DECL, get_identifier (name),
33409		     build_function_type_list (void_type_node, NULL_TREE));
33410  DECL_RESULT (decl) = build_decl (BUILTINS_LOCATION, RESULT_DECL,
33411				   NULL_TREE, void_type_node);
33412  TREE_PUBLIC (decl) = 1;
33413  TREE_STATIC (decl) = 1;
33414
33415#if RS6000_WEAK
33416  if (USE_HIDDEN_LINKONCE)
33417    {
33418      cgraph_node::create (decl)->set_comdat_group (DECL_ASSEMBLER_NAME (decl));
33419      targetm.asm_out.unique_section (decl, 0);
33420      switch_to_section (get_named_section (decl, NULL, 0));
33421      DECL_WEAK (decl) = 1;
33422      ASM_WEAKEN_DECL (asm_out_file, decl, name, 0);
33423      targetm.asm_out.globalize_label (asm_out_file, name);
33424      targetm.asm_out.assemble_visibility (decl, VISIBILITY_HIDDEN);
33425      ASM_DECLARE_FUNCTION_NAME (asm_out_file, name, decl);
33426    }
33427  else
33428#endif
33429    {
33430      switch_to_section (text_section);
33431      ASM_OUTPUT_LABEL (asm_out_file, name);
33432    }
33433
33434  DECL_INITIAL (decl) = make_node (BLOCK);
33435  current_function_decl = decl;
33436  init_function_start (decl);
33437  first_function_block_is_cold = false;
33438  /* Make sure unwind info is emitted for the thunk if needed.  */
33439  final_start_function (emit_barrier (), asm_out_file, 1);
33440
33441  fputs ("\tblr\n", asm_out_file);
33442
33443  final_end_function ();
33444  init_insn_lengths ();
33445  free_after_compilation (cfun);
33446  set_cfun (NULL);
33447  current_function_decl = NULL;
33448}
33449
33450/* Add r30 to hard reg set if the prologue sets it up and it is not
33451   pic_offset_table_rtx.  */
33452
33453static void
33454rs6000_set_up_by_prologue (struct hard_reg_set_container *set)
33455{
33456  if (!TARGET_SINGLE_PIC_BASE
33457      && TARGET_TOC
33458      && TARGET_MINIMAL_TOC
33459      && get_pool_size () != 0)
33460    add_to_hard_reg_set (&set->set, Pmode, RS6000_PIC_OFFSET_TABLE_REGNUM);
33461}
33462
33463
33464/* Helper function for rs6000_split_logical to emit a logical instruction after
33465   spliting the operation to single GPR registers.
33466
33467   DEST is the destination register.
33468   OP1 and OP2 are the input source registers.
33469   CODE is the base operation (AND, IOR, XOR, NOT).
33470   MODE is the machine mode.
33471   If COMPLEMENT_FINAL_P is true, wrap the whole operation with NOT.
33472   If COMPLEMENT_OP1_P is true, wrap operand1 with NOT.
33473   If COMPLEMENT_OP2_P is true, wrap operand2 with NOT.  */
33474
33475static void
33476rs6000_split_logical_inner (rtx dest,
33477			    rtx op1,
33478			    rtx op2,
33479			    enum rtx_code code,
33480			    machine_mode mode,
33481			    bool complement_final_p,
33482			    bool complement_op1_p,
33483			    bool complement_op2_p)
33484{
33485  rtx bool_rtx;
33486
33487  /* Optimize AND of 0/0xffffffff and IOR/XOR of 0.  */
33488  if (op2 && GET_CODE (op2) == CONST_INT
33489      && (mode == SImode || (mode == DImode && TARGET_POWERPC64))
33490      && !complement_final_p && !complement_op1_p && !complement_op2_p)
33491    {
33492      HOST_WIDE_INT mask = GET_MODE_MASK (mode);
33493      HOST_WIDE_INT value = INTVAL (op2) & mask;
33494
33495      /* Optimize AND of 0 to just set 0.  Optimize AND of -1 to be a move.  */
33496      if (code == AND)
33497	{
33498	  if (value == 0)
33499	    {
33500	      emit_insn (gen_rtx_SET (VOIDmode, dest, const0_rtx));
33501	      return;
33502	    }
33503
33504	  else if (value == mask)
33505	    {
33506	      if (!rtx_equal_p (dest, op1))
33507		emit_insn (gen_rtx_SET (VOIDmode, dest, op1));
33508	      return;
33509	    }
33510	}
33511
33512      /* Optimize IOR/XOR of 0 to be a simple move.  Split large operations
33513	 into separate ORI/ORIS or XORI/XORIS instrucitons.  */
33514      else if (code == IOR || code == XOR)
33515	{
33516	  if (value == 0)
33517	    {
33518	      if (!rtx_equal_p (dest, op1))
33519		emit_insn (gen_rtx_SET (VOIDmode, dest, op1));
33520	      return;
33521	    }
33522	}
33523    }
33524
33525  if (code == AND && mode == SImode
33526      && !complement_final_p && !complement_op1_p && !complement_op2_p)
33527    {
33528      emit_insn (gen_andsi3 (dest, op1, op2));
33529      return;
33530    }
33531
33532  if (complement_op1_p)
33533    op1 = gen_rtx_NOT (mode, op1);
33534
33535  if (complement_op2_p)
33536    op2 = gen_rtx_NOT (mode, op2);
33537
33538  /* For canonical RTL, if only one arm is inverted it is the first.  */
33539  if (!complement_op1_p && complement_op2_p)
33540    std::swap (op1, op2);
33541
33542  bool_rtx = ((code == NOT)
33543	      ? gen_rtx_NOT (mode, op1)
33544	      : gen_rtx_fmt_ee (code, mode, op1, op2));
33545
33546  if (complement_final_p)
33547    bool_rtx = gen_rtx_NOT (mode, bool_rtx);
33548
33549  emit_insn (gen_rtx_SET (VOIDmode, dest, bool_rtx));
33550}
33551
33552/* Split a DImode AND/IOR/XOR with a constant on a 32-bit system.  These
33553   operations are split immediately during RTL generation to allow for more
33554   optimizations of the AND/IOR/XOR.
33555
33556   OPERANDS is an array containing the destination and two input operands.
33557   CODE is the base operation (AND, IOR, XOR, NOT).
33558   MODE is the machine mode.
33559   If COMPLEMENT_FINAL_P is true, wrap the whole operation with NOT.
33560   If COMPLEMENT_OP1_P is true, wrap operand1 with NOT.
33561   If COMPLEMENT_OP2_P is true, wrap operand2 with NOT.
33562   CLOBBER_REG is either NULL or a scratch register of type CC to allow
33563   formation of the AND instructions.  */
33564
33565static void
33566rs6000_split_logical_di (rtx operands[3],
33567			 enum rtx_code code,
33568			 bool complement_final_p,
33569			 bool complement_op1_p,
33570			 bool complement_op2_p)
33571{
33572  const HOST_WIDE_INT lower_32bits = HOST_WIDE_INT_C(0xffffffff);
33573  const HOST_WIDE_INT upper_32bits = ~ lower_32bits;
33574  const HOST_WIDE_INT sign_bit = HOST_WIDE_INT_C(0x80000000);
33575  enum hi_lo { hi = 0, lo = 1 };
33576  rtx op0_hi_lo[2], op1_hi_lo[2], op2_hi_lo[2];
33577  size_t i;
33578
33579  op0_hi_lo[hi] = gen_highpart (SImode, operands[0]);
33580  op1_hi_lo[hi] = gen_highpart (SImode, operands[1]);
33581  op0_hi_lo[lo] = gen_lowpart (SImode, operands[0]);
33582  op1_hi_lo[lo] = gen_lowpart (SImode, operands[1]);
33583
33584  if (code == NOT)
33585    op2_hi_lo[hi] = op2_hi_lo[lo] = NULL_RTX;
33586  else
33587    {
33588      if (GET_CODE (operands[2]) != CONST_INT)
33589	{
33590	  op2_hi_lo[hi] = gen_highpart_mode (SImode, DImode, operands[2]);
33591	  op2_hi_lo[lo] = gen_lowpart (SImode, operands[2]);
33592	}
33593      else
33594	{
33595	  HOST_WIDE_INT value = INTVAL (operands[2]);
33596	  HOST_WIDE_INT value_hi_lo[2];
33597
33598	  gcc_assert (!complement_final_p);
33599	  gcc_assert (!complement_op1_p);
33600	  gcc_assert (!complement_op2_p);
33601
33602	  value_hi_lo[hi] = value >> 32;
33603	  value_hi_lo[lo] = value & lower_32bits;
33604
33605	  for (i = 0; i < 2; i++)
33606	    {
33607	      HOST_WIDE_INT sub_value = value_hi_lo[i];
33608
33609	      if (sub_value & sign_bit)
33610		sub_value |= upper_32bits;
33611
33612	      op2_hi_lo[i] = GEN_INT (sub_value);
33613
33614	      /* If this is an AND instruction, check to see if we need to load
33615		 the value in a register.  */
33616	      if (code == AND && sub_value != -1 && sub_value != 0
33617		  && !and_operand (op2_hi_lo[i], SImode))
33618		op2_hi_lo[i] = force_reg (SImode, op2_hi_lo[i]);
33619	    }
33620	}
33621    }
33622
33623  for (i = 0; i < 2; i++)
33624    {
33625      /* Split large IOR/XOR operations.  */
33626      if ((code == IOR || code == XOR)
33627	  && GET_CODE (op2_hi_lo[i]) == CONST_INT
33628	  && !complement_final_p
33629	  && !complement_op1_p
33630	  && !complement_op2_p
33631	  && !logical_const_operand (op2_hi_lo[i], SImode))
33632	{
33633	  HOST_WIDE_INT value = INTVAL (op2_hi_lo[i]);
33634	  HOST_WIDE_INT hi_16bits = value & HOST_WIDE_INT_C(0xffff0000);
33635	  HOST_WIDE_INT lo_16bits = value & HOST_WIDE_INT_C(0x0000ffff);
33636	  rtx tmp = gen_reg_rtx (SImode);
33637
33638	  /* Make sure the constant is sign extended.  */
33639	  if ((hi_16bits & sign_bit) != 0)
33640	    hi_16bits |= upper_32bits;
33641
33642	  rs6000_split_logical_inner (tmp, op1_hi_lo[i], GEN_INT (hi_16bits),
33643				      code, SImode, false, false, false);
33644
33645	  rs6000_split_logical_inner (op0_hi_lo[i], tmp, GEN_INT (lo_16bits),
33646				      code, SImode, false, false, false);
33647	}
33648      else
33649	rs6000_split_logical_inner (op0_hi_lo[i], op1_hi_lo[i], op2_hi_lo[i],
33650				    code, SImode, complement_final_p,
33651				    complement_op1_p, complement_op2_p);
33652    }
33653
33654  return;
33655}
33656
33657/* Split the insns that make up boolean operations operating on multiple GPR
33658   registers.  The boolean MD patterns ensure that the inputs either are
33659   exactly the same as the output registers, or there is no overlap.
33660
33661   OPERANDS is an array containing the destination and two input operands.
33662   CODE is the base operation (AND, IOR, XOR, NOT).
33663   If COMPLEMENT_FINAL_P is true, wrap the whole operation with NOT.
33664   If COMPLEMENT_OP1_P is true, wrap operand1 with NOT.
33665   If COMPLEMENT_OP2_P is true, wrap operand2 with NOT.  */
33666
33667void
33668rs6000_split_logical (rtx operands[3],
33669		      enum rtx_code code,
33670		      bool complement_final_p,
33671		      bool complement_op1_p,
33672		      bool complement_op2_p)
33673{
33674  machine_mode mode = GET_MODE (operands[0]);
33675  machine_mode sub_mode;
33676  rtx op0, op1, op2;
33677  int sub_size, regno0, regno1, nregs, i;
33678
33679  /* If this is DImode, use the specialized version that can run before
33680     register allocation.  */
33681  if (mode == DImode && !TARGET_POWERPC64)
33682    {
33683      rs6000_split_logical_di (operands, code, complement_final_p,
33684			       complement_op1_p, complement_op2_p);
33685      return;
33686    }
33687
33688  op0 = operands[0];
33689  op1 = operands[1];
33690  op2 = (code == NOT) ? NULL_RTX : operands[2];
33691  sub_mode = (TARGET_POWERPC64) ? DImode : SImode;
33692  sub_size = GET_MODE_SIZE (sub_mode);
33693  regno0 = REGNO (op0);
33694  regno1 = REGNO (op1);
33695
33696  gcc_assert (reload_completed);
33697  gcc_assert (IN_RANGE (regno0, FIRST_GPR_REGNO, LAST_GPR_REGNO));
33698  gcc_assert (IN_RANGE (regno1, FIRST_GPR_REGNO, LAST_GPR_REGNO));
33699
33700  nregs = rs6000_hard_regno_nregs[(int)mode][regno0];
33701  gcc_assert (nregs > 1);
33702
33703  if (op2 && REG_P (op2))
33704    gcc_assert (IN_RANGE (REGNO (op2), FIRST_GPR_REGNO, LAST_GPR_REGNO));
33705
33706  for (i = 0; i < nregs; i++)
33707    {
33708      int offset = i * sub_size;
33709      rtx sub_op0 = simplify_subreg (sub_mode, op0, mode, offset);
33710      rtx sub_op1 = simplify_subreg (sub_mode, op1, mode, offset);
33711      rtx sub_op2 = ((code == NOT)
33712		     ? NULL_RTX
33713		     : simplify_subreg (sub_mode, op2, mode, offset));
33714
33715      rs6000_split_logical_inner (sub_op0, sub_op1, sub_op2, code, sub_mode,
33716				  complement_final_p, complement_op1_p,
33717				  complement_op2_p);
33718    }
33719
33720  return;
33721}
33722
33723
33724/* Return true if the peephole2 can combine a load involving a combination of
33725   an addis instruction and a load with an offset that can be fused together on
33726   a power8.  */
33727
33728bool
33729fusion_gpr_load_p (rtx addis_reg,	/* register set via addis.  */
33730		   rtx addis_value,	/* addis value.  */
33731		   rtx target,		/* target register that is loaded.  */
33732		   rtx mem)		/* bottom part of the memory addr. */
33733{
33734  rtx addr;
33735  rtx base_reg;
33736
33737  /* Validate arguments.  */
33738  if (!base_reg_operand (addis_reg, GET_MODE (addis_reg)))
33739    return false;
33740
33741  if (!base_reg_operand (target, GET_MODE (target)))
33742    return false;
33743
33744  if (!fusion_gpr_addis (addis_value, GET_MODE (addis_value)))
33745    return false;
33746
33747  /* Allow sign/zero extension.  */
33748  if (GET_CODE (mem) == ZERO_EXTEND
33749      || (GET_CODE (mem) == SIGN_EXTEND && TARGET_P8_FUSION_SIGN))
33750    mem = XEXP (mem, 0);
33751
33752  if (!MEM_P (mem))
33753    return false;
33754
33755  if (!fusion_gpr_mem_load (mem, GET_MODE (mem)))
33756    return false;
33757
33758  addr = XEXP (mem, 0);			/* either PLUS or LO_SUM.  */
33759  if (GET_CODE (addr) != PLUS && GET_CODE (addr) != LO_SUM)
33760    return false;
33761
33762  /* Validate that the register used to load the high value is either the
33763     register being loaded, or we can safely replace its use.
33764
33765     This function is only called from the peephole2 pass and we assume that
33766     there are 2 instructions in the peephole (addis and load), so we want to
33767     check if the target register was not used in the memory address and the
33768     register to hold the addis result is dead after the peephole.  */
33769  if (REGNO (addis_reg) != REGNO (target))
33770    {
33771      if (reg_mentioned_p (target, mem))
33772	return false;
33773
33774      if (!peep2_reg_dead_p (2, addis_reg))
33775	return false;
33776
33777      /* If the target register being loaded is the stack pointer, we must
33778         avoid loading any other value into it, even temporarily.  */
33779      if (REG_P (target) && REGNO (target) == STACK_POINTER_REGNUM)
33780	return false;
33781    }
33782
33783  base_reg = XEXP (addr, 0);
33784  return REGNO (addis_reg) == REGNO (base_reg);
33785}
33786
33787/* During the peephole2 pass, adjust and expand the insns for a load fusion
33788   sequence.  We adjust the addis register to use the target register.  If the
33789   load sign extends, we adjust the code to do the zero extending load, and an
33790   explicit sign extension later since the fusion only covers zero extending
33791   loads.
33792
33793   The operands are:
33794	operands[0]	register set with addis (to be replaced with target)
33795	operands[1]	value set via addis
33796	operands[2]	target register being loaded
33797	operands[3]	D-form memory reference using operands[0].  */
33798
33799void
33800expand_fusion_gpr_load (rtx *operands)
33801{
33802  rtx addis_value = operands[1];
33803  rtx target = operands[2];
33804  rtx orig_mem = operands[3];
33805  rtx  new_addr, new_mem, orig_addr, offset;
33806  enum rtx_code plus_or_lo_sum;
33807  machine_mode target_mode = GET_MODE (target);
33808  machine_mode extend_mode = target_mode;
33809  machine_mode ptr_mode = Pmode;
33810  enum rtx_code extend = UNKNOWN;
33811
33812  if (GET_CODE (orig_mem) == ZERO_EXTEND
33813      || (TARGET_P8_FUSION_SIGN && GET_CODE (orig_mem) == SIGN_EXTEND))
33814    {
33815      extend = GET_CODE (orig_mem);
33816      orig_mem = XEXP (orig_mem, 0);
33817      target_mode = GET_MODE (orig_mem);
33818    }
33819
33820  gcc_assert (MEM_P (orig_mem));
33821
33822  orig_addr = XEXP (orig_mem, 0);
33823  plus_or_lo_sum = GET_CODE (orig_addr);
33824  gcc_assert (plus_or_lo_sum == PLUS || plus_or_lo_sum == LO_SUM);
33825
33826  offset = XEXP (orig_addr, 1);
33827  new_addr = gen_rtx_fmt_ee (plus_or_lo_sum, ptr_mode, addis_value, offset);
33828  new_mem = replace_equiv_address_nv (orig_mem, new_addr, false);
33829
33830  if (extend != UNKNOWN)
33831    new_mem = gen_rtx_fmt_e (ZERO_EXTEND, extend_mode, new_mem);
33832
33833  new_mem = gen_rtx_UNSPEC (extend_mode, gen_rtvec (1, new_mem),
33834			    UNSPEC_FUSION_GPR);
33835  emit_insn (gen_rtx_SET (VOIDmode, target, new_mem));
33836
33837  if (extend == SIGN_EXTEND)
33838    {
33839      int sub_off = ((BYTES_BIG_ENDIAN)
33840		     ? GET_MODE_SIZE (extend_mode) - GET_MODE_SIZE (target_mode)
33841		     : 0);
33842      rtx sign_reg
33843	= simplify_subreg (target_mode, target, extend_mode, sub_off);
33844
33845      emit_insn (gen_rtx_SET (VOIDmode, target,
33846			      gen_rtx_SIGN_EXTEND (extend_mode, sign_reg)));
33847    }
33848
33849  return;
33850}
33851
33852/* Return a string to fuse an addis instruction with a gpr load to the same
33853   register that we loaded up the addis instruction.  The address that is used
33854   is the logical address that was formed during peephole2:
33855	(lo_sum (high) (low-part))
33856
33857   The code is complicated, so we call output_asm_insn directly, and just
33858   return "".  */
33859
33860const char *
33861emit_fusion_gpr_load (rtx target, rtx mem)
33862{
33863  rtx addis_value;
33864  rtx fuse_ops[10];
33865  rtx addr;
33866  rtx load_offset;
33867  const char *addis_str = NULL;
33868  const char *load_str = NULL;
33869  const char *mode_name = NULL;
33870  char insn_template[80];
33871  machine_mode mode;
33872  const char *comment_str = ASM_COMMENT_START;
33873
33874  if (GET_CODE (mem) == ZERO_EXTEND)
33875    mem = XEXP (mem, 0);
33876
33877  gcc_assert (REG_P (target) && MEM_P (mem));
33878
33879  if (*comment_str == ' ')
33880    comment_str++;
33881
33882  addr = XEXP (mem, 0);
33883  if (GET_CODE (addr) != PLUS && GET_CODE (addr) != LO_SUM)
33884    gcc_unreachable ();
33885
33886  addis_value = XEXP (addr, 0);
33887  load_offset = XEXP (addr, 1);
33888
33889  /* Now emit the load instruction to the same register.  */
33890  mode = GET_MODE (mem);
33891  switch (mode)
33892    {
33893    case QImode:
33894      mode_name = "char";
33895      load_str = "lbz";
33896      break;
33897
33898    case HImode:
33899      mode_name = "short";
33900      load_str = "lhz";
33901      break;
33902
33903    case SImode:
33904      mode_name = "int";
33905      load_str = "lwz";
33906      break;
33907
33908    case DImode:
33909      gcc_assert (TARGET_POWERPC64);
33910      mode_name = "long";
33911      load_str = "ld";
33912      break;
33913
33914    default:
33915      gcc_unreachable ();
33916    }
33917
33918  /* Emit the addis instruction.  */
33919  fuse_ops[0] = target;
33920  if (satisfies_constraint_L (addis_value))
33921    {
33922      fuse_ops[1] = addis_value;
33923      addis_str = "lis %0,%v1";
33924    }
33925
33926  else if (GET_CODE (addis_value) == PLUS)
33927    {
33928      rtx op0 = XEXP (addis_value, 0);
33929      rtx op1 = XEXP (addis_value, 1);
33930
33931      if (REG_P (op0) && CONST_INT_P (op1)
33932	  && satisfies_constraint_L (op1))
33933	{
33934	  fuse_ops[1] = op0;
33935	  fuse_ops[2] = op1;
33936	  addis_str = "addis %0,%1,%v2";
33937	}
33938    }
33939
33940  else if (GET_CODE (addis_value) == HIGH)
33941    {
33942      rtx value = XEXP (addis_value, 0);
33943      if (GET_CODE (value) == UNSPEC && XINT (value, 1) == UNSPEC_TOCREL)
33944	{
33945	  fuse_ops[1] = XVECEXP (value, 0, 0);		/* symbol ref.  */
33946	  fuse_ops[2] = XVECEXP (value, 0, 1);		/* TOC register.  */
33947	  if (TARGET_ELF)
33948	    addis_str = "addis %0,%2,%1@toc@ha";
33949
33950	  else if (TARGET_XCOFF)
33951	    addis_str = "addis %0,%1@u(%2)";
33952
33953	  else
33954	    gcc_unreachable ();
33955	}
33956
33957      else if (GET_CODE (value) == PLUS)
33958	{
33959	  rtx op0 = XEXP (value, 0);
33960	  rtx op1 = XEXP (value, 1);
33961
33962	  if (GET_CODE (op0) == UNSPEC
33963	      && XINT (op0, 1) == UNSPEC_TOCREL
33964	      && CONST_INT_P (op1))
33965	    {
33966	      fuse_ops[1] = XVECEXP (op0, 0, 0);	/* symbol ref.  */
33967	      fuse_ops[2] = XVECEXP (op0, 0, 1);	/* TOC register.  */
33968	      fuse_ops[3] = op1;
33969	      if (TARGET_ELF)
33970		addis_str = "addis %0,%2,%1+%3@toc@ha";
33971
33972	      else if (TARGET_XCOFF)
33973		addis_str = "addis %0,%1+%3@u(%2)";
33974
33975	      else
33976		gcc_unreachable ();
33977	    }
33978	}
33979
33980      else if (satisfies_constraint_L (value))
33981	{
33982	  fuse_ops[1] = value;
33983	  addis_str = "lis %0,%v1";
33984	}
33985
33986      else if (TARGET_ELF && !TARGET_POWERPC64 && CONSTANT_P (value))
33987	{
33988	  fuse_ops[1] = value;
33989	  addis_str = "lis %0,%1@ha";
33990	}
33991    }
33992
33993  if (!addis_str)
33994    fatal_insn ("Could not generate addis value for fusion", addis_value);
33995
33996  sprintf (insn_template, "%s\t\t%s gpr load fusion, type %s", addis_str,
33997	   comment_str, mode_name);
33998  output_asm_insn (insn_template, fuse_ops);
33999
34000  /* Emit the D-form load instruction.  */
34001  if (CONST_INT_P (load_offset) && satisfies_constraint_I (load_offset))
34002    {
34003      sprintf (insn_template, "%s %%0,%%1(%%0)", load_str);
34004      fuse_ops[1] = load_offset;
34005      output_asm_insn (insn_template, fuse_ops);
34006    }
34007
34008  else if (GET_CODE (load_offset) == UNSPEC
34009	   && XINT (load_offset, 1) == UNSPEC_TOCREL)
34010    {
34011      if (TARGET_ELF)
34012	sprintf (insn_template, "%s %%0,%%1@toc@l(%%0)", load_str);
34013
34014      else if (TARGET_XCOFF)
34015	sprintf (insn_template, "%s %%0,%%1@l(%%0)", load_str);
34016
34017      else
34018	gcc_unreachable ();
34019
34020      fuse_ops[1] = XVECEXP (load_offset, 0, 0);
34021      output_asm_insn (insn_template, fuse_ops);
34022    }
34023
34024  else if (GET_CODE (load_offset) == PLUS
34025	   && GET_CODE (XEXP (load_offset, 0)) == UNSPEC
34026	   && XINT (XEXP (load_offset, 0), 1) == UNSPEC_TOCREL
34027	   && CONST_INT_P (XEXP (load_offset, 1)))
34028    {
34029      rtx tocrel_unspec = XEXP (load_offset, 0);
34030      if (TARGET_ELF)
34031	sprintf (insn_template, "%s %%0,%%1+%%2@toc@l(%%0)", load_str);
34032
34033      else if (TARGET_XCOFF)
34034	sprintf (insn_template, "%s %%0,%%1+%%2@l(%%0)", load_str);
34035
34036      else
34037	gcc_unreachable ();
34038
34039      fuse_ops[1] = XVECEXP (tocrel_unspec, 0, 0);
34040      fuse_ops[2] = XEXP (load_offset, 1);
34041      output_asm_insn (insn_template, fuse_ops);
34042    }
34043
34044  else if (TARGET_ELF && !TARGET_POWERPC64 && CONSTANT_P (load_offset))
34045    {
34046      sprintf (insn_template, "%s %%0,%%1@l(%%0)", load_str);
34047
34048      fuse_ops[1] = load_offset;
34049      output_asm_insn (insn_template, fuse_ops);
34050    }
34051
34052  else
34053    fatal_insn ("Unable to generate load offset for fusion", load_offset);
34054
34055  return "";
34056}
34057
34058/* Analyze vector computations and remove unnecessary doubleword
34059   swaps (xxswapdi instructions).  This pass is performed only
34060   for little-endian VSX code generation.
34061
34062   For this specific case, loads and stores of 4x32 and 2x64 vectors
34063   are inefficient.  These are implemented using the lvx2dx and
34064   stvx2dx instructions, which invert the order of doublewords in
34065   a vector register.  Thus the code generation inserts an xxswapdi
34066   after each such load, and prior to each such store.  (For spill
34067   code after register assignment, an additional xxswapdi is inserted
34068   following each store in order to return a hard register to its
34069   unpermuted value.)
34070
34071   The extra xxswapdi instructions reduce performance.  This can be
34072   particularly bad for vectorized code.  The purpose of this pass
34073   is to reduce the number of xxswapdi instructions required for
34074   correctness.
34075
34076   The primary insight is that much code that operates on vectors
34077   does not care about the relative order of elements in a register,
34078   so long as the correct memory order is preserved.  If we have
34079   a computation where all input values are provided by lvxd2x/xxswapdi
34080   sequences, all outputs are stored using xxswapdi/stvxd2x sequences,
34081   and all intermediate computations are pure SIMD (independent of
34082   element order), then all the xxswapdi's associated with the loads
34083   and stores may be removed.
34084
34085   This pass uses some of the infrastructure and logical ideas from
34086   the "web" pass in web.c.  We create maximal webs of computations
34087   fitting the description above using union-find.  Each such web is
34088   then optimized by removing its unnecessary xxswapdi instructions.
34089
34090   The pass is placed prior to global optimization so that we can
34091   perform the optimization in the safest and simplest way possible;
34092   that is, by replacing each xxswapdi insn with a register copy insn.
34093   Subsequent forward propagation will remove copies where possible.
34094
34095   There are some operations sensitive to element order for which we
34096   can still allow the operation, provided we modify those operations.
34097   These include CONST_VECTORs, for which we must swap the first and
34098   second halves of the constant vector; and SUBREGs, for which we
34099   must adjust the byte offset to account for the swapped doublewords.
34100   A remaining opportunity would be non-immediate-form splats, for
34101   which we should adjust the selected lane of the input.  We should
34102   also make code generation adjustments for sum-across operations,
34103   since this is a common vectorizer reduction.
34104
34105   Because we run prior to the first split, we can see loads and stores
34106   here that match *vsx_le_perm_{load,store}_<mode>.  These are vanilla
34107   vector loads and stores that have not yet been split into a permuting
34108   load/store and a swap.  (One way this can happen is with a builtin
34109   call to vec_vsx_{ld,st}.)  We can handle these as well, but rather
34110   than deleting a swap, we convert the load/store into a permuting
34111   load/store (which effectively removes the swap).  */
34112
34113/* Notes on Permutes
34114
34115   We do not currently handle computations that contain permutes.  There
34116   is a general transformation that can be performed correctly, but it
34117   may introduce more expensive code than it replaces.  To handle these
34118   would require a cost model to determine when to perform the optimization.
34119   This commentary records how this could be done if desired.
34120
34121   The most general permute is something like this (example for V16QI):
34122
34123   (vec_select:V16QI (vec_concat:V32QI (op1:V16QI) (op2:V16QI))
34124                     (parallel [(const_int a0) (const_int a1)
34125                                 ...
34126                                (const_int a14) (const_int a15)]))
34127
34128   where a0,...,a15 are in [0,31] and select elements from op1 and op2
34129   to produce in the result.
34130
34131   Regardless of mode, we can convert the PARALLEL to a mask of 16
34132   byte-element selectors.  Let's call this M, with M[i] representing
34133   the ith byte-element selector value.  Then if we swap doublewords
34134   throughout the computation, we can get correct behavior by replacing
34135   M with M' as follows:
34136
34137            { M[i+8]+8 : i < 8, M[i+8] in [0,7] U [16,23]
34138    M'[i] = { M[i+8]-8 : i < 8, M[i+8] in [8,15] U [24,31]
34139            { M[i-8]+8 : i >= 8, M[i-8] in [0,7] U [16,23]
34140            { M[i-8]-8 : i >= 8, M[i-8] in [8,15] U [24,31]
34141
34142   This seems promising at first, since we are just replacing one mask
34143   with another.  But certain masks are preferable to others.  If M
34144   is a mask that matches a vmrghh pattern, for example, M' certainly
34145   will not.  Instead of a single vmrghh, we would generate a load of
34146   M' and a vperm.  So we would need to know how many xxswapd's we can
34147   remove as a result of this transformation to determine if it's
34148   profitable; and preferably the logic would need to be aware of all
34149   the special preferable masks.
34150
34151   Another form of permute is an UNSPEC_VPERM, in which the mask is
34152   already in a register.  In some cases, this mask may be a constant
34153   that we can discover with ud-chains, in which case the above
34154   transformation is ok.  However, the common usage here is for the
34155   mask to be produced by an UNSPEC_LVSL, in which case the mask
34156   cannot be known at compile time.  In such a case we would have to
34157   generate several instructions to compute M' as above at run time,
34158   and a cost model is needed again.  */
34159
34160/* This is based on the union-find logic in web.c.  web_entry_base is
34161   defined in df.h.  */
34162class swap_web_entry : public web_entry_base
34163{
34164 public:
34165  /* Pointer to the insn.  */
34166  rtx_insn *insn;
34167  /* Set if insn contains a mention of a vector register.  All other
34168     fields are undefined if this field is unset.  */
34169  unsigned int is_relevant : 1;
34170  /* Set if insn is a load.  */
34171  unsigned int is_load : 1;
34172  /* Set if insn is a store.  */
34173  unsigned int is_store : 1;
34174  /* Set if insn is a doubleword swap.  This can either be a register swap
34175     or a permuting load or store (test is_load and is_store for this).  */
34176  unsigned int is_swap : 1;
34177  /* Set if the insn has a live-in use of a parameter register.  */
34178  unsigned int is_live_in : 1;
34179  /* Set if the insn has a live-out def of a return register.  */
34180  unsigned int is_live_out : 1;
34181  /* Set if the insn contains a subreg reference of a vector register.  */
34182  unsigned int contains_subreg : 1;
34183  /* Set if the insn contains a 128-bit integer operand.  */
34184  unsigned int is_128_int : 1;
34185  /* Set if this is a call-insn.  */
34186  unsigned int is_call : 1;
34187  /* Set if this insn does not perform a vector operation for which
34188     element order matters, or if we know how to fix it up if it does.
34189     Undefined if is_swap is set.  */
34190  unsigned int is_swappable : 1;
34191  /* A nonzero value indicates what kind of special handling for this
34192     insn is required if doublewords are swapped.  Undefined if
34193     is_swappable is not set.  */
34194  unsigned int special_handling : 3;
34195  /* Set if the web represented by this entry cannot be optimized.  */
34196  unsigned int web_not_optimizable : 1;
34197  /* Set if this insn should be deleted.  */
34198  unsigned int will_delete : 1;
34199};
34200
34201enum special_handling_values {
34202  SH_NONE = 0,
34203  SH_CONST_VECTOR,
34204  SH_SUBREG,
34205  SH_NOSWAP_LD,
34206  SH_NOSWAP_ST,
34207  SH_EXTRACT,
34208  SH_SPLAT
34209};
34210
34211/* Union INSN with all insns containing definitions that reach USE.
34212   Detect whether USE is live-in to the current function.  */
34213static void
34214union_defs (swap_web_entry *insn_entry, rtx insn, df_ref use)
34215{
34216  struct df_link *link = DF_REF_CHAIN (use);
34217
34218  if (!link)
34219    insn_entry[INSN_UID (insn)].is_live_in = 1;
34220
34221  while (link)
34222    {
34223      if (DF_REF_IS_ARTIFICIAL (link->ref))
34224	insn_entry[INSN_UID (insn)].is_live_in = 1;
34225
34226      if (DF_REF_INSN_INFO (link->ref))
34227	{
34228	  rtx def_insn = DF_REF_INSN (link->ref);
34229	  (void)unionfind_union (insn_entry + INSN_UID (insn),
34230				 insn_entry + INSN_UID (def_insn));
34231	}
34232
34233      link = link->next;
34234    }
34235}
34236
34237/* Union INSN with all insns containing uses reached from DEF.
34238   Detect whether DEF is live-out from the current function.  */
34239static void
34240union_uses (swap_web_entry *insn_entry, rtx insn, df_ref def)
34241{
34242  struct df_link *link = DF_REF_CHAIN (def);
34243
34244  if (!link)
34245    insn_entry[INSN_UID (insn)].is_live_out = 1;
34246
34247  while (link)
34248    {
34249      /* This could be an eh use or some other artificial use;
34250	 we treat these all the same (killing the optimization).  */
34251      if (DF_REF_IS_ARTIFICIAL (link->ref))
34252	insn_entry[INSN_UID (insn)].is_live_out = 1;
34253
34254      if (DF_REF_INSN_INFO (link->ref))
34255	{
34256	  rtx use_insn = DF_REF_INSN (link->ref);
34257	  (void)unionfind_union (insn_entry + INSN_UID (insn),
34258				 insn_entry + INSN_UID (use_insn));
34259	}
34260
34261      link = link->next;
34262    }
34263}
34264
34265/* Return 1 iff INSN is a load insn, including permuting loads that
34266   represent an lvxd2x instruction; else return 0.  */
34267static unsigned int
34268insn_is_load_p (rtx insn)
34269{
34270  rtx body = PATTERN (insn);
34271
34272  if (GET_CODE (body) == SET)
34273    {
34274      if (GET_CODE (SET_SRC (body)) == MEM)
34275	return 1;
34276
34277      if (GET_CODE (SET_SRC (body)) == VEC_SELECT
34278	  && GET_CODE (XEXP (SET_SRC (body), 0)) == MEM)
34279	return 1;
34280
34281      return 0;
34282    }
34283
34284  if (GET_CODE (body) != PARALLEL)
34285    return 0;
34286
34287  rtx set = XVECEXP (body, 0, 0);
34288
34289  if (GET_CODE (set) == SET && GET_CODE (SET_SRC (set)) == MEM)
34290    return 1;
34291
34292  return 0;
34293}
34294
34295/* Return 1 iff INSN is a store insn, including permuting stores that
34296   represent an stvxd2x instruction; else return 0.  */
34297static unsigned int
34298insn_is_store_p (rtx insn)
34299{
34300  rtx body = PATTERN (insn);
34301  if (GET_CODE (body) == SET && GET_CODE (SET_DEST (body)) == MEM)
34302    return 1;
34303  if (GET_CODE (body) != PARALLEL)
34304    return 0;
34305  rtx set = XVECEXP (body, 0, 0);
34306  if (GET_CODE (set) == SET && GET_CODE (SET_DEST (set)) == MEM)
34307    return 1;
34308  return 0;
34309}
34310
34311/* Return 1 iff INSN swaps doublewords.  This may be a reg-reg swap,
34312   a permuting load, or a permuting store.  */
34313static unsigned int
34314insn_is_swap_p (rtx insn)
34315{
34316  rtx body = PATTERN (insn);
34317  if (GET_CODE (body) != SET)
34318    return 0;
34319  rtx rhs = SET_SRC (body);
34320  if (GET_CODE (rhs) != VEC_SELECT)
34321    return 0;
34322  rtx parallel = XEXP (rhs, 1);
34323  if (GET_CODE (parallel) != PARALLEL)
34324    return 0;
34325  unsigned int len = XVECLEN (parallel, 0);
34326  if (len != 2 && len != 4 && len != 8 && len != 16)
34327    return 0;
34328  for (unsigned int i = 0; i < len / 2; ++i)
34329    {
34330      rtx op = XVECEXP (parallel, 0, i);
34331      if (GET_CODE (op) != CONST_INT || INTVAL (op) != len / 2 + i)
34332	return 0;
34333    }
34334  for (unsigned int i = len / 2; i < len; ++i)
34335    {
34336      rtx op = XVECEXP (parallel, 0, i);
34337      if (GET_CODE (op) != CONST_INT || INTVAL (op) != i - len / 2)
34338	return 0;
34339    }
34340  return 1;
34341}
34342
34343/* Return 1 iff OP is an operand that will not be affected by having
34344   vector doublewords swapped in memory.  */
34345static unsigned int
34346rtx_is_swappable_p (rtx op, unsigned int *special)
34347{
34348  enum rtx_code code = GET_CODE (op);
34349  int i, j;
34350  rtx parallel;
34351
34352  switch (code)
34353    {
34354    case LABEL_REF:
34355    case SYMBOL_REF:
34356    case CLOBBER:
34357    case REG:
34358      return 1;
34359
34360    case VEC_CONCAT:
34361    case ASM_INPUT:
34362    case ASM_OPERANDS:
34363      return 0;
34364
34365    case CONST_VECTOR:
34366      {
34367	*special = SH_CONST_VECTOR;
34368	return 1;
34369      }
34370
34371    case VEC_DUPLICATE:
34372      /* Opportunity: If XEXP (op, 0) has the same mode as the result,
34373	 and XEXP (op, 1) is a PARALLEL with a single QImode const int,
34374	 it represents a vector splat for which we can do special
34375	 handling.  */
34376      if (GET_CODE (XEXP (op, 0)) == CONST_INT)
34377	return 1;
34378      else if (GET_CODE (XEXP (op, 0)) == REG
34379	       && GET_MODE_INNER (GET_MODE (op)) == GET_MODE (XEXP (op, 0)))
34380	/* This catches V2DF and V2DI splat, at a minimum.  */
34381	return 1;
34382      else if (GET_CODE (XEXP (op, 0)) == VEC_SELECT)
34383	/* If the duplicated item is from a select, defer to the select
34384	   processing to see if we can change the lane for the splat.  */
34385	return rtx_is_swappable_p (XEXP (op, 0), special);
34386      else
34387	return 0;
34388
34389    case VEC_SELECT:
34390      /* A vec_extract operation is ok if we change the lane.  */
34391      if (GET_CODE (XEXP (op, 0)) == REG
34392	  && GET_MODE_INNER (GET_MODE (XEXP (op, 0))) == GET_MODE (op)
34393	  && GET_CODE ((parallel = XEXP (op, 1))) == PARALLEL
34394	  && XVECLEN (parallel, 0) == 1
34395	  && GET_CODE (XVECEXP (parallel, 0, 0)) == CONST_INT)
34396	{
34397	  *special = SH_EXTRACT;
34398	  return 1;
34399	}
34400      else
34401	return 0;
34402
34403    case UNSPEC:
34404      {
34405	/* Various operations are unsafe for this optimization, at least
34406	   without significant additional work.  Permutes are obviously
34407	   problematic, as both the permute control vector and the ordering
34408	   of the target values are invalidated by doubleword swapping.
34409	   Vector pack and unpack modify the number of vector lanes.
34410	   Merge-high/low will not operate correctly on swapped operands.
34411	   Vector shifts across element boundaries are clearly uncool,
34412	   as are vector select and concatenate operations.  Vector
34413	   sum-across instructions define one operand with a specific
34414	   order-dependent element, so additional fixup code would be
34415	   needed to make those work.  Vector set and non-immediate-form
34416	   vector splat are element-order sensitive.  A few of these
34417	   cases might be workable with special handling if required.
34418	   Adding cost modeling would be appropriate in some cases.  */
34419	int val = XINT (op, 1);
34420	switch (val)
34421	  {
34422	  default:
34423	    break;
34424	  case UNSPEC_VMRGH_DIRECT:
34425	  case UNSPEC_VMRGL_DIRECT:
34426	  case UNSPEC_VPACK_SIGN_SIGN_SAT:
34427	  case UNSPEC_VPACK_SIGN_UNS_SAT:
34428	  case UNSPEC_VPACK_UNS_UNS_MOD:
34429	  case UNSPEC_VPACK_UNS_UNS_MOD_DIRECT:
34430	  case UNSPEC_VPACK_UNS_UNS_SAT:
34431	  case UNSPEC_VPERM:
34432	  case UNSPEC_VPERM_UNS:
34433	  case UNSPEC_VPERMHI:
34434	  case UNSPEC_VPERMSI:
34435	  case UNSPEC_VPKPX:
34436	  case UNSPEC_VSLDOI:
34437	  case UNSPEC_VSLO:
34438	  case UNSPEC_VSRO:
34439	  case UNSPEC_VSUM2SWS:
34440	  case UNSPEC_VSUM4S:
34441	  case UNSPEC_VSUM4UBS:
34442	  case UNSPEC_VSUMSWS:
34443	  case UNSPEC_VSUMSWS_DIRECT:
34444	  case UNSPEC_VSX_CONCAT:
34445	  case UNSPEC_VSX_SET:
34446	  case UNSPEC_VSX_SLDWI:
34447	  case UNSPEC_VUNPACK_HI_SIGN:
34448	  case UNSPEC_VUNPACK_HI_SIGN_DIRECT:
34449	  case UNSPEC_VUNPACK_LO_SIGN:
34450	  case UNSPEC_VUNPACK_LO_SIGN_DIRECT:
34451	  case UNSPEC_VUPKHPX:
34452	  case UNSPEC_VUPKHS_V4SF:
34453	  case UNSPEC_VUPKHU_V4SF:
34454	  case UNSPEC_VUPKLPX:
34455	  case UNSPEC_VUPKLS_V4SF:
34456	  case UNSPEC_VUPKLU_V4SF:
34457	  case UNSPEC_VSX_CVDPSPN:
34458	  case UNSPEC_VSX_CVSPDP:
34459	  case UNSPEC_VSX_CVSPDPN:
34460	    return 0;
34461	  case UNSPEC_VSPLT_DIRECT:
34462	    *special = SH_SPLAT;
34463	    return 1;
34464	  }
34465      }
34466
34467    default:
34468      break;
34469    }
34470
34471  const char *fmt = GET_RTX_FORMAT (code);
34472  int ok = 1;
34473
34474  for (i = 0; i < GET_RTX_LENGTH (code); ++i)
34475    if (fmt[i] == 'e' || fmt[i] == 'u')
34476      {
34477	unsigned int special_op = SH_NONE;
34478	ok &= rtx_is_swappable_p (XEXP (op, i), &special_op);
34479	if (special_op == SH_NONE)
34480	  continue;
34481	/* Ensure we never have two kinds of special handling
34482	   for the same insn.  */
34483	if (*special != SH_NONE && *special != special_op)
34484	  return 0;
34485	*special = special_op;
34486      }
34487    else if (fmt[i] == 'E')
34488      for (j = 0; j < XVECLEN (op, i); ++j)
34489	{
34490	  unsigned int special_op = SH_NONE;
34491	  ok &= rtx_is_swappable_p (XVECEXP (op, i, j), &special_op);
34492	  if (special_op == SH_NONE)
34493	    continue;
34494	  /* Ensure we never have two kinds of special handling
34495	     for the same insn.  */
34496	  if (*special != SH_NONE && *special != special_op)
34497	    return 0;
34498	  *special = special_op;
34499	}
34500
34501  return ok;
34502}
34503
34504/* Return 1 iff INSN is an operand that will not be affected by
34505   having vector doublewords swapped in memory (in which case
34506   *SPECIAL is unchanged), or that can be modified to be correct
34507   if vector doublewords are swapped in memory (in which case
34508   *SPECIAL is changed to a value indicating how).  */
34509static unsigned int
34510insn_is_swappable_p (swap_web_entry *insn_entry, rtx insn,
34511		     unsigned int *special)
34512{
34513  /* Calls are always bad.  */
34514  if (GET_CODE (insn) == CALL_INSN)
34515    return 0;
34516
34517  /* Loads and stores seen here are not permuting, but we can still
34518     fix them up by converting them to permuting ones.  Exceptions:
34519     UNSPEC_LVE, UNSPEC_LVX, and UNSPEC_STVX, which have a PARALLEL
34520     body instead of a SET; and UNSPEC_STVE, which has an UNSPEC
34521     for the SET source.  */
34522  rtx body = PATTERN (insn);
34523  int i = INSN_UID (insn);
34524
34525  if (insn_entry[i].is_load)
34526    {
34527      if (GET_CODE (body) == SET)
34528	{
34529	  *special = SH_NOSWAP_LD;
34530	  return 1;
34531	}
34532      else
34533	return 0;
34534    }
34535
34536  if (insn_entry[i].is_store)
34537    {
34538      if (GET_CODE (body) == SET && GET_CODE (SET_SRC (body)) != UNSPEC)
34539	{
34540	  *special = SH_NOSWAP_ST;
34541	  return 1;
34542	}
34543      else
34544	return 0;
34545    }
34546
34547  /* A convert to single precision can be left as is provided that
34548     all of its uses are in xxspltw instructions that splat BE element
34549     zero.  */
34550  if (GET_CODE (body) == SET
34551      && GET_CODE (SET_SRC (body)) == UNSPEC
34552      && XINT (SET_SRC (body), 1) == UNSPEC_VSX_CVDPSPN)
34553    {
34554      df_ref def;
34555      struct df_insn_info *insn_info = DF_INSN_INFO_GET (insn);
34556
34557      FOR_EACH_INSN_INFO_DEF (def, insn_info)
34558	{
34559	  struct df_link *link = DF_REF_CHAIN (def);
34560	  if (!link)
34561	    return 0;
34562
34563	  for (; link; link = link->next) {
34564	    rtx use_insn = DF_REF_INSN (link->ref);
34565	    rtx use_body = PATTERN (use_insn);
34566	    if (GET_CODE (use_body) != SET
34567		|| GET_CODE (SET_SRC (use_body)) != UNSPEC
34568		|| XINT (SET_SRC (use_body), 1) != UNSPEC_VSX_XXSPLTW
34569		|| XEXP (XEXP (SET_SRC (use_body), 0), 1) != const0_rtx)
34570	      return 0;
34571	  }
34572	}
34573
34574      return 1;
34575    }
34576
34577  /* Otherwise check the operands for vector lane violations.  */
34578  return rtx_is_swappable_p (body, special);
34579}
34580
34581enum chain_purpose { FOR_LOADS, FOR_STORES };
34582
34583/* Return true if the UD or DU chain headed by LINK is non-empty,
34584   and every entry on the chain references an insn that is a
34585   register swap.  Furthermore, if PURPOSE is FOR_LOADS, each such
34586   register swap must have only permuting loads as reaching defs.
34587   If PURPOSE is FOR_STORES, each such register swap must have only
34588   register swaps or permuting stores as reached uses.  */
34589static bool
34590chain_contains_only_swaps (swap_web_entry *insn_entry, struct df_link *link,
34591			   enum chain_purpose purpose)
34592{
34593  if (!link)
34594    return false;
34595
34596  for (; link; link = link->next)
34597    {
34598      if (!VECTOR_MODE_P (GET_MODE (DF_REF_REG (link->ref))))
34599	continue;
34600
34601      if (DF_REF_IS_ARTIFICIAL (link->ref))
34602	return false;
34603
34604      rtx reached_insn = DF_REF_INSN (link->ref);
34605      unsigned uid = INSN_UID (reached_insn);
34606      struct df_insn_info *insn_info = DF_INSN_INFO_GET (reached_insn);
34607
34608      if (!insn_entry[uid].is_swap || insn_entry[uid].is_load
34609	  || insn_entry[uid].is_store)
34610	return false;
34611
34612      if (purpose == FOR_LOADS)
34613	{
34614	  df_ref use;
34615	  FOR_EACH_INSN_INFO_USE (use, insn_info)
34616	    {
34617	      struct df_link *swap_link = DF_REF_CHAIN (use);
34618
34619	      while (swap_link)
34620		{
34621		  if (DF_REF_IS_ARTIFICIAL (link->ref))
34622		    return false;
34623
34624		  rtx swap_def_insn = DF_REF_INSN (swap_link->ref);
34625		  unsigned uid2 = INSN_UID (swap_def_insn);
34626
34627		  /* Only permuting loads are allowed.  */
34628		  if (!insn_entry[uid2].is_swap || !insn_entry[uid2].is_load)
34629		    return false;
34630
34631		  swap_link = swap_link->next;
34632		}
34633	    }
34634	}
34635      else if (purpose == FOR_STORES)
34636	{
34637	  df_ref def;
34638	  FOR_EACH_INSN_INFO_DEF (def, insn_info)
34639	    {
34640	      struct df_link *swap_link = DF_REF_CHAIN (def);
34641
34642	      while (swap_link)
34643		{
34644		  if (DF_REF_IS_ARTIFICIAL (link->ref))
34645		    return false;
34646
34647		  rtx swap_use_insn = DF_REF_INSN (swap_link->ref);
34648		  unsigned uid2 = INSN_UID (swap_use_insn);
34649
34650		  /* Permuting stores or register swaps are allowed.  */
34651		  if (!insn_entry[uid2].is_swap || insn_entry[uid2].is_load)
34652		    return false;
34653
34654		  swap_link = swap_link->next;
34655		}
34656	    }
34657	}
34658    }
34659
34660  return true;
34661}
34662
34663/* Mark the xxswapdi instructions associated with permuting loads and
34664   stores for removal.  Note that we only flag them for deletion here,
34665   as there is a possibility of a swap being reached from multiple
34666   loads, etc.  */
34667static void
34668mark_swaps_for_removal (swap_web_entry *insn_entry, unsigned int i)
34669{
34670  rtx insn = insn_entry[i].insn;
34671  struct df_insn_info *insn_info = DF_INSN_INFO_GET (insn);
34672
34673  if (insn_entry[i].is_load)
34674    {
34675      df_ref def;
34676      FOR_EACH_INSN_INFO_DEF (def, insn_info)
34677	{
34678	  struct df_link *link = DF_REF_CHAIN (def);
34679
34680	  /* We know by now that these are swaps, so we can delete
34681	     them confidently.  */
34682	  while (link)
34683	    {
34684	      rtx use_insn = DF_REF_INSN (link->ref);
34685	      insn_entry[INSN_UID (use_insn)].will_delete = 1;
34686	      link = link->next;
34687	    }
34688	}
34689    }
34690  else if (insn_entry[i].is_store)
34691    {
34692      df_ref use;
34693      FOR_EACH_INSN_INFO_USE (use, insn_info)
34694	{
34695	  /* Ignore uses for addressability.  */
34696	  machine_mode mode = GET_MODE (DF_REF_REG (use));
34697	  if (!VECTOR_MODE_P (mode))
34698	    continue;
34699
34700	  struct df_link *link = DF_REF_CHAIN (use);
34701
34702	  /* We know by now that these are swaps, so we can delete
34703	     them confidently.  */
34704	  while (link)
34705	    {
34706	      rtx def_insn = DF_REF_INSN (link->ref);
34707	      insn_entry[INSN_UID (def_insn)].will_delete = 1;
34708	      link = link->next;
34709	    }
34710	}
34711    }
34712}
34713
34714/* OP is either a CONST_VECTOR or an expression containing one.
34715   Swap the first half of the vector with the second in the first
34716   case.  Recurse to find it in the second.  */
34717static void
34718swap_const_vector_halves (rtx op)
34719{
34720  int i;
34721  enum rtx_code code = GET_CODE (op);
34722  if (GET_CODE (op) == CONST_VECTOR)
34723    {
34724      int half_units = GET_MODE_NUNITS (GET_MODE (op)) / 2;
34725      for (i = 0; i < half_units; ++i)
34726	{
34727	  rtx temp = CONST_VECTOR_ELT (op, i);
34728	  CONST_VECTOR_ELT (op, i) = CONST_VECTOR_ELT (op, i + half_units);
34729	  CONST_VECTOR_ELT (op, i + half_units) = temp;
34730	}
34731    }
34732  else
34733    {
34734      int j;
34735      const char *fmt = GET_RTX_FORMAT (code);
34736      for (i = 0; i < GET_RTX_LENGTH (code); ++i)
34737	if (fmt[i] == 'e' || fmt[i] == 'u')
34738	  swap_const_vector_halves (XEXP (op, i));
34739	else if (fmt[i] == 'E')
34740	  for (j = 0; j < XVECLEN (op, i); ++j)
34741	    swap_const_vector_halves (XVECEXP (op, i, j));
34742    }
34743}
34744
34745/* Find all subregs of a vector expression that perform a narrowing,
34746   and adjust the subreg index to account for doubleword swapping.  */
34747static void
34748adjust_subreg_index (rtx op)
34749{
34750  enum rtx_code code = GET_CODE (op);
34751  if (code == SUBREG
34752      && (GET_MODE_SIZE (GET_MODE (op))
34753	  < GET_MODE_SIZE (GET_MODE (XEXP (op, 0)))))
34754    {
34755      unsigned int index = SUBREG_BYTE (op);
34756      if (index < 8)
34757	index += 8;
34758      else
34759	index -= 8;
34760      SUBREG_BYTE (op) = index;
34761    }
34762
34763  const char *fmt = GET_RTX_FORMAT (code);
34764  int i,j;
34765  for (i = 0; i < GET_RTX_LENGTH (code); ++i)
34766    if (fmt[i] == 'e' || fmt[i] == 'u')
34767      adjust_subreg_index (XEXP (op, i));
34768    else if (fmt[i] == 'E')
34769      for (j = 0; j < XVECLEN (op, i); ++j)
34770	adjust_subreg_index (XVECEXP (op, i, j));
34771}
34772
34773/* Convert the non-permuting load INSN to a permuting one.  */
34774static void
34775permute_load (rtx_insn *insn)
34776{
34777  rtx body = PATTERN (insn);
34778  rtx mem_op = SET_SRC (body);
34779  rtx tgt_reg = SET_DEST (body);
34780  machine_mode mode = GET_MODE (tgt_reg);
34781  int n_elts = GET_MODE_NUNITS (mode);
34782  int half_elts = n_elts / 2;
34783  rtx par = gen_rtx_PARALLEL (mode, rtvec_alloc (n_elts));
34784  int i, j;
34785  for (i = 0, j = half_elts; i < half_elts; ++i, ++j)
34786    XVECEXP (par, 0, i) = GEN_INT (j);
34787  for (i = half_elts, j = 0; j < half_elts; ++i, ++j)
34788    XVECEXP (par, 0, i) = GEN_INT (j);
34789  rtx sel = gen_rtx_VEC_SELECT (mode, mem_op, par);
34790  SET_SRC (body) = sel;
34791  INSN_CODE (insn) = -1; /* Force re-recognition.  */
34792  df_insn_rescan (insn);
34793
34794  if (dump_file)
34795    fprintf (dump_file, "Replacing load %d with permuted load\n",
34796	     INSN_UID (insn));
34797}
34798
34799/* Convert the non-permuting store INSN to a permuting one.  */
34800static void
34801permute_store (rtx_insn *insn)
34802{
34803  rtx body = PATTERN (insn);
34804  rtx src_reg = SET_SRC (body);
34805  machine_mode mode = GET_MODE (src_reg);
34806  int n_elts = GET_MODE_NUNITS (mode);
34807  int half_elts = n_elts / 2;
34808  rtx par = gen_rtx_PARALLEL (mode, rtvec_alloc (n_elts));
34809  int i, j;
34810  for (i = 0, j = half_elts; i < half_elts; ++i, ++j)
34811    XVECEXP (par, 0, i) = GEN_INT (j);
34812  for (i = half_elts, j = 0; j < half_elts; ++i, ++j)
34813    XVECEXP (par, 0, i) = GEN_INT (j);
34814  rtx sel = gen_rtx_VEC_SELECT (mode, src_reg, par);
34815  SET_SRC (body) = sel;
34816  INSN_CODE (insn) = -1; /* Force re-recognition.  */
34817  df_insn_rescan (insn);
34818
34819  if (dump_file)
34820    fprintf (dump_file, "Replacing store %d with permuted store\n",
34821	     INSN_UID (insn));
34822}
34823
34824/* Given OP that contains a vector extract operation, adjust the index
34825   of the extracted lane to account for the doubleword swap.  */
34826static void
34827adjust_extract (rtx_insn *insn)
34828{
34829  rtx pattern = PATTERN (insn);
34830  if (GET_CODE (pattern) == PARALLEL)
34831    pattern = XVECEXP (pattern, 0, 0);
34832  rtx src = SET_SRC (pattern);
34833  /* The vec_select may be wrapped in a vec_duplicate for a splat, so
34834     account for that.  */
34835  rtx sel = GET_CODE (src) == VEC_DUPLICATE ? XEXP (src, 0) : src;
34836  rtx par = XEXP (sel, 1);
34837  int half_elts = GET_MODE_NUNITS (GET_MODE (XEXP (sel, 0))) >> 1;
34838  int lane = INTVAL (XVECEXP (par, 0, 0));
34839  lane = lane >= half_elts ? lane - half_elts : lane + half_elts;
34840  XVECEXP (par, 0, 0) = GEN_INT (lane);
34841  INSN_CODE (insn) = -1; /* Force re-recognition.  */
34842  df_insn_rescan (insn);
34843
34844  if (dump_file)
34845    fprintf (dump_file, "Changing lane for extract %d\n", INSN_UID (insn));
34846}
34847
34848/* Given OP that contains a vector direct-splat operation, adjust the index
34849   of the source lane to account for the doubleword swap.  */
34850static void
34851adjust_splat (rtx_insn *insn)
34852{
34853  rtx body = PATTERN (insn);
34854  rtx unspec = XEXP (body, 1);
34855  int half_elts = GET_MODE_NUNITS (GET_MODE (unspec)) >> 1;
34856  int lane = INTVAL (XVECEXP (unspec, 0, 1));
34857  lane = lane >= half_elts ? lane - half_elts : lane + half_elts;
34858  XVECEXP (unspec, 0, 1) = GEN_INT (lane);
34859  INSN_CODE (insn) = -1; /* Force re-recognition.  */
34860  df_insn_rescan (insn);
34861
34862  if (dump_file)
34863    fprintf (dump_file, "Changing lane for splat %d\n", INSN_UID (insn));
34864}
34865
34866/* The insn described by INSN_ENTRY[I] can be swapped, but only
34867   with special handling.  Take care of that here.  */
34868static void
34869handle_special_swappables (swap_web_entry *insn_entry, unsigned i)
34870{
34871  rtx_insn *insn = insn_entry[i].insn;
34872  rtx body = PATTERN (insn);
34873
34874  switch (insn_entry[i].special_handling)
34875    {
34876    default:
34877      gcc_unreachable ();
34878    case SH_CONST_VECTOR:
34879      {
34880	/* A CONST_VECTOR will only show up somewhere in the RHS of a SET.  */
34881	gcc_assert (GET_CODE (body) == SET);
34882	rtx rhs = SET_SRC (body);
34883	swap_const_vector_halves (rhs);
34884	if (dump_file)
34885	  fprintf (dump_file, "Swapping constant halves in insn %d\n", i);
34886	break;
34887      }
34888    case SH_SUBREG:
34889      /* A subreg of the same size is already safe.  For subregs that
34890	 select a smaller portion of a reg, adjust the index for
34891	 swapped doublewords.  */
34892      adjust_subreg_index (body);
34893      if (dump_file)
34894	fprintf (dump_file, "Adjusting subreg in insn %d\n", i);
34895      break;
34896    case SH_NOSWAP_LD:
34897      /* Convert a non-permuting load to a permuting one.  */
34898      permute_load (insn);
34899      break;
34900    case SH_NOSWAP_ST:
34901      /* Convert a non-permuting store to a permuting one.  */
34902      permute_store (insn);
34903      break;
34904    case SH_EXTRACT:
34905      /* Change the lane on an extract operation.  */
34906      adjust_extract (insn);
34907      break;
34908    case SH_SPLAT:
34909      /* Change the lane on a direct-splat operation.  */
34910      adjust_splat (insn);
34911      break;
34912    }
34913}
34914
34915/* Find the insn from the Ith table entry, which is known to be a
34916   register swap Y = SWAP(X).  Replace it with a copy Y = X.  */
34917static void
34918replace_swap_with_copy (swap_web_entry *insn_entry, unsigned i)
34919{
34920  rtx_insn *insn = insn_entry[i].insn;
34921  rtx body = PATTERN (insn);
34922  rtx src_reg = XEXP (SET_SRC (body), 0);
34923  rtx copy = gen_rtx_SET (VOIDmode, SET_DEST (body), src_reg);
34924  rtx_insn *new_insn = emit_insn_before (copy, insn);
34925  set_block_for_insn (new_insn, BLOCK_FOR_INSN (insn));
34926  df_insn_rescan (new_insn);
34927
34928  if (dump_file)
34929    {
34930      unsigned int new_uid = INSN_UID (new_insn);
34931      fprintf (dump_file, "Replacing swap %d with copy %d\n", i, new_uid);
34932    }
34933
34934  df_insn_delete (insn);
34935  remove_insn (insn);
34936  insn->set_deleted ();
34937}
34938
34939/* Dump the swap table to DUMP_FILE.  */
34940static void
34941dump_swap_insn_table (swap_web_entry *insn_entry)
34942{
34943  int e = get_max_uid ();
34944  fprintf (dump_file, "\nRelevant insns with their flag settings\n\n");
34945
34946  for (int i = 0; i < e; ++i)
34947    if (insn_entry[i].is_relevant)
34948      {
34949	swap_web_entry *pred_entry = (swap_web_entry *)insn_entry[i].pred ();
34950	fprintf (dump_file, "%6d %6d  ", i,
34951		 pred_entry && pred_entry->insn
34952		 ? INSN_UID (pred_entry->insn) : 0);
34953	if (insn_entry[i].is_load)
34954	  fputs ("load ", dump_file);
34955	if (insn_entry[i].is_store)
34956	  fputs ("store ", dump_file);
34957	if (insn_entry[i].is_swap)
34958	  fputs ("swap ", dump_file);
34959	if (insn_entry[i].is_live_in)
34960	  fputs ("live-in ", dump_file);
34961	if (insn_entry[i].is_live_out)
34962	  fputs ("live-out ", dump_file);
34963	if (insn_entry[i].contains_subreg)
34964	  fputs ("subreg ", dump_file);
34965	if (insn_entry[i].is_128_int)
34966	  fputs ("int128 ", dump_file);
34967	if (insn_entry[i].is_call)
34968	  fputs ("call ", dump_file);
34969	if (insn_entry[i].is_swappable)
34970	  {
34971	    fputs ("swappable ", dump_file);
34972	    if (insn_entry[i].special_handling == SH_CONST_VECTOR)
34973	      fputs ("special:constvec ", dump_file);
34974	    else if (insn_entry[i].special_handling == SH_SUBREG)
34975	      fputs ("special:subreg ", dump_file);
34976	    else if (insn_entry[i].special_handling == SH_NOSWAP_LD)
34977	      fputs ("special:load ", dump_file);
34978	    else if (insn_entry[i].special_handling == SH_NOSWAP_ST)
34979	      fputs ("special:store ", dump_file);
34980	    else if (insn_entry[i].special_handling == SH_EXTRACT)
34981	      fputs ("special:extract ", dump_file);
34982	    else if (insn_entry[i].special_handling == SH_SPLAT)
34983	      fputs ("special:splat ", dump_file);
34984	  }
34985	if (insn_entry[i].web_not_optimizable)
34986	  fputs ("unoptimizable ", dump_file);
34987	if (insn_entry[i].will_delete)
34988	  fputs ("delete ", dump_file);
34989	fputs ("\n", dump_file);
34990      }
34991  fputs ("\n", dump_file);
34992}
34993
34994/* Main entry point for this pass.  */
34995unsigned int
34996rs6000_analyze_swaps (function *fun)
34997{
34998  swap_web_entry *insn_entry;
34999  basic_block bb;
35000  rtx_insn *insn;
35001
35002  /* Dataflow analysis for use-def chains.  */
35003  df_set_flags (DF_RD_PRUNE_DEAD_DEFS);
35004  df_chain_add_problem (DF_DU_CHAIN | DF_UD_CHAIN);
35005  df_analyze ();
35006  df_set_flags (DF_DEFER_INSN_RESCAN);
35007
35008  /* Allocate structure to represent webs of insns.  */
35009  insn_entry = XCNEWVEC (swap_web_entry, get_max_uid ());
35010
35011  /* Walk the insns to gather basic data.  */
35012  FOR_ALL_BB_FN (bb, fun)
35013    FOR_BB_INSNS (bb, insn)
35014    {
35015      unsigned int uid = INSN_UID (insn);
35016      if (NONDEBUG_INSN_P (insn))
35017	{
35018	  insn_entry[uid].insn = insn;
35019
35020	  if (GET_CODE (insn) == CALL_INSN)
35021	    insn_entry[uid].is_call = 1;
35022
35023	  /* Walk the uses and defs to see if we mention vector regs.
35024	     Record any constraints on optimization of such mentions.  */
35025	  struct df_insn_info *insn_info = DF_INSN_INFO_GET (insn);
35026	  df_ref mention;
35027	  FOR_EACH_INSN_INFO_USE (mention, insn_info)
35028	    {
35029	      /* We use DF_REF_REAL_REG here to get inside any subregs.  */
35030	      machine_mode mode = GET_MODE (DF_REF_REAL_REG (mention));
35031
35032	      /* If a use gets its value from a call insn, it will be
35033		 a hard register and will look like (reg:V4SI 3 3).
35034		 The df analysis creates two mentions for GPR3 and GPR4,
35035		 both DImode.  We must recognize this and treat it as a
35036		 vector mention to ensure the call is unioned with this
35037		 use.  */
35038	      if (mode == DImode && DF_REF_INSN_INFO (mention))
35039		{
35040		  rtx feeder = DF_REF_INSN (mention);
35041		  /* FIXME:  It is pretty hard to get from the df mention
35042		     to the mode of the use in the insn.  We arbitrarily
35043		     pick a vector mode here, even though the use might
35044		     be a real DImode.  We can be too conservative
35045		     (create a web larger than necessary) because of
35046		     this, so consider eventually fixing this.  */
35047		  if (GET_CODE (feeder) == CALL_INSN)
35048		    mode = V4SImode;
35049		}
35050
35051	      if (VECTOR_MODE_P (mode) || mode == TImode)
35052		{
35053		  insn_entry[uid].is_relevant = 1;
35054		  if (mode == TImode || mode == V1TImode)
35055		    insn_entry[uid].is_128_int = 1;
35056		  if (DF_REF_INSN_INFO (mention))
35057		    insn_entry[uid].contains_subreg
35058		      = !rtx_equal_p (DF_REF_REG (mention),
35059				      DF_REF_REAL_REG (mention));
35060		  union_defs (insn_entry, insn, mention);
35061		}
35062	    }
35063	  FOR_EACH_INSN_INFO_DEF (mention, insn_info)
35064	    {
35065	      /* We use DF_REF_REAL_REG here to get inside any subregs.  */
35066	      machine_mode mode = GET_MODE (DF_REF_REAL_REG (mention));
35067
35068	      /* If we're loading up a hard vector register for a call,
35069		 it looks like (set (reg:V4SI 9 9) (...)).  The df
35070		 analysis creates two mentions for GPR9 and GPR10, both
35071		 DImode.  So relying on the mode from the mentions
35072		 isn't sufficient to ensure we union the call into the
35073		 web with the parameter setup code.  */
35074	      if (mode == DImode && GET_CODE (insn) == SET
35075		  && VECTOR_MODE_P (GET_MODE (SET_DEST (insn))))
35076		mode = GET_MODE (SET_DEST (insn));
35077
35078	      if (VECTOR_MODE_P (mode) || mode == TImode)
35079		{
35080		  insn_entry[uid].is_relevant = 1;
35081		  if (mode == TImode || mode == V1TImode)
35082		    insn_entry[uid].is_128_int = 1;
35083		  if (DF_REF_INSN_INFO (mention))
35084		    insn_entry[uid].contains_subreg
35085		      = !rtx_equal_p (DF_REF_REG (mention),
35086				      DF_REF_REAL_REG (mention));
35087		  /* REG_FUNCTION_VALUE_P is not valid for subregs. */
35088		  else if (REG_FUNCTION_VALUE_P (DF_REF_REG (mention)))
35089		    insn_entry[uid].is_live_out = 1;
35090		  union_uses (insn_entry, insn, mention);
35091		}
35092	    }
35093
35094	  if (insn_entry[uid].is_relevant)
35095	    {
35096	      /* Determine if this is a load or store.  */
35097	      insn_entry[uid].is_load = insn_is_load_p (insn);
35098	      insn_entry[uid].is_store = insn_is_store_p (insn);
35099
35100	      /* Determine if this is a doubleword swap.  If not,
35101		 determine whether it can legally be swapped.  */
35102	      if (insn_is_swap_p (insn))
35103		insn_entry[uid].is_swap = 1;
35104	      else
35105		{
35106		  unsigned int special = SH_NONE;
35107		  insn_entry[uid].is_swappable
35108		    = insn_is_swappable_p (insn_entry, insn, &special);
35109		  if (special != SH_NONE && insn_entry[uid].contains_subreg)
35110		    insn_entry[uid].is_swappable = 0;
35111		  else if (special != SH_NONE)
35112		    insn_entry[uid].special_handling = special;
35113		  else if (insn_entry[uid].contains_subreg)
35114		    insn_entry[uid].special_handling = SH_SUBREG;
35115		}
35116	    }
35117	}
35118    }
35119
35120  if (dump_file)
35121    {
35122      fprintf (dump_file, "\nSwap insn entry table when first built\n");
35123      dump_swap_insn_table (insn_entry);
35124    }
35125
35126  /* Record unoptimizable webs.  */
35127  unsigned e = get_max_uid (), i;
35128  for (i = 0; i < e; ++i)
35129    {
35130      if (!insn_entry[i].is_relevant)
35131	continue;
35132
35133      swap_web_entry *root
35134	= (swap_web_entry*)(&insn_entry[i])->unionfind_root ();
35135
35136      if (insn_entry[i].is_live_in || insn_entry[i].is_live_out
35137	  || (insn_entry[i].contains_subreg
35138	      && insn_entry[i].special_handling != SH_SUBREG)
35139	  || insn_entry[i].is_128_int || insn_entry[i].is_call
35140	  || !(insn_entry[i].is_swappable || insn_entry[i].is_swap))
35141	root->web_not_optimizable = 1;
35142
35143      /* If we have loads or stores that aren't permuting then the
35144	 optimization isn't appropriate.  */
35145      else if ((insn_entry[i].is_load || insn_entry[i].is_store)
35146	  && !insn_entry[i].is_swap && !insn_entry[i].is_swappable)
35147	root->web_not_optimizable = 1;
35148
35149      /* If we have permuting loads or stores that are not accompanied
35150	 by a register swap, the optimization isn't appropriate.  */
35151      else if (insn_entry[i].is_load && insn_entry[i].is_swap)
35152	{
35153	  rtx insn = insn_entry[i].insn;
35154	  struct df_insn_info *insn_info = DF_INSN_INFO_GET (insn);
35155	  df_ref def;
35156
35157	  FOR_EACH_INSN_INFO_DEF (def, insn_info)
35158	    {
35159	      struct df_link *link = DF_REF_CHAIN (def);
35160
35161	      if (!chain_contains_only_swaps (insn_entry, link, FOR_LOADS))
35162		{
35163		  root->web_not_optimizable = 1;
35164		  break;
35165		}
35166	    }
35167	}
35168      else if (insn_entry[i].is_store && insn_entry[i].is_swap)
35169	{
35170	  rtx insn = insn_entry[i].insn;
35171	  struct df_insn_info *insn_info = DF_INSN_INFO_GET (insn);
35172	  df_ref use;
35173
35174	  FOR_EACH_INSN_INFO_USE (use, insn_info)
35175	    {
35176	      struct df_link *link = DF_REF_CHAIN (use);
35177
35178	      if (!chain_contains_only_swaps (insn_entry, link, FOR_STORES))
35179		{
35180		  root->web_not_optimizable = 1;
35181		  break;
35182		}
35183	    }
35184	}
35185    }
35186
35187  if (dump_file)
35188    {
35189      fprintf (dump_file, "\nSwap insn entry table after web analysis\n");
35190      dump_swap_insn_table (insn_entry);
35191    }
35192
35193  /* For each load and store in an optimizable web (which implies
35194     the loads and stores are permuting), find the associated
35195     register swaps and mark them for removal.  Due to various
35196     optimizations we may mark the same swap more than once.  Also
35197     perform special handling for swappable insns that require it.  */
35198  for (i = 0; i < e; ++i)
35199    if ((insn_entry[i].is_load || insn_entry[i].is_store)
35200	&& insn_entry[i].is_swap)
35201      {
35202	swap_web_entry* root_entry
35203	  = (swap_web_entry*)((&insn_entry[i])->unionfind_root ());
35204	if (!root_entry->web_not_optimizable)
35205	  mark_swaps_for_removal (insn_entry, i);
35206      }
35207    else if (insn_entry[i].is_swappable && insn_entry[i].special_handling)
35208      {
35209	swap_web_entry* root_entry
35210	  = (swap_web_entry*)((&insn_entry[i])->unionfind_root ());
35211	if (!root_entry->web_not_optimizable)
35212	  handle_special_swappables (insn_entry, i);
35213      }
35214
35215  /* Now delete the swaps marked for removal.  */
35216  for (i = 0; i < e; ++i)
35217    if (insn_entry[i].will_delete)
35218      replace_swap_with_copy (insn_entry, i);
35219
35220  /* Clean up.  */
35221  free (insn_entry);
35222  return 0;
35223}
35224
35225const pass_data pass_data_analyze_swaps =
35226{
35227  RTL_PASS, /* type */
35228  "swaps", /* name */
35229  OPTGROUP_NONE, /* optinfo_flags */
35230  TV_NONE, /* tv_id */
35231  0, /* properties_required */
35232  0, /* properties_provided */
35233  0, /* properties_destroyed */
35234  0, /* todo_flags_start */
35235  TODO_df_finish, /* todo_flags_finish */
35236};
35237
35238class pass_analyze_swaps : public rtl_opt_pass
35239{
35240public:
35241  pass_analyze_swaps(gcc::context *ctxt)
35242    : rtl_opt_pass(pass_data_analyze_swaps, ctxt)
35243  {}
35244
35245  /* opt_pass methods: */
35246  virtual bool gate (function *)
35247    {
35248      return (optimize > 0 && !BYTES_BIG_ENDIAN && TARGET_VSX
35249	      && rs6000_optimize_swaps);
35250    }
35251
35252  virtual unsigned int execute (function *fun)
35253    {
35254      return rs6000_analyze_swaps (fun);
35255    }
35256
35257}; // class pass_analyze_swaps
35258
35259rtl_opt_pass *
35260make_pass_analyze_swaps (gcc::context *ctxt)
35261{
35262  return new pass_analyze_swaps (ctxt);
35263}
35264
35265#ifdef RS6000_GLIBC_ATOMIC_FENV
35266/* Function declarations for rs6000_atomic_assign_expand_fenv.  */
35267static tree atomic_hold_decl, atomic_clear_decl, atomic_update_decl;
35268#endif
35269
35270/* Implement TARGET_ATOMIC_ASSIGN_EXPAND_FENV hook.  */
35271
35272static void
35273rs6000_atomic_assign_expand_fenv (tree *hold, tree *clear, tree *update)
35274{
35275  if (!TARGET_HARD_FLOAT || !TARGET_FPRS)
35276    {
35277#ifdef RS6000_GLIBC_ATOMIC_FENV
35278      if (atomic_hold_decl == NULL_TREE)
35279	{
35280	  atomic_hold_decl
35281	    = build_decl (BUILTINS_LOCATION, FUNCTION_DECL,
35282			  get_identifier ("__atomic_feholdexcept"),
35283			  build_function_type_list (void_type_node,
35284						    double_ptr_type_node,
35285						    NULL_TREE));
35286	  TREE_PUBLIC (atomic_hold_decl) = 1;
35287	  DECL_EXTERNAL (atomic_hold_decl) = 1;
35288	}
35289
35290      if (atomic_clear_decl == NULL_TREE)
35291	{
35292	  atomic_clear_decl
35293	    = build_decl (BUILTINS_LOCATION, FUNCTION_DECL,
35294			  get_identifier ("__atomic_feclearexcept"),
35295			  build_function_type_list (void_type_node,
35296						    NULL_TREE));
35297	  TREE_PUBLIC (atomic_clear_decl) = 1;
35298	  DECL_EXTERNAL (atomic_clear_decl) = 1;
35299	}
35300
35301      tree const_double = build_qualified_type (double_type_node,
35302						TYPE_QUAL_CONST);
35303      tree const_double_ptr = build_pointer_type (const_double);
35304      if (atomic_update_decl == NULL_TREE)
35305	{
35306	  atomic_update_decl
35307	    = build_decl (BUILTINS_LOCATION, FUNCTION_DECL,
35308			  get_identifier ("__atomic_feupdateenv"),
35309			  build_function_type_list (void_type_node,
35310						    const_double_ptr,
35311						    NULL_TREE));
35312	  TREE_PUBLIC (atomic_update_decl) = 1;
35313	  DECL_EXTERNAL (atomic_update_decl) = 1;
35314	}
35315
35316      tree fenv_var = create_tmp_var (double_type_node);
35317      mark_addressable (fenv_var);
35318      tree fenv_addr = build1 (ADDR_EXPR, double_ptr_type_node, fenv_var);
35319
35320      *hold = build_call_expr (atomic_hold_decl, 1, fenv_addr);
35321      *clear = build_call_expr (atomic_clear_decl, 0);
35322      *update = build_call_expr (atomic_update_decl, 1,
35323				 fold_convert (const_double_ptr, fenv_addr));
35324#endif
35325      return;
35326    }
35327
35328  tree mffs = rs6000_builtin_decls[RS6000_BUILTIN_MFFS];
35329  tree mtfsf = rs6000_builtin_decls[RS6000_BUILTIN_MTFSF];
35330  tree call_mffs = build_call_expr (mffs, 0);
35331
35332  /* Generates the equivalent of feholdexcept (&fenv_var)
35333
35334     *fenv_var = __builtin_mffs ();
35335     double fenv_hold;
35336     *(uint64_t*)&fenv_hold = *(uint64_t*)fenv_var & 0xffffffff00000007LL;
35337     __builtin_mtfsf (0xff, fenv_hold);  */
35338
35339  /* Mask to clear everything except for the rounding modes and non-IEEE
35340     arithmetic flag.  */
35341  const unsigned HOST_WIDE_INT hold_exception_mask =
35342    HOST_WIDE_INT_C (0xffffffff00000007);
35343
35344  tree fenv_var = create_tmp_var (double_type_node);
35345
35346  tree hold_mffs = build2 (MODIFY_EXPR, void_type_node, fenv_var, call_mffs);
35347
35348  tree fenv_llu = build1 (VIEW_CONVERT_EXPR, uint64_type_node, fenv_var);
35349  tree fenv_llu_and = build2 (BIT_AND_EXPR, uint64_type_node, fenv_llu,
35350			      build_int_cst (uint64_type_node,
35351					     hold_exception_mask));
35352
35353  tree fenv_hold_mtfsf = build1 (VIEW_CONVERT_EXPR, double_type_node,
35354				 fenv_llu_and);
35355
35356  tree hold_mtfsf = build_call_expr (mtfsf, 2,
35357				     build_int_cst (unsigned_type_node, 0xff),
35358				     fenv_hold_mtfsf);
35359
35360  *hold = build2 (COMPOUND_EXPR, void_type_node, hold_mffs, hold_mtfsf);
35361
35362  /* Generates the equivalent of feclearexcept (FE_ALL_EXCEPT):
35363
35364     double fenv_clear = __builtin_mffs ();
35365     *(uint64_t)&fenv_clear &= 0xffffffff00000000LL;
35366     __builtin_mtfsf (0xff, fenv_clear);  */
35367
35368  /* Mask to clear everything except for the rounding modes and non-IEEE
35369     arithmetic flag.  */
35370  const unsigned HOST_WIDE_INT clear_exception_mask =
35371    HOST_WIDE_INT_C (0xffffffff00000000);
35372
35373  tree fenv_clear = create_tmp_var (double_type_node);
35374
35375  tree clear_mffs = build2 (MODIFY_EXPR, void_type_node, fenv_clear, call_mffs);
35376
35377  tree fenv_clean_llu = build1 (VIEW_CONVERT_EXPR, uint64_type_node, fenv_clear);
35378  tree fenv_clear_llu_and = build2 (BIT_AND_EXPR, uint64_type_node,
35379				    fenv_clean_llu,
35380				    build_int_cst (uint64_type_node,
35381						   clear_exception_mask));
35382
35383  tree fenv_clear_mtfsf = build1 (VIEW_CONVERT_EXPR, double_type_node,
35384				  fenv_clear_llu_and);
35385
35386  tree clear_mtfsf = build_call_expr (mtfsf, 2,
35387				      build_int_cst (unsigned_type_node, 0xff),
35388				      fenv_clear_mtfsf);
35389
35390  *clear = build2 (COMPOUND_EXPR, void_type_node, clear_mffs, clear_mtfsf);
35391
35392  /* Generates the equivalent of feupdateenv (&fenv_var)
35393
35394     double old_fenv = __builtin_mffs ();
35395     double fenv_update;
35396     *(uint64_t*)&fenv_update = (*(uint64_t*)&old & 0xffffffff1fffff00LL) |
35397                                (*(uint64_t*)fenv_var 0x1ff80fff);
35398     __builtin_mtfsf (0xff, fenv_update);  */
35399
35400  const unsigned HOST_WIDE_INT update_exception_mask =
35401    HOST_WIDE_INT_C (0xffffffff1fffff00);
35402  const unsigned HOST_WIDE_INT new_exception_mask =
35403    HOST_WIDE_INT_C (0x1ff80fff);
35404
35405  tree old_fenv = create_tmp_var (double_type_node);
35406  tree update_mffs = build2 (MODIFY_EXPR, void_type_node, old_fenv, call_mffs);
35407
35408  tree old_llu = build1 (VIEW_CONVERT_EXPR, uint64_type_node, old_fenv);
35409  tree old_llu_and = build2 (BIT_AND_EXPR, uint64_type_node, old_llu,
35410			     build_int_cst (uint64_type_node,
35411					    update_exception_mask));
35412
35413  tree new_llu_and = build2 (BIT_AND_EXPR, uint64_type_node, fenv_llu,
35414			     build_int_cst (uint64_type_node,
35415					    new_exception_mask));
35416
35417  tree new_llu_mask = build2 (BIT_IOR_EXPR, uint64_type_node,
35418			      old_llu_and, new_llu_and);
35419
35420  tree fenv_update_mtfsf = build1 (VIEW_CONVERT_EXPR, double_type_node,
35421				   new_llu_mask);
35422
35423  tree update_mtfsf = build_call_expr (mtfsf, 2,
35424				       build_int_cst (unsigned_type_node, 0xff),
35425				       fenv_update_mtfsf);
35426
35427  *update = build2 (COMPOUND_EXPR, void_type_node, update_mffs, update_mtfsf);
35428}
35429
35430
35431struct gcc_target targetm = TARGET_INITIALIZER;
35432
35433#include "gt-rs6000.h"
35434