* tree-ssa-loop-ivopts.c (ivopts_estimate_reg_pressure): New
[official-gcc.git] / gcc / gimple-fold.c
blobd12f9d053c9a5f7e83065a5570640244a242c55a
1 /* Statement simplification on GIMPLE.
2 Copyright (C) 2010-2017 Free Software Foundation, Inc.
3 Split out from tree-ssa-ccp.c.
5 This file is part of GCC.
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 by the
9 Free Software Foundation; either version 3, or (at your option) any
10 later version.
12 GCC is distributed in the hope that it will be useful, but WITHOUT
13 ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
14 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
15 for more details.
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/>. */
21 #include "config.h"
22 #include "system.h"
23 #include "coretypes.h"
24 #include "backend.h"
25 #include "target.h"
26 #include "rtl.h"
27 #include "tree.h"
28 #include "gimple.h"
29 #include "predict.h"
30 #include "ssa.h"
31 #include "cgraph.h"
32 #include "gimple-pretty-print.h"
33 #include "fold-const.h"
34 #include "stmt.h"
35 #include "expr.h"
36 #include "stor-layout.h"
37 #include "dumpfile.h"
38 #include "gimple-fold.h"
39 #include "gimplify.h"
40 #include "gimple-iterator.h"
41 #include "tree-into-ssa.h"
42 #include "tree-dfa.h"
43 #include "tree-ssa.h"
44 #include "tree-ssa-propagate.h"
45 #include "ipa-utils.h"
46 #include "tree-ssa-address.h"
47 #include "langhooks.h"
48 #include "gimplify-me.h"
49 #include "dbgcnt.h"
50 #include "builtins.h"
51 #include "tree-eh.h"
52 #include "gimple-match.h"
53 #include "gomp-constants.h"
54 #include "optabs-query.h"
55 #include "omp-general.h"
56 #include "ipa-chkp.h"
57 #include "tree-cfg.h"
58 #include "fold-const-call.h"
60 /* Return true when DECL can be referenced from current unit.
61 FROM_DECL (if non-null) specify constructor of variable DECL was taken from.
62 We can get declarations that are not possible to reference for various
63 reasons:
65 1) When analyzing C++ virtual tables.
66 C++ virtual tables do have known constructors even
67 when they are keyed to other compilation unit.
68 Those tables can contain pointers to methods and vars
69 in other units. Those methods have both STATIC and EXTERNAL
70 set.
71 2) In WHOPR mode devirtualization might lead to reference
72 to method that was partitioned elsehwere.
73 In this case we have static VAR_DECL or FUNCTION_DECL
74 that has no corresponding callgraph/varpool node
75 declaring the body.
76 3) COMDAT functions referred by external vtables that
77 we devirtualize only during final compilation stage.
78 At this time we already decided that we will not output
79 the function body and thus we can't reference the symbol
80 directly. */
82 static bool
83 can_refer_decl_in_current_unit_p (tree decl, tree from_decl)
85 varpool_node *vnode;
86 struct cgraph_node *node;
87 symtab_node *snode;
89 if (DECL_ABSTRACT_P (decl))
90 return false;
92 /* We are concerned only about static/external vars and functions. */
93 if ((!TREE_STATIC (decl) && !DECL_EXTERNAL (decl))
94 || !VAR_OR_FUNCTION_DECL_P (decl))
95 return true;
97 /* Static objects can be referred only if they was not optimized out yet. */
98 if (!TREE_PUBLIC (decl) && !DECL_EXTERNAL (decl))
100 /* Before we start optimizing unreachable code we can be sure all
101 static objects are defined. */
102 if (symtab->function_flags_ready)
103 return true;
104 snode = symtab_node::get (decl);
105 if (!snode || !snode->definition)
106 return false;
107 node = dyn_cast <cgraph_node *> (snode);
108 return !node || !node->global.inlined_to;
111 /* We will later output the initializer, so we can refer to it.
112 So we are concerned only when DECL comes from initializer of
113 external var or var that has been optimized out. */
114 if (!from_decl
115 || !VAR_P (from_decl)
116 || (!DECL_EXTERNAL (from_decl)
117 && (vnode = varpool_node::get (from_decl)) != NULL
118 && vnode->definition)
119 || (flag_ltrans
120 && (vnode = varpool_node::get (from_decl)) != NULL
121 && vnode->in_other_partition))
122 return true;
123 /* We are folding reference from external vtable. The vtable may reffer
124 to a symbol keyed to other compilation unit. The other compilation
125 unit may be in separate DSO and the symbol may be hidden. */
126 if (DECL_VISIBILITY_SPECIFIED (decl)
127 && DECL_EXTERNAL (decl)
128 && DECL_VISIBILITY (decl) != VISIBILITY_DEFAULT
129 && (!(snode = symtab_node::get (decl)) || !snode->in_other_partition))
130 return false;
131 /* When function is public, we always can introduce new reference.
132 Exception are the COMDAT functions where introducing a direct
133 reference imply need to include function body in the curren tunit. */
134 if (TREE_PUBLIC (decl) && !DECL_COMDAT (decl))
135 return true;
136 /* We have COMDAT. We are going to check if we still have definition
137 or if the definition is going to be output in other partition.
138 Bypass this when gimplifying; all needed functions will be produced.
140 As observed in PR20991 for already optimized out comdat virtual functions
141 it may be tempting to not necessarily give up because the copy will be
142 output elsewhere when corresponding vtable is output.
143 This is however not possible - ABI specify that COMDATs are output in
144 units where they are used and when the other unit was compiled with LTO
145 it is possible that vtable was kept public while the function itself
146 was privatized. */
147 if (!symtab->function_flags_ready)
148 return true;
150 snode = symtab_node::get (decl);
151 if (!snode
152 || ((!snode->definition || DECL_EXTERNAL (decl))
153 && (!snode->in_other_partition
154 || (!snode->forced_by_abi && !snode->force_output))))
155 return false;
156 node = dyn_cast <cgraph_node *> (snode);
157 return !node || !node->global.inlined_to;
160 /* Create a temporary for TYPE for a statement STMT. If the current function
161 is in SSA form, a SSA name is created. Otherwise a temporary register
162 is made. */
164 tree
165 create_tmp_reg_or_ssa_name (tree type, gimple *stmt)
167 if (gimple_in_ssa_p (cfun))
168 return make_ssa_name (type, stmt);
169 else
170 return create_tmp_reg (type);
173 /* CVAL is value taken from DECL_INITIAL of variable. Try to transform it into
174 acceptable form for is_gimple_min_invariant.
175 FROM_DECL (if non-NULL) specify variable whose constructor contains CVAL. */
177 tree
178 canonicalize_constructor_val (tree cval, tree from_decl)
180 tree orig_cval = cval;
181 STRIP_NOPS (cval);
182 if (TREE_CODE (cval) == POINTER_PLUS_EXPR
183 && TREE_CODE (TREE_OPERAND (cval, 1)) == INTEGER_CST)
185 tree ptr = TREE_OPERAND (cval, 0);
186 if (is_gimple_min_invariant (ptr))
187 cval = build1_loc (EXPR_LOCATION (cval),
188 ADDR_EXPR, TREE_TYPE (ptr),
189 fold_build2 (MEM_REF, TREE_TYPE (TREE_TYPE (ptr)),
190 ptr,
191 fold_convert (ptr_type_node,
192 TREE_OPERAND (cval, 1))));
194 if (TREE_CODE (cval) == ADDR_EXPR)
196 tree base = NULL_TREE;
197 if (TREE_CODE (TREE_OPERAND (cval, 0)) == COMPOUND_LITERAL_EXPR)
199 base = COMPOUND_LITERAL_EXPR_DECL (TREE_OPERAND (cval, 0));
200 if (base)
201 TREE_OPERAND (cval, 0) = base;
203 else
204 base = get_base_address (TREE_OPERAND (cval, 0));
205 if (!base)
206 return NULL_TREE;
208 if (VAR_OR_FUNCTION_DECL_P (base)
209 && !can_refer_decl_in_current_unit_p (base, from_decl))
210 return NULL_TREE;
211 if (TREE_TYPE (base) == error_mark_node)
212 return NULL_TREE;
213 if (VAR_P (base))
214 TREE_ADDRESSABLE (base) = 1;
215 else if (TREE_CODE (base) == FUNCTION_DECL)
217 /* Make sure we create a cgraph node for functions we'll reference.
218 They can be non-existent if the reference comes from an entry
219 of an external vtable for example. */
220 cgraph_node::get_create (base);
222 /* Fixup types in global initializers. */
223 if (TREE_TYPE (TREE_TYPE (cval)) != TREE_TYPE (TREE_OPERAND (cval, 0)))
224 cval = build_fold_addr_expr (TREE_OPERAND (cval, 0));
226 if (!useless_type_conversion_p (TREE_TYPE (orig_cval), TREE_TYPE (cval)))
227 cval = fold_convert (TREE_TYPE (orig_cval), cval);
228 return cval;
230 if (TREE_OVERFLOW_P (cval))
231 return drop_tree_overflow (cval);
232 return orig_cval;
235 /* If SYM is a constant variable with known value, return the value.
236 NULL_TREE is returned otherwise. */
238 tree
239 get_symbol_constant_value (tree sym)
241 tree val = ctor_for_folding (sym);
242 if (val != error_mark_node)
244 if (val)
246 val = canonicalize_constructor_val (unshare_expr (val), sym);
247 if (val && is_gimple_min_invariant (val))
248 return val;
249 else
250 return NULL_TREE;
252 /* Variables declared 'const' without an initializer
253 have zero as the initializer if they may not be
254 overridden at link or run time. */
255 if (!val
256 && is_gimple_reg_type (TREE_TYPE (sym)))
257 return build_zero_cst (TREE_TYPE (sym));
260 return NULL_TREE;
265 /* Subroutine of fold_stmt. We perform several simplifications of the
266 memory reference tree EXPR and make sure to re-gimplify them properly
267 after propagation of constant addresses. IS_LHS is true if the
268 reference is supposed to be an lvalue. */
270 static tree
271 maybe_fold_reference (tree expr, bool is_lhs)
273 tree result;
275 if ((TREE_CODE (expr) == VIEW_CONVERT_EXPR
276 || TREE_CODE (expr) == REALPART_EXPR
277 || TREE_CODE (expr) == IMAGPART_EXPR)
278 && CONSTANT_CLASS_P (TREE_OPERAND (expr, 0)))
279 return fold_unary_loc (EXPR_LOCATION (expr),
280 TREE_CODE (expr),
281 TREE_TYPE (expr),
282 TREE_OPERAND (expr, 0));
283 else if (TREE_CODE (expr) == BIT_FIELD_REF
284 && CONSTANT_CLASS_P (TREE_OPERAND (expr, 0)))
285 return fold_ternary_loc (EXPR_LOCATION (expr),
286 TREE_CODE (expr),
287 TREE_TYPE (expr),
288 TREE_OPERAND (expr, 0),
289 TREE_OPERAND (expr, 1),
290 TREE_OPERAND (expr, 2));
292 if (!is_lhs
293 && (result = fold_const_aggregate_ref (expr))
294 && is_gimple_min_invariant (result))
295 return result;
297 return NULL_TREE;
301 /* Attempt to fold an assignment statement pointed-to by SI. Returns a
302 replacement rhs for the statement or NULL_TREE if no simplification
303 could be made. It is assumed that the operands have been previously
304 folded. */
306 static tree
307 fold_gimple_assign (gimple_stmt_iterator *si)
309 gimple *stmt = gsi_stmt (*si);
310 enum tree_code subcode = gimple_assign_rhs_code (stmt);
311 location_t loc = gimple_location (stmt);
313 tree result = NULL_TREE;
315 switch (get_gimple_rhs_class (subcode))
317 case GIMPLE_SINGLE_RHS:
319 tree rhs = gimple_assign_rhs1 (stmt);
321 if (TREE_CLOBBER_P (rhs))
322 return NULL_TREE;
324 if (REFERENCE_CLASS_P (rhs))
325 return maybe_fold_reference (rhs, false);
327 else if (TREE_CODE (rhs) == OBJ_TYPE_REF)
329 tree val = OBJ_TYPE_REF_EXPR (rhs);
330 if (is_gimple_min_invariant (val))
331 return val;
332 else if (flag_devirtualize && virtual_method_call_p (rhs))
334 bool final;
335 vec <cgraph_node *>targets
336 = possible_polymorphic_call_targets (rhs, stmt, &final);
337 if (final && targets.length () <= 1 && dbg_cnt (devirt))
339 if (dump_enabled_p ())
341 location_t loc = gimple_location_safe (stmt);
342 dump_printf_loc (MSG_OPTIMIZED_LOCATIONS, loc,
343 "resolving virtual function address "
344 "reference to function %s\n",
345 targets.length () == 1
346 ? targets[0]->name ()
347 : "NULL");
349 if (targets.length () == 1)
351 val = fold_convert (TREE_TYPE (val),
352 build_fold_addr_expr_loc
353 (loc, targets[0]->decl));
354 STRIP_USELESS_TYPE_CONVERSION (val);
356 else
357 /* We can not use __builtin_unreachable here because it
358 can not have address taken. */
359 val = build_int_cst (TREE_TYPE (val), 0);
360 return val;
365 else if (TREE_CODE (rhs) == ADDR_EXPR)
367 tree ref = TREE_OPERAND (rhs, 0);
368 tree tem = maybe_fold_reference (ref, true);
369 if (tem
370 && TREE_CODE (tem) == MEM_REF
371 && integer_zerop (TREE_OPERAND (tem, 1)))
372 result = fold_convert (TREE_TYPE (rhs), TREE_OPERAND (tem, 0));
373 else if (tem)
374 result = fold_convert (TREE_TYPE (rhs),
375 build_fold_addr_expr_loc (loc, tem));
376 else if (TREE_CODE (ref) == MEM_REF
377 && integer_zerop (TREE_OPERAND (ref, 1)))
378 result = fold_convert (TREE_TYPE (rhs), TREE_OPERAND (ref, 0));
380 if (result)
382 /* Strip away useless type conversions. Both the
383 NON_LVALUE_EXPR that may have been added by fold, and
384 "useless" type conversions that might now be apparent
385 due to propagation. */
386 STRIP_USELESS_TYPE_CONVERSION (result);
388 if (result != rhs && valid_gimple_rhs_p (result))
389 return result;
393 else if (TREE_CODE (rhs) == CONSTRUCTOR
394 && TREE_CODE (TREE_TYPE (rhs)) == VECTOR_TYPE)
396 /* Fold a constant vector CONSTRUCTOR to VECTOR_CST. */
397 unsigned i;
398 tree val;
400 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (rhs), i, val)
401 if (! CONSTANT_CLASS_P (val))
402 return NULL_TREE;
404 return build_vector_from_ctor (TREE_TYPE (rhs),
405 CONSTRUCTOR_ELTS (rhs));
408 else if (DECL_P (rhs))
409 return get_symbol_constant_value (rhs);
411 break;
413 case GIMPLE_UNARY_RHS:
414 break;
416 case GIMPLE_BINARY_RHS:
417 break;
419 case GIMPLE_TERNARY_RHS:
420 result = fold_ternary_loc (loc, subcode,
421 TREE_TYPE (gimple_assign_lhs (stmt)),
422 gimple_assign_rhs1 (stmt),
423 gimple_assign_rhs2 (stmt),
424 gimple_assign_rhs3 (stmt));
426 if (result)
428 STRIP_USELESS_TYPE_CONVERSION (result);
429 if (valid_gimple_rhs_p (result))
430 return result;
432 break;
434 case GIMPLE_INVALID_RHS:
435 gcc_unreachable ();
438 return NULL_TREE;
442 /* Replace a statement at *SI_P with a sequence of statements in STMTS,
443 adjusting the replacement stmts location and virtual operands.
444 If the statement has a lhs the last stmt in the sequence is expected
445 to assign to that lhs. */
447 static void
448 gsi_replace_with_seq_vops (gimple_stmt_iterator *si_p, gimple_seq stmts)
450 gimple *stmt = gsi_stmt (*si_p);
452 if (gimple_has_location (stmt))
453 annotate_all_with_location (stmts, gimple_location (stmt));
455 /* First iterate over the replacement statements backward, assigning
456 virtual operands to their defining statements. */
457 gimple *laststore = NULL;
458 for (gimple_stmt_iterator i = gsi_last (stmts);
459 !gsi_end_p (i); gsi_prev (&i))
461 gimple *new_stmt = gsi_stmt (i);
462 if ((gimple_assign_single_p (new_stmt)
463 && !is_gimple_reg (gimple_assign_lhs (new_stmt)))
464 || (is_gimple_call (new_stmt)
465 && (gimple_call_flags (new_stmt)
466 & (ECF_NOVOPS | ECF_PURE | ECF_CONST | ECF_NORETURN)) == 0))
468 tree vdef;
469 if (!laststore)
470 vdef = gimple_vdef (stmt);
471 else
472 vdef = make_ssa_name (gimple_vop (cfun), new_stmt);
473 gimple_set_vdef (new_stmt, vdef);
474 if (vdef && TREE_CODE (vdef) == SSA_NAME)
475 SSA_NAME_DEF_STMT (vdef) = new_stmt;
476 laststore = new_stmt;
480 /* Second iterate over the statements forward, assigning virtual
481 operands to their uses. */
482 tree reaching_vuse = gimple_vuse (stmt);
483 for (gimple_stmt_iterator i = gsi_start (stmts);
484 !gsi_end_p (i); gsi_next (&i))
486 gimple *new_stmt = gsi_stmt (i);
487 /* If the new statement possibly has a VUSE, update it with exact SSA
488 name we know will reach this one. */
489 if (gimple_has_mem_ops (new_stmt))
490 gimple_set_vuse (new_stmt, reaching_vuse);
491 gimple_set_modified (new_stmt, true);
492 if (gimple_vdef (new_stmt))
493 reaching_vuse = gimple_vdef (new_stmt);
496 /* If the new sequence does not do a store release the virtual
497 definition of the original statement. */
498 if (reaching_vuse
499 && reaching_vuse == gimple_vuse (stmt))
501 tree vdef = gimple_vdef (stmt);
502 if (vdef
503 && TREE_CODE (vdef) == SSA_NAME)
505 unlink_stmt_vdef (stmt);
506 release_ssa_name (vdef);
510 /* Finally replace the original statement with the sequence. */
511 gsi_replace_with_seq (si_p, stmts, false);
514 /* Convert EXPR into a GIMPLE value suitable for substitution on the
515 RHS of an assignment. Insert the necessary statements before
516 iterator *SI_P. The statement at *SI_P, which must be a GIMPLE_CALL
517 is replaced. If the call is expected to produces a result, then it
518 is replaced by an assignment of the new RHS to the result variable.
519 If the result is to be ignored, then the call is replaced by a
520 GIMPLE_NOP. A proper VDEF chain is retained by making the first
521 VUSE and the last VDEF of the whole sequence be the same as the replaced
522 statement and using new SSA names for stores in between. */
524 void
525 gimplify_and_update_call_from_tree (gimple_stmt_iterator *si_p, tree expr)
527 tree lhs;
528 gimple *stmt, *new_stmt;
529 gimple_stmt_iterator i;
530 gimple_seq stmts = NULL;
532 stmt = gsi_stmt (*si_p);
534 gcc_assert (is_gimple_call (stmt));
536 push_gimplify_context (gimple_in_ssa_p (cfun));
538 lhs = gimple_call_lhs (stmt);
539 if (lhs == NULL_TREE)
541 gimplify_and_add (expr, &stmts);
542 /* We can end up with folding a memcpy of an empty class assignment
543 which gets optimized away by C++ gimplification. */
544 if (gimple_seq_empty_p (stmts))
546 pop_gimplify_context (NULL);
547 if (gimple_in_ssa_p (cfun))
549 unlink_stmt_vdef (stmt);
550 release_defs (stmt);
552 gsi_replace (si_p, gimple_build_nop (), false);
553 return;
556 else
558 tree tmp = force_gimple_operand (expr, &stmts, false, NULL_TREE);
559 new_stmt = gimple_build_assign (lhs, tmp);
560 i = gsi_last (stmts);
561 gsi_insert_after_without_update (&i, new_stmt,
562 GSI_CONTINUE_LINKING);
565 pop_gimplify_context (NULL);
567 gsi_replace_with_seq_vops (si_p, stmts);
571 /* Replace the call at *GSI with the gimple value VAL. */
573 static void
574 replace_call_with_value (gimple_stmt_iterator *gsi, tree val)
576 gimple *stmt = gsi_stmt (*gsi);
577 tree lhs = gimple_call_lhs (stmt);
578 gimple *repl;
579 if (lhs)
581 if (!useless_type_conversion_p (TREE_TYPE (lhs), TREE_TYPE (val)))
582 val = fold_convert (TREE_TYPE (lhs), val);
583 repl = gimple_build_assign (lhs, val);
585 else
586 repl = gimple_build_nop ();
587 tree vdef = gimple_vdef (stmt);
588 if (vdef && TREE_CODE (vdef) == SSA_NAME)
590 unlink_stmt_vdef (stmt);
591 release_ssa_name (vdef);
593 gsi_replace (gsi, repl, false);
596 /* Replace the call at *GSI with the new call REPL and fold that
597 again. */
599 static void
600 replace_call_with_call_and_fold (gimple_stmt_iterator *gsi, gimple *repl)
602 gimple *stmt = gsi_stmt (*gsi);
603 gimple_call_set_lhs (repl, gimple_call_lhs (stmt));
604 gimple_set_location (repl, gimple_location (stmt));
605 if (gimple_vdef (stmt)
606 && TREE_CODE (gimple_vdef (stmt)) == SSA_NAME)
608 gimple_set_vdef (repl, gimple_vdef (stmt));
609 gimple_set_vuse (repl, gimple_vuse (stmt));
610 SSA_NAME_DEF_STMT (gimple_vdef (repl)) = repl;
612 gsi_replace (gsi, repl, false);
613 fold_stmt (gsi);
616 /* Return true if VAR is a VAR_DECL or a component thereof. */
618 static bool
619 var_decl_component_p (tree var)
621 tree inner = var;
622 while (handled_component_p (inner))
623 inner = TREE_OPERAND (inner, 0);
624 return SSA_VAR_P (inner);
627 /* Fold function call to builtin mem{{,p}cpy,move}. Return
628 false if no simplification can be made.
629 If ENDP is 0, return DEST (like memcpy).
630 If ENDP is 1, return DEST+LEN (like mempcpy).
631 If ENDP is 2, return DEST+LEN-1 (like stpcpy).
632 If ENDP is 3, return DEST, additionally *SRC and *DEST may overlap
633 (memmove). */
635 static bool
636 gimple_fold_builtin_memory_op (gimple_stmt_iterator *gsi,
637 tree dest, tree src, int endp)
639 gimple *stmt = gsi_stmt (*gsi);
640 tree lhs = gimple_call_lhs (stmt);
641 tree len = gimple_call_arg (stmt, 2);
642 tree destvar, srcvar;
643 location_t loc = gimple_location (stmt);
645 /* If the LEN parameter is zero, return DEST. */
646 if (integer_zerop (len))
648 gimple *repl;
649 if (gimple_call_lhs (stmt))
650 repl = gimple_build_assign (gimple_call_lhs (stmt), dest);
651 else
652 repl = gimple_build_nop ();
653 tree vdef = gimple_vdef (stmt);
654 if (vdef && TREE_CODE (vdef) == SSA_NAME)
656 unlink_stmt_vdef (stmt);
657 release_ssa_name (vdef);
659 gsi_replace (gsi, repl, false);
660 return true;
663 /* If SRC and DEST are the same (and not volatile), return
664 DEST{,+LEN,+LEN-1}. */
665 if (operand_equal_p (src, dest, 0))
667 unlink_stmt_vdef (stmt);
668 if (gimple_vdef (stmt) && TREE_CODE (gimple_vdef (stmt)) == SSA_NAME)
669 release_ssa_name (gimple_vdef (stmt));
670 if (!lhs)
672 gsi_replace (gsi, gimple_build_nop (), false);
673 return true;
675 goto done;
677 else
679 tree srctype, desttype;
680 unsigned int src_align, dest_align;
681 tree off0;
683 /* Inlining of memcpy/memmove may cause bounds lost (if we copy
684 pointers as wide integer) and also may result in huge function
685 size because of inlined bounds copy. Thus don't inline for
686 functions we want to instrument. */
687 if (flag_check_pointer_bounds
688 && chkp_instrumentable_p (cfun->decl)
689 /* Even if data may contain pointers we can inline if copy
690 less than a pointer size. */
691 && (!tree_fits_uhwi_p (len)
692 || compare_tree_int (len, POINTER_SIZE_UNITS) >= 0))
693 return false;
695 /* Build accesses at offset zero with a ref-all character type. */
696 off0 = build_int_cst (build_pointer_type_for_mode (char_type_node,
697 ptr_mode, true), 0);
699 /* If we can perform the copy efficiently with first doing all loads
700 and then all stores inline it that way. Currently efficiently
701 means that we can load all the memory into a single integer
702 register which is what MOVE_MAX gives us. */
703 src_align = get_pointer_alignment (src);
704 dest_align = get_pointer_alignment (dest);
705 if (tree_fits_uhwi_p (len)
706 && compare_tree_int (len, MOVE_MAX) <= 0
707 /* ??? Don't transform copies from strings with known length this
708 confuses the tree-ssa-strlen.c. This doesn't handle
709 the case in gcc.dg/strlenopt-8.c which is XFAILed for that
710 reason. */
711 && !c_strlen (src, 2))
713 unsigned ilen = tree_to_uhwi (len);
714 if (pow2p_hwi (ilen))
716 tree type = lang_hooks.types.type_for_size (ilen * 8, 1);
717 if (type
718 && TYPE_MODE (type) != BLKmode
719 && (GET_MODE_SIZE (TYPE_MODE (type)) * BITS_PER_UNIT
720 == ilen * 8)
721 /* If the destination pointer is not aligned we must be able
722 to emit an unaligned store. */
723 && (dest_align >= GET_MODE_ALIGNMENT (TYPE_MODE (type))
724 || !SLOW_UNALIGNED_ACCESS (TYPE_MODE (type), dest_align)
725 || (optab_handler (movmisalign_optab, TYPE_MODE (type))
726 != CODE_FOR_nothing)))
728 tree srctype = type;
729 tree desttype = type;
730 if (src_align < GET_MODE_ALIGNMENT (TYPE_MODE (type)))
731 srctype = build_aligned_type (type, src_align);
732 tree srcmem = fold_build2 (MEM_REF, srctype, src, off0);
733 tree tem = fold_const_aggregate_ref (srcmem);
734 if (tem)
735 srcmem = tem;
736 else if (src_align < GET_MODE_ALIGNMENT (TYPE_MODE (type))
737 && SLOW_UNALIGNED_ACCESS (TYPE_MODE (type),
738 src_align)
739 && (optab_handler (movmisalign_optab,
740 TYPE_MODE (type))
741 == CODE_FOR_nothing))
742 srcmem = NULL_TREE;
743 if (srcmem)
745 gimple *new_stmt;
746 if (is_gimple_reg_type (TREE_TYPE (srcmem)))
748 new_stmt = gimple_build_assign (NULL_TREE, srcmem);
749 srcmem
750 = create_tmp_reg_or_ssa_name (TREE_TYPE (srcmem),
751 new_stmt);
752 gimple_assign_set_lhs (new_stmt, srcmem);
753 gimple_set_vuse (new_stmt, gimple_vuse (stmt));
754 gsi_insert_before (gsi, new_stmt, GSI_SAME_STMT);
756 if (dest_align < GET_MODE_ALIGNMENT (TYPE_MODE (type)))
757 desttype = build_aligned_type (type, dest_align);
758 new_stmt
759 = gimple_build_assign (fold_build2 (MEM_REF, desttype,
760 dest, off0),
761 srcmem);
762 gimple_set_vuse (new_stmt, gimple_vuse (stmt));
763 gimple_set_vdef (new_stmt, gimple_vdef (stmt));
764 if (gimple_vdef (new_stmt)
765 && TREE_CODE (gimple_vdef (new_stmt)) == SSA_NAME)
766 SSA_NAME_DEF_STMT (gimple_vdef (new_stmt)) = new_stmt;
767 if (!lhs)
769 gsi_replace (gsi, new_stmt, false);
770 return true;
772 gsi_insert_before (gsi, new_stmt, GSI_SAME_STMT);
773 goto done;
779 if (endp == 3)
781 /* Both DEST and SRC must be pointer types.
782 ??? This is what old code did. Is the testing for pointer types
783 really mandatory?
785 If either SRC is readonly or length is 1, we can use memcpy. */
786 if (!dest_align || !src_align)
787 return false;
788 if (readonly_data_expr (src)
789 || (tree_fits_uhwi_p (len)
790 && (MIN (src_align, dest_align) / BITS_PER_UNIT
791 >= tree_to_uhwi (len))))
793 tree fn = builtin_decl_implicit (BUILT_IN_MEMCPY);
794 if (!fn)
795 return false;
796 gimple_call_set_fndecl (stmt, fn);
797 gimple_call_set_arg (stmt, 0, dest);
798 gimple_call_set_arg (stmt, 1, src);
799 fold_stmt (gsi);
800 return true;
803 /* If *src and *dest can't overlap, optimize into memcpy as well. */
804 if (TREE_CODE (src) == ADDR_EXPR
805 && TREE_CODE (dest) == ADDR_EXPR)
807 tree src_base, dest_base, fn;
808 HOST_WIDE_INT src_offset = 0, dest_offset = 0;
809 HOST_WIDE_INT maxsize;
811 srcvar = TREE_OPERAND (src, 0);
812 src_base = get_addr_base_and_unit_offset (srcvar, &src_offset);
813 if (src_base == NULL)
814 src_base = srcvar;
815 destvar = TREE_OPERAND (dest, 0);
816 dest_base = get_addr_base_and_unit_offset (destvar,
817 &dest_offset);
818 if (dest_base == NULL)
819 dest_base = destvar;
820 if (tree_fits_uhwi_p (len))
821 maxsize = tree_to_uhwi (len);
822 else
823 maxsize = -1;
824 if (SSA_VAR_P (src_base)
825 && SSA_VAR_P (dest_base))
827 if (operand_equal_p (src_base, dest_base, 0)
828 && ranges_overlap_p (src_offset, maxsize,
829 dest_offset, maxsize))
830 return false;
832 else if (TREE_CODE (src_base) == MEM_REF
833 && TREE_CODE (dest_base) == MEM_REF)
835 if (! operand_equal_p (TREE_OPERAND (src_base, 0),
836 TREE_OPERAND (dest_base, 0), 0))
837 return false;
838 offset_int off = mem_ref_offset (src_base) + src_offset;
839 if (!wi::fits_shwi_p (off))
840 return false;
841 src_offset = off.to_shwi ();
843 off = mem_ref_offset (dest_base) + dest_offset;
844 if (!wi::fits_shwi_p (off))
845 return false;
846 dest_offset = off.to_shwi ();
847 if (ranges_overlap_p (src_offset, maxsize,
848 dest_offset, maxsize))
849 return false;
851 else
852 return false;
854 fn = builtin_decl_implicit (BUILT_IN_MEMCPY);
855 if (!fn)
856 return false;
857 gimple_call_set_fndecl (stmt, fn);
858 gimple_call_set_arg (stmt, 0, dest);
859 gimple_call_set_arg (stmt, 1, src);
860 fold_stmt (gsi);
861 return true;
864 /* If the destination and source do not alias optimize into
865 memcpy as well. */
866 if ((is_gimple_min_invariant (dest)
867 || TREE_CODE (dest) == SSA_NAME)
868 && (is_gimple_min_invariant (src)
869 || TREE_CODE (src) == SSA_NAME))
871 ao_ref destr, srcr;
872 ao_ref_init_from_ptr_and_size (&destr, dest, len);
873 ao_ref_init_from_ptr_and_size (&srcr, src, len);
874 if (!refs_may_alias_p_1 (&destr, &srcr, false))
876 tree fn;
877 fn = builtin_decl_implicit (BUILT_IN_MEMCPY);
878 if (!fn)
879 return false;
880 gimple_call_set_fndecl (stmt, fn);
881 gimple_call_set_arg (stmt, 0, dest);
882 gimple_call_set_arg (stmt, 1, src);
883 fold_stmt (gsi);
884 return true;
888 return false;
891 if (!tree_fits_shwi_p (len))
892 return false;
893 /* FIXME:
894 This logic lose for arguments like (type *)malloc (sizeof (type)),
895 since we strip the casts of up to VOID return value from malloc.
896 Perhaps we ought to inherit type from non-VOID argument here? */
897 STRIP_NOPS (src);
898 STRIP_NOPS (dest);
899 if (!POINTER_TYPE_P (TREE_TYPE (src))
900 || !POINTER_TYPE_P (TREE_TYPE (dest)))
901 return false;
902 /* In the following try to find a type that is most natural to be
903 used for the memcpy source and destination and that allows
904 the most optimization when memcpy is turned into a plain assignment
905 using that type. In theory we could always use a char[len] type
906 but that only gains us that the destination and source possibly
907 no longer will have their address taken. */
908 /* As we fold (void *)(p + CST) to (void *)p + CST undo this here. */
909 if (TREE_CODE (src) == POINTER_PLUS_EXPR)
911 tree tem = TREE_OPERAND (src, 0);
912 STRIP_NOPS (tem);
913 if (tem != TREE_OPERAND (src, 0))
914 src = build1 (NOP_EXPR, TREE_TYPE (tem), src);
916 if (TREE_CODE (dest) == POINTER_PLUS_EXPR)
918 tree tem = TREE_OPERAND (dest, 0);
919 STRIP_NOPS (tem);
920 if (tem != TREE_OPERAND (dest, 0))
921 dest = build1 (NOP_EXPR, TREE_TYPE (tem), dest);
923 srctype = TREE_TYPE (TREE_TYPE (src));
924 if (TREE_CODE (srctype) == ARRAY_TYPE
925 && !tree_int_cst_equal (TYPE_SIZE_UNIT (srctype), len))
927 srctype = TREE_TYPE (srctype);
928 STRIP_NOPS (src);
929 src = build1 (NOP_EXPR, build_pointer_type (srctype), src);
931 desttype = TREE_TYPE (TREE_TYPE (dest));
932 if (TREE_CODE (desttype) == ARRAY_TYPE
933 && !tree_int_cst_equal (TYPE_SIZE_UNIT (desttype), len))
935 desttype = TREE_TYPE (desttype);
936 STRIP_NOPS (dest);
937 dest = build1 (NOP_EXPR, build_pointer_type (desttype), dest);
939 if (TREE_ADDRESSABLE (srctype)
940 || TREE_ADDRESSABLE (desttype))
941 return false;
943 /* Make sure we are not copying using a floating-point mode or
944 a type whose size possibly does not match its precision. */
945 if (FLOAT_MODE_P (TYPE_MODE (desttype))
946 || TREE_CODE (desttype) == BOOLEAN_TYPE
947 || TREE_CODE (desttype) == ENUMERAL_TYPE)
948 desttype = bitwise_type_for_mode (TYPE_MODE (desttype));
949 if (FLOAT_MODE_P (TYPE_MODE (srctype))
950 || TREE_CODE (srctype) == BOOLEAN_TYPE
951 || TREE_CODE (srctype) == ENUMERAL_TYPE)
952 srctype = bitwise_type_for_mode (TYPE_MODE (srctype));
953 if (!srctype)
954 srctype = desttype;
955 if (!desttype)
956 desttype = srctype;
957 if (!srctype)
958 return false;
960 src_align = get_pointer_alignment (src);
961 dest_align = get_pointer_alignment (dest);
962 if (dest_align < TYPE_ALIGN (desttype)
963 || src_align < TYPE_ALIGN (srctype))
964 return false;
966 destvar = dest;
967 STRIP_NOPS (destvar);
968 if (TREE_CODE (destvar) == ADDR_EXPR
969 && var_decl_component_p (TREE_OPERAND (destvar, 0))
970 && tree_int_cst_equal (TYPE_SIZE_UNIT (desttype), len))
971 destvar = fold_build2 (MEM_REF, desttype, destvar, off0);
972 else
973 destvar = NULL_TREE;
975 srcvar = src;
976 STRIP_NOPS (srcvar);
977 if (TREE_CODE (srcvar) == ADDR_EXPR
978 && var_decl_component_p (TREE_OPERAND (srcvar, 0))
979 && tree_int_cst_equal (TYPE_SIZE_UNIT (srctype), len))
981 if (!destvar
982 || src_align >= TYPE_ALIGN (desttype))
983 srcvar = fold_build2 (MEM_REF, destvar ? desttype : srctype,
984 srcvar, off0);
985 else if (!STRICT_ALIGNMENT)
987 srctype = build_aligned_type (TYPE_MAIN_VARIANT (desttype),
988 src_align);
989 srcvar = fold_build2 (MEM_REF, srctype, srcvar, off0);
991 else
992 srcvar = NULL_TREE;
994 else
995 srcvar = NULL_TREE;
997 if (srcvar == NULL_TREE && destvar == NULL_TREE)
998 return false;
1000 if (srcvar == NULL_TREE)
1002 STRIP_NOPS (src);
1003 if (src_align >= TYPE_ALIGN (desttype))
1004 srcvar = fold_build2 (MEM_REF, desttype, src, off0);
1005 else
1007 if (STRICT_ALIGNMENT)
1008 return false;
1009 srctype = build_aligned_type (TYPE_MAIN_VARIANT (desttype),
1010 src_align);
1011 srcvar = fold_build2 (MEM_REF, srctype, src, off0);
1014 else if (destvar == NULL_TREE)
1016 STRIP_NOPS (dest);
1017 if (dest_align >= TYPE_ALIGN (srctype))
1018 destvar = fold_build2 (MEM_REF, srctype, dest, off0);
1019 else
1021 if (STRICT_ALIGNMENT)
1022 return false;
1023 desttype = build_aligned_type (TYPE_MAIN_VARIANT (srctype),
1024 dest_align);
1025 destvar = fold_build2 (MEM_REF, desttype, dest, off0);
1029 gimple *new_stmt;
1030 if (is_gimple_reg_type (TREE_TYPE (srcvar)))
1032 tree tem = fold_const_aggregate_ref (srcvar);
1033 if (tem)
1034 srcvar = tem;
1035 if (! is_gimple_min_invariant (srcvar))
1037 new_stmt = gimple_build_assign (NULL_TREE, srcvar);
1038 srcvar = create_tmp_reg_or_ssa_name (TREE_TYPE (srcvar),
1039 new_stmt);
1040 gimple_assign_set_lhs (new_stmt, srcvar);
1041 gimple_set_vuse (new_stmt, gimple_vuse (stmt));
1042 gsi_insert_before (gsi, new_stmt, GSI_SAME_STMT);
1045 new_stmt = gimple_build_assign (destvar, srcvar);
1046 gimple_set_vuse (new_stmt, gimple_vuse (stmt));
1047 gimple_set_vdef (new_stmt, gimple_vdef (stmt));
1048 if (gimple_vdef (new_stmt)
1049 && TREE_CODE (gimple_vdef (new_stmt)) == SSA_NAME)
1050 SSA_NAME_DEF_STMT (gimple_vdef (new_stmt)) = new_stmt;
1051 if (!lhs)
1053 gsi_replace (gsi, new_stmt, false);
1054 return true;
1056 gsi_insert_before (gsi, new_stmt, GSI_SAME_STMT);
1059 done:
1060 gimple_seq stmts = NULL;
1061 if (endp == 0 || endp == 3)
1062 len = NULL_TREE;
1063 else if (endp == 2)
1064 len = gimple_build (&stmts, loc, MINUS_EXPR, TREE_TYPE (len), len,
1065 ssize_int (1));
1066 if (endp == 2 || endp == 1)
1068 len = gimple_convert_to_ptrofftype (&stmts, loc, len);
1069 dest = gimple_build (&stmts, loc, POINTER_PLUS_EXPR,
1070 TREE_TYPE (dest), dest, len);
1073 gsi_insert_seq_before (gsi, stmts, GSI_SAME_STMT);
1074 gimple *repl = gimple_build_assign (lhs, dest);
1075 gsi_replace (gsi, repl, false);
1076 return true;
1079 /* Fold function call to builtin memset or bzero at *GSI setting the
1080 memory of size LEN to VAL. Return whether a simplification was made. */
1082 static bool
1083 gimple_fold_builtin_memset (gimple_stmt_iterator *gsi, tree c, tree len)
1085 gimple *stmt = gsi_stmt (*gsi);
1086 tree etype;
1087 unsigned HOST_WIDE_INT length, cval;
1089 /* If the LEN parameter is zero, return DEST. */
1090 if (integer_zerop (len))
1092 replace_call_with_value (gsi, gimple_call_arg (stmt, 0));
1093 return true;
1096 if (! tree_fits_uhwi_p (len))
1097 return false;
1099 if (TREE_CODE (c) != INTEGER_CST)
1100 return false;
1102 tree dest = gimple_call_arg (stmt, 0);
1103 tree var = dest;
1104 if (TREE_CODE (var) != ADDR_EXPR)
1105 return false;
1107 var = TREE_OPERAND (var, 0);
1108 if (TREE_THIS_VOLATILE (var))
1109 return false;
1111 etype = TREE_TYPE (var);
1112 if (TREE_CODE (etype) == ARRAY_TYPE)
1113 etype = TREE_TYPE (etype);
1115 if (!INTEGRAL_TYPE_P (etype)
1116 && !POINTER_TYPE_P (etype))
1117 return NULL_TREE;
1119 if (! var_decl_component_p (var))
1120 return NULL_TREE;
1122 length = tree_to_uhwi (len);
1123 if (GET_MODE_SIZE (TYPE_MODE (etype)) != length
1124 || get_pointer_alignment (dest) / BITS_PER_UNIT < length)
1125 return NULL_TREE;
1127 if (length > HOST_BITS_PER_WIDE_INT / BITS_PER_UNIT)
1128 return NULL_TREE;
1130 if (integer_zerop (c))
1131 cval = 0;
1132 else
1134 if (CHAR_BIT != 8 || BITS_PER_UNIT != 8 || HOST_BITS_PER_WIDE_INT > 64)
1135 return NULL_TREE;
1137 cval = TREE_INT_CST_LOW (c);
1138 cval &= 0xff;
1139 cval |= cval << 8;
1140 cval |= cval << 16;
1141 cval |= (cval << 31) << 1;
1144 var = fold_build2 (MEM_REF, etype, dest, build_int_cst (ptr_type_node, 0));
1145 gimple *store = gimple_build_assign (var, build_int_cst_type (etype, cval));
1146 gimple_set_vuse (store, gimple_vuse (stmt));
1147 tree vdef = gimple_vdef (stmt);
1148 if (vdef && TREE_CODE (vdef) == SSA_NAME)
1150 gimple_set_vdef (store, gimple_vdef (stmt));
1151 SSA_NAME_DEF_STMT (gimple_vdef (stmt)) = store;
1153 gsi_insert_before (gsi, store, GSI_SAME_STMT);
1154 if (gimple_call_lhs (stmt))
1156 gimple *asgn = gimple_build_assign (gimple_call_lhs (stmt), dest);
1157 gsi_replace (gsi, asgn, false);
1159 else
1161 gimple_stmt_iterator gsi2 = *gsi;
1162 gsi_prev (gsi);
1163 gsi_remove (&gsi2, true);
1166 return true;
1170 /* Obtain the minimum and maximum string length or minimum and maximum
1171 value of ARG in LENGTH[0] and LENGTH[1], respectively.
1172 If ARG is an SSA name variable, follow its use-def chains. When
1173 TYPE == 0, if LENGTH[1] is not equal to the length we determine or
1174 if we are unable to determine the length or value, return False.
1175 VISITED is a bitmap of visited variables.
1176 TYPE is 0 if string length should be obtained, 1 for maximum string
1177 length and 2 for maximum value ARG can have.
1178 When FUZZY is set and the length of a string cannot be determined,
1179 the function instead considers as the maximum possible length the
1180 size of a character array it may refer to.
1181 Set *FLEXP to true if the range of the string lengths has been
1182 obtained from the upper bound of an array at the end of a struct.
1183 Such an array may hold a string that's longer than its upper bound
1184 due to it being used as a poor-man's flexible array member. */
1186 static bool
1187 get_range_strlen (tree arg, tree length[2], bitmap *visited, int type,
1188 bool fuzzy, bool *flexp)
1190 tree var, val;
1191 gimple *def_stmt;
1193 /* The minimum and maximum length. The MAXLEN pointer stays unchanged
1194 but MINLEN may be cleared during the execution of the function. */
1195 tree *minlen = length;
1196 tree *const maxlen = length + 1;
1198 if (TREE_CODE (arg) != SSA_NAME)
1200 /* We can end up with &(*iftmp_1)[0] here as well, so handle it. */
1201 if (TREE_CODE (arg) == ADDR_EXPR
1202 && TREE_CODE (TREE_OPERAND (arg, 0)) == ARRAY_REF
1203 && integer_zerop (TREE_OPERAND (TREE_OPERAND (arg, 0), 1)))
1205 tree aop0 = TREE_OPERAND (TREE_OPERAND (arg, 0), 0);
1206 if (TREE_CODE (aop0) == INDIRECT_REF
1207 && TREE_CODE (TREE_OPERAND (aop0, 0)) == SSA_NAME)
1208 return get_range_strlen (TREE_OPERAND (aop0, 0),
1209 length, visited, type, fuzzy, flexp);
1212 if (type == 2)
1214 val = arg;
1215 if (TREE_CODE (val) != INTEGER_CST
1216 || tree_int_cst_sgn (val) < 0)
1217 return false;
1219 else
1220 val = c_strlen (arg, 1);
1222 if (!val && fuzzy)
1224 if (TREE_CODE (arg) == ADDR_EXPR)
1225 return get_range_strlen (TREE_OPERAND (arg, 0), length,
1226 visited, type, fuzzy, flexp);
1228 if (TREE_CODE (arg) == COMPONENT_REF
1229 && TREE_CODE (TREE_TYPE (TREE_OPERAND (arg, 1))) == ARRAY_TYPE)
1231 /* Use the type of the member array to determine the upper
1232 bound on the length of the array. This may be overly
1233 optimistic if the array itself isn't NUL-terminated and
1234 the caller relies on the subsequent member to contain
1235 the NUL.
1236 Set *FLEXP to true if the array whose bound is being
1237 used is at the end of a struct. */
1238 if (array_at_struct_end_p (arg))
1239 *flexp = true;
1241 arg = TREE_OPERAND (arg, 1);
1242 val = TYPE_SIZE_UNIT (TREE_TYPE (arg));
1243 if (!val || integer_zerop (val))
1244 return false;
1245 val = fold_build2 (MINUS_EXPR, TREE_TYPE (val), val,
1246 integer_one_node);
1247 /* Set the minimum size to zero since the string in
1248 the array could have zero length. */
1249 *minlen = ssize_int (0);
1253 if (!val)
1254 return false;
1256 if (minlen
1257 && (!*minlen
1258 || (type > 0
1259 && TREE_CODE (*minlen) == INTEGER_CST
1260 && TREE_CODE (val) == INTEGER_CST
1261 && tree_int_cst_lt (val, *minlen))))
1262 *minlen = val;
1264 if (*maxlen)
1266 if (type > 0)
1268 if (TREE_CODE (*maxlen) != INTEGER_CST
1269 || TREE_CODE (val) != INTEGER_CST)
1270 return false;
1272 if (tree_int_cst_lt (*maxlen, val))
1273 *maxlen = val;
1274 return true;
1276 else if (simple_cst_equal (val, *maxlen) != 1)
1277 return false;
1280 *maxlen = val;
1281 return true;
1284 /* If ARG is registered for SSA update we cannot look at its defining
1285 statement. */
1286 if (name_registered_for_update_p (arg))
1287 return false;
1289 /* If we were already here, break the infinite cycle. */
1290 if (!*visited)
1291 *visited = BITMAP_ALLOC (NULL);
1292 if (!bitmap_set_bit (*visited, SSA_NAME_VERSION (arg)))
1293 return true;
1295 var = arg;
1296 def_stmt = SSA_NAME_DEF_STMT (var);
1298 switch (gimple_code (def_stmt))
1300 case GIMPLE_ASSIGN:
1301 /* The RHS of the statement defining VAR must either have a
1302 constant length or come from another SSA_NAME with a constant
1303 length. */
1304 if (gimple_assign_single_p (def_stmt)
1305 || gimple_assign_unary_nop_p (def_stmt))
1307 tree rhs = gimple_assign_rhs1 (def_stmt);
1308 return get_range_strlen (rhs, length, visited, type, fuzzy, flexp);
1310 else if (gimple_assign_rhs_code (def_stmt) == COND_EXPR)
1312 tree op2 = gimple_assign_rhs2 (def_stmt);
1313 tree op3 = gimple_assign_rhs3 (def_stmt);
1314 return get_range_strlen (op2, length, visited, type, fuzzy, flexp)
1315 && get_range_strlen (op3, length, visited, type, fuzzy, flexp);
1317 return false;
1319 case GIMPLE_PHI:
1321 /* All the arguments of the PHI node must have the same constant
1322 length. */
1323 unsigned i;
1325 for (i = 0; i < gimple_phi_num_args (def_stmt); i++)
1327 tree arg = gimple_phi_arg (def_stmt, i)->def;
1329 /* If this PHI has itself as an argument, we cannot
1330 determine the string length of this argument. However,
1331 if we can find a constant string length for the other
1332 PHI args then we can still be sure that this is a
1333 constant string length. So be optimistic and just
1334 continue with the next argument. */
1335 if (arg == gimple_phi_result (def_stmt))
1336 continue;
1338 if (!get_range_strlen (arg, length, visited, type, fuzzy, flexp))
1340 if (fuzzy)
1341 *maxlen = build_all_ones_cst (size_type_node);
1342 else
1343 return false;
1347 return true;
1349 default:
1350 return false;
1354 /* Determine the minimum and maximum value or string length that ARG
1355 refers to and store each in the first two elements of MINMAXLEN.
1356 For expressions that point to strings of unknown lengths that are
1357 character arrays, use the upper bound of the array as the maximum
1358 length. For example, given an expression like 'x ? array : "xyz"'
1359 and array declared as 'char array[8]', MINMAXLEN[0] will be set
1360 to 3 and MINMAXLEN[1] to 7, the longest string that could be
1361 stored in array.
1362 Return true if the range of the string lengths has been obtained
1363 from the upper bound of an array at the end of a struct. Such
1364 an array may hold a string that's longer than its upper bound
1365 due to it being used as a poor-man's flexible array member. */
1367 bool
1368 get_range_strlen (tree arg, tree minmaxlen[2])
1370 bitmap visited = NULL;
1372 minmaxlen[0] = NULL_TREE;
1373 minmaxlen[1] = NULL_TREE;
1375 bool flexarray = false;
1376 get_range_strlen (arg, minmaxlen, &visited, 1, true, &flexarray);
1378 if (visited)
1379 BITMAP_FREE (visited);
1381 return flexarray;
1384 tree
1385 get_maxval_strlen (tree arg, int type)
1387 bitmap visited = NULL;
1388 tree len[2] = { NULL_TREE, NULL_TREE };
1390 bool dummy;
1391 if (!get_range_strlen (arg, len, &visited, type, false, &dummy))
1392 len[1] = NULL_TREE;
1393 if (visited)
1394 BITMAP_FREE (visited);
1396 return len[1];
1400 /* Fold function call to builtin strcpy with arguments DEST and SRC.
1401 If LEN is not NULL, it represents the length of the string to be
1402 copied. Return NULL_TREE if no simplification can be made. */
1404 static bool
1405 gimple_fold_builtin_strcpy (gimple_stmt_iterator *gsi,
1406 tree dest, tree src)
1408 location_t loc = gimple_location (gsi_stmt (*gsi));
1409 tree fn;
1411 /* If SRC and DEST are the same (and not volatile), return DEST. */
1412 if (operand_equal_p (src, dest, 0))
1414 replace_call_with_value (gsi, dest);
1415 return true;
1418 if (optimize_function_for_size_p (cfun))
1419 return false;
1421 fn = builtin_decl_implicit (BUILT_IN_MEMCPY);
1422 if (!fn)
1423 return false;
1425 tree len = get_maxval_strlen (src, 0);
1426 if (!len)
1427 return false;
1429 len = fold_convert_loc (loc, size_type_node, len);
1430 len = size_binop_loc (loc, PLUS_EXPR, len, build_int_cst (size_type_node, 1));
1431 len = force_gimple_operand_gsi (gsi, len, true,
1432 NULL_TREE, true, GSI_SAME_STMT);
1433 gimple *repl = gimple_build_call (fn, 3, dest, src, len);
1434 replace_call_with_call_and_fold (gsi, repl);
1435 return true;
1438 /* Fold function call to builtin strncpy with arguments DEST, SRC, and LEN.
1439 If SLEN is not NULL, it represents the length of the source string.
1440 Return NULL_TREE if no simplification can be made. */
1442 static bool
1443 gimple_fold_builtin_strncpy (gimple_stmt_iterator *gsi,
1444 tree dest, tree src, tree len)
1446 location_t loc = gimple_location (gsi_stmt (*gsi));
1447 tree fn;
1449 /* If the LEN parameter is zero, return DEST. */
1450 if (integer_zerop (len))
1452 replace_call_with_value (gsi, dest);
1453 return true;
1456 /* We can't compare slen with len as constants below if len is not a
1457 constant. */
1458 if (TREE_CODE (len) != INTEGER_CST)
1459 return false;
1461 /* Now, we must be passed a constant src ptr parameter. */
1462 tree slen = get_maxval_strlen (src, 0);
1463 if (!slen || TREE_CODE (slen) != INTEGER_CST)
1464 return false;
1466 slen = size_binop_loc (loc, PLUS_EXPR, slen, ssize_int (1));
1468 /* We do not support simplification of this case, though we do
1469 support it when expanding trees into RTL. */
1470 /* FIXME: generate a call to __builtin_memset. */
1471 if (tree_int_cst_lt (slen, len))
1472 return false;
1474 /* OK transform into builtin memcpy. */
1475 fn = builtin_decl_implicit (BUILT_IN_MEMCPY);
1476 if (!fn)
1477 return false;
1479 len = fold_convert_loc (loc, size_type_node, len);
1480 len = force_gimple_operand_gsi (gsi, len, true,
1481 NULL_TREE, true, GSI_SAME_STMT);
1482 gimple *repl = gimple_build_call (fn, 3, dest, src, len);
1483 replace_call_with_call_and_fold (gsi, repl);
1484 return true;
1487 /* Fold function call to builtin strchr or strrchr.
1488 If both arguments are constant, evaluate and fold the result,
1489 otherwise simplify str(r)chr (str, 0) into str + strlen (str).
1490 In general strlen is significantly faster than strchr
1491 due to being a simpler operation. */
1492 static bool
1493 gimple_fold_builtin_strchr (gimple_stmt_iterator *gsi, bool is_strrchr)
1495 gimple *stmt = gsi_stmt (*gsi);
1496 tree str = gimple_call_arg (stmt, 0);
1497 tree c = gimple_call_arg (stmt, 1);
1498 location_t loc = gimple_location (stmt);
1499 const char *p;
1500 char ch;
1502 if (!gimple_call_lhs (stmt))
1503 return false;
1505 if ((p = c_getstr (str)) && target_char_cst_p (c, &ch))
1507 const char *p1 = is_strrchr ? strrchr (p, ch) : strchr (p, ch);
1509 if (p1 == NULL)
1511 replace_call_with_value (gsi, integer_zero_node);
1512 return true;
1515 tree len = build_int_cst (size_type_node, p1 - p);
1516 gimple_seq stmts = NULL;
1517 gimple *new_stmt = gimple_build_assign (gimple_call_lhs (stmt),
1518 POINTER_PLUS_EXPR, str, len);
1519 gimple_seq_add_stmt_without_update (&stmts, new_stmt);
1520 gsi_replace_with_seq_vops (gsi, stmts);
1521 return true;
1524 if (!integer_zerop (c))
1525 return false;
1527 /* Transform strrchr (s, 0) to strchr (s, 0) when optimizing for size. */
1528 if (is_strrchr && optimize_function_for_size_p (cfun))
1530 tree strchr_fn = builtin_decl_implicit (BUILT_IN_STRCHR);
1532 if (strchr_fn)
1534 gimple *repl = gimple_build_call (strchr_fn, 2, str, c);
1535 replace_call_with_call_and_fold (gsi, repl);
1536 return true;
1539 return false;
1542 tree len;
1543 tree strlen_fn = builtin_decl_implicit (BUILT_IN_STRLEN);
1545 if (!strlen_fn)
1546 return false;
1548 /* Create newstr = strlen (str). */
1549 gimple_seq stmts = NULL;
1550 gimple *new_stmt = gimple_build_call (strlen_fn, 1, str);
1551 gimple_set_location (new_stmt, loc);
1552 len = create_tmp_reg_or_ssa_name (size_type_node);
1553 gimple_call_set_lhs (new_stmt, len);
1554 gimple_seq_add_stmt_without_update (&stmts, new_stmt);
1556 /* Create (str p+ strlen (str)). */
1557 new_stmt = gimple_build_assign (gimple_call_lhs (stmt),
1558 POINTER_PLUS_EXPR, str, len);
1559 gimple_seq_add_stmt_without_update (&stmts, new_stmt);
1560 gsi_replace_with_seq_vops (gsi, stmts);
1561 /* gsi now points at the assignment to the lhs, get a
1562 stmt iterator to the strlen.
1563 ??? We can't use gsi_for_stmt as that doesn't work when the
1564 CFG isn't built yet. */
1565 gimple_stmt_iterator gsi2 = *gsi;
1566 gsi_prev (&gsi2);
1567 fold_stmt (&gsi2);
1568 return true;
1571 /* Fold function call to builtin strstr.
1572 If both arguments are constant, evaluate and fold the result,
1573 additionally fold strstr (x, "") into x and strstr (x, "c")
1574 into strchr (x, 'c'). */
1575 static bool
1576 gimple_fold_builtin_strstr (gimple_stmt_iterator *gsi)
1578 gimple *stmt = gsi_stmt (*gsi);
1579 tree haystack = gimple_call_arg (stmt, 0);
1580 tree needle = gimple_call_arg (stmt, 1);
1581 const char *p, *q;
1583 if (!gimple_call_lhs (stmt))
1584 return false;
1586 q = c_getstr (needle);
1587 if (q == NULL)
1588 return false;
1590 if ((p = c_getstr (haystack)))
1592 const char *r = strstr (p, q);
1594 if (r == NULL)
1596 replace_call_with_value (gsi, integer_zero_node);
1597 return true;
1600 tree len = build_int_cst (size_type_node, r - p);
1601 gimple_seq stmts = NULL;
1602 gimple *new_stmt
1603 = gimple_build_assign (gimple_call_lhs (stmt), POINTER_PLUS_EXPR,
1604 haystack, len);
1605 gimple_seq_add_stmt_without_update (&stmts, new_stmt);
1606 gsi_replace_with_seq_vops (gsi, stmts);
1607 return true;
1610 /* For strstr (x, "") return x. */
1611 if (q[0] == '\0')
1613 replace_call_with_value (gsi, haystack);
1614 return true;
1617 /* Transform strstr (x, "c") into strchr (x, 'c'). */
1618 if (q[1] == '\0')
1620 tree strchr_fn = builtin_decl_implicit (BUILT_IN_STRCHR);
1621 if (strchr_fn)
1623 tree c = build_int_cst (integer_type_node, q[0]);
1624 gimple *repl = gimple_build_call (strchr_fn, 2, haystack, c);
1625 replace_call_with_call_and_fold (gsi, repl);
1626 return true;
1630 return false;
1633 /* Simplify a call to the strcat builtin. DST and SRC are the arguments
1634 to the call.
1636 Return NULL_TREE if no simplification was possible, otherwise return the
1637 simplified form of the call as a tree.
1639 The simplified form may be a constant or other expression which
1640 computes the same value, but in a more efficient manner (including
1641 calls to other builtin functions).
1643 The call may contain arguments which need to be evaluated, but
1644 which are not useful to determine the result of the call. In
1645 this case we return a chain of COMPOUND_EXPRs. The LHS of each
1646 COMPOUND_EXPR will be an argument which must be evaluated.
1647 COMPOUND_EXPRs are chained through their RHS. The RHS of the last
1648 COMPOUND_EXPR in the chain will contain the tree for the simplified
1649 form of the builtin function call. */
1651 static bool
1652 gimple_fold_builtin_strcat (gimple_stmt_iterator *gsi, tree dst, tree src)
1654 gimple *stmt = gsi_stmt (*gsi);
1655 location_t loc = gimple_location (stmt);
1657 const char *p = c_getstr (src);
1659 /* If the string length is zero, return the dst parameter. */
1660 if (p && *p == '\0')
1662 replace_call_with_value (gsi, dst);
1663 return true;
1666 if (!optimize_bb_for_speed_p (gimple_bb (stmt)))
1667 return false;
1669 /* See if we can store by pieces into (dst + strlen(dst)). */
1670 tree newdst;
1671 tree strlen_fn = builtin_decl_implicit (BUILT_IN_STRLEN);
1672 tree memcpy_fn = builtin_decl_implicit (BUILT_IN_MEMCPY);
1674 if (!strlen_fn || !memcpy_fn)
1675 return false;
1677 /* If the length of the source string isn't computable don't
1678 split strcat into strlen and memcpy. */
1679 tree len = get_maxval_strlen (src, 0);
1680 if (! len)
1681 return false;
1683 /* Create strlen (dst). */
1684 gimple_seq stmts = NULL, stmts2;
1685 gimple *repl = gimple_build_call (strlen_fn, 1, dst);
1686 gimple_set_location (repl, loc);
1687 newdst = create_tmp_reg_or_ssa_name (size_type_node);
1688 gimple_call_set_lhs (repl, newdst);
1689 gimple_seq_add_stmt_without_update (&stmts, repl);
1691 /* Create (dst p+ strlen (dst)). */
1692 newdst = fold_build_pointer_plus_loc (loc, dst, newdst);
1693 newdst = force_gimple_operand (newdst, &stmts2, true, NULL_TREE);
1694 gimple_seq_add_seq_without_update (&stmts, stmts2);
1696 len = fold_convert_loc (loc, size_type_node, len);
1697 len = size_binop_loc (loc, PLUS_EXPR, len,
1698 build_int_cst (size_type_node, 1));
1699 len = force_gimple_operand (len, &stmts2, true, NULL_TREE);
1700 gimple_seq_add_seq_without_update (&stmts, stmts2);
1702 repl = gimple_build_call (memcpy_fn, 3, newdst, src, len);
1703 gimple_seq_add_stmt_without_update (&stmts, repl);
1704 if (gimple_call_lhs (stmt))
1706 repl = gimple_build_assign (gimple_call_lhs (stmt), dst);
1707 gimple_seq_add_stmt_without_update (&stmts, repl);
1708 gsi_replace_with_seq_vops (gsi, stmts);
1709 /* gsi now points at the assignment to the lhs, get a
1710 stmt iterator to the memcpy call.
1711 ??? We can't use gsi_for_stmt as that doesn't work when the
1712 CFG isn't built yet. */
1713 gimple_stmt_iterator gsi2 = *gsi;
1714 gsi_prev (&gsi2);
1715 fold_stmt (&gsi2);
1717 else
1719 gsi_replace_with_seq_vops (gsi, stmts);
1720 fold_stmt (gsi);
1722 return true;
1725 /* Fold a call to the __strcat_chk builtin FNDECL. DEST, SRC, and SIZE
1726 are the arguments to the call. */
1728 static bool
1729 gimple_fold_builtin_strcat_chk (gimple_stmt_iterator *gsi)
1731 gimple *stmt = gsi_stmt (*gsi);
1732 tree dest = gimple_call_arg (stmt, 0);
1733 tree src = gimple_call_arg (stmt, 1);
1734 tree size = gimple_call_arg (stmt, 2);
1735 tree fn;
1736 const char *p;
1739 p = c_getstr (src);
1740 /* If the SRC parameter is "", return DEST. */
1741 if (p && *p == '\0')
1743 replace_call_with_value (gsi, dest);
1744 return true;
1747 if (! tree_fits_uhwi_p (size) || ! integer_all_onesp (size))
1748 return false;
1750 /* If __builtin_strcat_chk is used, assume strcat is available. */
1751 fn = builtin_decl_explicit (BUILT_IN_STRCAT);
1752 if (!fn)
1753 return false;
1755 gimple *repl = gimple_build_call (fn, 2, dest, src);
1756 replace_call_with_call_and_fold (gsi, repl);
1757 return true;
1760 /* Simplify a call to the strncat builtin. */
1762 static bool
1763 gimple_fold_builtin_strncat (gimple_stmt_iterator *gsi)
1765 gcall *stmt = as_a <gcall *> (gsi_stmt (*gsi));
1766 tree dst = gimple_call_arg (stmt, 0);
1767 tree src = gimple_call_arg (stmt, 1);
1768 tree len = gimple_call_arg (stmt, 2);
1770 const char *p = c_getstr (src);
1772 /* If the requested length is zero, or the src parameter string
1773 length is zero, return the dst parameter. */
1774 if (integer_zerop (len) || (p && *p == '\0'))
1776 replace_call_with_value (gsi, dst);
1777 return true;
1780 /* If the requested len is greater than or equal to the string
1781 length, call strcat. */
1782 if (TREE_CODE (len) == INTEGER_CST && p
1783 && compare_tree_int (len, strlen (p)) >= 0)
1785 tree fn = builtin_decl_implicit (BUILT_IN_STRCAT);
1787 /* If the replacement _DECL isn't initialized, don't do the
1788 transformation. */
1789 if (!fn)
1790 return false;
1792 gcall *repl = gimple_build_call (fn, 2, dst, src);
1793 replace_call_with_call_and_fold (gsi, repl);
1794 return true;
1797 return false;
1800 /* Fold a call to the __strncat_chk builtin with arguments DEST, SRC,
1801 LEN, and SIZE. */
1803 static bool
1804 gimple_fold_builtin_strncat_chk (gimple_stmt_iterator *gsi)
1806 gimple *stmt = gsi_stmt (*gsi);
1807 tree dest = gimple_call_arg (stmt, 0);
1808 tree src = gimple_call_arg (stmt, 1);
1809 tree len = gimple_call_arg (stmt, 2);
1810 tree size = gimple_call_arg (stmt, 3);
1811 tree fn;
1812 const char *p;
1814 p = c_getstr (src);
1815 /* If the SRC parameter is "" or if LEN is 0, return DEST. */
1816 if ((p && *p == '\0')
1817 || integer_zerop (len))
1819 replace_call_with_value (gsi, dest);
1820 return true;
1823 if (! tree_fits_uhwi_p (size))
1824 return false;
1826 if (! integer_all_onesp (size))
1828 tree src_len = c_strlen (src, 1);
1829 if (src_len
1830 && tree_fits_uhwi_p (src_len)
1831 && tree_fits_uhwi_p (len)
1832 && ! tree_int_cst_lt (len, src_len))
1834 /* If LEN >= strlen (SRC), optimize into __strcat_chk. */
1835 fn = builtin_decl_explicit (BUILT_IN_STRCAT_CHK);
1836 if (!fn)
1837 return false;
1839 gimple *repl = gimple_build_call (fn, 3, dest, src, size);
1840 replace_call_with_call_and_fold (gsi, repl);
1841 return true;
1843 return false;
1846 /* If __builtin_strncat_chk is used, assume strncat is available. */
1847 fn = builtin_decl_explicit (BUILT_IN_STRNCAT);
1848 if (!fn)
1849 return false;
1851 gimple *repl = gimple_build_call (fn, 3, dest, src, len);
1852 replace_call_with_call_and_fold (gsi, repl);
1853 return true;
1856 /* Build and append gimple statements to STMTS that would load a first
1857 character of a memory location identified by STR. LOC is location
1858 of the statement. */
1860 static tree
1861 gimple_load_first_char (location_t loc, tree str, gimple_seq *stmts)
1863 tree var;
1865 tree cst_uchar_node = build_type_variant (unsigned_char_type_node, 1, 0);
1866 tree cst_uchar_ptr_node
1867 = build_pointer_type_for_mode (cst_uchar_node, ptr_mode, true);
1868 tree off0 = build_int_cst (cst_uchar_ptr_node, 0);
1870 tree temp = fold_build2_loc (loc, MEM_REF, cst_uchar_node, str, off0);
1871 gassign *stmt = gimple_build_assign (NULL_TREE, temp);
1872 var = create_tmp_reg_or_ssa_name (cst_uchar_node, stmt);
1874 gimple_assign_set_lhs (stmt, var);
1875 gimple_seq_add_stmt_without_update (stmts, stmt);
1877 return var;
1880 /* Fold a call to the str{n}{case}cmp builtin pointed by GSI iterator.
1881 FCODE is the name of the builtin. */
1883 static bool
1884 gimple_fold_builtin_string_compare (gimple_stmt_iterator *gsi)
1886 gimple *stmt = gsi_stmt (*gsi);
1887 tree callee = gimple_call_fndecl (stmt);
1888 enum built_in_function fcode = DECL_FUNCTION_CODE (callee);
1890 tree type = integer_type_node;
1891 tree str1 = gimple_call_arg (stmt, 0);
1892 tree str2 = gimple_call_arg (stmt, 1);
1893 tree lhs = gimple_call_lhs (stmt);
1894 HOST_WIDE_INT length = -1;
1896 /* Handle strncmp and strncasecmp functions. */
1897 if (gimple_call_num_args (stmt) == 3)
1899 tree len = gimple_call_arg (stmt, 2);
1900 if (tree_fits_uhwi_p (len))
1901 length = tree_to_uhwi (len);
1904 /* If the LEN parameter is zero, return zero. */
1905 if (length == 0)
1907 replace_call_with_value (gsi, integer_zero_node);
1908 return true;
1911 /* If ARG1 and ARG2 are the same (and not volatile), return zero. */
1912 if (operand_equal_p (str1, str2, 0))
1914 replace_call_with_value (gsi, integer_zero_node);
1915 return true;
1918 const char *p1 = c_getstr (str1);
1919 const char *p2 = c_getstr (str2);
1921 /* For known strings, return an immediate value. */
1922 if (p1 && p2)
1924 int r = 0;
1925 bool known_result = false;
1927 switch (fcode)
1929 case BUILT_IN_STRCMP:
1931 r = strcmp (p1, p2);
1932 known_result = true;
1933 break;
1935 case BUILT_IN_STRNCMP:
1937 if (length == -1)
1938 break;
1939 r = strncmp (p1, p2, length);
1940 known_result = true;
1941 break;
1943 /* Only handleable situation is where the string are equal (result 0),
1944 which is already handled by operand_equal_p case. */
1945 case BUILT_IN_STRCASECMP:
1946 break;
1947 case BUILT_IN_STRNCASECMP:
1949 if (length == -1)
1950 break;
1951 r = strncmp (p1, p2, length);
1952 if (r == 0)
1953 known_result = true;
1954 break;;
1956 default:
1957 gcc_unreachable ();
1960 if (known_result)
1962 replace_call_with_value (gsi, build_cmp_result (type, r));
1963 return true;
1967 bool nonzero_length = length >= 1
1968 || fcode == BUILT_IN_STRCMP
1969 || fcode == BUILT_IN_STRCASECMP;
1971 location_t loc = gimple_location (stmt);
1973 /* If the second arg is "", return *(const unsigned char*)arg1. */
1974 if (p2 && *p2 == '\0' && nonzero_length)
1976 gimple_seq stmts = NULL;
1977 tree var = gimple_load_first_char (loc, str1, &stmts);
1978 if (lhs)
1980 stmt = gimple_build_assign (lhs, NOP_EXPR, var);
1981 gimple_seq_add_stmt_without_update (&stmts, stmt);
1984 gsi_replace_with_seq_vops (gsi, stmts);
1985 return true;
1988 /* If the first arg is "", return -*(const unsigned char*)arg2. */
1989 if (p1 && *p1 == '\0' && nonzero_length)
1991 gimple_seq stmts = NULL;
1992 tree var = gimple_load_first_char (loc, str2, &stmts);
1994 if (lhs)
1996 tree c = create_tmp_reg_or_ssa_name (integer_type_node);
1997 stmt = gimple_build_assign (c, NOP_EXPR, var);
1998 gimple_seq_add_stmt_without_update (&stmts, stmt);
2000 stmt = gimple_build_assign (lhs, NEGATE_EXPR, c);
2001 gimple_seq_add_stmt_without_update (&stmts, stmt);
2004 gsi_replace_with_seq_vops (gsi, stmts);
2005 return true;
2008 /* If len parameter is one, return an expression corresponding to
2009 (*(const unsigned char*)arg2 - *(const unsigned char*)arg1). */
2010 if (fcode == BUILT_IN_STRNCMP && length == 1)
2012 gimple_seq stmts = NULL;
2013 tree temp1 = gimple_load_first_char (loc, str1, &stmts);
2014 tree temp2 = gimple_load_first_char (loc, str2, &stmts);
2016 if (lhs)
2018 tree c1 = create_tmp_reg_or_ssa_name (integer_type_node);
2019 gassign *convert1 = gimple_build_assign (c1, NOP_EXPR, temp1);
2020 gimple_seq_add_stmt_without_update (&stmts, convert1);
2022 tree c2 = create_tmp_reg_or_ssa_name (integer_type_node);
2023 gassign *convert2 = gimple_build_assign (c2, NOP_EXPR, temp2);
2024 gimple_seq_add_stmt_without_update (&stmts, convert2);
2026 stmt = gimple_build_assign (lhs, MINUS_EXPR, c1, c2);
2027 gimple_seq_add_stmt_without_update (&stmts, stmt);
2030 gsi_replace_with_seq_vops (gsi, stmts);
2031 return true;
2034 return false;
2037 /* Fold a call to the memchr pointed by GSI iterator. */
2039 static bool
2040 gimple_fold_builtin_memchr (gimple_stmt_iterator *gsi)
2042 gimple *stmt = gsi_stmt (*gsi);
2043 tree lhs = gimple_call_lhs (stmt);
2044 tree arg1 = gimple_call_arg (stmt, 0);
2045 tree arg2 = gimple_call_arg (stmt, 1);
2046 tree len = gimple_call_arg (stmt, 2);
2048 /* If the LEN parameter is zero, return zero. */
2049 if (integer_zerop (len))
2051 replace_call_with_value (gsi, build_int_cst (ptr_type_node, 0));
2052 return true;
2055 char c;
2056 if (TREE_CODE (arg2) != INTEGER_CST
2057 || !tree_fits_uhwi_p (len)
2058 || !target_char_cst_p (arg2, &c))
2059 return false;
2061 unsigned HOST_WIDE_INT length = tree_to_uhwi (len);
2062 unsigned HOST_WIDE_INT string_length;
2063 const char *p1 = c_getstr (arg1, &string_length);
2065 if (p1)
2067 const char *r = (const char *)memchr (p1, c, MIN (length, string_length));
2068 if (r == NULL)
2070 if (length <= string_length)
2072 replace_call_with_value (gsi, build_int_cst (ptr_type_node, 0));
2073 return true;
2076 else
2078 unsigned HOST_WIDE_INT offset = r - p1;
2079 gimple_seq stmts = NULL;
2080 if (lhs != NULL_TREE)
2082 tree offset_cst = build_int_cst (TREE_TYPE (len), offset);
2083 gassign *stmt = gimple_build_assign (lhs, POINTER_PLUS_EXPR,
2084 arg1, offset_cst);
2085 gimple_seq_add_stmt_without_update (&stmts, stmt);
2087 else
2088 gimple_seq_add_stmt_without_update (&stmts,
2089 gimple_build_nop ());
2091 gsi_replace_with_seq_vops (gsi, stmts);
2092 return true;
2096 return false;
2099 /* Fold a call to the fputs builtin. ARG0 and ARG1 are the arguments
2100 to the call. IGNORE is true if the value returned
2101 by the builtin will be ignored. UNLOCKED is true is true if this
2102 actually a call to fputs_unlocked. If LEN in non-NULL, it represents
2103 the known length of the string. Return NULL_TREE if no simplification
2104 was possible. */
2106 static bool
2107 gimple_fold_builtin_fputs (gimple_stmt_iterator *gsi,
2108 tree arg0, tree arg1,
2109 bool unlocked)
2111 gimple *stmt = gsi_stmt (*gsi);
2113 /* If we're using an unlocked function, assume the other unlocked
2114 functions exist explicitly. */
2115 tree const fn_fputc = (unlocked
2116 ? builtin_decl_explicit (BUILT_IN_FPUTC_UNLOCKED)
2117 : builtin_decl_implicit (BUILT_IN_FPUTC));
2118 tree const fn_fwrite = (unlocked
2119 ? builtin_decl_explicit (BUILT_IN_FWRITE_UNLOCKED)
2120 : builtin_decl_implicit (BUILT_IN_FWRITE));
2122 /* If the return value is used, don't do the transformation. */
2123 if (gimple_call_lhs (stmt))
2124 return false;
2126 /* Get the length of the string passed to fputs. If the length
2127 can't be determined, punt. */
2128 tree len = get_maxval_strlen (arg0, 0);
2129 if (!len
2130 || TREE_CODE (len) != INTEGER_CST)
2131 return false;
2133 switch (compare_tree_int (len, 1))
2135 case -1: /* length is 0, delete the call entirely . */
2136 replace_call_with_value (gsi, integer_zero_node);
2137 return true;
2139 case 0: /* length is 1, call fputc. */
2141 const char *p = c_getstr (arg0);
2142 if (p != NULL)
2144 if (!fn_fputc)
2145 return false;
2147 gimple *repl = gimple_build_call (fn_fputc, 2,
2148 build_int_cst
2149 (integer_type_node, p[0]), arg1);
2150 replace_call_with_call_and_fold (gsi, repl);
2151 return true;
2154 /* FALLTHROUGH */
2155 case 1: /* length is greater than 1, call fwrite. */
2157 /* If optimizing for size keep fputs. */
2158 if (optimize_function_for_size_p (cfun))
2159 return false;
2160 /* New argument list transforming fputs(string, stream) to
2161 fwrite(string, 1, len, stream). */
2162 if (!fn_fwrite)
2163 return false;
2165 gimple *repl = gimple_build_call (fn_fwrite, 4, arg0,
2166 size_one_node, len, arg1);
2167 replace_call_with_call_and_fold (gsi, repl);
2168 return true;
2170 default:
2171 gcc_unreachable ();
2173 return false;
2176 /* Fold a call to the __mem{cpy,pcpy,move,set}_chk builtin.
2177 DEST, SRC, LEN, and SIZE are the arguments to the call.
2178 IGNORE is true, if return value can be ignored. FCODE is the BUILT_IN_*
2179 code of the builtin. If MAXLEN is not NULL, it is maximum length
2180 passed as third argument. */
2182 static bool
2183 gimple_fold_builtin_memory_chk (gimple_stmt_iterator *gsi,
2184 tree dest, tree src, tree len, tree size,
2185 enum built_in_function fcode)
2187 gimple *stmt = gsi_stmt (*gsi);
2188 location_t loc = gimple_location (stmt);
2189 bool ignore = gimple_call_lhs (stmt) == NULL_TREE;
2190 tree fn;
2192 /* If SRC and DEST are the same (and not volatile), return DEST
2193 (resp. DEST+LEN for __mempcpy_chk). */
2194 if (fcode != BUILT_IN_MEMSET_CHK && operand_equal_p (src, dest, 0))
2196 if (fcode != BUILT_IN_MEMPCPY_CHK)
2198 replace_call_with_value (gsi, dest);
2199 return true;
2201 else
2203 gimple_seq stmts = NULL;
2204 len = gimple_convert_to_ptrofftype (&stmts, loc, len);
2205 tree temp = gimple_build (&stmts, loc, POINTER_PLUS_EXPR,
2206 TREE_TYPE (dest), dest, len);
2207 gsi_insert_seq_before (gsi, stmts, GSI_SAME_STMT);
2208 replace_call_with_value (gsi, temp);
2209 return true;
2213 if (! tree_fits_uhwi_p (size))
2214 return false;
2216 tree maxlen = get_maxval_strlen (len, 2);
2217 if (! integer_all_onesp (size))
2219 if (! tree_fits_uhwi_p (len))
2221 /* If LEN is not constant, try MAXLEN too.
2222 For MAXLEN only allow optimizing into non-_ocs function
2223 if SIZE is >= MAXLEN, never convert to __ocs_fail (). */
2224 if (maxlen == NULL_TREE || ! tree_fits_uhwi_p (maxlen))
2226 if (fcode == BUILT_IN_MEMPCPY_CHK && ignore)
2228 /* (void) __mempcpy_chk () can be optimized into
2229 (void) __memcpy_chk (). */
2230 fn = builtin_decl_explicit (BUILT_IN_MEMCPY_CHK);
2231 if (!fn)
2232 return false;
2234 gimple *repl = gimple_build_call (fn, 4, dest, src, len, size);
2235 replace_call_with_call_and_fold (gsi, repl);
2236 return true;
2238 return false;
2241 else
2242 maxlen = len;
2244 if (tree_int_cst_lt (size, maxlen))
2245 return false;
2248 fn = NULL_TREE;
2249 /* If __builtin_mem{cpy,pcpy,move,set}_chk is used, assume
2250 mem{cpy,pcpy,move,set} is available. */
2251 switch (fcode)
2253 case BUILT_IN_MEMCPY_CHK:
2254 fn = builtin_decl_explicit (BUILT_IN_MEMCPY);
2255 break;
2256 case BUILT_IN_MEMPCPY_CHK:
2257 fn = builtin_decl_explicit (BUILT_IN_MEMPCPY);
2258 break;
2259 case BUILT_IN_MEMMOVE_CHK:
2260 fn = builtin_decl_explicit (BUILT_IN_MEMMOVE);
2261 break;
2262 case BUILT_IN_MEMSET_CHK:
2263 fn = builtin_decl_explicit (BUILT_IN_MEMSET);
2264 break;
2265 default:
2266 break;
2269 if (!fn)
2270 return false;
2272 gimple *repl = gimple_build_call (fn, 3, dest, src, len);
2273 replace_call_with_call_and_fold (gsi, repl);
2274 return true;
2277 /* Fold a call to the __st[rp]cpy_chk builtin.
2278 DEST, SRC, and SIZE are the arguments to the call.
2279 IGNORE is true if return value can be ignored. FCODE is the BUILT_IN_*
2280 code of the builtin. If MAXLEN is not NULL, it is maximum length of
2281 strings passed as second argument. */
2283 static bool
2284 gimple_fold_builtin_stxcpy_chk (gimple_stmt_iterator *gsi,
2285 tree dest,
2286 tree src, tree size,
2287 enum built_in_function fcode)
2289 gimple *stmt = gsi_stmt (*gsi);
2290 location_t loc = gimple_location (stmt);
2291 bool ignore = gimple_call_lhs (stmt) == NULL_TREE;
2292 tree len, fn;
2294 /* If SRC and DEST are the same (and not volatile), return DEST. */
2295 if (fcode == BUILT_IN_STRCPY_CHK && operand_equal_p (src, dest, 0))
2297 replace_call_with_value (gsi, dest);
2298 return true;
2301 if (! tree_fits_uhwi_p (size))
2302 return false;
2304 tree maxlen = get_maxval_strlen (src, 1);
2305 if (! integer_all_onesp (size))
2307 len = c_strlen (src, 1);
2308 if (! len || ! tree_fits_uhwi_p (len))
2310 /* If LEN is not constant, try MAXLEN too.
2311 For MAXLEN only allow optimizing into non-_ocs function
2312 if SIZE is >= MAXLEN, never convert to __ocs_fail (). */
2313 if (maxlen == NULL_TREE || ! tree_fits_uhwi_p (maxlen))
2315 if (fcode == BUILT_IN_STPCPY_CHK)
2317 if (! ignore)
2318 return false;
2320 /* If return value of __stpcpy_chk is ignored,
2321 optimize into __strcpy_chk. */
2322 fn = builtin_decl_explicit (BUILT_IN_STRCPY_CHK);
2323 if (!fn)
2324 return false;
2326 gimple *repl = gimple_build_call (fn, 3, dest, src, size);
2327 replace_call_with_call_and_fold (gsi, repl);
2328 return true;
2331 if (! len || TREE_SIDE_EFFECTS (len))
2332 return false;
2334 /* If c_strlen returned something, but not a constant,
2335 transform __strcpy_chk into __memcpy_chk. */
2336 fn = builtin_decl_explicit (BUILT_IN_MEMCPY_CHK);
2337 if (!fn)
2338 return false;
2340 gimple_seq stmts = NULL;
2341 len = gimple_convert (&stmts, loc, size_type_node, len);
2342 len = gimple_build (&stmts, loc, PLUS_EXPR, size_type_node, len,
2343 build_int_cst (size_type_node, 1));
2344 gsi_insert_seq_before (gsi, stmts, GSI_SAME_STMT);
2345 gimple *repl = gimple_build_call (fn, 4, dest, src, len, size);
2346 replace_call_with_call_and_fold (gsi, repl);
2347 return true;
2350 else
2351 maxlen = len;
2353 if (! tree_int_cst_lt (maxlen, size))
2354 return false;
2357 /* If __builtin_st{r,p}cpy_chk is used, assume st{r,p}cpy is available. */
2358 fn = builtin_decl_explicit (fcode == BUILT_IN_STPCPY_CHK
2359 ? BUILT_IN_STPCPY : BUILT_IN_STRCPY);
2360 if (!fn)
2361 return false;
2363 gimple *repl = gimple_build_call (fn, 2, dest, src);
2364 replace_call_with_call_and_fold (gsi, repl);
2365 return true;
2368 /* Fold a call to the __st{r,p}ncpy_chk builtin. DEST, SRC, LEN, and SIZE
2369 are the arguments to the call. If MAXLEN is not NULL, it is maximum
2370 length passed as third argument. IGNORE is true if return value can be
2371 ignored. FCODE is the BUILT_IN_* code of the builtin. */
2373 static bool
2374 gimple_fold_builtin_stxncpy_chk (gimple_stmt_iterator *gsi,
2375 tree dest, tree src,
2376 tree len, tree size,
2377 enum built_in_function fcode)
2379 gimple *stmt = gsi_stmt (*gsi);
2380 bool ignore = gimple_call_lhs (stmt) == NULL_TREE;
2381 tree fn;
2383 if (fcode == BUILT_IN_STPNCPY_CHK && ignore)
2385 /* If return value of __stpncpy_chk is ignored,
2386 optimize into __strncpy_chk. */
2387 fn = builtin_decl_explicit (BUILT_IN_STRNCPY_CHK);
2388 if (fn)
2390 gimple *repl = gimple_build_call (fn, 4, dest, src, len, size);
2391 replace_call_with_call_and_fold (gsi, repl);
2392 return true;
2396 if (! tree_fits_uhwi_p (size))
2397 return false;
2399 tree maxlen = get_maxval_strlen (len, 2);
2400 if (! integer_all_onesp (size))
2402 if (! tree_fits_uhwi_p (len))
2404 /* If LEN is not constant, try MAXLEN too.
2405 For MAXLEN only allow optimizing into non-_ocs function
2406 if SIZE is >= MAXLEN, never convert to __ocs_fail (). */
2407 if (maxlen == NULL_TREE || ! tree_fits_uhwi_p (maxlen))
2408 return false;
2410 else
2411 maxlen = len;
2413 if (tree_int_cst_lt (size, maxlen))
2414 return false;
2417 /* If __builtin_st{r,p}ncpy_chk is used, assume st{r,p}ncpy is available. */
2418 fn = builtin_decl_explicit (fcode == BUILT_IN_STPNCPY_CHK
2419 ? BUILT_IN_STPNCPY : BUILT_IN_STRNCPY);
2420 if (!fn)
2421 return false;
2423 gimple *repl = gimple_build_call (fn, 3, dest, src, len);
2424 replace_call_with_call_and_fold (gsi, repl);
2425 return true;
2428 /* Fold function call to builtin stpcpy with arguments DEST and SRC.
2429 Return NULL_TREE if no simplification can be made. */
2431 static bool
2432 gimple_fold_builtin_stpcpy (gimple_stmt_iterator *gsi)
2434 gcall *stmt = as_a <gcall *> (gsi_stmt (*gsi));
2435 location_t loc = gimple_location (stmt);
2436 tree dest = gimple_call_arg (stmt, 0);
2437 tree src = gimple_call_arg (stmt, 1);
2438 tree fn, len, lenp1;
2440 /* If the result is unused, replace stpcpy with strcpy. */
2441 if (gimple_call_lhs (stmt) == NULL_TREE)
2443 tree fn = builtin_decl_implicit (BUILT_IN_STRCPY);
2444 if (!fn)
2445 return false;
2446 gimple_call_set_fndecl (stmt, fn);
2447 fold_stmt (gsi);
2448 return true;
2451 len = c_strlen (src, 1);
2452 if (!len
2453 || TREE_CODE (len) != INTEGER_CST)
2454 return false;
2456 if (optimize_function_for_size_p (cfun)
2457 /* If length is zero it's small enough. */
2458 && !integer_zerop (len))
2459 return false;
2461 /* If the source has a known length replace stpcpy with memcpy. */
2462 fn = builtin_decl_implicit (BUILT_IN_MEMCPY);
2463 if (!fn)
2464 return false;
2466 gimple_seq stmts = NULL;
2467 tree tem = gimple_convert (&stmts, loc, size_type_node, len);
2468 lenp1 = gimple_build (&stmts, loc, PLUS_EXPR, size_type_node,
2469 tem, build_int_cst (size_type_node, 1));
2470 gsi_insert_seq_before (gsi, stmts, GSI_SAME_STMT);
2471 gcall *repl = gimple_build_call (fn, 3, dest, src, lenp1);
2472 gimple_set_vuse (repl, gimple_vuse (stmt));
2473 gimple_set_vdef (repl, gimple_vdef (stmt));
2474 if (gimple_vdef (repl)
2475 && TREE_CODE (gimple_vdef (repl)) == SSA_NAME)
2476 SSA_NAME_DEF_STMT (gimple_vdef (repl)) = repl;
2477 gsi_insert_before (gsi, repl, GSI_SAME_STMT);
2478 /* Replace the result with dest + len. */
2479 stmts = NULL;
2480 tem = gimple_convert (&stmts, loc, sizetype, len);
2481 gsi_insert_seq_before (gsi, stmts, GSI_SAME_STMT);
2482 gassign *ret = gimple_build_assign (gimple_call_lhs (stmt),
2483 POINTER_PLUS_EXPR, dest, tem);
2484 gsi_replace (gsi, ret, false);
2485 /* Finally fold the memcpy call. */
2486 gimple_stmt_iterator gsi2 = *gsi;
2487 gsi_prev (&gsi2);
2488 fold_stmt (&gsi2);
2489 return true;
2492 /* Fold a call EXP to {,v}snprintf having NARGS passed as ARGS. Return
2493 NULL_TREE if a normal call should be emitted rather than expanding
2494 the function inline. FCODE is either BUILT_IN_SNPRINTF_CHK or
2495 BUILT_IN_VSNPRINTF_CHK. If MAXLEN is not NULL, it is maximum length
2496 passed as second argument. */
2498 static bool
2499 gimple_fold_builtin_snprintf_chk (gimple_stmt_iterator *gsi,
2500 enum built_in_function fcode)
2502 gcall *stmt = as_a <gcall *> (gsi_stmt (*gsi));
2503 tree dest, size, len, fn, fmt, flag;
2504 const char *fmt_str;
2506 /* Verify the required arguments in the original call. */
2507 if (gimple_call_num_args (stmt) < 5)
2508 return false;
2510 dest = gimple_call_arg (stmt, 0);
2511 len = gimple_call_arg (stmt, 1);
2512 flag = gimple_call_arg (stmt, 2);
2513 size = gimple_call_arg (stmt, 3);
2514 fmt = gimple_call_arg (stmt, 4);
2516 if (! tree_fits_uhwi_p (size))
2517 return false;
2519 if (! integer_all_onesp (size))
2521 tree maxlen = get_maxval_strlen (len, 2);
2522 if (! tree_fits_uhwi_p (len))
2524 /* If LEN is not constant, try MAXLEN too.
2525 For MAXLEN only allow optimizing into non-_ocs function
2526 if SIZE is >= MAXLEN, never convert to __ocs_fail (). */
2527 if (maxlen == NULL_TREE || ! tree_fits_uhwi_p (maxlen))
2528 return false;
2530 else
2531 maxlen = len;
2533 if (tree_int_cst_lt (size, maxlen))
2534 return false;
2537 if (!init_target_chars ())
2538 return false;
2540 /* Only convert __{,v}snprintf_chk to {,v}snprintf if flag is 0
2541 or if format doesn't contain % chars or is "%s". */
2542 if (! integer_zerop (flag))
2544 fmt_str = c_getstr (fmt);
2545 if (fmt_str == NULL)
2546 return false;
2547 if (strchr (fmt_str, target_percent) != NULL
2548 && strcmp (fmt_str, target_percent_s))
2549 return false;
2552 /* If __builtin_{,v}snprintf_chk is used, assume {,v}snprintf is
2553 available. */
2554 fn = builtin_decl_explicit (fcode == BUILT_IN_VSNPRINTF_CHK
2555 ? BUILT_IN_VSNPRINTF : BUILT_IN_SNPRINTF);
2556 if (!fn)
2557 return false;
2559 /* Replace the called function and the first 5 argument by 3 retaining
2560 trailing varargs. */
2561 gimple_call_set_fndecl (stmt, fn);
2562 gimple_call_set_fntype (stmt, TREE_TYPE (fn));
2563 gimple_call_set_arg (stmt, 0, dest);
2564 gimple_call_set_arg (stmt, 1, len);
2565 gimple_call_set_arg (stmt, 2, fmt);
2566 for (unsigned i = 3; i < gimple_call_num_args (stmt) - 2; ++i)
2567 gimple_call_set_arg (stmt, i, gimple_call_arg (stmt, i + 2));
2568 gimple_set_num_ops (stmt, gimple_num_ops (stmt) - 2);
2569 fold_stmt (gsi);
2570 return true;
2573 /* Fold a call EXP to __{,v}sprintf_chk having NARGS passed as ARGS.
2574 Return NULL_TREE if a normal call should be emitted rather than
2575 expanding the function inline. FCODE is either BUILT_IN_SPRINTF_CHK
2576 or BUILT_IN_VSPRINTF_CHK. */
2578 static bool
2579 gimple_fold_builtin_sprintf_chk (gimple_stmt_iterator *gsi,
2580 enum built_in_function fcode)
2582 gcall *stmt = as_a <gcall *> (gsi_stmt (*gsi));
2583 tree dest, size, len, fn, fmt, flag;
2584 const char *fmt_str;
2585 unsigned nargs = gimple_call_num_args (stmt);
2587 /* Verify the required arguments in the original call. */
2588 if (nargs < 4)
2589 return false;
2590 dest = gimple_call_arg (stmt, 0);
2591 flag = gimple_call_arg (stmt, 1);
2592 size = gimple_call_arg (stmt, 2);
2593 fmt = gimple_call_arg (stmt, 3);
2595 if (! tree_fits_uhwi_p (size))
2596 return false;
2598 len = NULL_TREE;
2600 if (!init_target_chars ())
2601 return false;
2603 /* Check whether the format is a literal string constant. */
2604 fmt_str = c_getstr (fmt);
2605 if (fmt_str != NULL)
2607 /* If the format doesn't contain % args or %%, we know the size. */
2608 if (strchr (fmt_str, target_percent) == 0)
2610 if (fcode != BUILT_IN_SPRINTF_CHK || nargs == 4)
2611 len = build_int_cstu (size_type_node, strlen (fmt_str));
2613 /* If the format is "%s" and first ... argument is a string literal,
2614 we know the size too. */
2615 else if (fcode == BUILT_IN_SPRINTF_CHK
2616 && strcmp (fmt_str, target_percent_s) == 0)
2618 tree arg;
2620 if (nargs == 5)
2622 arg = gimple_call_arg (stmt, 4);
2623 if (POINTER_TYPE_P (TREE_TYPE (arg)))
2625 len = c_strlen (arg, 1);
2626 if (! len || ! tree_fits_uhwi_p (len))
2627 len = NULL_TREE;
2633 if (! integer_all_onesp (size))
2635 if (! len || ! tree_int_cst_lt (len, size))
2636 return false;
2639 /* Only convert __{,v}sprintf_chk to {,v}sprintf if flag is 0
2640 or if format doesn't contain % chars or is "%s". */
2641 if (! integer_zerop (flag))
2643 if (fmt_str == NULL)
2644 return false;
2645 if (strchr (fmt_str, target_percent) != NULL
2646 && strcmp (fmt_str, target_percent_s))
2647 return false;
2650 /* If __builtin_{,v}sprintf_chk is used, assume {,v}sprintf is available. */
2651 fn = builtin_decl_explicit (fcode == BUILT_IN_VSPRINTF_CHK
2652 ? BUILT_IN_VSPRINTF : BUILT_IN_SPRINTF);
2653 if (!fn)
2654 return false;
2656 /* Replace the called function and the first 4 argument by 2 retaining
2657 trailing varargs. */
2658 gimple_call_set_fndecl (stmt, fn);
2659 gimple_call_set_fntype (stmt, TREE_TYPE (fn));
2660 gimple_call_set_arg (stmt, 0, dest);
2661 gimple_call_set_arg (stmt, 1, fmt);
2662 for (unsigned i = 2; i < gimple_call_num_args (stmt) - 2; ++i)
2663 gimple_call_set_arg (stmt, i, gimple_call_arg (stmt, i + 2));
2664 gimple_set_num_ops (stmt, gimple_num_ops (stmt) - 2);
2665 fold_stmt (gsi);
2666 return true;
2669 /* Simplify a call to the sprintf builtin with arguments DEST, FMT, and ORIG.
2670 ORIG may be null if this is a 2-argument call. We don't attempt to
2671 simplify calls with more than 3 arguments.
2673 Return true if simplification was possible, otherwise false. */
2675 bool
2676 gimple_fold_builtin_sprintf (gimple_stmt_iterator *gsi)
2678 gimple *stmt = gsi_stmt (*gsi);
2679 tree dest = gimple_call_arg (stmt, 0);
2680 tree fmt = gimple_call_arg (stmt, 1);
2681 tree orig = NULL_TREE;
2682 const char *fmt_str = NULL;
2684 /* Verify the required arguments in the original call. We deal with two
2685 types of sprintf() calls: 'sprintf (str, fmt)' and
2686 'sprintf (dest, "%s", orig)'. */
2687 if (gimple_call_num_args (stmt) > 3)
2688 return false;
2690 if (gimple_call_num_args (stmt) == 3)
2691 orig = gimple_call_arg (stmt, 2);
2693 /* Check whether the format is a literal string constant. */
2694 fmt_str = c_getstr (fmt);
2695 if (fmt_str == NULL)
2696 return false;
2698 if (!init_target_chars ())
2699 return false;
2701 /* If the format doesn't contain % args or %%, use strcpy. */
2702 if (strchr (fmt_str, target_percent) == NULL)
2704 tree fn = builtin_decl_implicit (BUILT_IN_STRCPY);
2706 if (!fn)
2707 return false;
2709 /* Don't optimize sprintf (buf, "abc", ptr++). */
2710 if (orig)
2711 return false;
2713 /* Convert sprintf (str, fmt) into strcpy (str, fmt) when
2714 'format' is known to contain no % formats. */
2715 gimple_seq stmts = NULL;
2716 gimple *repl = gimple_build_call (fn, 2, dest, fmt);
2717 gimple_seq_add_stmt_without_update (&stmts, repl);
2718 if (gimple_call_lhs (stmt))
2720 repl = gimple_build_assign (gimple_call_lhs (stmt),
2721 build_int_cst (integer_type_node,
2722 strlen (fmt_str)));
2723 gimple_seq_add_stmt_without_update (&stmts, repl);
2724 gsi_replace_with_seq_vops (gsi, stmts);
2725 /* gsi now points at the assignment to the lhs, get a
2726 stmt iterator to the memcpy call.
2727 ??? We can't use gsi_for_stmt as that doesn't work when the
2728 CFG isn't built yet. */
2729 gimple_stmt_iterator gsi2 = *gsi;
2730 gsi_prev (&gsi2);
2731 fold_stmt (&gsi2);
2733 else
2735 gsi_replace_with_seq_vops (gsi, stmts);
2736 fold_stmt (gsi);
2738 return true;
2741 /* If the format is "%s", use strcpy if the result isn't used. */
2742 else if (fmt_str && strcmp (fmt_str, target_percent_s) == 0)
2744 tree fn;
2745 fn = builtin_decl_implicit (BUILT_IN_STRCPY);
2747 if (!fn)
2748 return false;
2750 /* Don't crash on sprintf (str1, "%s"). */
2751 if (!orig)
2752 return false;
2754 tree orig_len = NULL_TREE;
2755 if (gimple_call_lhs (stmt))
2757 orig_len = get_maxval_strlen (orig, 0);
2758 if (!orig_len)
2759 return false;
2762 /* Convert sprintf (str1, "%s", str2) into strcpy (str1, str2). */
2763 gimple_seq stmts = NULL;
2764 gimple *repl = gimple_build_call (fn, 2, dest, orig);
2765 gimple_seq_add_stmt_without_update (&stmts, repl);
2766 if (gimple_call_lhs (stmt))
2768 if (!useless_type_conversion_p (integer_type_node,
2769 TREE_TYPE (orig_len)))
2770 orig_len = fold_convert (integer_type_node, orig_len);
2771 repl = gimple_build_assign (gimple_call_lhs (stmt), orig_len);
2772 gimple_seq_add_stmt_without_update (&stmts, repl);
2773 gsi_replace_with_seq_vops (gsi, stmts);
2774 /* gsi now points at the assignment to the lhs, get a
2775 stmt iterator to the memcpy call.
2776 ??? We can't use gsi_for_stmt as that doesn't work when the
2777 CFG isn't built yet. */
2778 gimple_stmt_iterator gsi2 = *gsi;
2779 gsi_prev (&gsi2);
2780 fold_stmt (&gsi2);
2782 else
2784 gsi_replace_with_seq_vops (gsi, stmts);
2785 fold_stmt (gsi);
2787 return true;
2789 return false;
2792 /* Simplify a call to the snprintf builtin with arguments DEST, DESTSIZE,
2793 FMT, and ORIG. ORIG may be null if this is a 3-argument call. We don't
2794 attempt to simplify calls with more than 4 arguments.
2796 Return true if simplification was possible, otherwise false. */
2798 bool
2799 gimple_fold_builtin_snprintf (gimple_stmt_iterator *gsi)
2801 gcall *stmt = as_a <gcall *> (gsi_stmt (*gsi));
2802 tree dest = gimple_call_arg (stmt, 0);
2803 tree destsize = gimple_call_arg (stmt, 1);
2804 tree fmt = gimple_call_arg (stmt, 2);
2805 tree orig = NULL_TREE;
2806 const char *fmt_str = NULL;
2808 if (gimple_call_num_args (stmt) > 4)
2809 return false;
2811 if (gimple_call_num_args (stmt) == 4)
2812 orig = gimple_call_arg (stmt, 3);
2814 if (!tree_fits_uhwi_p (destsize))
2815 return false;
2816 unsigned HOST_WIDE_INT destlen = tree_to_uhwi (destsize);
2818 /* Check whether the format is a literal string constant. */
2819 fmt_str = c_getstr (fmt);
2820 if (fmt_str == NULL)
2821 return false;
2823 if (!init_target_chars ())
2824 return false;
2826 /* If the format doesn't contain % args or %%, use strcpy. */
2827 if (strchr (fmt_str, target_percent) == NULL)
2829 tree fn = builtin_decl_implicit (BUILT_IN_STRCPY);
2830 if (!fn)
2831 return false;
2833 /* Don't optimize snprintf (buf, 4, "abc", ptr++). */
2834 if (orig)
2835 return false;
2837 /* We could expand this as
2838 memcpy (str, fmt, cst - 1); str[cst - 1] = '\0';
2839 or to
2840 memcpy (str, fmt_with_nul_at_cstm1, cst);
2841 but in the former case that might increase code size
2842 and in the latter case grow .rodata section too much.
2843 So punt for now. */
2844 size_t len = strlen (fmt_str);
2845 if (len >= destlen)
2846 return false;
2848 gimple_seq stmts = NULL;
2849 gimple *repl = gimple_build_call (fn, 2, dest, fmt);
2850 gimple_seq_add_stmt_without_update (&stmts, repl);
2851 if (gimple_call_lhs (stmt))
2853 repl = gimple_build_assign (gimple_call_lhs (stmt),
2854 build_int_cst (integer_type_node, len));
2855 gimple_seq_add_stmt_without_update (&stmts, repl);
2856 gsi_replace_with_seq_vops (gsi, stmts);
2857 /* gsi now points at the assignment to the lhs, get a
2858 stmt iterator to the memcpy call.
2859 ??? We can't use gsi_for_stmt as that doesn't work when the
2860 CFG isn't built yet. */
2861 gimple_stmt_iterator gsi2 = *gsi;
2862 gsi_prev (&gsi2);
2863 fold_stmt (&gsi2);
2865 else
2867 gsi_replace_with_seq_vops (gsi, stmts);
2868 fold_stmt (gsi);
2870 return true;
2873 /* If the format is "%s", use strcpy if the result isn't used. */
2874 else if (fmt_str && strcmp (fmt_str, target_percent_s) == 0)
2876 tree fn = builtin_decl_implicit (BUILT_IN_STRCPY);
2877 if (!fn)
2878 return false;
2880 /* Don't crash on snprintf (str1, cst, "%s"). */
2881 if (!orig)
2882 return false;
2884 tree orig_len = get_maxval_strlen (orig, 0);
2885 if (!orig_len || TREE_CODE (orig_len) != INTEGER_CST)
2886 return false;
2888 /* We could expand this as
2889 memcpy (str1, str2, cst - 1); str1[cst - 1] = '\0';
2890 or to
2891 memcpy (str1, str2_with_nul_at_cstm1, cst);
2892 but in the former case that might increase code size
2893 and in the latter case grow .rodata section too much.
2894 So punt for now. */
2895 if (compare_tree_int (orig_len, destlen) >= 0)
2896 return false;
2898 /* Convert snprintf (str1, cst, "%s", str2) into
2899 strcpy (str1, str2) if strlen (str2) < cst. */
2900 gimple_seq stmts = NULL;
2901 gimple *repl = gimple_build_call (fn, 2, dest, orig);
2902 gimple_seq_add_stmt_without_update (&stmts, repl);
2903 if (gimple_call_lhs (stmt))
2905 if (!useless_type_conversion_p (integer_type_node,
2906 TREE_TYPE (orig_len)))
2907 orig_len = fold_convert (integer_type_node, orig_len);
2908 repl = gimple_build_assign (gimple_call_lhs (stmt), orig_len);
2909 gimple_seq_add_stmt_without_update (&stmts, repl);
2910 gsi_replace_with_seq_vops (gsi, stmts);
2911 /* gsi now points at the assignment to the lhs, get a
2912 stmt iterator to the memcpy call.
2913 ??? We can't use gsi_for_stmt as that doesn't work when the
2914 CFG isn't built yet. */
2915 gimple_stmt_iterator gsi2 = *gsi;
2916 gsi_prev (&gsi2);
2917 fold_stmt (&gsi2);
2919 else
2921 gsi_replace_with_seq_vops (gsi, stmts);
2922 fold_stmt (gsi);
2924 return true;
2926 return false;
2929 /* Fold a call to the {,v}fprintf{,_unlocked} and __{,v}printf_chk builtins.
2930 FP, FMT, and ARG are the arguments to the call. We don't fold calls with
2931 more than 3 arguments, and ARG may be null in the 2-argument case.
2933 Return NULL_TREE if no simplification was possible, otherwise return the
2934 simplified form of the call as a tree. FCODE is the BUILT_IN_*
2935 code of the function to be simplified. */
2937 static bool
2938 gimple_fold_builtin_fprintf (gimple_stmt_iterator *gsi,
2939 tree fp, tree fmt, tree arg,
2940 enum built_in_function fcode)
2942 gcall *stmt = as_a <gcall *> (gsi_stmt (*gsi));
2943 tree fn_fputc, fn_fputs;
2944 const char *fmt_str = NULL;
2946 /* If the return value is used, don't do the transformation. */
2947 if (gimple_call_lhs (stmt) != NULL_TREE)
2948 return false;
2950 /* Check whether the format is a literal string constant. */
2951 fmt_str = c_getstr (fmt);
2952 if (fmt_str == NULL)
2953 return false;
2955 if (fcode == BUILT_IN_FPRINTF_UNLOCKED)
2957 /* If we're using an unlocked function, assume the other
2958 unlocked functions exist explicitly. */
2959 fn_fputc = builtin_decl_explicit (BUILT_IN_FPUTC_UNLOCKED);
2960 fn_fputs = builtin_decl_explicit (BUILT_IN_FPUTS_UNLOCKED);
2962 else
2964 fn_fputc = builtin_decl_implicit (BUILT_IN_FPUTC);
2965 fn_fputs = builtin_decl_implicit (BUILT_IN_FPUTS);
2968 if (!init_target_chars ())
2969 return false;
2971 /* If the format doesn't contain % args or %%, use strcpy. */
2972 if (strchr (fmt_str, target_percent) == NULL)
2974 if (fcode != BUILT_IN_VFPRINTF && fcode != BUILT_IN_VFPRINTF_CHK
2975 && arg)
2976 return false;
2978 /* If the format specifier was "", fprintf does nothing. */
2979 if (fmt_str[0] == '\0')
2981 replace_call_with_value (gsi, NULL_TREE);
2982 return true;
2985 /* When "string" doesn't contain %, replace all cases of
2986 fprintf (fp, string) with fputs (string, fp). The fputs
2987 builtin will take care of special cases like length == 1. */
2988 if (fn_fputs)
2990 gcall *repl = gimple_build_call (fn_fputs, 2, fmt, fp);
2991 replace_call_with_call_and_fold (gsi, repl);
2992 return true;
2996 /* The other optimizations can be done only on the non-va_list variants. */
2997 else if (fcode == BUILT_IN_VFPRINTF || fcode == BUILT_IN_VFPRINTF_CHK)
2998 return false;
3000 /* If the format specifier was "%s", call __builtin_fputs (arg, fp). */
3001 else if (strcmp (fmt_str, target_percent_s) == 0)
3003 if (!arg || ! POINTER_TYPE_P (TREE_TYPE (arg)))
3004 return false;
3005 if (fn_fputs)
3007 gcall *repl = gimple_build_call (fn_fputs, 2, arg, fp);
3008 replace_call_with_call_and_fold (gsi, repl);
3009 return true;
3013 /* If the format specifier was "%c", call __builtin_fputc (arg, fp). */
3014 else if (strcmp (fmt_str, target_percent_c) == 0)
3016 if (!arg
3017 || ! useless_type_conversion_p (integer_type_node, TREE_TYPE (arg)))
3018 return false;
3019 if (fn_fputc)
3021 gcall *repl = gimple_build_call (fn_fputc, 2, arg, fp);
3022 replace_call_with_call_and_fold (gsi, repl);
3023 return true;
3027 return false;
3030 /* Fold a call to the {,v}printf{,_unlocked} and __{,v}printf_chk builtins.
3031 FMT and ARG are the arguments to the call; we don't fold cases with
3032 more than 2 arguments, and ARG may be null if this is a 1-argument case.
3034 Return NULL_TREE if no simplification was possible, otherwise return the
3035 simplified form of the call as a tree. FCODE is the BUILT_IN_*
3036 code of the function to be simplified. */
3038 static bool
3039 gimple_fold_builtin_printf (gimple_stmt_iterator *gsi, tree fmt,
3040 tree arg, enum built_in_function fcode)
3042 gcall *stmt = as_a <gcall *> (gsi_stmt (*gsi));
3043 tree fn_putchar, fn_puts, newarg;
3044 const char *fmt_str = NULL;
3046 /* If the return value is used, don't do the transformation. */
3047 if (gimple_call_lhs (stmt) != NULL_TREE)
3048 return false;
3050 /* Check whether the format is a literal string constant. */
3051 fmt_str = c_getstr (fmt);
3052 if (fmt_str == NULL)
3053 return false;
3055 if (fcode == BUILT_IN_PRINTF_UNLOCKED)
3057 /* If we're using an unlocked function, assume the other
3058 unlocked functions exist explicitly. */
3059 fn_putchar = builtin_decl_explicit (BUILT_IN_PUTCHAR_UNLOCKED);
3060 fn_puts = builtin_decl_explicit (BUILT_IN_PUTS_UNLOCKED);
3062 else
3064 fn_putchar = builtin_decl_implicit (BUILT_IN_PUTCHAR);
3065 fn_puts = builtin_decl_implicit (BUILT_IN_PUTS);
3068 if (!init_target_chars ())
3069 return false;
3071 if (strcmp (fmt_str, target_percent_s) == 0
3072 || strchr (fmt_str, target_percent) == NULL)
3074 const char *str;
3076 if (strcmp (fmt_str, target_percent_s) == 0)
3078 if (fcode == BUILT_IN_VPRINTF || fcode == BUILT_IN_VPRINTF_CHK)
3079 return false;
3081 if (!arg || ! POINTER_TYPE_P (TREE_TYPE (arg)))
3082 return false;
3084 str = c_getstr (arg);
3085 if (str == NULL)
3086 return false;
3088 else
3090 /* The format specifier doesn't contain any '%' characters. */
3091 if (fcode != BUILT_IN_VPRINTF && fcode != BUILT_IN_VPRINTF_CHK
3092 && arg)
3093 return false;
3094 str = fmt_str;
3097 /* If the string was "", printf does nothing. */
3098 if (str[0] == '\0')
3100 replace_call_with_value (gsi, NULL_TREE);
3101 return true;
3104 /* If the string has length of 1, call putchar. */
3105 if (str[1] == '\0')
3107 /* Given printf("c"), (where c is any one character,)
3108 convert "c"[0] to an int and pass that to the replacement
3109 function. */
3110 newarg = build_int_cst (integer_type_node, str[0]);
3111 if (fn_putchar)
3113 gcall *repl = gimple_build_call (fn_putchar, 1, newarg);
3114 replace_call_with_call_and_fold (gsi, repl);
3115 return true;
3118 else
3120 /* If the string was "string\n", call puts("string"). */
3121 size_t len = strlen (str);
3122 if ((unsigned char)str[len - 1] == target_newline
3123 && (size_t) (int) len == len
3124 && (int) len > 0)
3126 char *newstr;
3127 tree offset_node, string_cst;
3129 /* Create a NUL-terminated string that's one char shorter
3130 than the original, stripping off the trailing '\n'. */
3131 newarg = build_string_literal (len, str);
3132 string_cst = string_constant (newarg, &offset_node);
3133 gcc_checking_assert (string_cst
3134 && (TREE_STRING_LENGTH (string_cst)
3135 == (int) len)
3136 && integer_zerop (offset_node)
3137 && (unsigned char)
3138 TREE_STRING_POINTER (string_cst)[len - 1]
3139 == target_newline);
3140 /* build_string_literal creates a new STRING_CST,
3141 modify it in place to avoid double copying. */
3142 newstr = CONST_CAST (char *, TREE_STRING_POINTER (string_cst));
3143 newstr[len - 1] = '\0';
3144 if (fn_puts)
3146 gcall *repl = gimple_build_call (fn_puts, 1, newarg);
3147 replace_call_with_call_and_fold (gsi, repl);
3148 return true;
3151 else
3152 /* We'd like to arrange to call fputs(string,stdout) here,
3153 but we need stdout and don't have a way to get it yet. */
3154 return false;
3158 /* The other optimizations can be done only on the non-va_list variants. */
3159 else if (fcode == BUILT_IN_VPRINTF || fcode == BUILT_IN_VPRINTF_CHK)
3160 return false;
3162 /* If the format specifier was "%s\n", call __builtin_puts(arg). */
3163 else if (strcmp (fmt_str, target_percent_s_newline) == 0)
3165 if (!arg || ! POINTER_TYPE_P (TREE_TYPE (arg)))
3166 return false;
3167 if (fn_puts)
3169 gcall *repl = gimple_build_call (fn_puts, 1, arg);
3170 replace_call_with_call_and_fold (gsi, repl);
3171 return true;
3175 /* If the format specifier was "%c", call __builtin_putchar(arg). */
3176 else if (strcmp (fmt_str, target_percent_c) == 0)
3178 if (!arg || ! useless_type_conversion_p (integer_type_node,
3179 TREE_TYPE (arg)))
3180 return false;
3181 if (fn_putchar)
3183 gcall *repl = gimple_build_call (fn_putchar, 1, arg);
3184 replace_call_with_call_and_fold (gsi, repl);
3185 return true;
3189 return false;
3194 /* Fold a call to __builtin_strlen with known length LEN. */
3196 static bool
3197 gimple_fold_builtin_strlen (gimple_stmt_iterator *gsi)
3199 gimple *stmt = gsi_stmt (*gsi);
3200 tree len = get_maxval_strlen (gimple_call_arg (stmt, 0), 0);
3201 if (!len)
3202 return false;
3203 len = force_gimple_operand_gsi (gsi, len, true, NULL, true, GSI_SAME_STMT);
3204 replace_call_with_value (gsi, len);
3205 return true;
3208 /* Fold a call to __builtin_acc_on_device. */
3210 static bool
3211 gimple_fold_builtin_acc_on_device (gimple_stmt_iterator *gsi, tree arg0)
3213 /* Defer folding until we know which compiler we're in. */
3214 if (symtab->state != EXPANSION)
3215 return false;
3217 unsigned val_host = GOMP_DEVICE_HOST;
3218 unsigned val_dev = GOMP_DEVICE_NONE;
3220 #ifdef ACCEL_COMPILER
3221 val_host = GOMP_DEVICE_NOT_HOST;
3222 val_dev = ACCEL_COMPILER_acc_device;
3223 #endif
3225 location_t loc = gimple_location (gsi_stmt (*gsi));
3227 tree host_eq = make_ssa_name (boolean_type_node);
3228 gimple *host_ass = gimple_build_assign
3229 (host_eq, EQ_EXPR, arg0, build_int_cst (TREE_TYPE (arg0), val_host));
3230 gimple_set_location (host_ass, loc);
3231 gsi_insert_before (gsi, host_ass, GSI_SAME_STMT);
3233 tree dev_eq = make_ssa_name (boolean_type_node);
3234 gimple *dev_ass = gimple_build_assign
3235 (dev_eq, EQ_EXPR, arg0, build_int_cst (TREE_TYPE (arg0), val_dev));
3236 gimple_set_location (dev_ass, loc);
3237 gsi_insert_before (gsi, dev_ass, GSI_SAME_STMT);
3239 tree result = make_ssa_name (boolean_type_node);
3240 gimple *result_ass = gimple_build_assign
3241 (result, BIT_IOR_EXPR, host_eq, dev_eq);
3242 gimple_set_location (result_ass, loc);
3243 gsi_insert_before (gsi, result_ass, GSI_SAME_STMT);
3245 replace_call_with_value (gsi, result);
3247 return true;
3250 /* Fold realloc (0, n) -> malloc (n). */
3252 static bool
3253 gimple_fold_builtin_realloc (gimple_stmt_iterator *gsi)
3255 gimple *stmt = gsi_stmt (*gsi);
3256 tree arg = gimple_call_arg (stmt, 0);
3257 tree size = gimple_call_arg (stmt, 1);
3259 if (operand_equal_p (arg, null_pointer_node, 0))
3261 tree fn_malloc = builtin_decl_implicit (BUILT_IN_MALLOC);
3262 if (fn_malloc)
3264 gcall *repl = gimple_build_call (fn_malloc, 1, size);
3265 replace_call_with_call_and_fold (gsi, repl);
3266 return true;
3269 return false;
3272 /* Fold the non-target builtin at *GSI and return whether any simplification
3273 was made. */
3275 static bool
3276 gimple_fold_builtin (gimple_stmt_iterator *gsi)
3278 gcall *stmt = as_a <gcall *>(gsi_stmt (*gsi));
3279 tree callee = gimple_call_fndecl (stmt);
3281 /* Give up for always_inline inline builtins until they are
3282 inlined. */
3283 if (avoid_folding_inline_builtin (callee))
3284 return false;
3286 unsigned n = gimple_call_num_args (stmt);
3287 enum built_in_function fcode = DECL_FUNCTION_CODE (callee);
3288 switch (fcode)
3290 case BUILT_IN_BZERO:
3291 return gimple_fold_builtin_memset (gsi, integer_zero_node,
3292 gimple_call_arg (stmt, 1));
3293 case BUILT_IN_MEMSET:
3294 return gimple_fold_builtin_memset (gsi,
3295 gimple_call_arg (stmt, 1),
3296 gimple_call_arg (stmt, 2));
3297 case BUILT_IN_BCOPY:
3298 return gimple_fold_builtin_memory_op (gsi, gimple_call_arg (stmt, 1),
3299 gimple_call_arg (stmt, 0), 3);
3300 case BUILT_IN_MEMCPY:
3301 return gimple_fold_builtin_memory_op (gsi, gimple_call_arg (stmt, 0),
3302 gimple_call_arg (stmt, 1), 0);
3303 case BUILT_IN_MEMPCPY:
3304 return gimple_fold_builtin_memory_op (gsi, gimple_call_arg (stmt, 0),
3305 gimple_call_arg (stmt, 1), 1);
3306 case BUILT_IN_MEMMOVE:
3307 return gimple_fold_builtin_memory_op (gsi, gimple_call_arg (stmt, 0),
3308 gimple_call_arg (stmt, 1), 3);
3309 case BUILT_IN_SPRINTF_CHK:
3310 case BUILT_IN_VSPRINTF_CHK:
3311 return gimple_fold_builtin_sprintf_chk (gsi, fcode);
3312 case BUILT_IN_STRCAT_CHK:
3313 return gimple_fold_builtin_strcat_chk (gsi);
3314 case BUILT_IN_STRNCAT_CHK:
3315 return gimple_fold_builtin_strncat_chk (gsi);
3316 case BUILT_IN_STRLEN:
3317 return gimple_fold_builtin_strlen (gsi);
3318 case BUILT_IN_STRCPY:
3319 return gimple_fold_builtin_strcpy (gsi,
3320 gimple_call_arg (stmt, 0),
3321 gimple_call_arg (stmt, 1));
3322 case BUILT_IN_STRNCPY:
3323 return gimple_fold_builtin_strncpy (gsi,
3324 gimple_call_arg (stmt, 0),
3325 gimple_call_arg (stmt, 1),
3326 gimple_call_arg (stmt, 2));
3327 case BUILT_IN_STRCAT:
3328 return gimple_fold_builtin_strcat (gsi, gimple_call_arg (stmt, 0),
3329 gimple_call_arg (stmt, 1));
3330 case BUILT_IN_STRNCAT:
3331 return gimple_fold_builtin_strncat (gsi);
3332 case BUILT_IN_INDEX:
3333 case BUILT_IN_STRCHR:
3334 return gimple_fold_builtin_strchr (gsi, false);
3335 case BUILT_IN_RINDEX:
3336 case BUILT_IN_STRRCHR:
3337 return gimple_fold_builtin_strchr (gsi, true);
3338 case BUILT_IN_STRSTR:
3339 return gimple_fold_builtin_strstr (gsi);
3340 case BUILT_IN_STRCMP:
3341 case BUILT_IN_STRCASECMP:
3342 case BUILT_IN_STRNCMP:
3343 case BUILT_IN_STRNCASECMP:
3344 return gimple_fold_builtin_string_compare (gsi);
3345 case BUILT_IN_MEMCHR:
3346 return gimple_fold_builtin_memchr (gsi);
3347 case BUILT_IN_FPUTS:
3348 return gimple_fold_builtin_fputs (gsi, gimple_call_arg (stmt, 0),
3349 gimple_call_arg (stmt, 1), false);
3350 case BUILT_IN_FPUTS_UNLOCKED:
3351 return gimple_fold_builtin_fputs (gsi, gimple_call_arg (stmt, 0),
3352 gimple_call_arg (stmt, 1), true);
3353 case BUILT_IN_MEMCPY_CHK:
3354 case BUILT_IN_MEMPCPY_CHK:
3355 case BUILT_IN_MEMMOVE_CHK:
3356 case BUILT_IN_MEMSET_CHK:
3357 return gimple_fold_builtin_memory_chk (gsi,
3358 gimple_call_arg (stmt, 0),
3359 gimple_call_arg (stmt, 1),
3360 gimple_call_arg (stmt, 2),
3361 gimple_call_arg (stmt, 3),
3362 fcode);
3363 case BUILT_IN_STPCPY:
3364 return gimple_fold_builtin_stpcpy (gsi);
3365 case BUILT_IN_STRCPY_CHK:
3366 case BUILT_IN_STPCPY_CHK:
3367 return gimple_fold_builtin_stxcpy_chk (gsi,
3368 gimple_call_arg (stmt, 0),
3369 gimple_call_arg (stmt, 1),
3370 gimple_call_arg (stmt, 2),
3371 fcode);
3372 case BUILT_IN_STRNCPY_CHK:
3373 case BUILT_IN_STPNCPY_CHK:
3374 return gimple_fold_builtin_stxncpy_chk (gsi,
3375 gimple_call_arg (stmt, 0),
3376 gimple_call_arg (stmt, 1),
3377 gimple_call_arg (stmt, 2),
3378 gimple_call_arg (stmt, 3),
3379 fcode);
3380 case BUILT_IN_SNPRINTF_CHK:
3381 case BUILT_IN_VSNPRINTF_CHK:
3382 return gimple_fold_builtin_snprintf_chk (gsi, fcode);
3384 case BUILT_IN_FPRINTF:
3385 case BUILT_IN_FPRINTF_UNLOCKED:
3386 case BUILT_IN_VFPRINTF:
3387 if (n == 2 || n == 3)
3388 return gimple_fold_builtin_fprintf (gsi,
3389 gimple_call_arg (stmt, 0),
3390 gimple_call_arg (stmt, 1),
3391 n == 3
3392 ? gimple_call_arg (stmt, 2)
3393 : NULL_TREE,
3394 fcode);
3395 break;
3396 case BUILT_IN_FPRINTF_CHK:
3397 case BUILT_IN_VFPRINTF_CHK:
3398 if (n == 3 || n == 4)
3399 return gimple_fold_builtin_fprintf (gsi,
3400 gimple_call_arg (stmt, 0),
3401 gimple_call_arg (stmt, 2),
3402 n == 4
3403 ? gimple_call_arg (stmt, 3)
3404 : NULL_TREE,
3405 fcode);
3406 break;
3407 case BUILT_IN_PRINTF:
3408 case BUILT_IN_PRINTF_UNLOCKED:
3409 case BUILT_IN_VPRINTF:
3410 if (n == 1 || n == 2)
3411 return gimple_fold_builtin_printf (gsi, gimple_call_arg (stmt, 0),
3412 n == 2
3413 ? gimple_call_arg (stmt, 1)
3414 : NULL_TREE, fcode);
3415 break;
3416 case BUILT_IN_PRINTF_CHK:
3417 case BUILT_IN_VPRINTF_CHK:
3418 if (n == 2 || n == 3)
3419 return gimple_fold_builtin_printf (gsi, gimple_call_arg (stmt, 1),
3420 n == 3
3421 ? gimple_call_arg (stmt, 2)
3422 : NULL_TREE, fcode);
3423 break;
3424 case BUILT_IN_ACC_ON_DEVICE:
3425 return gimple_fold_builtin_acc_on_device (gsi,
3426 gimple_call_arg (stmt, 0));
3427 case BUILT_IN_REALLOC:
3428 return gimple_fold_builtin_realloc (gsi);
3430 default:;
3433 /* Try the generic builtin folder. */
3434 bool ignore = (gimple_call_lhs (stmt) == NULL);
3435 tree result = fold_call_stmt (stmt, ignore);
3436 if (result)
3438 if (ignore)
3439 STRIP_NOPS (result);
3440 else
3441 result = fold_convert (gimple_call_return_type (stmt), result);
3442 if (!update_call_from_tree (gsi, result))
3443 gimplify_and_update_call_from_tree (gsi, result);
3444 return true;
3447 return false;
3450 /* Transform IFN_GOACC_DIM_SIZE and IFN_GOACC_DIM_POS internal
3451 function calls to constants, where possible. */
3453 static tree
3454 fold_internal_goacc_dim (const gimple *call)
3456 int axis = oacc_get_ifn_dim_arg (call);
3457 int size = oacc_get_fn_dim_size (current_function_decl, axis);
3458 bool is_pos = gimple_call_internal_fn (call) == IFN_GOACC_DIM_POS;
3459 tree result = NULL_TREE;
3461 /* If the size is 1, or we only want the size and it is not dynamic,
3462 we know the answer. */
3463 if (size == 1 || (!is_pos && size))
3465 tree type = TREE_TYPE (gimple_call_lhs (call));
3466 result = build_int_cst (type, size - is_pos);
3469 return result;
3472 /* Return true if stmt is __atomic_compare_exchange_N call which is suitable
3473 for conversion into ATOMIC_COMPARE_EXCHANGE if the second argument is
3474 &var where var is only addressable because of such calls. */
3476 bool
3477 optimize_atomic_compare_exchange_p (gimple *stmt)
3479 if (gimple_call_num_args (stmt) != 6
3480 || !flag_inline_atomics
3481 || !optimize
3482 || (flag_sanitize & (SANITIZE_THREAD | SANITIZE_ADDRESS)) != 0
3483 || !gimple_call_builtin_p (stmt, BUILT_IN_NORMAL)
3484 || !gimple_vdef (stmt)
3485 || !gimple_vuse (stmt))
3486 return false;
3488 tree fndecl = gimple_call_fndecl (stmt);
3489 switch (DECL_FUNCTION_CODE (fndecl))
3491 case BUILT_IN_ATOMIC_COMPARE_EXCHANGE_1:
3492 case BUILT_IN_ATOMIC_COMPARE_EXCHANGE_2:
3493 case BUILT_IN_ATOMIC_COMPARE_EXCHANGE_4:
3494 case BUILT_IN_ATOMIC_COMPARE_EXCHANGE_8:
3495 case BUILT_IN_ATOMIC_COMPARE_EXCHANGE_16:
3496 break;
3497 default:
3498 return false;
3501 tree expected = gimple_call_arg (stmt, 1);
3502 if (TREE_CODE (expected) != ADDR_EXPR
3503 || !SSA_VAR_P (TREE_OPERAND (expected, 0)))
3504 return false;
3506 tree etype = TREE_TYPE (TREE_OPERAND (expected, 0));
3507 if (!is_gimple_reg_type (etype)
3508 || !auto_var_in_fn_p (TREE_OPERAND (expected, 0), current_function_decl)
3509 || TREE_THIS_VOLATILE (etype)
3510 || VECTOR_TYPE_P (etype)
3511 || TREE_CODE (etype) == COMPLEX_TYPE
3512 /* Don't optimize floating point expected vars, VIEW_CONVERT_EXPRs
3513 might not preserve all the bits. See PR71716. */
3514 || SCALAR_FLOAT_TYPE_P (etype)
3515 || TYPE_PRECISION (etype) != GET_MODE_BITSIZE (TYPE_MODE (etype)))
3516 return false;
3518 tree weak = gimple_call_arg (stmt, 3);
3519 if (!integer_zerop (weak) && !integer_onep (weak))
3520 return false;
3522 tree parmt = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
3523 tree itype = TREE_VALUE (TREE_CHAIN (TREE_CHAIN (parmt)));
3524 machine_mode mode = TYPE_MODE (itype);
3526 if (direct_optab_handler (atomic_compare_and_swap_optab, mode)
3527 == CODE_FOR_nothing
3528 && optab_handler (sync_compare_and_swap_optab, mode) == CODE_FOR_nothing)
3529 return false;
3531 if (int_size_in_bytes (etype) != GET_MODE_SIZE (mode))
3532 return false;
3534 return true;
3537 /* Fold
3538 r = __atomic_compare_exchange_N (p, &e, d, w, s, f);
3539 into
3540 _Complex uintN_t t = ATOMIC_COMPARE_EXCHANGE (p, e, d, w * 256 + N, s, f);
3541 i = IMAGPART_EXPR <t>;
3542 r = (_Bool) i;
3543 e = REALPART_EXPR <t>; */
3545 void
3546 fold_builtin_atomic_compare_exchange (gimple_stmt_iterator *gsi)
3548 gimple *stmt = gsi_stmt (*gsi);
3549 tree fndecl = gimple_call_fndecl (stmt);
3550 tree parmt = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
3551 tree itype = TREE_VALUE (TREE_CHAIN (TREE_CHAIN (parmt)));
3552 tree ctype = build_complex_type (itype);
3553 tree expected = TREE_OPERAND (gimple_call_arg (stmt, 1), 0);
3554 bool throws = false;
3555 edge e = NULL;
3556 gimple *g = gimple_build_assign (make_ssa_name (TREE_TYPE (expected)),
3557 expected);
3558 gsi_insert_before (gsi, g, GSI_SAME_STMT);
3559 gimple_stmt_iterator gsiret = gsi_for_stmt (g);
3560 if (!useless_type_conversion_p (itype, TREE_TYPE (expected)))
3562 g = gimple_build_assign (make_ssa_name (itype), VIEW_CONVERT_EXPR,
3563 build1 (VIEW_CONVERT_EXPR, itype,
3564 gimple_assign_lhs (g)));
3565 gsi_insert_before (gsi, g, GSI_SAME_STMT);
3567 int flag = (integer_onep (gimple_call_arg (stmt, 3)) ? 256 : 0)
3568 + int_size_in_bytes (itype);
3569 g = gimple_build_call_internal (IFN_ATOMIC_COMPARE_EXCHANGE, 6,
3570 gimple_call_arg (stmt, 0),
3571 gimple_assign_lhs (g),
3572 gimple_call_arg (stmt, 2),
3573 build_int_cst (integer_type_node, flag),
3574 gimple_call_arg (stmt, 4),
3575 gimple_call_arg (stmt, 5));
3576 tree lhs = make_ssa_name (ctype);
3577 gimple_call_set_lhs (g, lhs);
3578 gimple_set_vdef (g, gimple_vdef (stmt));
3579 gimple_set_vuse (g, gimple_vuse (stmt));
3580 SSA_NAME_DEF_STMT (gimple_vdef (g)) = g;
3581 tree oldlhs = gimple_call_lhs (stmt);
3582 if (stmt_can_throw_internal (stmt))
3584 throws = true;
3585 e = find_fallthru_edge (gsi_bb (*gsi)->succs);
3587 gimple_call_set_nothrow (as_a <gcall *> (g),
3588 gimple_call_nothrow_p (as_a <gcall *> (stmt)));
3589 gimple_call_set_lhs (stmt, NULL_TREE);
3590 gsi_replace (gsi, g, true);
3591 if (oldlhs)
3593 g = gimple_build_assign (make_ssa_name (itype), IMAGPART_EXPR,
3594 build1 (IMAGPART_EXPR, itype, lhs));
3595 if (throws)
3597 gsi_insert_on_edge_immediate (e, g);
3598 *gsi = gsi_for_stmt (g);
3600 else
3601 gsi_insert_after (gsi, g, GSI_NEW_STMT);
3602 g = gimple_build_assign (oldlhs, NOP_EXPR, gimple_assign_lhs (g));
3603 gsi_insert_after (gsi, g, GSI_NEW_STMT);
3605 g = gimple_build_assign (make_ssa_name (itype), REALPART_EXPR,
3606 build1 (REALPART_EXPR, itype, lhs));
3607 if (throws && oldlhs == NULL_TREE)
3609 gsi_insert_on_edge_immediate (e, g);
3610 *gsi = gsi_for_stmt (g);
3612 else
3613 gsi_insert_after (gsi, g, GSI_NEW_STMT);
3614 if (!useless_type_conversion_p (TREE_TYPE (expected), itype))
3616 g = gimple_build_assign (make_ssa_name (TREE_TYPE (expected)),
3617 VIEW_CONVERT_EXPR,
3618 build1 (VIEW_CONVERT_EXPR, TREE_TYPE (expected),
3619 gimple_assign_lhs (g)));
3620 gsi_insert_after (gsi, g, GSI_NEW_STMT);
3622 g = gimple_build_assign (expected, SSA_NAME, gimple_assign_lhs (g));
3623 gsi_insert_after (gsi, g, GSI_NEW_STMT);
3624 *gsi = gsiret;
3627 /* Return true if ARG0 CODE ARG1 in infinite signed precision operation
3628 doesn't fit into TYPE. The test for overflow should be regardless of
3629 -fwrapv, and even for unsigned types. */
3631 bool
3632 arith_overflowed_p (enum tree_code code, const_tree type,
3633 const_tree arg0, const_tree arg1)
3635 typedef FIXED_WIDE_INT (WIDE_INT_MAX_PRECISION * 2) widest2_int;
3636 typedef generic_wide_int <wi::extended_tree <WIDE_INT_MAX_PRECISION * 2> >
3637 widest2_int_cst;
3638 widest2_int warg0 = widest2_int_cst (arg0);
3639 widest2_int warg1 = widest2_int_cst (arg1);
3640 widest2_int wres;
3641 switch (code)
3643 case PLUS_EXPR: wres = wi::add (warg0, warg1); break;
3644 case MINUS_EXPR: wres = wi::sub (warg0, warg1); break;
3645 case MULT_EXPR: wres = wi::mul (warg0, warg1); break;
3646 default: gcc_unreachable ();
3648 signop sign = TYPE_SIGN (type);
3649 if (sign == UNSIGNED && wi::neg_p (wres))
3650 return true;
3651 return wi::min_precision (wres, sign) > TYPE_PRECISION (type);
3654 /* Attempt to fold a call statement referenced by the statement iterator GSI.
3655 The statement may be replaced by another statement, e.g., if the call
3656 simplifies to a constant value. Return true if any changes were made.
3657 It is assumed that the operands have been previously folded. */
3659 static bool
3660 gimple_fold_call (gimple_stmt_iterator *gsi, bool inplace)
3662 gcall *stmt = as_a <gcall *> (gsi_stmt (*gsi));
3663 tree callee;
3664 bool changed = false;
3665 unsigned i;
3667 /* Fold *& in call arguments. */
3668 for (i = 0; i < gimple_call_num_args (stmt); ++i)
3669 if (REFERENCE_CLASS_P (gimple_call_arg (stmt, i)))
3671 tree tmp = maybe_fold_reference (gimple_call_arg (stmt, i), false);
3672 if (tmp)
3674 gimple_call_set_arg (stmt, i, tmp);
3675 changed = true;
3679 /* Check for virtual calls that became direct calls. */
3680 callee = gimple_call_fn (stmt);
3681 if (callee && TREE_CODE (callee) == OBJ_TYPE_REF)
3683 if (gimple_call_addr_fndecl (OBJ_TYPE_REF_EXPR (callee)) != NULL_TREE)
3685 if (dump_file && virtual_method_call_p (callee)
3686 && !possible_polymorphic_call_target_p
3687 (callee, stmt, cgraph_node::get (gimple_call_addr_fndecl
3688 (OBJ_TYPE_REF_EXPR (callee)))))
3690 fprintf (dump_file,
3691 "Type inheritance inconsistent devirtualization of ");
3692 print_gimple_stmt (dump_file, stmt, 0, TDF_SLIM);
3693 fprintf (dump_file, " to ");
3694 print_generic_expr (dump_file, callee, TDF_SLIM);
3695 fprintf (dump_file, "\n");
3698 gimple_call_set_fn (stmt, OBJ_TYPE_REF_EXPR (callee));
3699 changed = true;
3701 else if (flag_devirtualize && !inplace && virtual_method_call_p (callee))
3703 bool final;
3704 vec <cgraph_node *>targets
3705 = possible_polymorphic_call_targets (callee, stmt, &final);
3706 if (final && targets.length () <= 1 && dbg_cnt (devirt))
3708 tree lhs = gimple_call_lhs (stmt);
3709 if (dump_enabled_p ())
3711 location_t loc = gimple_location_safe (stmt);
3712 dump_printf_loc (MSG_OPTIMIZED_LOCATIONS, loc,
3713 "folding virtual function call to %s\n",
3714 targets.length () == 1
3715 ? targets[0]->name ()
3716 : "__builtin_unreachable");
3718 if (targets.length () == 1)
3720 tree fndecl = targets[0]->decl;
3721 gimple_call_set_fndecl (stmt, fndecl);
3722 changed = true;
3723 /* If changing the call to __cxa_pure_virtual
3724 or similar noreturn function, adjust gimple_call_fntype
3725 too. */
3726 if (gimple_call_noreturn_p (stmt)
3727 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fndecl)))
3728 && TYPE_ARG_TYPES (TREE_TYPE (fndecl))
3729 && (TREE_VALUE (TYPE_ARG_TYPES (TREE_TYPE (fndecl)))
3730 == void_type_node))
3731 gimple_call_set_fntype (stmt, TREE_TYPE (fndecl));
3732 /* If the call becomes noreturn, remove the lhs. */
3733 if (lhs
3734 && gimple_call_noreturn_p (stmt)
3735 && (VOID_TYPE_P (TREE_TYPE (gimple_call_fntype (stmt)))
3736 || should_remove_lhs_p (lhs)))
3738 if (TREE_CODE (lhs) == SSA_NAME)
3740 tree var = create_tmp_var (TREE_TYPE (lhs));
3741 tree def = get_or_create_ssa_default_def (cfun, var);
3742 gimple *new_stmt = gimple_build_assign (lhs, def);
3743 gsi_insert_before (gsi, new_stmt, GSI_SAME_STMT);
3745 gimple_call_set_lhs (stmt, NULL_TREE);
3747 maybe_remove_unused_call_args (cfun, stmt);
3749 else
3751 tree fndecl = builtin_decl_implicit (BUILT_IN_UNREACHABLE);
3752 gimple *new_stmt = gimple_build_call (fndecl, 0);
3753 gimple_set_location (new_stmt, gimple_location (stmt));
3754 if (lhs && TREE_CODE (lhs) == SSA_NAME)
3756 tree var = create_tmp_var (TREE_TYPE (lhs));
3757 tree def = get_or_create_ssa_default_def (cfun, var);
3759 /* To satisfy condition for
3760 cgraph_update_edges_for_call_stmt_node,
3761 we need to preserve GIMPLE_CALL statement
3762 at position of GSI iterator. */
3763 update_call_from_tree (gsi, def);
3764 gsi_insert_before (gsi, new_stmt, GSI_NEW_STMT);
3766 else
3768 gimple_set_vuse (new_stmt, gimple_vuse (stmt));
3769 gimple_set_vdef (new_stmt, gimple_vdef (stmt));
3770 gsi_replace (gsi, new_stmt, false);
3772 return true;
3778 /* Check for indirect calls that became direct calls, and then
3779 no longer require a static chain. */
3780 if (gimple_call_chain (stmt))
3782 tree fn = gimple_call_fndecl (stmt);
3783 if (fn && !DECL_STATIC_CHAIN (fn))
3785 gimple_call_set_chain (stmt, NULL);
3786 changed = true;
3788 else
3790 tree tmp = maybe_fold_reference (gimple_call_chain (stmt), false);
3791 if (tmp)
3793 gimple_call_set_chain (stmt, tmp);
3794 changed = true;
3799 if (inplace)
3800 return changed;
3802 /* Check for builtins that CCP can handle using information not
3803 available in the generic fold routines. */
3804 if (gimple_call_builtin_p (stmt, BUILT_IN_NORMAL))
3806 if (gimple_fold_builtin (gsi))
3807 changed = true;
3809 else if (gimple_call_builtin_p (stmt, BUILT_IN_MD))
3811 changed |= targetm.gimple_fold_builtin (gsi);
3813 else if (gimple_call_internal_p (stmt))
3815 enum tree_code subcode = ERROR_MARK;
3816 tree result = NULL_TREE;
3817 bool cplx_result = false;
3818 tree overflow = NULL_TREE;
3819 switch (gimple_call_internal_fn (stmt))
3821 case IFN_BUILTIN_EXPECT:
3822 result = fold_builtin_expect (gimple_location (stmt),
3823 gimple_call_arg (stmt, 0),
3824 gimple_call_arg (stmt, 1),
3825 gimple_call_arg (stmt, 2));
3826 break;
3827 case IFN_UBSAN_OBJECT_SIZE:
3828 if (integer_all_onesp (gimple_call_arg (stmt, 2))
3829 || (TREE_CODE (gimple_call_arg (stmt, 1)) == INTEGER_CST
3830 && TREE_CODE (gimple_call_arg (stmt, 2)) == INTEGER_CST
3831 && tree_int_cst_le (gimple_call_arg (stmt, 1),
3832 gimple_call_arg (stmt, 2))))
3834 gsi_replace (gsi, gimple_build_nop (), false);
3835 unlink_stmt_vdef (stmt);
3836 release_defs (stmt);
3837 return true;
3839 break;
3840 case IFN_GOACC_DIM_SIZE:
3841 case IFN_GOACC_DIM_POS:
3842 result = fold_internal_goacc_dim (stmt);
3843 break;
3844 case IFN_UBSAN_CHECK_ADD:
3845 subcode = PLUS_EXPR;
3846 break;
3847 case IFN_UBSAN_CHECK_SUB:
3848 subcode = MINUS_EXPR;
3849 break;
3850 case IFN_UBSAN_CHECK_MUL:
3851 subcode = MULT_EXPR;
3852 break;
3853 case IFN_ADD_OVERFLOW:
3854 subcode = PLUS_EXPR;
3855 cplx_result = true;
3856 break;
3857 case IFN_SUB_OVERFLOW:
3858 subcode = MINUS_EXPR;
3859 cplx_result = true;
3860 break;
3861 case IFN_MUL_OVERFLOW:
3862 subcode = MULT_EXPR;
3863 cplx_result = true;
3864 break;
3865 default:
3866 break;
3868 if (subcode != ERROR_MARK)
3870 tree arg0 = gimple_call_arg (stmt, 0);
3871 tree arg1 = gimple_call_arg (stmt, 1);
3872 tree type = TREE_TYPE (arg0);
3873 if (cplx_result)
3875 tree lhs = gimple_call_lhs (stmt);
3876 if (lhs == NULL_TREE)
3877 type = NULL_TREE;
3878 else
3879 type = TREE_TYPE (TREE_TYPE (lhs));
3881 if (type == NULL_TREE)
3883 /* x = y + 0; x = y - 0; x = y * 0; */
3884 else if (integer_zerop (arg1))
3885 result = subcode == MULT_EXPR ? integer_zero_node : arg0;
3886 /* x = 0 + y; x = 0 * y; */
3887 else if (subcode != MINUS_EXPR && integer_zerop (arg0))
3888 result = subcode == MULT_EXPR ? integer_zero_node : arg1;
3889 /* x = y - y; */
3890 else if (subcode == MINUS_EXPR && operand_equal_p (arg0, arg1, 0))
3891 result = integer_zero_node;
3892 /* x = y * 1; x = 1 * y; */
3893 else if (subcode == MULT_EXPR && integer_onep (arg1))
3894 result = arg0;
3895 else if (subcode == MULT_EXPR && integer_onep (arg0))
3896 result = arg1;
3897 else if (TREE_CODE (arg0) == INTEGER_CST
3898 && TREE_CODE (arg1) == INTEGER_CST)
3900 if (cplx_result)
3901 result = int_const_binop (subcode, fold_convert (type, arg0),
3902 fold_convert (type, arg1));
3903 else
3904 result = int_const_binop (subcode, arg0, arg1);
3905 if (result && arith_overflowed_p (subcode, type, arg0, arg1))
3907 if (cplx_result)
3908 overflow = build_one_cst (type);
3909 else
3910 result = NULL_TREE;
3913 if (result)
3915 if (result == integer_zero_node)
3916 result = build_zero_cst (type);
3917 else if (cplx_result && TREE_TYPE (result) != type)
3919 if (TREE_CODE (result) == INTEGER_CST)
3921 if (arith_overflowed_p (PLUS_EXPR, type, result,
3922 integer_zero_node))
3923 overflow = build_one_cst (type);
3925 else if ((!TYPE_UNSIGNED (TREE_TYPE (result))
3926 && TYPE_UNSIGNED (type))
3927 || (TYPE_PRECISION (type)
3928 < (TYPE_PRECISION (TREE_TYPE (result))
3929 + (TYPE_UNSIGNED (TREE_TYPE (result))
3930 && !TYPE_UNSIGNED (type)))))
3931 result = NULL_TREE;
3932 if (result)
3933 result = fold_convert (type, result);
3938 if (result)
3940 if (TREE_CODE (result) == INTEGER_CST && TREE_OVERFLOW (result))
3941 result = drop_tree_overflow (result);
3942 if (cplx_result)
3944 if (overflow == NULL_TREE)
3945 overflow = build_zero_cst (TREE_TYPE (result));
3946 tree ctype = build_complex_type (TREE_TYPE (result));
3947 if (TREE_CODE (result) == INTEGER_CST
3948 && TREE_CODE (overflow) == INTEGER_CST)
3949 result = build_complex (ctype, result, overflow);
3950 else
3951 result = build2_loc (gimple_location (stmt), COMPLEX_EXPR,
3952 ctype, result, overflow);
3954 if (!update_call_from_tree (gsi, result))
3955 gimplify_and_update_call_from_tree (gsi, result);
3956 changed = true;
3960 return changed;
3964 /* Return true whether NAME has a use on STMT. */
3966 static bool
3967 has_use_on_stmt (tree name, gimple *stmt)
3969 imm_use_iterator iter;
3970 use_operand_p use_p;
3971 FOR_EACH_IMM_USE_FAST (use_p, iter, name)
3972 if (USE_STMT (use_p) == stmt)
3973 return true;
3974 return false;
3977 /* Worker for fold_stmt_1 dispatch to pattern based folding with
3978 gimple_simplify.
3980 Replaces *GSI with the simplification result in RCODE and OPS
3981 and the associated statements in *SEQ. Does the replacement
3982 according to INPLACE and returns true if the operation succeeded. */
3984 static bool
3985 replace_stmt_with_simplification (gimple_stmt_iterator *gsi,
3986 code_helper rcode, tree *ops,
3987 gimple_seq *seq, bool inplace)
3989 gimple *stmt = gsi_stmt (*gsi);
3991 /* Play safe and do not allow abnormals to be mentioned in
3992 newly created statements. See also maybe_push_res_to_seq.
3993 As an exception allow such uses if there was a use of the
3994 same SSA name on the old stmt. */
3995 if ((TREE_CODE (ops[0]) == SSA_NAME
3996 && SSA_NAME_OCCURS_IN_ABNORMAL_PHI (ops[0])
3997 && !has_use_on_stmt (ops[0], stmt))
3998 || (ops[1]
3999 && TREE_CODE (ops[1]) == SSA_NAME
4000 && SSA_NAME_OCCURS_IN_ABNORMAL_PHI (ops[1])
4001 && !has_use_on_stmt (ops[1], stmt))
4002 || (ops[2]
4003 && TREE_CODE (ops[2]) == SSA_NAME
4004 && SSA_NAME_OCCURS_IN_ABNORMAL_PHI (ops[2])
4005 && !has_use_on_stmt (ops[2], stmt))
4006 || (COMPARISON_CLASS_P (ops[0])
4007 && ((TREE_CODE (TREE_OPERAND (ops[0], 0)) == SSA_NAME
4008 && SSA_NAME_OCCURS_IN_ABNORMAL_PHI (TREE_OPERAND (ops[0], 0))
4009 && !has_use_on_stmt (TREE_OPERAND (ops[0], 0), stmt))
4010 || (TREE_CODE (TREE_OPERAND (ops[0], 1)) == SSA_NAME
4011 && SSA_NAME_OCCURS_IN_ABNORMAL_PHI (TREE_OPERAND (ops[0], 1))
4012 && !has_use_on_stmt (TREE_OPERAND (ops[0], 1), stmt)))))
4013 return false;
4015 /* Don't insert new statements when INPLACE is true, even if we could
4016 reuse STMT for the final statement. */
4017 if (inplace && !gimple_seq_empty_p (*seq))
4018 return false;
4020 if (gcond *cond_stmt = dyn_cast <gcond *> (stmt))
4022 gcc_assert (rcode.is_tree_code ());
4023 if (TREE_CODE_CLASS ((enum tree_code)rcode) == tcc_comparison
4024 /* GIMPLE_CONDs condition may not throw. */
4025 && (!flag_exceptions
4026 || !cfun->can_throw_non_call_exceptions
4027 || !operation_could_trap_p (rcode,
4028 FLOAT_TYPE_P (TREE_TYPE (ops[0])),
4029 false, NULL_TREE)))
4030 gimple_cond_set_condition (cond_stmt, rcode, ops[0], ops[1]);
4031 else if (rcode == SSA_NAME)
4032 gimple_cond_set_condition (cond_stmt, NE_EXPR, ops[0],
4033 build_zero_cst (TREE_TYPE (ops[0])));
4034 else if (rcode == INTEGER_CST)
4036 if (integer_zerop (ops[0]))
4037 gimple_cond_make_false (cond_stmt);
4038 else
4039 gimple_cond_make_true (cond_stmt);
4041 else if (!inplace)
4043 tree res = maybe_push_res_to_seq (rcode, boolean_type_node,
4044 ops, seq);
4045 if (!res)
4046 return false;
4047 gimple_cond_set_condition (cond_stmt, NE_EXPR, res,
4048 build_zero_cst (TREE_TYPE (res)));
4050 else
4051 return false;
4052 if (dump_file && (dump_flags & TDF_DETAILS))
4054 fprintf (dump_file, "gimple_simplified to ");
4055 if (!gimple_seq_empty_p (*seq))
4056 print_gimple_seq (dump_file, *seq, 0, TDF_SLIM);
4057 print_gimple_stmt (dump_file, gsi_stmt (*gsi),
4058 0, TDF_SLIM);
4060 gsi_insert_seq_before (gsi, *seq, GSI_SAME_STMT);
4061 return true;
4063 else if (is_gimple_assign (stmt)
4064 && rcode.is_tree_code ())
4066 if (!inplace
4067 || gimple_num_ops (stmt) > get_gimple_rhs_num_ops (rcode))
4069 maybe_build_generic_op (rcode,
4070 TREE_TYPE (gimple_assign_lhs (stmt)), ops);
4071 gimple_assign_set_rhs_with_ops (gsi, rcode, ops[0], ops[1], ops[2]);
4072 if (dump_file && (dump_flags & TDF_DETAILS))
4074 fprintf (dump_file, "gimple_simplified to ");
4075 if (!gimple_seq_empty_p (*seq))
4076 print_gimple_seq (dump_file, *seq, 0, TDF_SLIM);
4077 print_gimple_stmt (dump_file, gsi_stmt (*gsi),
4078 0, TDF_SLIM);
4080 gsi_insert_seq_before (gsi, *seq, GSI_SAME_STMT);
4081 return true;
4084 else if (rcode.is_fn_code ()
4085 && gimple_call_combined_fn (stmt) == rcode)
4087 unsigned i;
4088 for (i = 0; i < gimple_call_num_args (stmt); ++i)
4090 gcc_assert (ops[i] != NULL_TREE);
4091 gimple_call_set_arg (stmt, i, ops[i]);
4093 if (i < 3)
4094 gcc_assert (ops[i] == NULL_TREE);
4095 if (dump_file && (dump_flags & TDF_DETAILS))
4097 fprintf (dump_file, "gimple_simplified to ");
4098 if (!gimple_seq_empty_p (*seq))
4099 print_gimple_seq (dump_file, *seq, 0, TDF_SLIM);
4100 print_gimple_stmt (dump_file, gsi_stmt (*gsi), 0, TDF_SLIM);
4102 gsi_insert_seq_before (gsi, *seq, GSI_SAME_STMT);
4103 return true;
4105 else if (!inplace)
4107 if (gimple_has_lhs (stmt))
4109 tree lhs = gimple_get_lhs (stmt);
4110 if (!maybe_push_res_to_seq (rcode, TREE_TYPE (lhs),
4111 ops, seq, lhs))
4112 return false;
4113 if (dump_file && (dump_flags & TDF_DETAILS))
4115 fprintf (dump_file, "gimple_simplified to ");
4116 print_gimple_seq (dump_file, *seq, 0, TDF_SLIM);
4118 gsi_replace_with_seq_vops (gsi, *seq);
4119 return true;
4121 else
4122 gcc_unreachable ();
4125 return false;
4128 /* Canonicalize MEM_REFs invariant address operand after propagation. */
4130 static bool
4131 maybe_canonicalize_mem_ref_addr (tree *t)
4133 bool res = false;
4135 if (TREE_CODE (*t) == ADDR_EXPR)
4136 t = &TREE_OPERAND (*t, 0);
4138 /* The C and C++ frontends use an ARRAY_REF for indexing with their
4139 generic vector extension. The actual vector referenced is
4140 view-converted to an array type for this purpose. If the index
4141 is constant the canonical representation in the middle-end is a
4142 BIT_FIELD_REF so re-write the former to the latter here. */
4143 if (TREE_CODE (*t) == ARRAY_REF
4144 && TREE_CODE (TREE_OPERAND (*t, 0)) == VIEW_CONVERT_EXPR
4145 && TREE_CODE (TREE_OPERAND (*t, 1)) == INTEGER_CST
4146 && VECTOR_TYPE_P (TREE_TYPE (TREE_OPERAND (TREE_OPERAND (*t, 0), 0))))
4148 tree vtype = TREE_TYPE (TREE_OPERAND (TREE_OPERAND (*t, 0), 0));
4149 if (VECTOR_TYPE_P (vtype))
4151 tree low = array_ref_low_bound (*t);
4152 if (TREE_CODE (low) == INTEGER_CST)
4154 if (tree_int_cst_le (low, TREE_OPERAND (*t, 1)))
4156 widest_int idx = wi::sub (wi::to_widest (TREE_OPERAND (*t, 1)),
4157 wi::to_widest (low));
4158 idx = wi::mul (idx, wi::to_widest
4159 (TYPE_SIZE (TREE_TYPE (*t))));
4160 widest_int ext
4161 = wi::add (idx, wi::to_widest (TYPE_SIZE (TREE_TYPE (*t))));
4162 if (wi::les_p (ext, wi::to_widest (TYPE_SIZE (vtype))))
4164 *t = build3_loc (EXPR_LOCATION (*t), BIT_FIELD_REF,
4165 TREE_TYPE (*t),
4166 TREE_OPERAND (TREE_OPERAND (*t, 0), 0),
4167 TYPE_SIZE (TREE_TYPE (*t)),
4168 wide_int_to_tree (sizetype, idx));
4169 res = true;
4176 while (handled_component_p (*t))
4177 t = &TREE_OPERAND (*t, 0);
4179 /* Canonicalize MEM [&foo.bar, 0] which appears after propagating
4180 of invariant addresses into a SSA name MEM_REF address. */
4181 if (TREE_CODE (*t) == MEM_REF
4182 || TREE_CODE (*t) == TARGET_MEM_REF)
4184 tree addr = TREE_OPERAND (*t, 0);
4185 if (TREE_CODE (addr) == ADDR_EXPR
4186 && (TREE_CODE (TREE_OPERAND (addr, 0)) == MEM_REF
4187 || handled_component_p (TREE_OPERAND (addr, 0))))
4189 tree base;
4190 HOST_WIDE_INT coffset;
4191 base = get_addr_base_and_unit_offset (TREE_OPERAND (addr, 0),
4192 &coffset);
4193 if (!base)
4194 gcc_unreachable ();
4196 TREE_OPERAND (*t, 0) = build_fold_addr_expr (base);
4197 TREE_OPERAND (*t, 1) = int_const_binop (PLUS_EXPR,
4198 TREE_OPERAND (*t, 1),
4199 size_int (coffset));
4200 res = true;
4202 gcc_checking_assert (TREE_CODE (TREE_OPERAND (*t, 0)) == DEBUG_EXPR_DECL
4203 || is_gimple_mem_ref_addr (TREE_OPERAND (*t, 0)));
4206 /* Canonicalize back MEM_REFs to plain reference trees if the object
4207 accessed is a decl that has the same access semantics as the MEM_REF. */
4208 if (TREE_CODE (*t) == MEM_REF
4209 && TREE_CODE (TREE_OPERAND (*t, 0)) == ADDR_EXPR
4210 && integer_zerop (TREE_OPERAND (*t, 1))
4211 && MR_DEPENDENCE_CLIQUE (*t) == 0)
4213 tree decl = TREE_OPERAND (TREE_OPERAND (*t, 0), 0);
4214 tree alias_type = TREE_TYPE (TREE_OPERAND (*t, 1));
4215 if (/* Same volatile qualification. */
4216 TREE_THIS_VOLATILE (*t) == TREE_THIS_VOLATILE (decl)
4217 /* Same TBAA behavior with -fstrict-aliasing. */
4218 && !TYPE_REF_CAN_ALIAS_ALL (alias_type)
4219 && (TYPE_MAIN_VARIANT (TREE_TYPE (decl))
4220 == TYPE_MAIN_VARIANT (TREE_TYPE (alias_type)))
4221 /* Same alignment. */
4222 && TYPE_ALIGN (TREE_TYPE (decl)) == TYPE_ALIGN (TREE_TYPE (*t))
4223 /* We have to look out here to not drop a required conversion
4224 from the rhs to the lhs if *t appears on the lhs or vice-versa
4225 if it appears on the rhs. Thus require strict type
4226 compatibility. */
4227 && types_compatible_p (TREE_TYPE (*t), TREE_TYPE (decl)))
4229 *t = TREE_OPERAND (TREE_OPERAND (*t, 0), 0);
4230 res = true;
4234 /* Canonicalize TARGET_MEM_REF in particular with respect to
4235 the indexes becoming constant. */
4236 else if (TREE_CODE (*t) == TARGET_MEM_REF)
4238 tree tem = maybe_fold_tmr (*t);
4239 if (tem)
4241 *t = tem;
4242 res = true;
4246 return res;
4249 /* Worker for both fold_stmt and fold_stmt_inplace. The INPLACE argument
4250 distinguishes both cases. */
4252 static bool
4253 fold_stmt_1 (gimple_stmt_iterator *gsi, bool inplace, tree (*valueize) (tree))
4255 bool changed = false;
4256 gimple *stmt = gsi_stmt (*gsi);
4257 bool nowarning = gimple_no_warning_p (stmt);
4258 unsigned i;
4259 fold_defer_overflow_warnings ();
4261 /* First do required canonicalization of [TARGET_]MEM_REF addresses
4262 after propagation.
4263 ??? This shouldn't be done in generic folding but in the
4264 propagation helpers which also know whether an address was
4265 propagated.
4266 Also canonicalize operand order. */
4267 switch (gimple_code (stmt))
4269 case GIMPLE_ASSIGN:
4270 if (gimple_assign_rhs_class (stmt) == GIMPLE_SINGLE_RHS)
4272 tree *rhs = gimple_assign_rhs1_ptr (stmt);
4273 if ((REFERENCE_CLASS_P (*rhs)
4274 || TREE_CODE (*rhs) == ADDR_EXPR)
4275 && maybe_canonicalize_mem_ref_addr (rhs))
4276 changed = true;
4277 tree *lhs = gimple_assign_lhs_ptr (stmt);
4278 if (REFERENCE_CLASS_P (*lhs)
4279 && maybe_canonicalize_mem_ref_addr (lhs))
4280 changed = true;
4282 else
4284 /* Canonicalize operand order. */
4285 enum tree_code code = gimple_assign_rhs_code (stmt);
4286 if (TREE_CODE_CLASS (code) == tcc_comparison
4287 || commutative_tree_code (code)
4288 || commutative_ternary_tree_code (code))
4290 tree rhs1 = gimple_assign_rhs1 (stmt);
4291 tree rhs2 = gimple_assign_rhs2 (stmt);
4292 if (tree_swap_operands_p (rhs1, rhs2))
4294 gimple_assign_set_rhs1 (stmt, rhs2);
4295 gimple_assign_set_rhs2 (stmt, rhs1);
4296 if (TREE_CODE_CLASS (code) == tcc_comparison)
4297 gimple_assign_set_rhs_code (stmt,
4298 swap_tree_comparison (code));
4299 changed = true;
4303 break;
4304 case GIMPLE_CALL:
4306 for (i = 0; i < gimple_call_num_args (stmt); ++i)
4308 tree *arg = gimple_call_arg_ptr (stmt, i);
4309 if (REFERENCE_CLASS_P (*arg)
4310 && maybe_canonicalize_mem_ref_addr (arg))
4311 changed = true;
4313 tree *lhs = gimple_call_lhs_ptr (stmt);
4314 if (*lhs
4315 && REFERENCE_CLASS_P (*lhs)
4316 && maybe_canonicalize_mem_ref_addr (lhs))
4317 changed = true;
4318 break;
4320 case GIMPLE_ASM:
4322 gasm *asm_stmt = as_a <gasm *> (stmt);
4323 for (i = 0; i < gimple_asm_noutputs (asm_stmt); ++i)
4325 tree link = gimple_asm_output_op (asm_stmt, i);
4326 tree op = TREE_VALUE (link);
4327 if (REFERENCE_CLASS_P (op)
4328 && maybe_canonicalize_mem_ref_addr (&TREE_VALUE (link)))
4329 changed = true;
4331 for (i = 0; i < gimple_asm_ninputs (asm_stmt); ++i)
4333 tree link = gimple_asm_input_op (asm_stmt, i);
4334 tree op = TREE_VALUE (link);
4335 if ((REFERENCE_CLASS_P (op)
4336 || TREE_CODE (op) == ADDR_EXPR)
4337 && maybe_canonicalize_mem_ref_addr (&TREE_VALUE (link)))
4338 changed = true;
4341 break;
4342 case GIMPLE_DEBUG:
4343 if (gimple_debug_bind_p (stmt))
4345 tree *val = gimple_debug_bind_get_value_ptr (stmt);
4346 if (*val
4347 && (REFERENCE_CLASS_P (*val)
4348 || TREE_CODE (*val) == ADDR_EXPR)
4349 && maybe_canonicalize_mem_ref_addr (val))
4350 changed = true;
4352 break;
4353 case GIMPLE_COND:
4355 /* Canonicalize operand order. */
4356 tree lhs = gimple_cond_lhs (stmt);
4357 tree rhs = gimple_cond_rhs (stmt);
4358 if (tree_swap_operands_p (lhs, rhs))
4360 gcond *gc = as_a <gcond *> (stmt);
4361 gimple_cond_set_lhs (gc, rhs);
4362 gimple_cond_set_rhs (gc, lhs);
4363 gimple_cond_set_code (gc,
4364 swap_tree_comparison (gimple_cond_code (gc)));
4365 changed = true;
4368 default:;
4371 /* Dispatch to pattern-based folding. */
4372 if (!inplace
4373 || is_gimple_assign (stmt)
4374 || gimple_code (stmt) == GIMPLE_COND)
4376 gimple_seq seq = NULL;
4377 code_helper rcode;
4378 tree ops[3] = {};
4379 if (gimple_simplify (stmt, &rcode, ops, inplace ? NULL : &seq,
4380 valueize, valueize))
4382 if (replace_stmt_with_simplification (gsi, rcode, ops, &seq, inplace))
4383 changed = true;
4384 else
4385 gimple_seq_discard (seq);
4389 stmt = gsi_stmt (*gsi);
4391 /* Fold the main computation performed by the statement. */
4392 switch (gimple_code (stmt))
4394 case GIMPLE_ASSIGN:
4396 /* Try to canonicalize for boolean-typed X the comparisons
4397 X == 0, X == 1, X != 0, and X != 1. */
4398 if (gimple_assign_rhs_code (stmt) == EQ_EXPR
4399 || gimple_assign_rhs_code (stmt) == NE_EXPR)
4401 tree lhs = gimple_assign_lhs (stmt);
4402 tree op1 = gimple_assign_rhs1 (stmt);
4403 tree op2 = gimple_assign_rhs2 (stmt);
4404 tree type = TREE_TYPE (op1);
4406 /* Check whether the comparison operands are of the same boolean
4407 type as the result type is.
4408 Check that second operand is an integer-constant with value
4409 one or zero. */
4410 if (TREE_CODE (op2) == INTEGER_CST
4411 && (integer_zerop (op2) || integer_onep (op2))
4412 && useless_type_conversion_p (TREE_TYPE (lhs), type))
4414 enum tree_code cmp_code = gimple_assign_rhs_code (stmt);
4415 bool is_logical_not = false;
4417 /* X == 0 and X != 1 is a logical-not.of X
4418 X == 1 and X != 0 is X */
4419 if ((cmp_code == EQ_EXPR && integer_zerop (op2))
4420 || (cmp_code == NE_EXPR && integer_onep (op2)))
4421 is_logical_not = true;
4423 if (is_logical_not == false)
4424 gimple_assign_set_rhs_with_ops (gsi, TREE_CODE (op1), op1);
4425 /* Only for one-bit precision typed X the transformation
4426 !X -> ~X is valied. */
4427 else if (TYPE_PRECISION (type) == 1)
4428 gimple_assign_set_rhs_with_ops (gsi, BIT_NOT_EXPR, op1);
4429 /* Otherwise we use !X -> X ^ 1. */
4430 else
4431 gimple_assign_set_rhs_with_ops (gsi, BIT_XOR_EXPR, op1,
4432 build_int_cst (type, 1));
4433 changed = true;
4434 break;
4438 unsigned old_num_ops = gimple_num_ops (stmt);
4439 tree lhs = gimple_assign_lhs (stmt);
4440 tree new_rhs = fold_gimple_assign (gsi);
4441 if (new_rhs
4442 && !useless_type_conversion_p (TREE_TYPE (lhs),
4443 TREE_TYPE (new_rhs)))
4444 new_rhs = fold_convert (TREE_TYPE (lhs), new_rhs);
4445 if (new_rhs
4446 && (!inplace
4447 || get_gimple_rhs_num_ops (TREE_CODE (new_rhs)) < old_num_ops))
4449 gimple_assign_set_rhs_from_tree (gsi, new_rhs);
4450 changed = true;
4452 break;
4455 case GIMPLE_CALL:
4456 changed |= gimple_fold_call (gsi, inplace);
4457 break;
4459 case GIMPLE_ASM:
4460 /* Fold *& in asm operands. */
4462 gasm *asm_stmt = as_a <gasm *> (stmt);
4463 size_t noutputs;
4464 const char **oconstraints;
4465 const char *constraint;
4466 bool allows_mem, allows_reg;
4468 noutputs = gimple_asm_noutputs (asm_stmt);
4469 oconstraints = XALLOCAVEC (const char *, noutputs);
4471 for (i = 0; i < gimple_asm_noutputs (asm_stmt); ++i)
4473 tree link = gimple_asm_output_op (asm_stmt, i);
4474 tree op = TREE_VALUE (link);
4475 oconstraints[i]
4476 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
4477 if (REFERENCE_CLASS_P (op)
4478 && (op = maybe_fold_reference (op, true)) != NULL_TREE)
4480 TREE_VALUE (link) = op;
4481 changed = true;
4484 for (i = 0; i < gimple_asm_ninputs (asm_stmt); ++i)
4486 tree link = gimple_asm_input_op (asm_stmt, i);
4487 tree op = TREE_VALUE (link);
4488 constraint
4489 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
4490 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
4491 oconstraints, &allows_mem, &allows_reg);
4492 if (REFERENCE_CLASS_P (op)
4493 && (op = maybe_fold_reference (op, !allows_reg && allows_mem))
4494 != NULL_TREE)
4496 TREE_VALUE (link) = op;
4497 changed = true;
4501 break;
4503 case GIMPLE_DEBUG:
4504 if (gimple_debug_bind_p (stmt))
4506 tree val = gimple_debug_bind_get_value (stmt);
4507 if (val
4508 && REFERENCE_CLASS_P (val))
4510 tree tem = maybe_fold_reference (val, false);
4511 if (tem)
4513 gimple_debug_bind_set_value (stmt, tem);
4514 changed = true;
4517 else if (val
4518 && TREE_CODE (val) == ADDR_EXPR)
4520 tree ref = TREE_OPERAND (val, 0);
4521 tree tem = maybe_fold_reference (ref, false);
4522 if (tem)
4524 tem = build_fold_addr_expr_with_type (tem, TREE_TYPE (val));
4525 gimple_debug_bind_set_value (stmt, tem);
4526 changed = true;
4530 break;
4532 case GIMPLE_RETURN:
4534 greturn *ret_stmt = as_a<greturn *> (stmt);
4535 tree ret = gimple_return_retval(ret_stmt);
4537 if (ret && TREE_CODE (ret) == SSA_NAME && valueize)
4539 tree val = valueize (ret);
4540 if (val && val != ret
4541 && may_propagate_copy (ret, val))
4543 gimple_return_set_retval (ret_stmt, val);
4544 changed = true;
4548 break;
4550 default:;
4553 stmt = gsi_stmt (*gsi);
4555 /* Fold *& on the lhs. */
4556 if (gimple_has_lhs (stmt))
4558 tree lhs = gimple_get_lhs (stmt);
4559 if (lhs && REFERENCE_CLASS_P (lhs))
4561 tree new_lhs = maybe_fold_reference (lhs, true);
4562 if (new_lhs)
4564 gimple_set_lhs (stmt, new_lhs);
4565 changed = true;
4570 fold_undefer_overflow_warnings (changed && !nowarning, stmt, 0);
4571 return changed;
4574 /* Valueziation callback that ends up not following SSA edges. */
4576 tree
4577 no_follow_ssa_edges (tree)
4579 return NULL_TREE;
4582 /* Valueization callback that ends up following single-use SSA edges only. */
4584 tree
4585 follow_single_use_edges (tree val)
4587 if (TREE_CODE (val) == SSA_NAME
4588 && !has_single_use (val))
4589 return NULL_TREE;
4590 return val;
4593 /* Fold the statement pointed to by GSI. In some cases, this function may
4594 replace the whole statement with a new one. Returns true iff folding
4595 makes any changes.
4596 The statement pointed to by GSI should be in valid gimple form but may
4597 be in unfolded state as resulting from for example constant propagation
4598 which can produce *&x = 0. */
4600 bool
4601 fold_stmt (gimple_stmt_iterator *gsi)
4603 return fold_stmt_1 (gsi, false, no_follow_ssa_edges);
4606 bool
4607 fold_stmt (gimple_stmt_iterator *gsi, tree (*valueize) (tree))
4609 return fold_stmt_1 (gsi, false, valueize);
4612 /* Perform the minimal folding on statement *GSI. Only operations like
4613 *&x created by constant propagation are handled. The statement cannot
4614 be replaced with a new one. Return true if the statement was
4615 changed, false otherwise.
4616 The statement *GSI should be in valid gimple form but may
4617 be in unfolded state as resulting from for example constant propagation
4618 which can produce *&x = 0. */
4620 bool
4621 fold_stmt_inplace (gimple_stmt_iterator *gsi)
4623 gimple *stmt = gsi_stmt (*gsi);
4624 bool changed = fold_stmt_1 (gsi, true, no_follow_ssa_edges);
4625 gcc_assert (gsi_stmt (*gsi) == stmt);
4626 return changed;
4629 /* Canonicalize and possibly invert the boolean EXPR; return NULL_TREE
4630 if EXPR is null or we don't know how.
4631 If non-null, the result always has boolean type. */
4633 static tree
4634 canonicalize_bool (tree expr, bool invert)
4636 if (!expr)
4637 return NULL_TREE;
4638 else if (invert)
4640 if (integer_nonzerop (expr))
4641 return boolean_false_node;
4642 else if (integer_zerop (expr))
4643 return boolean_true_node;
4644 else if (TREE_CODE (expr) == SSA_NAME)
4645 return fold_build2 (EQ_EXPR, boolean_type_node, expr,
4646 build_int_cst (TREE_TYPE (expr), 0));
4647 else if (COMPARISON_CLASS_P (expr))
4648 return fold_build2 (invert_tree_comparison (TREE_CODE (expr), false),
4649 boolean_type_node,
4650 TREE_OPERAND (expr, 0),
4651 TREE_OPERAND (expr, 1));
4652 else
4653 return NULL_TREE;
4655 else
4657 if (TREE_CODE (TREE_TYPE (expr)) == BOOLEAN_TYPE)
4658 return expr;
4659 if (integer_nonzerop (expr))
4660 return boolean_true_node;
4661 else if (integer_zerop (expr))
4662 return boolean_false_node;
4663 else if (TREE_CODE (expr) == SSA_NAME)
4664 return fold_build2 (NE_EXPR, boolean_type_node, expr,
4665 build_int_cst (TREE_TYPE (expr), 0));
4666 else if (COMPARISON_CLASS_P (expr))
4667 return fold_build2 (TREE_CODE (expr),
4668 boolean_type_node,
4669 TREE_OPERAND (expr, 0),
4670 TREE_OPERAND (expr, 1));
4671 else
4672 return NULL_TREE;
4676 /* Check to see if a boolean expression EXPR is logically equivalent to the
4677 comparison (OP1 CODE OP2). Check for various identities involving
4678 SSA_NAMEs. */
4680 static bool
4681 same_bool_comparison_p (const_tree expr, enum tree_code code,
4682 const_tree op1, const_tree op2)
4684 gimple *s;
4686 /* The obvious case. */
4687 if (TREE_CODE (expr) == code
4688 && operand_equal_p (TREE_OPERAND (expr, 0), op1, 0)
4689 && operand_equal_p (TREE_OPERAND (expr, 1), op2, 0))
4690 return true;
4692 /* Check for comparing (name, name != 0) and the case where expr
4693 is an SSA_NAME with a definition matching the comparison. */
4694 if (TREE_CODE (expr) == SSA_NAME
4695 && TREE_CODE (TREE_TYPE (expr)) == BOOLEAN_TYPE)
4697 if (operand_equal_p (expr, op1, 0))
4698 return ((code == NE_EXPR && integer_zerop (op2))
4699 || (code == EQ_EXPR && integer_nonzerop (op2)));
4700 s = SSA_NAME_DEF_STMT (expr);
4701 if (is_gimple_assign (s)
4702 && gimple_assign_rhs_code (s) == code
4703 && operand_equal_p (gimple_assign_rhs1 (s), op1, 0)
4704 && operand_equal_p (gimple_assign_rhs2 (s), op2, 0))
4705 return true;
4708 /* If op1 is of the form (name != 0) or (name == 0), and the definition
4709 of name is a comparison, recurse. */
4710 if (TREE_CODE (op1) == SSA_NAME
4711 && TREE_CODE (TREE_TYPE (op1)) == BOOLEAN_TYPE)
4713 s = SSA_NAME_DEF_STMT (op1);
4714 if (is_gimple_assign (s)
4715 && TREE_CODE_CLASS (gimple_assign_rhs_code (s)) == tcc_comparison)
4717 enum tree_code c = gimple_assign_rhs_code (s);
4718 if ((c == NE_EXPR && integer_zerop (op2))
4719 || (c == EQ_EXPR && integer_nonzerop (op2)))
4720 return same_bool_comparison_p (expr, c,
4721 gimple_assign_rhs1 (s),
4722 gimple_assign_rhs2 (s));
4723 if ((c == EQ_EXPR && integer_zerop (op2))
4724 || (c == NE_EXPR && integer_nonzerop (op2)))
4725 return same_bool_comparison_p (expr,
4726 invert_tree_comparison (c, false),
4727 gimple_assign_rhs1 (s),
4728 gimple_assign_rhs2 (s));
4731 return false;
4734 /* Check to see if two boolean expressions OP1 and OP2 are logically
4735 equivalent. */
4737 static bool
4738 same_bool_result_p (const_tree op1, const_tree op2)
4740 /* Simple cases first. */
4741 if (operand_equal_p (op1, op2, 0))
4742 return true;
4744 /* Check the cases where at least one of the operands is a comparison.
4745 These are a bit smarter than operand_equal_p in that they apply some
4746 identifies on SSA_NAMEs. */
4747 if (COMPARISON_CLASS_P (op2)
4748 && same_bool_comparison_p (op1, TREE_CODE (op2),
4749 TREE_OPERAND (op2, 0),
4750 TREE_OPERAND (op2, 1)))
4751 return true;
4752 if (COMPARISON_CLASS_P (op1)
4753 && same_bool_comparison_p (op2, TREE_CODE (op1),
4754 TREE_OPERAND (op1, 0),
4755 TREE_OPERAND (op1, 1)))
4756 return true;
4758 /* Default case. */
4759 return false;
4762 /* Forward declarations for some mutually recursive functions. */
4764 static tree
4765 and_comparisons_1 (enum tree_code code1, tree op1a, tree op1b,
4766 enum tree_code code2, tree op2a, tree op2b);
4767 static tree
4768 and_var_with_comparison (tree var, bool invert,
4769 enum tree_code code2, tree op2a, tree op2b);
4770 static tree
4771 and_var_with_comparison_1 (gimple *stmt,
4772 enum tree_code code2, tree op2a, tree op2b);
4773 static tree
4774 or_comparisons_1 (enum tree_code code1, tree op1a, tree op1b,
4775 enum tree_code code2, tree op2a, tree op2b);
4776 static tree
4777 or_var_with_comparison (tree var, bool invert,
4778 enum tree_code code2, tree op2a, tree op2b);
4779 static tree
4780 or_var_with_comparison_1 (gimple *stmt,
4781 enum tree_code code2, tree op2a, tree op2b);
4783 /* Helper function for and_comparisons_1: try to simplify the AND of the
4784 ssa variable VAR with the comparison specified by (OP2A CODE2 OP2B).
4785 If INVERT is true, invert the value of the VAR before doing the AND.
4786 Return NULL_EXPR if we can't simplify this to a single expression. */
4788 static tree
4789 and_var_with_comparison (tree var, bool invert,
4790 enum tree_code code2, tree op2a, tree op2b)
4792 tree t;
4793 gimple *stmt = SSA_NAME_DEF_STMT (var);
4795 /* We can only deal with variables whose definitions are assignments. */
4796 if (!is_gimple_assign (stmt))
4797 return NULL_TREE;
4799 /* If we have an inverted comparison, apply DeMorgan's law and rewrite
4800 !var AND (op2a code2 op2b) => !(var OR !(op2a code2 op2b))
4801 Then we only have to consider the simpler non-inverted cases. */
4802 if (invert)
4803 t = or_var_with_comparison_1 (stmt,
4804 invert_tree_comparison (code2, false),
4805 op2a, op2b);
4806 else
4807 t = and_var_with_comparison_1 (stmt, code2, op2a, op2b);
4808 return canonicalize_bool (t, invert);
4811 /* Try to simplify the AND of the ssa variable defined by the assignment
4812 STMT with the comparison specified by (OP2A CODE2 OP2B).
4813 Return NULL_EXPR if we can't simplify this to a single expression. */
4815 static tree
4816 and_var_with_comparison_1 (gimple *stmt,
4817 enum tree_code code2, tree op2a, tree op2b)
4819 tree var = gimple_assign_lhs (stmt);
4820 tree true_test_var = NULL_TREE;
4821 tree false_test_var = NULL_TREE;
4822 enum tree_code innercode = gimple_assign_rhs_code (stmt);
4824 /* Check for identities like (var AND (var == 0)) => false. */
4825 if (TREE_CODE (op2a) == SSA_NAME
4826 && TREE_CODE (TREE_TYPE (var)) == BOOLEAN_TYPE)
4828 if ((code2 == NE_EXPR && integer_zerop (op2b))
4829 || (code2 == EQ_EXPR && integer_nonzerop (op2b)))
4831 true_test_var = op2a;
4832 if (var == true_test_var)
4833 return var;
4835 else if ((code2 == EQ_EXPR && integer_zerop (op2b))
4836 || (code2 == NE_EXPR && integer_nonzerop (op2b)))
4838 false_test_var = op2a;
4839 if (var == false_test_var)
4840 return boolean_false_node;
4844 /* If the definition is a comparison, recurse on it. */
4845 if (TREE_CODE_CLASS (innercode) == tcc_comparison)
4847 tree t = and_comparisons_1 (innercode,
4848 gimple_assign_rhs1 (stmt),
4849 gimple_assign_rhs2 (stmt),
4850 code2,
4851 op2a,
4852 op2b);
4853 if (t)
4854 return t;
4857 /* If the definition is an AND or OR expression, we may be able to
4858 simplify by reassociating. */
4859 if (TREE_CODE (TREE_TYPE (var)) == BOOLEAN_TYPE
4860 && (innercode == BIT_AND_EXPR || innercode == BIT_IOR_EXPR))
4862 tree inner1 = gimple_assign_rhs1 (stmt);
4863 tree inner2 = gimple_assign_rhs2 (stmt);
4864 gimple *s;
4865 tree t;
4866 tree partial = NULL_TREE;
4867 bool is_and = (innercode == BIT_AND_EXPR);
4869 /* Check for boolean identities that don't require recursive examination
4870 of inner1/inner2:
4871 inner1 AND (inner1 AND inner2) => inner1 AND inner2 => var
4872 inner1 AND (inner1 OR inner2) => inner1
4873 !inner1 AND (inner1 AND inner2) => false
4874 !inner1 AND (inner1 OR inner2) => !inner1 AND inner2
4875 Likewise for similar cases involving inner2. */
4876 if (inner1 == true_test_var)
4877 return (is_and ? var : inner1);
4878 else if (inner2 == true_test_var)
4879 return (is_and ? var : inner2);
4880 else if (inner1 == false_test_var)
4881 return (is_and
4882 ? boolean_false_node
4883 : and_var_with_comparison (inner2, false, code2, op2a, op2b));
4884 else if (inner2 == false_test_var)
4885 return (is_and
4886 ? boolean_false_node
4887 : and_var_with_comparison (inner1, false, code2, op2a, op2b));
4889 /* Next, redistribute/reassociate the AND across the inner tests.
4890 Compute the first partial result, (inner1 AND (op2a code op2b)) */
4891 if (TREE_CODE (inner1) == SSA_NAME
4892 && is_gimple_assign (s = SSA_NAME_DEF_STMT (inner1))
4893 && TREE_CODE_CLASS (gimple_assign_rhs_code (s)) == tcc_comparison
4894 && (t = maybe_fold_and_comparisons (gimple_assign_rhs_code (s),
4895 gimple_assign_rhs1 (s),
4896 gimple_assign_rhs2 (s),
4897 code2, op2a, op2b)))
4899 /* Handle the AND case, where we are reassociating:
4900 (inner1 AND inner2) AND (op2a code2 op2b)
4901 => (t AND inner2)
4902 If the partial result t is a constant, we win. Otherwise
4903 continue on to try reassociating with the other inner test. */
4904 if (is_and)
4906 if (integer_onep (t))
4907 return inner2;
4908 else if (integer_zerop (t))
4909 return boolean_false_node;
4912 /* Handle the OR case, where we are redistributing:
4913 (inner1 OR inner2) AND (op2a code2 op2b)
4914 => (t OR (inner2 AND (op2a code2 op2b))) */
4915 else if (integer_onep (t))
4916 return boolean_true_node;
4918 /* Save partial result for later. */
4919 partial = t;
4922 /* Compute the second partial result, (inner2 AND (op2a code op2b)) */
4923 if (TREE_CODE (inner2) == SSA_NAME
4924 && is_gimple_assign (s = SSA_NAME_DEF_STMT (inner2))
4925 && TREE_CODE_CLASS (gimple_assign_rhs_code (s)) == tcc_comparison
4926 && (t = maybe_fold_and_comparisons (gimple_assign_rhs_code (s),
4927 gimple_assign_rhs1 (s),
4928 gimple_assign_rhs2 (s),
4929 code2, op2a, op2b)))
4931 /* Handle the AND case, where we are reassociating:
4932 (inner1 AND inner2) AND (op2a code2 op2b)
4933 => (inner1 AND t) */
4934 if (is_and)
4936 if (integer_onep (t))
4937 return inner1;
4938 else if (integer_zerop (t))
4939 return boolean_false_node;
4940 /* If both are the same, we can apply the identity
4941 (x AND x) == x. */
4942 else if (partial && same_bool_result_p (t, partial))
4943 return t;
4946 /* Handle the OR case. where we are redistributing:
4947 (inner1 OR inner2) AND (op2a code2 op2b)
4948 => (t OR (inner1 AND (op2a code2 op2b)))
4949 => (t OR partial) */
4950 else
4952 if (integer_onep (t))
4953 return boolean_true_node;
4954 else if (partial)
4956 /* We already got a simplification for the other
4957 operand to the redistributed OR expression. The
4958 interesting case is when at least one is false.
4959 Or, if both are the same, we can apply the identity
4960 (x OR x) == x. */
4961 if (integer_zerop (partial))
4962 return t;
4963 else if (integer_zerop (t))
4964 return partial;
4965 else if (same_bool_result_p (t, partial))
4966 return t;
4971 return NULL_TREE;
4974 /* Try to simplify the AND of two comparisons defined by
4975 (OP1A CODE1 OP1B) and (OP2A CODE2 OP2B), respectively.
4976 If this can be done without constructing an intermediate value,
4977 return the resulting tree; otherwise NULL_TREE is returned.
4978 This function is deliberately asymmetric as it recurses on SSA_DEFs
4979 in the first comparison but not the second. */
4981 static tree
4982 and_comparisons_1 (enum tree_code code1, tree op1a, tree op1b,
4983 enum tree_code code2, tree op2a, tree op2b)
4985 tree truth_type = truth_type_for (TREE_TYPE (op1a));
4987 /* First check for ((x CODE1 y) AND (x CODE2 y)). */
4988 if (operand_equal_p (op1a, op2a, 0)
4989 && operand_equal_p (op1b, op2b, 0))
4991 /* Result will be either NULL_TREE, or a combined comparison. */
4992 tree t = combine_comparisons (UNKNOWN_LOCATION,
4993 TRUTH_ANDIF_EXPR, code1, code2,
4994 truth_type, op1a, op1b);
4995 if (t)
4996 return t;
4999 /* Likewise the swapped case of the above. */
5000 if (operand_equal_p (op1a, op2b, 0)
5001 && operand_equal_p (op1b, op2a, 0))
5003 /* Result will be either NULL_TREE, or a combined comparison. */
5004 tree t = combine_comparisons (UNKNOWN_LOCATION,
5005 TRUTH_ANDIF_EXPR, code1,
5006 swap_tree_comparison (code2),
5007 truth_type, op1a, op1b);
5008 if (t)
5009 return t;
5012 /* If both comparisons are of the same value against constants, we might
5013 be able to merge them. */
5014 if (operand_equal_p (op1a, op2a, 0)
5015 && TREE_CODE (op1b) == INTEGER_CST
5016 && TREE_CODE (op2b) == INTEGER_CST)
5018 int cmp = tree_int_cst_compare (op1b, op2b);
5020 /* If we have (op1a == op1b), we should either be able to
5021 return that or FALSE, depending on whether the constant op1b
5022 also satisfies the other comparison against op2b. */
5023 if (code1 == EQ_EXPR)
5025 bool done = true;
5026 bool val;
5027 switch (code2)
5029 case EQ_EXPR: val = (cmp == 0); break;
5030 case NE_EXPR: val = (cmp != 0); break;
5031 case LT_EXPR: val = (cmp < 0); break;
5032 case GT_EXPR: val = (cmp > 0); break;
5033 case LE_EXPR: val = (cmp <= 0); break;
5034 case GE_EXPR: val = (cmp >= 0); break;
5035 default: done = false;
5037 if (done)
5039 if (val)
5040 return fold_build2 (code1, boolean_type_node, op1a, op1b);
5041 else
5042 return boolean_false_node;
5045 /* Likewise if the second comparison is an == comparison. */
5046 else if (code2 == EQ_EXPR)
5048 bool done = true;
5049 bool val;
5050 switch (code1)
5052 case EQ_EXPR: val = (cmp == 0); break;
5053 case NE_EXPR: val = (cmp != 0); break;
5054 case LT_EXPR: val = (cmp > 0); break;
5055 case GT_EXPR: val = (cmp < 0); break;
5056 case LE_EXPR: val = (cmp >= 0); break;
5057 case GE_EXPR: val = (cmp <= 0); break;
5058 default: done = false;
5060 if (done)
5062 if (val)
5063 return fold_build2 (code2, boolean_type_node, op2a, op2b);
5064 else
5065 return boolean_false_node;
5069 /* Same business with inequality tests. */
5070 else if (code1 == NE_EXPR)
5072 bool val;
5073 switch (code2)
5075 case EQ_EXPR: val = (cmp != 0); break;
5076 case NE_EXPR: val = (cmp == 0); break;
5077 case LT_EXPR: val = (cmp >= 0); break;
5078 case GT_EXPR: val = (cmp <= 0); break;
5079 case LE_EXPR: val = (cmp > 0); break;
5080 case GE_EXPR: val = (cmp < 0); break;
5081 default:
5082 val = false;
5084 if (val)
5085 return fold_build2 (code2, boolean_type_node, op2a, op2b);
5087 else if (code2 == NE_EXPR)
5089 bool val;
5090 switch (code1)
5092 case EQ_EXPR: val = (cmp == 0); break;
5093 case NE_EXPR: val = (cmp != 0); break;
5094 case LT_EXPR: val = (cmp <= 0); break;
5095 case GT_EXPR: val = (cmp >= 0); break;
5096 case LE_EXPR: val = (cmp < 0); break;
5097 case GE_EXPR: val = (cmp > 0); break;
5098 default:
5099 val = false;
5101 if (val)
5102 return fold_build2 (code1, boolean_type_node, op1a, op1b);
5105 /* Chose the more restrictive of two < or <= comparisons. */
5106 else if ((code1 == LT_EXPR || code1 == LE_EXPR)
5107 && (code2 == LT_EXPR || code2 == LE_EXPR))
5109 if ((cmp < 0) || (cmp == 0 && code1 == LT_EXPR))
5110 return fold_build2 (code1, boolean_type_node, op1a, op1b);
5111 else
5112 return fold_build2 (code2, boolean_type_node, op2a, op2b);
5115 /* Likewise chose the more restrictive of two > or >= comparisons. */
5116 else if ((code1 == GT_EXPR || code1 == GE_EXPR)
5117 && (code2 == GT_EXPR || code2 == GE_EXPR))
5119 if ((cmp > 0) || (cmp == 0 && code1 == GT_EXPR))
5120 return fold_build2 (code1, boolean_type_node, op1a, op1b);
5121 else
5122 return fold_build2 (code2, boolean_type_node, op2a, op2b);
5125 /* Check for singleton ranges. */
5126 else if (cmp == 0
5127 && ((code1 == LE_EXPR && code2 == GE_EXPR)
5128 || (code1 == GE_EXPR && code2 == LE_EXPR)))
5129 return fold_build2 (EQ_EXPR, boolean_type_node, op1a, op2b);
5131 /* Check for disjoint ranges. */
5132 else if (cmp <= 0
5133 && (code1 == LT_EXPR || code1 == LE_EXPR)
5134 && (code2 == GT_EXPR || code2 == GE_EXPR))
5135 return boolean_false_node;
5136 else if (cmp >= 0
5137 && (code1 == GT_EXPR || code1 == GE_EXPR)
5138 && (code2 == LT_EXPR || code2 == LE_EXPR))
5139 return boolean_false_node;
5142 /* Perhaps the first comparison is (NAME != 0) or (NAME == 1) where
5143 NAME's definition is a truth value. See if there are any simplifications
5144 that can be done against the NAME's definition. */
5145 if (TREE_CODE (op1a) == SSA_NAME
5146 && (code1 == NE_EXPR || code1 == EQ_EXPR)
5147 && (integer_zerop (op1b) || integer_onep (op1b)))
5149 bool invert = ((code1 == EQ_EXPR && integer_zerop (op1b))
5150 || (code1 == NE_EXPR && integer_onep (op1b)));
5151 gimple *stmt = SSA_NAME_DEF_STMT (op1a);
5152 switch (gimple_code (stmt))
5154 case GIMPLE_ASSIGN:
5155 /* Try to simplify by copy-propagating the definition. */
5156 return and_var_with_comparison (op1a, invert, code2, op2a, op2b);
5158 case GIMPLE_PHI:
5159 /* If every argument to the PHI produces the same result when
5160 ANDed with the second comparison, we win.
5161 Do not do this unless the type is bool since we need a bool
5162 result here anyway. */
5163 if (TREE_CODE (TREE_TYPE (op1a)) == BOOLEAN_TYPE)
5165 tree result = NULL_TREE;
5166 unsigned i;
5167 for (i = 0; i < gimple_phi_num_args (stmt); i++)
5169 tree arg = gimple_phi_arg_def (stmt, i);
5171 /* If this PHI has itself as an argument, ignore it.
5172 If all the other args produce the same result,
5173 we're still OK. */
5174 if (arg == gimple_phi_result (stmt))
5175 continue;
5176 else if (TREE_CODE (arg) == INTEGER_CST)
5178 if (invert ? integer_nonzerop (arg) : integer_zerop (arg))
5180 if (!result)
5181 result = boolean_false_node;
5182 else if (!integer_zerop (result))
5183 return NULL_TREE;
5185 else if (!result)
5186 result = fold_build2 (code2, boolean_type_node,
5187 op2a, op2b);
5188 else if (!same_bool_comparison_p (result,
5189 code2, op2a, op2b))
5190 return NULL_TREE;
5192 else if (TREE_CODE (arg) == SSA_NAME
5193 && !SSA_NAME_IS_DEFAULT_DEF (arg))
5195 tree temp;
5196 gimple *def_stmt = SSA_NAME_DEF_STMT (arg);
5197 /* In simple cases we can look through PHI nodes,
5198 but we have to be careful with loops.
5199 See PR49073. */
5200 if (! dom_info_available_p (CDI_DOMINATORS)
5201 || gimple_bb (def_stmt) == gimple_bb (stmt)
5202 || dominated_by_p (CDI_DOMINATORS,
5203 gimple_bb (def_stmt),
5204 gimple_bb (stmt)))
5205 return NULL_TREE;
5206 temp = and_var_with_comparison (arg, invert, code2,
5207 op2a, op2b);
5208 if (!temp)
5209 return NULL_TREE;
5210 else if (!result)
5211 result = temp;
5212 else if (!same_bool_result_p (result, temp))
5213 return NULL_TREE;
5215 else
5216 return NULL_TREE;
5218 return result;
5221 default:
5222 break;
5225 return NULL_TREE;
5228 /* Try to simplify the AND of two comparisons, specified by
5229 (OP1A CODE1 OP1B) and (OP2B CODE2 OP2B), respectively.
5230 If this can be simplified to a single expression (without requiring
5231 introducing more SSA variables to hold intermediate values),
5232 return the resulting tree. Otherwise return NULL_TREE.
5233 If the result expression is non-null, it has boolean type. */
5235 tree
5236 maybe_fold_and_comparisons (enum tree_code code1, tree op1a, tree op1b,
5237 enum tree_code code2, tree op2a, tree op2b)
5239 tree t = and_comparisons_1 (code1, op1a, op1b, code2, op2a, op2b);
5240 if (t)
5241 return t;
5242 else
5243 return and_comparisons_1 (code2, op2a, op2b, code1, op1a, op1b);
5246 /* Helper function for or_comparisons_1: try to simplify the OR of the
5247 ssa variable VAR with the comparison specified by (OP2A CODE2 OP2B).
5248 If INVERT is true, invert the value of VAR before doing the OR.
5249 Return NULL_EXPR if we can't simplify this to a single expression. */
5251 static tree
5252 or_var_with_comparison (tree var, bool invert,
5253 enum tree_code code2, tree op2a, tree op2b)
5255 tree t;
5256 gimple *stmt = SSA_NAME_DEF_STMT (var);
5258 /* We can only deal with variables whose definitions are assignments. */
5259 if (!is_gimple_assign (stmt))
5260 return NULL_TREE;
5262 /* If we have an inverted comparison, apply DeMorgan's law and rewrite
5263 !var OR (op2a code2 op2b) => !(var AND !(op2a code2 op2b))
5264 Then we only have to consider the simpler non-inverted cases. */
5265 if (invert)
5266 t = and_var_with_comparison_1 (stmt,
5267 invert_tree_comparison (code2, false),
5268 op2a, op2b);
5269 else
5270 t = or_var_with_comparison_1 (stmt, code2, op2a, op2b);
5271 return canonicalize_bool (t, invert);
5274 /* Try to simplify the OR of the ssa variable defined by the assignment
5275 STMT with the comparison specified by (OP2A CODE2 OP2B).
5276 Return NULL_EXPR if we can't simplify this to a single expression. */
5278 static tree
5279 or_var_with_comparison_1 (gimple *stmt,
5280 enum tree_code code2, tree op2a, tree op2b)
5282 tree var = gimple_assign_lhs (stmt);
5283 tree true_test_var = NULL_TREE;
5284 tree false_test_var = NULL_TREE;
5285 enum tree_code innercode = gimple_assign_rhs_code (stmt);
5287 /* Check for identities like (var OR (var != 0)) => true . */
5288 if (TREE_CODE (op2a) == SSA_NAME
5289 && TREE_CODE (TREE_TYPE (var)) == BOOLEAN_TYPE)
5291 if ((code2 == NE_EXPR && integer_zerop (op2b))
5292 || (code2 == EQ_EXPR && integer_nonzerop (op2b)))
5294 true_test_var = op2a;
5295 if (var == true_test_var)
5296 return var;
5298 else if ((code2 == EQ_EXPR && integer_zerop (op2b))
5299 || (code2 == NE_EXPR && integer_nonzerop (op2b)))
5301 false_test_var = op2a;
5302 if (var == false_test_var)
5303 return boolean_true_node;
5307 /* If the definition is a comparison, recurse on it. */
5308 if (TREE_CODE_CLASS (innercode) == tcc_comparison)
5310 tree t = or_comparisons_1 (innercode,
5311 gimple_assign_rhs1 (stmt),
5312 gimple_assign_rhs2 (stmt),
5313 code2,
5314 op2a,
5315 op2b);
5316 if (t)
5317 return t;
5320 /* If the definition is an AND or OR expression, we may be able to
5321 simplify by reassociating. */
5322 if (TREE_CODE (TREE_TYPE (var)) == BOOLEAN_TYPE
5323 && (innercode == BIT_AND_EXPR || innercode == BIT_IOR_EXPR))
5325 tree inner1 = gimple_assign_rhs1 (stmt);
5326 tree inner2 = gimple_assign_rhs2 (stmt);
5327 gimple *s;
5328 tree t;
5329 tree partial = NULL_TREE;
5330 bool is_or = (innercode == BIT_IOR_EXPR);
5332 /* Check for boolean identities that don't require recursive examination
5333 of inner1/inner2:
5334 inner1 OR (inner1 OR inner2) => inner1 OR inner2 => var
5335 inner1 OR (inner1 AND inner2) => inner1
5336 !inner1 OR (inner1 OR inner2) => true
5337 !inner1 OR (inner1 AND inner2) => !inner1 OR inner2
5339 if (inner1 == true_test_var)
5340 return (is_or ? var : inner1);
5341 else if (inner2 == true_test_var)
5342 return (is_or ? var : inner2);
5343 else if (inner1 == false_test_var)
5344 return (is_or
5345 ? boolean_true_node
5346 : or_var_with_comparison (inner2, false, code2, op2a, op2b));
5347 else if (inner2 == false_test_var)
5348 return (is_or
5349 ? boolean_true_node
5350 : or_var_with_comparison (inner1, false, code2, op2a, op2b));
5352 /* Next, redistribute/reassociate the OR across the inner tests.
5353 Compute the first partial result, (inner1 OR (op2a code op2b)) */
5354 if (TREE_CODE (inner1) == SSA_NAME
5355 && is_gimple_assign (s = SSA_NAME_DEF_STMT (inner1))
5356 && TREE_CODE_CLASS (gimple_assign_rhs_code (s)) == tcc_comparison
5357 && (t = maybe_fold_or_comparisons (gimple_assign_rhs_code (s),
5358 gimple_assign_rhs1 (s),
5359 gimple_assign_rhs2 (s),
5360 code2, op2a, op2b)))
5362 /* Handle the OR case, where we are reassociating:
5363 (inner1 OR inner2) OR (op2a code2 op2b)
5364 => (t OR inner2)
5365 If the partial result t is a constant, we win. Otherwise
5366 continue on to try reassociating with the other inner test. */
5367 if (is_or)
5369 if (integer_onep (t))
5370 return boolean_true_node;
5371 else if (integer_zerop (t))
5372 return inner2;
5375 /* Handle the AND case, where we are redistributing:
5376 (inner1 AND inner2) OR (op2a code2 op2b)
5377 => (t AND (inner2 OR (op2a code op2b))) */
5378 else if (integer_zerop (t))
5379 return boolean_false_node;
5381 /* Save partial result for later. */
5382 partial = t;
5385 /* Compute the second partial result, (inner2 OR (op2a code op2b)) */
5386 if (TREE_CODE (inner2) == SSA_NAME
5387 && is_gimple_assign (s = SSA_NAME_DEF_STMT (inner2))
5388 && TREE_CODE_CLASS (gimple_assign_rhs_code (s)) == tcc_comparison
5389 && (t = maybe_fold_or_comparisons (gimple_assign_rhs_code (s),
5390 gimple_assign_rhs1 (s),
5391 gimple_assign_rhs2 (s),
5392 code2, op2a, op2b)))
5394 /* Handle the OR case, where we are reassociating:
5395 (inner1 OR inner2) OR (op2a code2 op2b)
5396 => (inner1 OR t)
5397 => (t OR partial) */
5398 if (is_or)
5400 if (integer_zerop (t))
5401 return inner1;
5402 else if (integer_onep (t))
5403 return boolean_true_node;
5404 /* If both are the same, we can apply the identity
5405 (x OR x) == x. */
5406 else if (partial && same_bool_result_p (t, partial))
5407 return t;
5410 /* Handle the AND case, where we are redistributing:
5411 (inner1 AND inner2) OR (op2a code2 op2b)
5412 => (t AND (inner1 OR (op2a code2 op2b)))
5413 => (t AND partial) */
5414 else
5416 if (integer_zerop (t))
5417 return boolean_false_node;
5418 else if (partial)
5420 /* We already got a simplification for the other
5421 operand to the redistributed AND expression. The
5422 interesting case is when at least one is true.
5423 Or, if both are the same, we can apply the identity
5424 (x AND x) == x. */
5425 if (integer_onep (partial))
5426 return t;
5427 else if (integer_onep (t))
5428 return partial;
5429 else if (same_bool_result_p (t, partial))
5430 return t;
5435 return NULL_TREE;
5438 /* Try to simplify the OR of two comparisons defined by
5439 (OP1A CODE1 OP1B) and (OP2A CODE2 OP2B), respectively.
5440 If this can be done without constructing an intermediate value,
5441 return the resulting tree; otherwise NULL_TREE is returned.
5442 This function is deliberately asymmetric as it recurses on SSA_DEFs
5443 in the first comparison but not the second. */
5445 static tree
5446 or_comparisons_1 (enum tree_code code1, tree op1a, tree op1b,
5447 enum tree_code code2, tree op2a, tree op2b)
5449 tree truth_type = truth_type_for (TREE_TYPE (op1a));
5451 /* First check for ((x CODE1 y) OR (x CODE2 y)). */
5452 if (operand_equal_p (op1a, op2a, 0)
5453 && operand_equal_p (op1b, op2b, 0))
5455 /* Result will be either NULL_TREE, or a combined comparison. */
5456 tree t = combine_comparisons (UNKNOWN_LOCATION,
5457 TRUTH_ORIF_EXPR, code1, code2,
5458 truth_type, op1a, op1b);
5459 if (t)
5460 return t;
5463 /* Likewise the swapped case of the above. */
5464 if (operand_equal_p (op1a, op2b, 0)
5465 && operand_equal_p (op1b, op2a, 0))
5467 /* Result will be either NULL_TREE, or a combined comparison. */
5468 tree t = combine_comparisons (UNKNOWN_LOCATION,
5469 TRUTH_ORIF_EXPR, code1,
5470 swap_tree_comparison (code2),
5471 truth_type, op1a, op1b);
5472 if (t)
5473 return t;
5476 /* If both comparisons are of the same value against constants, we might
5477 be able to merge them. */
5478 if (operand_equal_p (op1a, op2a, 0)
5479 && TREE_CODE (op1b) == INTEGER_CST
5480 && TREE_CODE (op2b) == INTEGER_CST)
5482 int cmp = tree_int_cst_compare (op1b, op2b);
5484 /* If we have (op1a != op1b), we should either be able to
5485 return that or TRUE, depending on whether the constant op1b
5486 also satisfies the other comparison against op2b. */
5487 if (code1 == NE_EXPR)
5489 bool done = true;
5490 bool val;
5491 switch (code2)
5493 case EQ_EXPR: val = (cmp == 0); break;
5494 case NE_EXPR: val = (cmp != 0); break;
5495 case LT_EXPR: val = (cmp < 0); break;
5496 case GT_EXPR: val = (cmp > 0); break;
5497 case LE_EXPR: val = (cmp <= 0); break;
5498 case GE_EXPR: val = (cmp >= 0); break;
5499 default: done = false;
5501 if (done)
5503 if (val)
5504 return boolean_true_node;
5505 else
5506 return fold_build2 (code1, boolean_type_node, op1a, op1b);
5509 /* Likewise if the second comparison is a != comparison. */
5510 else if (code2 == NE_EXPR)
5512 bool done = true;
5513 bool val;
5514 switch (code1)
5516 case EQ_EXPR: val = (cmp == 0); break;
5517 case NE_EXPR: val = (cmp != 0); break;
5518 case LT_EXPR: val = (cmp > 0); break;
5519 case GT_EXPR: val = (cmp < 0); break;
5520 case LE_EXPR: val = (cmp >= 0); break;
5521 case GE_EXPR: val = (cmp <= 0); break;
5522 default: done = false;
5524 if (done)
5526 if (val)
5527 return boolean_true_node;
5528 else
5529 return fold_build2 (code2, boolean_type_node, op2a, op2b);
5533 /* See if an equality test is redundant with the other comparison. */
5534 else if (code1 == EQ_EXPR)
5536 bool val;
5537 switch (code2)
5539 case EQ_EXPR: val = (cmp == 0); break;
5540 case NE_EXPR: val = (cmp != 0); break;
5541 case LT_EXPR: val = (cmp < 0); break;
5542 case GT_EXPR: val = (cmp > 0); break;
5543 case LE_EXPR: val = (cmp <= 0); break;
5544 case GE_EXPR: val = (cmp >= 0); break;
5545 default:
5546 val = false;
5548 if (val)
5549 return fold_build2 (code2, boolean_type_node, op2a, op2b);
5551 else if (code2 == EQ_EXPR)
5553 bool val;
5554 switch (code1)
5556 case EQ_EXPR: val = (cmp == 0); break;
5557 case NE_EXPR: val = (cmp != 0); break;
5558 case LT_EXPR: val = (cmp > 0); break;
5559 case GT_EXPR: val = (cmp < 0); break;
5560 case LE_EXPR: val = (cmp >= 0); break;
5561 case GE_EXPR: val = (cmp <= 0); break;
5562 default:
5563 val = false;
5565 if (val)
5566 return fold_build2 (code1, boolean_type_node, op1a, op1b);
5569 /* Chose the less restrictive of two < or <= comparisons. */
5570 else if ((code1 == LT_EXPR || code1 == LE_EXPR)
5571 && (code2 == LT_EXPR || code2 == LE_EXPR))
5573 if ((cmp < 0) || (cmp == 0 && code1 == LT_EXPR))
5574 return fold_build2 (code2, boolean_type_node, op2a, op2b);
5575 else
5576 return fold_build2 (code1, boolean_type_node, op1a, op1b);
5579 /* Likewise chose the less restrictive of two > or >= comparisons. */
5580 else if ((code1 == GT_EXPR || code1 == GE_EXPR)
5581 && (code2 == GT_EXPR || code2 == GE_EXPR))
5583 if ((cmp > 0) || (cmp == 0 && code1 == GT_EXPR))
5584 return fold_build2 (code2, boolean_type_node, op2a, op2b);
5585 else
5586 return fold_build2 (code1, boolean_type_node, op1a, op1b);
5589 /* Check for singleton ranges. */
5590 else if (cmp == 0
5591 && ((code1 == LT_EXPR && code2 == GT_EXPR)
5592 || (code1 == GT_EXPR && code2 == LT_EXPR)))
5593 return fold_build2 (NE_EXPR, boolean_type_node, op1a, op2b);
5595 /* Check for less/greater pairs that don't restrict the range at all. */
5596 else if (cmp >= 0
5597 && (code1 == LT_EXPR || code1 == LE_EXPR)
5598 && (code2 == GT_EXPR || code2 == GE_EXPR))
5599 return boolean_true_node;
5600 else if (cmp <= 0
5601 && (code1 == GT_EXPR || code1 == GE_EXPR)
5602 && (code2 == LT_EXPR || code2 == LE_EXPR))
5603 return boolean_true_node;
5606 /* Perhaps the first comparison is (NAME != 0) or (NAME == 1) where
5607 NAME's definition is a truth value. See if there are any simplifications
5608 that can be done against the NAME's definition. */
5609 if (TREE_CODE (op1a) == SSA_NAME
5610 && (code1 == NE_EXPR || code1 == EQ_EXPR)
5611 && (integer_zerop (op1b) || integer_onep (op1b)))
5613 bool invert = ((code1 == EQ_EXPR && integer_zerop (op1b))
5614 || (code1 == NE_EXPR && integer_onep (op1b)));
5615 gimple *stmt = SSA_NAME_DEF_STMT (op1a);
5616 switch (gimple_code (stmt))
5618 case GIMPLE_ASSIGN:
5619 /* Try to simplify by copy-propagating the definition. */
5620 return or_var_with_comparison (op1a, invert, code2, op2a, op2b);
5622 case GIMPLE_PHI:
5623 /* If every argument to the PHI produces the same result when
5624 ORed with the second comparison, we win.
5625 Do not do this unless the type is bool since we need a bool
5626 result here anyway. */
5627 if (TREE_CODE (TREE_TYPE (op1a)) == BOOLEAN_TYPE)
5629 tree result = NULL_TREE;
5630 unsigned i;
5631 for (i = 0; i < gimple_phi_num_args (stmt); i++)
5633 tree arg = gimple_phi_arg_def (stmt, i);
5635 /* If this PHI has itself as an argument, ignore it.
5636 If all the other args produce the same result,
5637 we're still OK. */
5638 if (arg == gimple_phi_result (stmt))
5639 continue;
5640 else if (TREE_CODE (arg) == INTEGER_CST)
5642 if (invert ? integer_zerop (arg) : integer_nonzerop (arg))
5644 if (!result)
5645 result = boolean_true_node;
5646 else if (!integer_onep (result))
5647 return NULL_TREE;
5649 else if (!result)
5650 result = fold_build2 (code2, boolean_type_node,
5651 op2a, op2b);
5652 else if (!same_bool_comparison_p (result,
5653 code2, op2a, op2b))
5654 return NULL_TREE;
5656 else if (TREE_CODE (arg) == SSA_NAME
5657 && !SSA_NAME_IS_DEFAULT_DEF (arg))
5659 tree temp;
5660 gimple *def_stmt = SSA_NAME_DEF_STMT (arg);
5661 /* In simple cases we can look through PHI nodes,
5662 but we have to be careful with loops.
5663 See PR49073. */
5664 if (! dom_info_available_p (CDI_DOMINATORS)
5665 || gimple_bb (def_stmt) == gimple_bb (stmt)
5666 || dominated_by_p (CDI_DOMINATORS,
5667 gimple_bb (def_stmt),
5668 gimple_bb (stmt)))
5669 return NULL_TREE;
5670 temp = or_var_with_comparison (arg, invert, code2,
5671 op2a, op2b);
5672 if (!temp)
5673 return NULL_TREE;
5674 else if (!result)
5675 result = temp;
5676 else if (!same_bool_result_p (result, temp))
5677 return NULL_TREE;
5679 else
5680 return NULL_TREE;
5682 return result;
5685 default:
5686 break;
5689 return NULL_TREE;
5692 /* Try to simplify the OR of two comparisons, specified by
5693 (OP1A CODE1 OP1B) and (OP2B CODE2 OP2B), respectively.
5694 If this can be simplified to a single expression (without requiring
5695 introducing more SSA variables to hold intermediate values),
5696 return the resulting tree. Otherwise return NULL_TREE.
5697 If the result expression is non-null, it has boolean type. */
5699 tree
5700 maybe_fold_or_comparisons (enum tree_code code1, tree op1a, tree op1b,
5701 enum tree_code code2, tree op2a, tree op2b)
5703 tree t = or_comparisons_1 (code1, op1a, op1b, code2, op2a, op2b);
5704 if (t)
5705 return t;
5706 else
5707 return or_comparisons_1 (code2, op2a, op2b, code1, op1a, op1b);
5711 /* Fold STMT to a constant using VALUEIZE to valueize SSA names.
5713 Either NULL_TREE, a simplified but non-constant or a constant
5714 is returned.
5716 ??? This should go into a gimple-fold-inline.h file to be eventually
5717 privatized with the single valueize function used in the various TUs
5718 to avoid the indirect function call overhead. */
5720 tree
5721 gimple_fold_stmt_to_constant_1 (gimple *stmt, tree (*valueize) (tree),
5722 tree (*gvalueize) (tree))
5724 code_helper rcode;
5725 tree ops[3] = {};
5726 /* ??? The SSA propagators do not correctly deal with following SSA use-def
5727 edges if there are intermediate VARYING defs. For this reason
5728 do not follow SSA edges here even though SCCVN can technically
5729 just deal fine with that. */
5730 if (gimple_simplify (stmt, &rcode, ops, NULL, gvalueize, valueize))
5732 tree res = NULL_TREE;
5733 if (gimple_simplified_result_is_gimple_val (rcode, ops))
5734 res = ops[0];
5735 else if (mprts_hook)
5736 res = mprts_hook (rcode, gimple_expr_type (stmt), ops);
5737 if (res)
5739 if (dump_file && dump_flags & TDF_DETAILS)
5741 fprintf (dump_file, "Match-and-simplified ");
5742 print_gimple_expr (dump_file, stmt, 0, TDF_SLIM);
5743 fprintf (dump_file, " to ");
5744 print_generic_expr (dump_file, res);
5745 fprintf (dump_file, "\n");
5747 return res;
5751 location_t loc = gimple_location (stmt);
5752 switch (gimple_code (stmt))
5754 case GIMPLE_ASSIGN:
5756 enum tree_code subcode = gimple_assign_rhs_code (stmt);
5758 switch (get_gimple_rhs_class (subcode))
5760 case GIMPLE_SINGLE_RHS:
5762 tree rhs = gimple_assign_rhs1 (stmt);
5763 enum tree_code_class kind = TREE_CODE_CLASS (subcode);
5765 if (TREE_CODE (rhs) == SSA_NAME)
5767 /* If the RHS is an SSA_NAME, return its known constant value,
5768 if any. */
5769 return (*valueize) (rhs);
5771 /* Handle propagating invariant addresses into address
5772 operations. */
5773 else if (TREE_CODE (rhs) == ADDR_EXPR
5774 && !is_gimple_min_invariant (rhs))
5776 HOST_WIDE_INT offset = 0;
5777 tree base;
5778 base = get_addr_base_and_unit_offset_1 (TREE_OPERAND (rhs, 0),
5779 &offset,
5780 valueize);
5781 if (base
5782 && (CONSTANT_CLASS_P (base)
5783 || decl_address_invariant_p (base)))
5784 return build_invariant_address (TREE_TYPE (rhs),
5785 base, offset);
5787 else if (TREE_CODE (rhs) == CONSTRUCTOR
5788 && TREE_CODE (TREE_TYPE (rhs)) == VECTOR_TYPE
5789 && (CONSTRUCTOR_NELTS (rhs)
5790 == TYPE_VECTOR_SUBPARTS (TREE_TYPE (rhs))))
5792 unsigned i;
5793 tree val, *vec;
5795 vec = XALLOCAVEC (tree,
5796 TYPE_VECTOR_SUBPARTS (TREE_TYPE (rhs)));
5797 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (rhs), i, val)
5799 val = (*valueize) (val);
5800 if (TREE_CODE (val) == INTEGER_CST
5801 || TREE_CODE (val) == REAL_CST
5802 || TREE_CODE (val) == FIXED_CST)
5803 vec[i] = val;
5804 else
5805 return NULL_TREE;
5808 return build_vector (TREE_TYPE (rhs), vec);
5810 if (subcode == OBJ_TYPE_REF)
5812 tree val = (*valueize) (OBJ_TYPE_REF_EXPR (rhs));
5813 /* If callee is constant, we can fold away the wrapper. */
5814 if (is_gimple_min_invariant (val))
5815 return val;
5818 if (kind == tcc_reference)
5820 if ((TREE_CODE (rhs) == VIEW_CONVERT_EXPR
5821 || TREE_CODE (rhs) == REALPART_EXPR
5822 || TREE_CODE (rhs) == IMAGPART_EXPR)
5823 && TREE_CODE (TREE_OPERAND (rhs, 0)) == SSA_NAME)
5825 tree val = (*valueize) (TREE_OPERAND (rhs, 0));
5826 return fold_unary_loc (EXPR_LOCATION (rhs),
5827 TREE_CODE (rhs),
5828 TREE_TYPE (rhs), val);
5830 else if (TREE_CODE (rhs) == BIT_FIELD_REF
5831 && TREE_CODE (TREE_OPERAND (rhs, 0)) == SSA_NAME)
5833 tree val = (*valueize) (TREE_OPERAND (rhs, 0));
5834 return fold_ternary_loc (EXPR_LOCATION (rhs),
5835 TREE_CODE (rhs),
5836 TREE_TYPE (rhs), val,
5837 TREE_OPERAND (rhs, 1),
5838 TREE_OPERAND (rhs, 2));
5840 else if (TREE_CODE (rhs) == MEM_REF
5841 && TREE_CODE (TREE_OPERAND (rhs, 0)) == SSA_NAME)
5843 tree val = (*valueize) (TREE_OPERAND (rhs, 0));
5844 if (TREE_CODE (val) == ADDR_EXPR
5845 && is_gimple_min_invariant (val))
5847 tree tem = fold_build2 (MEM_REF, TREE_TYPE (rhs),
5848 unshare_expr (val),
5849 TREE_OPERAND (rhs, 1));
5850 if (tem)
5851 rhs = tem;
5854 return fold_const_aggregate_ref_1 (rhs, valueize);
5856 else if (kind == tcc_declaration)
5857 return get_symbol_constant_value (rhs);
5858 return rhs;
5861 case GIMPLE_UNARY_RHS:
5862 return NULL_TREE;
5864 case GIMPLE_BINARY_RHS:
5865 /* Translate &x + CST into an invariant form suitable for
5866 further propagation. */
5867 if (subcode == POINTER_PLUS_EXPR)
5869 tree op0 = (*valueize) (gimple_assign_rhs1 (stmt));
5870 tree op1 = (*valueize) (gimple_assign_rhs2 (stmt));
5871 if (TREE_CODE (op0) == ADDR_EXPR
5872 && TREE_CODE (op1) == INTEGER_CST)
5874 tree off = fold_convert (ptr_type_node, op1);
5875 return build_fold_addr_expr_loc
5876 (loc,
5877 fold_build2 (MEM_REF,
5878 TREE_TYPE (TREE_TYPE (op0)),
5879 unshare_expr (op0), off));
5882 /* Canonicalize bool != 0 and bool == 0 appearing after
5883 valueization. While gimple_simplify handles this
5884 it can get confused by the ~X == 1 -> X == 0 transform
5885 which we cant reduce to a SSA name or a constant
5886 (and we have no way to tell gimple_simplify to not
5887 consider those transforms in the first place). */
5888 else if (subcode == EQ_EXPR
5889 || subcode == NE_EXPR)
5891 tree lhs = gimple_assign_lhs (stmt);
5892 tree op0 = gimple_assign_rhs1 (stmt);
5893 if (useless_type_conversion_p (TREE_TYPE (lhs),
5894 TREE_TYPE (op0)))
5896 tree op1 = (*valueize) (gimple_assign_rhs2 (stmt));
5897 op0 = (*valueize) (op0);
5898 if (TREE_CODE (op0) == INTEGER_CST)
5899 std::swap (op0, op1);
5900 if (TREE_CODE (op1) == INTEGER_CST
5901 && ((subcode == NE_EXPR && integer_zerop (op1))
5902 || (subcode == EQ_EXPR && integer_onep (op1))))
5903 return op0;
5906 return NULL_TREE;
5908 case GIMPLE_TERNARY_RHS:
5910 /* Handle ternary operators that can appear in GIMPLE form. */
5911 tree op0 = (*valueize) (gimple_assign_rhs1 (stmt));
5912 tree op1 = (*valueize) (gimple_assign_rhs2 (stmt));
5913 tree op2 = (*valueize) (gimple_assign_rhs3 (stmt));
5914 return fold_ternary_loc (loc, subcode,
5915 gimple_expr_type (stmt), op0, op1, op2);
5918 default:
5919 gcc_unreachable ();
5923 case GIMPLE_CALL:
5925 tree fn;
5926 gcall *call_stmt = as_a <gcall *> (stmt);
5928 if (gimple_call_internal_p (stmt))
5930 enum tree_code subcode = ERROR_MARK;
5931 switch (gimple_call_internal_fn (stmt))
5933 case IFN_UBSAN_CHECK_ADD:
5934 subcode = PLUS_EXPR;
5935 break;
5936 case IFN_UBSAN_CHECK_SUB:
5937 subcode = MINUS_EXPR;
5938 break;
5939 case IFN_UBSAN_CHECK_MUL:
5940 subcode = MULT_EXPR;
5941 break;
5942 case IFN_BUILTIN_EXPECT:
5944 tree arg0 = gimple_call_arg (stmt, 0);
5945 tree op0 = (*valueize) (arg0);
5946 if (TREE_CODE (op0) == INTEGER_CST)
5947 return op0;
5948 return NULL_TREE;
5950 default:
5951 return NULL_TREE;
5953 tree arg0 = gimple_call_arg (stmt, 0);
5954 tree arg1 = gimple_call_arg (stmt, 1);
5955 tree op0 = (*valueize) (arg0);
5956 tree op1 = (*valueize) (arg1);
5958 if (TREE_CODE (op0) != INTEGER_CST
5959 || TREE_CODE (op1) != INTEGER_CST)
5961 switch (subcode)
5963 case MULT_EXPR:
5964 /* x * 0 = 0 * x = 0 without overflow. */
5965 if (integer_zerop (op0) || integer_zerop (op1))
5966 return build_zero_cst (TREE_TYPE (arg0));
5967 break;
5968 case MINUS_EXPR:
5969 /* y - y = 0 without overflow. */
5970 if (operand_equal_p (op0, op1, 0))
5971 return build_zero_cst (TREE_TYPE (arg0));
5972 break;
5973 default:
5974 break;
5977 tree res
5978 = fold_binary_loc (loc, subcode, TREE_TYPE (arg0), op0, op1);
5979 if (res
5980 && TREE_CODE (res) == INTEGER_CST
5981 && !TREE_OVERFLOW (res))
5982 return res;
5983 return NULL_TREE;
5986 fn = (*valueize) (gimple_call_fn (stmt));
5987 if (TREE_CODE (fn) == ADDR_EXPR
5988 && TREE_CODE (TREE_OPERAND (fn, 0)) == FUNCTION_DECL
5989 && DECL_BUILT_IN (TREE_OPERAND (fn, 0))
5990 && gimple_builtin_call_types_compatible_p (stmt,
5991 TREE_OPERAND (fn, 0)))
5993 tree *args = XALLOCAVEC (tree, gimple_call_num_args (stmt));
5994 tree retval;
5995 unsigned i;
5996 for (i = 0; i < gimple_call_num_args (stmt); ++i)
5997 args[i] = (*valueize) (gimple_call_arg (stmt, i));
5998 retval = fold_builtin_call_array (loc,
5999 gimple_call_return_type (call_stmt),
6000 fn, gimple_call_num_args (stmt), args);
6001 if (retval)
6003 /* fold_call_expr wraps the result inside a NOP_EXPR. */
6004 STRIP_NOPS (retval);
6005 retval = fold_convert (gimple_call_return_type (call_stmt),
6006 retval);
6008 return retval;
6010 return NULL_TREE;
6013 default:
6014 return NULL_TREE;
6018 /* Fold STMT to a constant using VALUEIZE to valueize SSA names.
6019 Returns NULL_TREE if folding to a constant is not possible, otherwise
6020 returns a constant according to is_gimple_min_invariant. */
6022 tree
6023 gimple_fold_stmt_to_constant (gimple *stmt, tree (*valueize) (tree))
6025 tree res = gimple_fold_stmt_to_constant_1 (stmt, valueize);
6026 if (res && is_gimple_min_invariant (res))
6027 return res;
6028 return NULL_TREE;
6032 /* The following set of functions are supposed to fold references using
6033 their constant initializers. */
6035 /* See if we can find constructor defining value of BASE.
6036 When we know the consructor with constant offset (such as
6037 base is array[40] and we do know constructor of array), then
6038 BIT_OFFSET is adjusted accordingly.
6040 As a special case, return error_mark_node when constructor
6041 is not explicitly available, but it is known to be zero
6042 such as 'static const int a;'. */
6043 static tree
6044 get_base_constructor (tree base, HOST_WIDE_INT *bit_offset,
6045 tree (*valueize)(tree))
6047 HOST_WIDE_INT bit_offset2, size, max_size;
6048 bool reverse;
6050 if (TREE_CODE (base) == MEM_REF)
6052 if (!integer_zerop (TREE_OPERAND (base, 1)))
6054 if (!tree_fits_shwi_p (TREE_OPERAND (base, 1)))
6055 return NULL_TREE;
6056 *bit_offset += (mem_ref_offset (base).to_short_addr ()
6057 * BITS_PER_UNIT);
6060 if (valueize
6061 && TREE_CODE (TREE_OPERAND (base, 0)) == SSA_NAME)
6062 base = valueize (TREE_OPERAND (base, 0));
6063 if (!base || TREE_CODE (base) != ADDR_EXPR)
6064 return NULL_TREE;
6065 base = TREE_OPERAND (base, 0);
6067 else if (valueize
6068 && TREE_CODE (base) == SSA_NAME)
6069 base = valueize (base);
6071 /* Get a CONSTRUCTOR. If BASE is a VAR_DECL, get its
6072 DECL_INITIAL. If BASE is a nested reference into another
6073 ARRAY_REF or COMPONENT_REF, make a recursive call to resolve
6074 the inner reference. */
6075 switch (TREE_CODE (base))
6077 case VAR_DECL:
6078 case CONST_DECL:
6080 tree init = ctor_for_folding (base);
6082 /* Our semantic is exact opposite of ctor_for_folding;
6083 NULL means unknown, while error_mark_node is 0. */
6084 if (init == error_mark_node)
6085 return NULL_TREE;
6086 if (!init)
6087 return error_mark_node;
6088 return init;
6091 case VIEW_CONVERT_EXPR:
6092 return get_base_constructor (TREE_OPERAND (base, 0),
6093 bit_offset, valueize);
6095 case ARRAY_REF:
6096 case COMPONENT_REF:
6097 base = get_ref_base_and_extent (base, &bit_offset2, &size, &max_size,
6098 &reverse);
6099 if (max_size == -1 || size != max_size)
6100 return NULL_TREE;
6101 *bit_offset += bit_offset2;
6102 return get_base_constructor (base, bit_offset, valueize);
6104 case CONSTRUCTOR:
6105 return base;
6107 default:
6108 if (CONSTANT_CLASS_P (base))
6109 return base;
6111 return NULL_TREE;
6115 /* CTOR is CONSTRUCTOR of an array type. Fold reference of type TYPE and size
6116 SIZE to the memory at bit OFFSET. */
6118 static tree
6119 fold_array_ctor_reference (tree type, tree ctor,
6120 unsigned HOST_WIDE_INT offset,
6121 unsigned HOST_WIDE_INT size,
6122 tree from_decl)
6124 offset_int low_bound;
6125 offset_int elt_size;
6126 offset_int access_index;
6127 tree domain_type = NULL_TREE;
6128 HOST_WIDE_INT inner_offset;
6130 /* Compute low bound and elt size. */
6131 if (TREE_CODE (TREE_TYPE (ctor)) == ARRAY_TYPE)
6132 domain_type = TYPE_DOMAIN (TREE_TYPE (ctor));
6133 if (domain_type && TYPE_MIN_VALUE (domain_type))
6135 /* Static constructors for variably sized objects makes no sense. */
6136 if (TREE_CODE (TYPE_MIN_VALUE (domain_type)) != INTEGER_CST)
6137 return NULL_TREE;
6138 low_bound = wi::to_offset (TYPE_MIN_VALUE (domain_type));
6140 else
6141 low_bound = 0;
6142 /* Static constructors for variably sized objects makes no sense. */
6143 if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (ctor)))) != INTEGER_CST)
6144 return NULL_TREE;
6145 elt_size = wi::to_offset (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (ctor))));
6147 /* We can handle only constantly sized accesses that are known to not
6148 be larger than size of array element. */
6149 if (!TYPE_SIZE_UNIT (type)
6150 || TREE_CODE (TYPE_SIZE_UNIT (type)) != INTEGER_CST
6151 || elt_size < wi::to_offset (TYPE_SIZE_UNIT (type))
6152 || elt_size == 0)
6153 return NULL_TREE;
6155 /* Compute the array index we look for. */
6156 access_index = wi::udiv_trunc (offset_int (offset / BITS_PER_UNIT),
6157 elt_size);
6158 access_index += low_bound;
6160 /* And offset within the access. */
6161 inner_offset = offset % (elt_size.to_uhwi () * BITS_PER_UNIT);
6163 /* See if the array field is large enough to span whole access. We do not
6164 care to fold accesses spanning multiple array indexes. */
6165 if (inner_offset + size > elt_size.to_uhwi () * BITS_PER_UNIT)
6166 return NULL_TREE;
6167 if (tree val = get_array_ctor_element_at_index (ctor, access_index))
6168 return fold_ctor_reference (type, val, inner_offset, size, from_decl);
6170 /* When memory is not explicitely mentioned in constructor,
6171 it is 0 (or out of range). */
6172 return build_zero_cst (type);
6175 /* CTOR is CONSTRUCTOR of an aggregate or vector.
6176 Fold reference of type TYPE and size SIZE to the memory at bit OFFSET. */
6178 static tree
6179 fold_nonarray_ctor_reference (tree type, tree ctor,
6180 unsigned HOST_WIDE_INT offset,
6181 unsigned HOST_WIDE_INT size,
6182 tree from_decl)
6184 unsigned HOST_WIDE_INT cnt;
6185 tree cfield, cval;
6187 FOR_EACH_CONSTRUCTOR_ELT (CONSTRUCTOR_ELTS (ctor), cnt, cfield,
6188 cval)
6190 tree byte_offset = DECL_FIELD_OFFSET (cfield);
6191 tree field_offset = DECL_FIELD_BIT_OFFSET (cfield);
6192 tree field_size = DECL_SIZE (cfield);
6193 offset_int bitoffset;
6194 offset_int bitoffset_end, access_end;
6196 /* Variable sized objects in static constructors makes no sense,
6197 but field_size can be NULL for flexible array members. */
6198 gcc_assert (TREE_CODE (field_offset) == INTEGER_CST
6199 && TREE_CODE (byte_offset) == INTEGER_CST
6200 && (field_size != NULL_TREE
6201 ? TREE_CODE (field_size) == INTEGER_CST
6202 : TREE_CODE (TREE_TYPE (cfield)) == ARRAY_TYPE));
6204 /* Compute bit offset of the field. */
6205 bitoffset = (wi::to_offset (field_offset)
6206 + (wi::to_offset (byte_offset) << LOG2_BITS_PER_UNIT));
6207 /* Compute bit offset where the field ends. */
6208 if (field_size != NULL_TREE)
6209 bitoffset_end = bitoffset + wi::to_offset (field_size);
6210 else
6211 bitoffset_end = 0;
6213 access_end = offset_int (offset) + size;
6215 /* Is there any overlap between [OFFSET, OFFSET+SIZE) and
6216 [BITOFFSET, BITOFFSET_END)? */
6217 if (wi::cmps (access_end, bitoffset) > 0
6218 && (field_size == NULL_TREE
6219 || wi::lts_p (offset, bitoffset_end)))
6221 offset_int inner_offset = offset_int (offset) - bitoffset;
6222 /* We do have overlap. Now see if field is large enough to
6223 cover the access. Give up for accesses spanning multiple
6224 fields. */
6225 if (wi::cmps (access_end, bitoffset_end) > 0)
6226 return NULL_TREE;
6227 if (offset < bitoffset)
6228 return NULL_TREE;
6229 return fold_ctor_reference (type, cval,
6230 inner_offset.to_uhwi (), size,
6231 from_decl);
6234 /* When memory is not explicitely mentioned in constructor, it is 0. */
6235 return build_zero_cst (type);
6238 /* CTOR is value initializing memory, fold reference of type TYPE and size SIZE
6239 to the memory at bit OFFSET. */
6241 tree
6242 fold_ctor_reference (tree type, tree ctor, unsigned HOST_WIDE_INT offset,
6243 unsigned HOST_WIDE_INT size, tree from_decl)
6245 tree ret;
6247 /* We found the field with exact match. */
6248 if (useless_type_conversion_p (type, TREE_TYPE (ctor))
6249 && !offset)
6250 return canonicalize_constructor_val (unshare_expr (ctor), from_decl);
6252 /* We are at the end of walk, see if we can view convert the
6253 result. */
6254 if (!AGGREGATE_TYPE_P (TREE_TYPE (ctor)) && !offset
6255 /* VIEW_CONVERT_EXPR is defined only for matching sizes. */
6256 && !compare_tree_int (TYPE_SIZE (type), size)
6257 && !compare_tree_int (TYPE_SIZE (TREE_TYPE (ctor)), size))
6259 ret = canonicalize_constructor_val (unshare_expr (ctor), from_decl);
6260 if (ret)
6262 ret = fold_unary (VIEW_CONVERT_EXPR, type, ret);
6263 if (ret)
6264 STRIP_USELESS_TYPE_CONVERSION (ret);
6266 return ret;
6268 /* For constants and byte-aligned/sized reads try to go through
6269 native_encode/interpret. */
6270 if (CONSTANT_CLASS_P (ctor)
6271 && BITS_PER_UNIT == 8
6272 && offset % BITS_PER_UNIT == 0
6273 && size % BITS_PER_UNIT == 0
6274 && size <= MAX_BITSIZE_MODE_ANY_MODE)
6276 unsigned char buf[MAX_BITSIZE_MODE_ANY_MODE / BITS_PER_UNIT];
6277 int len = native_encode_expr (ctor, buf, size / BITS_PER_UNIT,
6278 offset / BITS_PER_UNIT);
6279 if (len > 0)
6280 return native_interpret_expr (type, buf, len);
6282 if (TREE_CODE (ctor) == CONSTRUCTOR)
6285 if (TREE_CODE (TREE_TYPE (ctor)) == ARRAY_TYPE
6286 || TREE_CODE (TREE_TYPE (ctor)) == VECTOR_TYPE)
6287 return fold_array_ctor_reference (type, ctor, offset, size,
6288 from_decl);
6289 else
6290 return fold_nonarray_ctor_reference (type, ctor, offset, size,
6291 from_decl);
6294 return NULL_TREE;
6297 /* Return the tree representing the element referenced by T if T is an
6298 ARRAY_REF or COMPONENT_REF into constant aggregates valuezing SSA
6299 names using VALUEIZE. Return NULL_TREE otherwise. */
6301 tree
6302 fold_const_aggregate_ref_1 (tree t, tree (*valueize) (tree))
6304 tree ctor, idx, base;
6305 HOST_WIDE_INT offset, size, max_size;
6306 tree tem;
6307 bool reverse;
6309 if (TREE_THIS_VOLATILE (t))
6310 return NULL_TREE;
6312 if (DECL_P (t))
6313 return get_symbol_constant_value (t);
6315 tem = fold_read_from_constant_string (t);
6316 if (tem)
6317 return tem;
6319 switch (TREE_CODE (t))
6321 case ARRAY_REF:
6322 case ARRAY_RANGE_REF:
6323 /* Constant indexes are handled well by get_base_constructor.
6324 Only special case variable offsets.
6325 FIXME: This code can't handle nested references with variable indexes
6326 (they will be handled only by iteration of ccp). Perhaps we can bring
6327 get_ref_base_and_extent here and make it use a valueize callback. */
6328 if (TREE_CODE (TREE_OPERAND (t, 1)) == SSA_NAME
6329 && valueize
6330 && (idx = (*valueize) (TREE_OPERAND (t, 1)))
6331 && TREE_CODE (idx) == INTEGER_CST)
6333 tree low_bound, unit_size;
6335 /* If the resulting bit-offset is constant, track it. */
6336 if ((low_bound = array_ref_low_bound (t),
6337 TREE_CODE (low_bound) == INTEGER_CST)
6338 && (unit_size = array_ref_element_size (t),
6339 tree_fits_uhwi_p (unit_size)))
6341 offset_int woffset
6342 = wi::sext (wi::to_offset (idx) - wi::to_offset (low_bound),
6343 TYPE_PRECISION (TREE_TYPE (idx)));
6345 if (wi::fits_shwi_p (woffset))
6347 offset = woffset.to_shwi ();
6348 /* TODO: This code seems wrong, multiply then check
6349 to see if it fits. */
6350 offset *= tree_to_uhwi (unit_size);
6351 offset *= BITS_PER_UNIT;
6353 base = TREE_OPERAND (t, 0);
6354 ctor = get_base_constructor (base, &offset, valueize);
6355 /* Empty constructor. Always fold to 0. */
6356 if (ctor == error_mark_node)
6357 return build_zero_cst (TREE_TYPE (t));
6358 /* Out of bound array access. Value is undefined,
6359 but don't fold. */
6360 if (offset < 0)
6361 return NULL_TREE;
6362 /* We can not determine ctor. */
6363 if (!ctor)
6364 return NULL_TREE;
6365 return fold_ctor_reference (TREE_TYPE (t), ctor, offset,
6366 tree_to_uhwi (unit_size)
6367 * BITS_PER_UNIT,
6368 base);
6372 /* Fallthru. */
6374 case COMPONENT_REF:
6375 case BIT_FIELD_REF:
6376 case TARGET_MEM_REF:
6377 case MEM_REF:
6378 base = get_ref_base_and_extent (t, &offset, &size, &max_size, &reverse);
6379 ctor = get_base_constructor (base, &offset, valueize);
6381 /* Empty constructor. Always fold to 0. */
6382 if (ctor == error_mark_node)
6383 return build_zero_cst (TREE_TYPE (t));
6384 /* We do not know precise address. */
6385 if (max_size == -1 || max_size != size)
6386 return NULL_TREE;
6387 /* We can not determine ctor. */
6388 if (!ctor)
6389 return NULL_TREE;
6391 /* Out of bound array access. Value is undefined, but don't fold. */
6392 if (offset < 0)
6393 return NULL_TREE;
6395 return fold_ctor_reference (TREE_TYPE (t), ctor, offset, size,
6396 base);
6398 case REALPART_EXPR:
6399 case IMAGPART_EXPR:
6401 tree c = fold_const_aggregate_ref_1 (TREE_OPERAND (t, 0), valueize);
6402 if (c && TREE_CODE (c) == COMPLEX_CST)
6403 return fold_build1_loc (EXPR_LOCATION (t),
6404 TREE_CODE (t), TREE_TYPE (t), c);
6405 break;
6408 default:
6409 break;
6412 return NULL_TREE;
6415 tree
6416 fold_const_aggregate_ref (tree t)
6418 return fold_const_aggregate_ref_1 (t, NULL);
6421 /* Lookup virtual method with index TOKEN in a virtual table V
6422 at OFFSET.
6423 Set CAN_REFER if non-NULL to false if method
6424 is not referable or if the virtual table is ill-formed (such as rewriten
6425 by non-C++ produced symbol). Otherwise just return NULL in that calse. */
6427 tree
6428 gimple_get_virt_method_for_vtable (HOST_WIDE_INT token,
6429 tree v,
6430 unsigned HOST_WIDE_INT offset,
6431 bool *can_refer)
6433 tree vtable = v, init, fn;
6434 unsigned HOST_WIDE_INT size;
6435 unsigned HOST_WIDE_INT elt_size, access_index;
6436 tree domain_type;
6438 if (can_refer)
6439 *can_refer = true;
6441 /* First of all double check we have virtual table. */
6442 if (!VAR_P (v) || !DECL_VIRTUAL_P (v))
6444 /* Pass down that we lost track of the target. */
6445 if (can_refer)
6446 *can_refer = false;
6447 return NULL_TREE;
6450 init = ctor_for_folding (v);
6452 /* The virtual tables should always be born with constructors
6453 and we always should assume that they are avaialble for
6454 folding. At the moment we do not stream them in all cases,
6455 but it should never happen that ctor seem unreachable. */
6456 gcc_assert (init);
6457 if (init == error_mark_node)
6459 gcc_assert (in_lto_p);
6460 /* Pass down that we lost track of the target. */
6461 if (can_refer)
6462 *can_refer = false;
6463 return NULL_TREE;
6465 gcc_checking_assert (TREE_CODE (TREE_TYPE (v)) == ARRAY_TYPE);
6466 size = tree_to_uhwi (TYPE_SIZE (TREE_TYPE (TREE_TYPE (v))));
6467 offset *= BITS_PER_UNIT;
6468 offset += token * size;
6470 /* Lookup the value in the constructor that is assumed to be array.
6471 This is equivalent to
6472 fn = fold_ctor_reference (TREE_TYPE (TREE_TYPE (v)), init,
6473 offset, size, NULL);
6474 but in a constant time. We expect that frontend produced a simple
6475 array without indexed initializers. */
6477 gcc_checking_assert (TREE_CODE (TREE_TYPE (init)) == ARRAY_TYPE);
6478 domain_type = TYPE_DOMAIN (TREE_TYPE (init));
6479 gcc_checking_assert (integer_zerop (TYPE_MIN_VALUE (domain_type)));
6480 elt_size = tree_to_uhwi (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (init))));
6482 access_index = offset / BITS_PER_UNIT / elt_size;
6483 gcc_checking_assert (offset % (elt_size * BITS_PER_UNIT) == 0);
6485 /* This code makes an assumption that there are no
6486 indexed fileds produced by C++ FE, so we can directly index the array. */
6487 if (access_index < CONSTRUCTOR_NELTS (init))
6489 fn = CONSTRUCTOR_ELT (init, access_index)->value;
6490 gcc_checking_assert (!CONSTRUCTOR_ELT (init, access_index)->index);
6491 STRIP_NOPS (fn);
6493 else
6494 fn = NULL;
6496 /* For type inconsistent program we may end up looking up virtual method
6497 in virtual table that does not contain TOKEN entries. We may overrun
6498 the virtual table and pick up a constant or RTTI info pointer.
6499 In any case the call is undefined. */
6500 if (!fn
6501 || (TREE_CODE (fn) != ADDR_EXPR && TREE_CODE (fn) != FDESC_EXPR)
6502 || TREE_CODE (TREE_OPERAND (fn, 0)) != FUNCTION_DECL)
6503 fn = builtin_decl_implicit (BUILT_IN_UNREACHABLE);
6504 else
6506 fn = TREE_OPERAND (fn, 0);
6508 /* When cgraph node is missing and function is not public, we cannot
6509 devirtualize. This can happen in WHOPR when the actual method
6510 ends up in other partition, because we found devirtualization
6511 possibility too late. */
6512 if (!can_refer_decl_in_current_unit_p (fn, vtable))
6514 if (can_refer)
6516 *can_refer = false;
6517 return fn;
6519 return NULL_TREE;
6523 /* Make sure we create a cgraph node for functions we'll reference.
6524 They can be non-existent if the reference comes from an entry
6525 of an external vtable for example. */
6526 cgraph_node::get_create (fn);
6528 return fn;
6531 /* Return a declaration of a function which an OBJ_TYPE_REF references. TOKEN
6532 is integer form of OBJ_TYPE_REF_TOKEN of the reference expression.
6533 KNOWN_BINFO carries the binfo describing the true type of
6534 OBJ_TYPE_REF_OBJECT(REF).
6535 Set CAN_REFER if non-NULL to false if method
6536 is not referable or if the virtual table is ill-formed (such as rewriten
6537 by non-C++ produced symbol). Otherwise just return NULL in that calse. */
6539 tree
6540 gimple_get_virt_method_for_binfo (HOST_WIDE_INT token, tree known_binfo,
6541 bool *can_refer)
6543 unsigned HOST_WIDE_INT offset;
6544 tree v;
6546 v = BINFO_VTABLE (known_binfo);
6547 /* If there is no virtual methods table, leave the OBJ_TYPE_REF alone. */
6548 if (!v)
6549 return NULL_TREE;
6551 if (!vtable_pointer_value_to_vtable (v, &v, &offset))
6553 if (can_refer)
6554 *can_refer = false;
6555 return NULL_TREE;
6557 return gimple_get_virt_method_for_vtable (token, v, offset, can_refer);
6560 /* Given a pointer value T, return a simplified version of an
6561 indirection through T, or NULL_TREE if no simplification is
6562 possible. Note that the resulting type may be different from
6563 the type pointed to in the sense that it is still compatible
6564 from the langhooks point of view. */
6566 tree
6567 gimple_fold_indirect_ref (tree t)
6569 tree ptype = TREE_TYPE (t), type = TREE_TYPE (ptype);
6570 tree sub = t;
6571 tree subtype;
6573 STRIP_NOPS (sub);
6574 subtype = TREE_TYPE (sub);
6575 if (!POINTER_TYPE_P (subtype)
6576 || TYPE_REF_CAN_ALIAS_ALL (ptype))
6577 return NULL_TREE;
6579 if (TREE_CODE (sub) == ADDR_EXPR)
6581 tree op = TREE_OPERAND (sub, 0);
6582 tree optype = TREE_TYPE (op);
6583 /* *&p => p */
6584 if (useless_type_conversion_p (type, optype))
6585 return op;
6587 /* *(foo *)&fooarray => fooarray[0] */
6588 if (TREE_CODE (optype) == ARRAY_TYPE
6589 && TREE_CODE (TYPE_SIZE (TREE_TYPE (optype))) == INTEGER_CST
6590 && useless_type_conversion_p (type, TREE_TYPE (optype)))
6592 tree type_domain = TYPE_DOMAIN (optype);
6593 tree min_val = size_zero_node;
6594 if (type_domain && TYPE_MIN_VALUE (type_domain))
6595 min_val = TYPE_MIN_VALUE (type_domain);
6596 if (TREE_CODE (min_val) == INTEGER_CST)
6597 return build4 (ARRAY_REF, type, op, min_val, NULL_TREE, NULL_TREE);
6599 /* *(foo *)&complexfoo => __real__ complexfoo */
6600 else if (TREE_CODE (optype) == COMPLEX_TYPE
6601 && useless_type_conversion_p (type, TREE_TYPE (optype)))
6602 return fold_build1 (REALPART_EXPR, type, op);
6603 /* *(foo *)&vectorfoo => BIT_FIELD_REF<vectorfoo,...> */
6604 else if (TREE_CODE (optype) == VECTOR_TYPE
6605 && useless_type_conversion_p (type, TREE_TYPE (optype)))
6607 tree part_width = TYPE_SIZE (type);
6608 tree index = bitsize_int (0);
6609 return fold_build3 (BIT_FIELD_REF, type, op, part_width, index);
6613 /* *(p + CST) -> ... */
6614 if (TREE_CODE (sub) == POINTER_PLUS_EXPR
6615 && TREE_CODE (TREE_OPERAND (sub, 1)) == INTEGER_CST)
6617 tree addr = TREE_OPERAND (sub, 0);
6618 tree off = TREE_OPERAND (sub, 1);
6619 tree addrtype;
6621 STRIP_NOPS (addr);
6622 addrtype = TREE_TYPE (addr);
6624 /* ((foo*)&vectorfoo)[1] -> BIT_FIELD_REF<vectorfoo,...> */
6625 if (TREE_CODE (addr) == ADDR_EXPR
6626 && TREE_CODE (TREE_TYPE (addrtype)) == VECTOR_TYPE
6627 && useless_type_conversion_p (type, TREE_TYPE (TREE_TYPE (addrtype)))
6628 && tree_fits_uhwi_p (off))
6630 unsigned HOST_WIDE_INT offset = tree_to_uhwi (off);
6631 tree part_width = TYPE_SIZE (type);
6632 unsigned HOST_WIDE_INT part_widthi
6633 = tree_to_shwi (part_width) / BITS_PER_UNIT;
6634 unsigned HOST_WIDE_INT indexi = offset * BITS_PER_UNIT;
6635 tree index = bitsize_int (indexi);
6636 if (offset / part_widthi
6637 < TYPE_VECTOR_SUBPARTS (TREE_TYPE (addrtype)))
6638 return fold_build3 (BIT_FIELD_REF, type, TREE_OPERAND (addr, 0),
6639 part_width, index);
6642 /* ((foo*)&complexfoo)[1] -> __imag__ complexfoo */
6643 if (TREE_CODE (addr) == ADDR_EXPR
6644 && TREE_CODE (TREE_TYPE (addrtype)) == COMPLEX_TYPE
6645 && useless_type_conversion_p (type, TREE_TYPE (TREE_TYPE (addrtype))))
6647 tree size = TYPE_SIZE_UNIT (type);
6648 if (tree_int_cst_equal (size, off))
6649 return fold_build1 (IMAGPART_EXPR, type, TREE_OPERAND (addr, 0));
6652 /* *(p + CST) -> MEM_REF <p, CST>. */
6653 if (TREE_CODE (addr) != ADDR_EXPR
6654 || DECL_P (TREE_OPERAND (addr, 0)))
6655 return fold_build2 (MEM_REF, type,
6656 addr,
6657 wide_int_to_tree (ptype, off));
6660 /* *(foo *)fooarrptr => (*fooarrptr)[0] */
6661 if (TREE_CODE (TREE_TYPE (subtype)) == ARRAY_TYPE
6662 && TREE_CODE (TYPE_SIZE (TREE_TYPE (TREE_TYPE (subtype)))) == INTEGER_CST
6663 && useless_type_conversion_p (type, TREE_TYPE (TREE_TYPE (subtype))))
6665 tree type_domain;
6666 tree min_val = size_zero_node;
6667 tree osub = sub;
6668 sub = gimple_fold_indirect_ref (sub);
6669 if (! sub)
6670 sub = build1 (INDIRECT_REF, TREE_TYPE (subtype), osub);
6671 type_domain = TYPE_DOMAIN (TREE_TYPE (sub));
6672 if (type_domain && TYPE_MIN_VALUE (type_domain))
6673 min_val = TYPE_MIN_VALUE (type_domain);
6674 if (TREE_CODE (min_val) == INTEGER_CST)
6675 return build4 (ARRAY_REF, type, sub, min_val, NULL_TREE, NULL_TREE);
6678 return NULL_TREE;
6681 /* Return true if CODE is an operation that when operating on signed
6682 integer types involves undefined behavior on overflow and the
6683 operation can be expressed with unsigned arithmetic. */
6685 bool
6686 arith_code_with_undefined_signed_overflow (tree_code code)
6688 switch (code)
6690 case PLUS_EXPR:
6691 case MINUS_EXPR:
6692 case MULT_EXPR:
6693 case NEGATE_EXPR:
6694 case POINTER_PLUS_EXPR:
6695 return true;
6696 default:
6697 return false;
6701 /* Rewrite STMT, an assignment with a signed integer or pointer arithmetic
6702 operation that can be transformed to unsigned arithmetic by converting
6703 its operand, carrying out the operation in the corresponding unsigned
6704 type and converting the result back to the original type.
6706 Returns a sequence of statements that replace STMT and also contain
6707 a modified form of STMT itself. */
6709 gimple_seq
6710 rewrite_to_defined_overflow (gimple *stmt)
6712 if (dump_file && (dump_flags & TDF_DETAILS))
6714 fprintf (dump_file, "rewriting stmt with undefined signed "
6715 "overflow ");
6716 print_gimple_stmt (dump_file, stmt, 0, TDF_SLIM);
6719 tree lhs = gimple_assign_lhs (stmt);
6720 tree type = unsigned_type_for (TREE_TYPE (lhs));
6721 gimple_seq stmts = NULL;
6722 for (unsigned i = 1; i < gimple_num_ops (stmt); ++i)
6724 tree op = gimple_op (stmt, i);
6725 op = gimple_convert (&stmts, type, op);
6726 gimple_set_op (stmt, i, op);
6728 gimple_assign_set_lhs (stmt, make_ssa_name (type, stmt));
6729 if (gimple_assign_rhs_code (stmt) == POINTER_PLUS_EXPR)
6730 gimple_assign_set_rhs_code (stmt, PLUS_EXPR);
6731 gimple_seq_add_stmt (&stmts, stmt);
6732 gimple *cvt = gimple_build_assign (lhs, NOP_EXPR, gimple_assign_lhs (stmt));
6733 gimple_seq_add_stmt (&stmts, cvt);
6735 return stmts;
6739 /* The valueization hook we use for the gimple_build API simplification.
6740 This makes us match fold_buildN behavior by only combining with
6741 statements in the sequence(s) we are currently building. */
6743 static tree
6744 gimple_build_valueize (tree op)
6746 if (gimple_bb (SSA_NAME_DEF_STMT (op)) == NULL)
6747 return op;
6748 return NULL_TREE;
6751 /* Build the expression CODE OP0 of type TYPE with location LOC,
6752 simplifying it first if possible. Returns the built
6753 expression value and appends statements possibly defining it
6754 to SEQ. */
6756 tree
6757 gimple_build (gimple_seq *seq, location_t loc,
6758 enum tree_code code, tree type, tree op0)
6760 tree res = gimple_simplify (code, type, op0, seq, gimple_build_valueize);
6761 if (!res)
6763 res = create_tmp_reg_or_ssa_name (type);
6764 gimple *stmt;
6765 if (code == REALPART_EXPR
6766 || code == IMAGPART_EXPR
6767 || code == VIEW_CONVERT_EXPR)
6768 stmt = gimple_build_assign (res, code, build1 (code, type, op0));
6769 else
6770 stmt = gimple_build_assign (res, code, op0);
6771 gimple_set_location (stmt, loc);
6772 gimple_seq_add_stmt_without_update (seq, stmt);
6774 return res;
6777 /* Build the expression OP0 CODE OP1 of type TYPE with location LOC,
6778 simplifying it first if possible. Returns the built
6779 expression value and appends statements possibly defining it
6780 to SEQ. */
6782 tree
6783 gimple_build (gimple_seq *seq, location_t loc,
6784 enum tree_code code, tree type, tree op0, tree op1)
6786 tree res = gimple_simplify (code, type, op0, op1, seq, gimple_build_valueize);
6787 if (!res)
6789 res = create_tmp_reg_or_ssa_name (type);
6790 gimple *stmt = gimple_build_assign (res, code, op0, op1);
6791 gimple_set_location (stmt, loc);
6792 gimple_seq_add_stmt_without_update (seq, stmt);
6794 return res;
6797 /* Build the expression (CODE OP0 OP1 OP2) of type TYPE with location LOC,
6798 simplifying it first if possible. Returns the built
6799 expression value and appends statements possibly defining it
6800 to SEQ. */
6802 tree
6803 gimple_build (gimple_seq *seq, location_t loc,
6804 enum tree_code code, tree type, tree op0, tree op1, tree op2)
6806 tree res = gimple_simplify (code, type, op0, op1, op2,
6807 seq, gimple_build_valueize);
6808 if (!res)
6810 res = create_tmp_reg_or_ssa_name (type);
6811 gimple *stmt;
6812 if (code == BIT_FIELD_REF)
6813 stmt = gimple_build_assign (res, code,
6814 build3 (code, type, op0, op1, op2));
6815 else
6816 stmt = gimple_build_assign (res, code, op0, op1, op2);
6817 gimple_set_location (stmt, loc);
6818 gimple_seq_add_stmt_without_update (seq, stmt);
6820 return res;
6823 /* Build the call FN (ARG0) with a result of type TYPE
6824 (or no result if TYPE is void) with location LOC,
6825 simplifying it first if possible. Returns the built
6826 expression value (or NULL_TREE if TYPE is void) and appends
6827 statements possibly defining it to SEQ. */
6829 tree
6830 gimple_build (gimple_seq *seq, location_t loc,
6831 enum built_in_function fn, tree type, tree arg0)
6833 tree res = gimple_simplify (fn, type, arg0, seq, gimple_build_valueize);
6834 if (!res)
6836 tree decl = builtin_decl_implicit (fn);
6837 gimple *stmt = gimple_build_call (decl, 1, arg0);
6838 if (!VOID_TYPE_P (type))
6840 res = create_tmp_reg_or_ssa_name (type);
6841 gimple_call_set_lhs (stmt, res);
6843 gimple_set_location (stmt, loc);
6844 gimple_seq_add_stmt_without_update (seq, stmt);
6846 return res;
6849 /* Build the call FN (ARG0, ARG1) with a result of type TYPE
6850 (or no result if TYPE is void) with location LOC,
6851 simplifying it first if possible. Returns the built
6852 expression value (or NULL_TREE if TYPE is void) and appends
6853 statements possibly defining it to SEQ. */
6855 tree
6856 gimple_build (gimple_seq *seq, location_t loc,
6857 enum built_in_function fn, tree type, tree arg0, tree arg1)
6859 tree res = gimple_simplify (fn, type, arg0, arg1, seq, gimple_build_valueize);
6860 if (!res)
6862 tree decl = builtin_decl_implicit (fn);
6863 gimple *stmt = gimple_build_call (decl, 2, arg0, arg1);
6864 if (!VOID_TYPE_P (type))
6866 res = create_tmp_reg_or_ssa_name (type);
6867 gimple_call_set_lhs (stmt, res);
6869 gimple_set_location (stmt, loc);
6870 gimple_seq_add_stmt_without_update (seq, stmt);
6872 return res;
6875 /* Build the call FN (ARG0, ARG1, ARG2) with a result of type TYPE
6876 (or no result if TYPE is void) with location LOC,
6877 simplifying it first if possible. Returns the built
6878 expression value (or NULL_TREE if TYPE is void) and appends
6879 statements possibly defining it to SEQ. */
6881 tree
6882 gimple_build (gimple_seq *seq, location_t loc,
6883 enum built_in_function fn, tree type,
6884 tree arg0, tree arg1, tree arg2)
6886 tree res = gimple_simplify (fn, type, arg0, arg1, arg2,
6887 seq, gimple_build_valueize);
6888 if (!res)
6890 tree decl = builtin_decl_implicit (fn);
6891 gimple *stmt = gimple_build_call (decl, 3, arg0, arg1, arg2);
6892 if (!VOID_TYPE_P (type))
6894 res = create_tmp_reg_or_ssa_name (type);
6895 gimple_call_set_lhs (stmt, res);
6897 gimple_set_location (stmt, loc);
6898 gimple_seq_add_stmt_without_update (seq, stmt);
6900 return res;
6903 /* Build the conversion (TYPE) OP with a result of type TYPE
6904 with location LOC if such conversion is neccesary in GIMPLE,
6905 simplifying it first.
6906 Returns the built expression value and appends
6907 statements possibly defining it to SEQ. */
6909 tree
6910 gimple_convert (gimple_seq *seq, location_t loc, tree type, tree op)
6912 if (useless_type_conversion_p (type, TREE_TYPE (op)))
6913 return op;
6914 return gimple_build (seq, loc, NOP_EXPR, type, op);
6917 /* Build the conversion (ptrofftype) OP with a result of a type
6918 compatible with ptrofftype with location LOC if such conversion
6919 is neccesary in GIMPLE, simplifying it first.
6920 Returns the built expression value and appends
6921 statements possibly defining it to SEQ. */
6923 tree
6924 gimple_convert_to_ptrofftype (gimple_seq *seq, location_t loc, tree op)
6926 if (ptrofftype_p (TREE_TYPE (op)))
6927 return op;
6928 return gimple_convert (seq, loc, sizetype, op);
6931 /* Return true if the result of assignment STMT is known to be non-negative.
6932 If the return value is based on the assumption that signed overflow is
6933 undefined, set *STRICT_OVERFLOW_P to true; otherwise, don't change
6934 *STRICT_OVERFLOW_P. DEPTH is the current nesting depth of the query. */
6936 static bool
6937 gimple_assign_nonnegative_warnv_p (gimple *stmt, bool *strict_overflow_p,
6938 int depth)
6940 enum tree_code code = gimple_assign_rhs_code (stmt);
6941 switch (get_gimple_rhs_class (code))
6943 case GIMPLE_UNARY_RHS:
6944 return tree_unary_nonnegative_warnv_p (gimple_assign_rhs_code (stmt),
6945 gimple_expr_type (stmt),
6946 gimple_assign_rhs1 (stmt),
6947 strict_overflow_p, depth);
6948 case GIMPLE_BINARY_RHS:
6949 return tree_binary_nonnegative_warnv_p (gimple_assign_rhs_code (stmt),
6950 gimple_expr_type (stmt),
6951 gimple_assign_rhs1 (stmt),
6952 gimple_assign_rhs2 (stmt),
6953 strict_overflow_p, depth);
6954 case GIMPLE_TERNARY_RHS:
6955 return false;
6956 case GIMPLE_SINGLE_RHS:
6957 return tree_single_nonnegative_warnv_p (gimple_assign_rhs1 (stmt),
6958 strict_overflow_p, depth);
6959 case GIMPLE_INVALID_RHS:
6960 break;
6962 gcc_unreachable ();
6965 /* Return true if return value of call STMT is known to be non-negative.
6966 If the return value is based on the assumption that signed overflow is
6967 undefined, set *STRICT_OVERFLOW_P to true; otherwise, don't change
6968 *STRICT_OVERFLOW_P. DEPTH is the current nesting depth of the query. */
6970 static bool
6971 gimple_call_nonnegative_warnv_p (gimple *stmt, bool *strict_overflow_p,
6972 int depth)
6974 tree arg0 = gimple_call_num_args (stmt) > 0 ?
6975 gimple_call_arg (stmt, 0) : NULL_TREE;
6976 tree arg1 = gimple_call_num_args (stmt) > 1 ?
6977 gimple_call_arg (stmt, 1) : NULL_TREE;
6979 return tree_call_nonnegative_warnv_p (gimple_expr_type (stmt),
6980 gimple_call_combined_fn (stmt),
6981 arg0,
6982 arg1,
6983 strict_overflow_p, depth);
6986 /* Return true if return value of call STMT is known to be non-negative.
6987 If the return value is based on the assumption that signed overflow is
6988 undefined, set *STRICT_OVERFLOW_P to true; otherwise, don't change
6989 *STRICT_OVERFLOW_P. DEPTH is the current nesting depth of the query. */
6991 static bool
6992 gimple_phi_nonnegative_warnv_p (gimple *stmt, bool *strict_overflow_p,
6993 int depth)
6995 for (unsigned i = 0; i < gimple_phi_num_args (stmt); ++i)
6997 tree arg = gimple_phi_arg_def (stmt, i);
6998 if (!tree_single_nonnegative_warnv_p (arg, strict_overflow_p, depth + 1))
6999 return false;
7001 return true;
7004 /* Return true if STMT is known to compute a non-negative value.
7005 If the return value is based on the assumption that signed overflow is
7006 undefined, set *STRICT_OVERFLOW_P to true; otherwise, don't change
7007 *STRICT_OVERFLOW_P. DEPTH is the current nesting depth of the query. */
7009 bool
7010 gimple_stmt_nonnegative_warnv_p (gimple *stmt, bool *strict_overflow_p,
7011 int depth)
7013 switch (gimple_code (stmt))
7015 case GIMPLE_ASSIGN:
7016 return gimple_assign_nonnegative_warnv_p (stmt, strict_overflow_p,
7017 depth);
7018 case GIMPLE_CALL:
7019 return gimple_call_nonnegative_warnv_p (stmt, strict_overflow_p,
7020 depth);
7021 case GIMPLE_PHI:
7022 return gimple_phi_nonnegative_warnv_p (stmt, strict_overflow_p,
7023 depth);
7024 default:
7025 return false;
7029 /* Return true if the floating-point value computed by assignment STMT
7030 is known to have an integer value. We also allow +Inf, -Inf and NaN
7031 to be considered integer values. Return false for signaling NaN.
7033 DEPTH is the current nesting depth of the query. */
7035 static bool
7036 gimple_assign_integer_valued_real_p (gimple *stmt, int depth)
7038 enum tree_code code = gimple_assign_rhs_code (stmt);
7039 switch (get_gimple_rhs_class (code))
7041 case GIMPLE_UNARY_RHS:
7042 return integer_valued_real_unary_p (gimple_assign_rhs_code (stmt),
7043 gimple_assign_rhs1 (stmt), depth);
7044 case GIMPLE_BINARY_RHS:
7045 return integer_valued_real_binary_p (gimple_assign_rhs_code (stmt),
7046 gimple_assign_rhs1 (stmt),
7047 gimple_assign_rhs2 (stmt), depth);
7048 case GIMPLE_TERNARY_RHS:
7049 return false;
7050 case GIMPLE_SINGLE_RHS:
7051 return integer_valued_real_single_p (gimple_assign_rhs1 (stmt), depth);
7052 case GIMPLE_INVALID_RHS:
7053 break;
7055 gcc_unreachable ();
7058 /* Return true if the floating-point value computed by call STMT is known
7059 to have an integer value. We also allow +Inf, -Inf and NaN to be
7060 considered integer values. Return false for signaling NaN.
7062 DEPTH is the current nesting depth of the query. */
7064 static bool
7065 gimple_call_integer_valued_real_p (gimple *stmt, int depth)
7067 tree arg0 = (gimple_call_num_args (stmt) > 0
7068 ? gimple_call_arg (stmt, 0)
7069 : NULL_TREE);
7070 tree arg1 = (gimple_call_num_args (stmt) > 1
7071 ? gimple_call_arg (stmt, 1)
7072 : NULL_TREE);
7073 return integer_valued_real_call_p (gimple_call_combined_fn (stmt),
7074 arg0, arg1, depth);
7077 /* Return true if the floating-point result of phi STMT is known to have
7078 an integer value. We also allow +Inf, -Inf and NaN to be considered
7079 integer values. Return false for signaling NaN.
7081 DEPTH is the current nesting depth of the query. */
7083 static bool
7084 gimple_phi_integer_valued_real_p (gimple *stmt, int depth)
7086 for (unsigned i = 0; i < gimple_phi_num_args (stmt); ++i)
7088 tree arg = gimple_phi_arg_def (stmt, i);
7089 if (!integer_valued_real_single_p (arg, depth + 1))
7090 return false;
7092 return true;
7095 /* Return true if the floating-point value computed by STMT is known
7096 to have an integer value. We also allow +Inf, -Inf and NaN to be
7097 considered integer values. Return false for signaling NaN.
7099 DEPTH is the current nesting depth of the query. */
7101 bool
7102 gimple_stmt_integer_valued_real_p (gimple *stmt, int depth)
7104 switch (gimple_code (stmt))
7106 case GIMPLE_ASSIGN:
7107 return gimple_assign_integer_valued_real_p (stmt, depth);
7108 case GIMPLE_CALL:
7109 return gimple_call_integer_valued_real_p (stmt, depth);
7110 case GIMPLE_PHI:
7111 return gimple_phi_integer_valued_real_p (stmt, depth);
7112 default:
7113 return false;