re PR c++/68464 (ICE in valid constexpr function: ../../src/gcc/tree.c:11497)
[platform/upstream/gcc.git] / gcc / cp / cp-gimplify.c
1 /* C++-specific tree lowering bits; see also c-gimplify.c and tree-gimple.c.
2
3    Copyright (C) 2002-2015 Free Software Foundation, Inc.
4    Contributed by Jason Merrill <jason@redhat.com>
5
6 This file is part of GCC.
7
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, or (at your option) any later
11 version.
12
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
16 for more details.
17
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING3.  If not see
20 <http://www.gnu.org/licenses/>.  */
21
22 #include "config.h"
23 #include "system.h"
24 #include "coretypes.h"
25 #include "target.h"
26 #include "basic-block.h"
27 #include "cp-tree.h"
28 #include "gimple.h"
29 #include "predict.h"
30 #include "stor-layout.h"
31 #include "tree-iterator.h"
32 #include "gimplify.h"
33 #include "c-family/c-ubsan.h"
34 #include "cilk.h"
35
36 /* Forward declarations.  */
37
38 static tree cp_genericize_r (tree *, int *, void *);
39 static tree cp_fold_r (tree *, int *, void *);
40 static void cp_genericize_tree (tree*);
41 static tree cp_fold (tree);
42
43 /* Local declarations.  */
44
45 enum bc_t { bc_break = 0, bc_continue = 1 };
46
47 /* Stack of labels which are targets for "break" or "continue",
48    linked through TREE_CHAIN.  */
49 static tree bc_label[2];
50
51 /* Begin a scope which can be exited by a break or continue statement.  BC
52    indicates which.
53
54    Just creates a label with location LOCATION and pushes it into the current
55    context.  */
56
57 static tree
58 begin_bc_block (enum bc_t bc, location_t location)
59 {
60   tree label = create_artificial_label (location);
61   DECL_CHAIN (label) = bc_label[bc];
62   bc_label[bc] = label;
63   if (bc == bc_break)
64     LABEL_DECL_BREAK (label) = true;
65   else
66     LABEL_DECL_CONTINUE (label) = true;
67   return label;
68 }
69
70 /* Finish a scope which can be exited by a break or continue statement.
71    LABEL was returned from the most recent call to begin_bc_block.  BLOCK is
72    an expression for the contents of the scope.
73
74    If we saw a break (or continue) in the scope, append a LABEL_EXPR to
75    BLOCK.  Otherwise, just forget the label.  */
76
77 static void
78 finish_bc_block (tree *block, enum bc_t bc, tree label)
79 {
80   gcc_assert (label == bc_label[bc]);
81
82   if (TREE_USED (label))
83     append_to_statement_list (build1 (LABEL_EXPR, void_type_node, label),
84                               block);
85
86   bc_label[bc] = DECL_CHAIN (label);
87   DECL_CHAIN (label) = NULL_TREE;
88 }
89
90 /* This function is a wrapper for cilk_gimplify_call_params_in_spawned_fn.
91    *EXPR_P can be a CALL_EXPR, INIT_EXPR, MODIFY_EXPR, AGGR_INIT_EXPR or
92    TARGET_EXPR.  *PRE_P and *POST_P are gimple sequences from the caller
93    of gimplify_cilk_spawn.  */
94
95 static void
96 cilk_cp_gimplify_call_params_in_spawned_fn (tree *expr_p, gimple_seq *pre_p,
97                                             gimple_seq *post_p)
98 {
99   int ii = 0;
100
101   cilk_gimplify_call_params_in_spawned_fn (expr_p, pre_p, post_p);  
102   if (TREE_CODE (*expr_p) == AGGR_INIT_EXPR)
103     for (ii = 0; ii < aggr_init_expr_nargs (*expr_p); ii++)
104       gimplify_expr (&AGGR_INIT_EXPR_ARG (*expr_p, ii), pre_p, post_p,
105                      is_gimple_reg, fb_rvalue);
106 }
107
108
109 /* Get the LABEL_EXPR to represent a break or continue statement
110    in the current block scope.  BC indicates which.  */
111
112 static tree
113 get_bc_label (enum bc_t bc)
114 {
115   tree label = bc_label[bc];
116
117   /* Mark the label used for finish_bc_block.  */
118   TREE_USED (label) = 1;
119   return label;
120 }
121
122 /* Genericize a TRY_BLOCK.  */
123
124 static void
125 genericize_try_block (tree *stmt_p)
126 {
127   tree body = TRY_STMTS (*stmt_p);
128   tree cleanup = TRY_HANDLERS (*stmt_p);
129
130   *stmt_p = build2 (TRY_CATCH_EXPR, void_type_node, body, cleanup);
131 }
132
133 /* Genericize a HANDLER by converting to a CATCH_EXPR.  */
134
135 static void
136 genericize_catch_block (tree *stmt_p)
137 {
138   tree type = HANDLER_TYPE (*stmt_p);
139   tree body = HANDLER_BODY (*stmt_p);
140
141   /* FIXME should the caught type go in TREE_TYPE?  */
142   *stmt_p = build2 (CATCH_EXPR, void_type_node, type, body);
143 }
144
145 /* A terser interface for building a representation of an exception
146    specification.  */
147
148 static tree
149 build_gimple_eh_filter_tree (tree body, tree allowed, tree failure)
150 {
151   tree t;
152
153   /* FIXME should the allowed types go in TREE_TYPE?  */
154   t = build2 (EH_FILTER_EXPR, void_type_node, allowed, NULL_TREE);
155   append_to_statement_list (failure, &EH_FILTER_FAILURE (t));
156
157   t = build2 (TRY_CATCH_EXPR, void_type_node, NULL_TREE, t);
158   append_to_statement_list (body, &TREE_OPERAND (t, 0));
159
160   return t;
161 }
162
163 /* Genericize an EH_SPEC_BLOCK by converting it to a
164    TRY_CATCH_EXPR/EH_FILTER_EXPR pair.  */
165
166 static void
167 genericize_eh_spec_block (tree *stmt_p)
168 {
169   tree body = EH_SPEC_STMTS (*stmt_p);
170   tree allowed = EH_SPEC_RAISES (*stmt_p);
171   tree failure = build_call_n (call_unexpected_node, 1, build_exc_ptr ());
172
173   *stmt_p = build_gimple_eh_filter_tree (body, allowed, failure);
174   TREE_NO_WARNING (*stmt_p) = true;
175   TREE_NO_WARNING (TREE_OPERAND (*stmt_p, 1)) = true;
176 }
177
178 /* Genericize an IF_STMT by turning it into a COND_EXPR.  */
179
180 static void
181 genericize_if_stmt (tree *stmt_p)
182 {
183   tree stmt, cond, then_, else_;
184   location_t locus = EXPR_LOCATION (*stmt_p);
185
186   stmt = *stmt_p;
187   cond = IF_COND (stmt);
188   then_ = THEN_CLAUSE (stmt);
189   else_ = ELSE_CLAUSE (stmt);
190
191   if (!then_)
192     then_ = build_empty_stmt (locus);
193   if (!else_)
194     else_ = build_empty_stmt (locus);
195
196   if (integer_nonzerop (cond) && !TREE_SIDE_EFFECTS (else_))
197     stmt = then_;
198   else if (integer_zerop (cond) && !TREE_SIDE_EFFECTS (then_))
199     stmt = else_;
200   else
201     stmt = build3 (COND_EXPR, void_type_node, cond, then_, else_);
202   if (!EXPR_HAS_LOCATION (stmt))
203     protected_set_expr_location (stmt, locus);
204   *stmt_p = stmt;
205 }
206
207 /* Build a generic representation of one of the C loop forms.  COND is the
208    loop condition or NULL_TREE.  BODY is the (possibly compound) statement
209    controlled by the loop.  INCR is the increment expression of a for-loop,
210    or NULL_TREE.  COND_IS_FIRST indicates whether the condition is
211    evaluated before the loop body as in while and for loops, or after the
212    loop body as in do-while loops.  */
213
214 static void
215 genericize_cp_loop (tree *stmt_p, location_t start_locus, tree cond, tree body,
216                     tree incr, bool cond_is_first, int *walk_subtrees,
217                     void *data)
218 {
219   tree blab, clab;
220   tree exit = NULL;
221   tree stmt_list = NULL;
222
223   blab = begin_bc_block (bc_break, start_locus);
224   clab = begin_bc_block (bc_continue, start_locus);
225
226   protected_set_expr_location (incr, start_locus);
227
228   cp_walk_tree (&cond, cp_genericize_r, data, NULL);
229   cp_walk_tree (&body, cp_genericize_r, data, NULL);
230   cp_walk_tree (&incr, cp_genericize_r, data, NULL);
231   *walk_subtrees = 0;
232
233   if (cond && TREE_CODE (cond) != INTEGER_CST)
234     {
235       /* If COND is constant, don't bother building an exit.  If it's false,
236          we won't build a loop.  If it's true, any exits are in the body.  */
237       location_t cloc = EXPR_LOC_OR_LOC (cond, start_locus);
238       exit = build1_loc (cloc, GOTO_EXPR, void_type_node,
239                          get_bc_label (bc_break));
240       exit = fold_build3_loc (cloc, COND_EXPR, void_type_node, cond,
241                               build_empty_stmt (cloc), exit);
242     }
243
244   if (exit && cond_is_first)
245     append_to_statement_list (exit, &stmt_list);
246   append_to_statement_list (body, &stmt_list);
247   finish_bc_block (&stmt_list, bc_continue, clab);
248   append_to_statement_list (incr, &stmt_list);
249   if (exit && !cond_is_first)
250     append_to_statement_list (exit, &stmt_list);
251
252   if (!stmt_list)
253     stmt_list = build_empty_stmt (start_locus);
254
255   tree loop;
256   if (cond && integer_zerop (cond))
257     {
258       if (cond_is_first)
259         loop = fold_build3_loc (start_locus, COND_EXPR,
260                                 void_type_node, cond, stmt_list,
261                                 build_empty_stmt (start_locus));
262       else
263         loop = stmt_list;
264     }
265   else
266     {
267       location_t loc = start_locus;
268       if (!cond || integer_nonzerop (cond))
269         loc = EXPR_LOCATION (expr_first (body));
270       if (loc == UNKNOWN_LOCATION)
271         loc = start_locus;
272       loop = build1_loc (loc, LOOP_EXPR, void_type_node, stmt_list);
273     }
274
275   stmt_list = NULL;
276   append_to_statement_list (loop, &stmt_list);
277   finish_bc_block (&stmt_list, bc_break, blab);
278   if (!stmt_list)
279     stmt_list = build_empty_stmt (start_locus);
280
281   *stmt_p = stmt_list;
282 }
283
284 /* Genericize a FOR_STMT node *STMT_P.  */
285
286 static void
287 genericize_for_stmt (tree *stmt_p, int *walk_subtrees, void *data)
288 {
289   tree stmt = *stmt_p;
290   tree expr = NULL;
291   tree loop;
292   tree init = FOR_INIT_STMT (stmt);
293
294   if (init)
295     {
296       cp_walk_tree (&init, cp_genericize_r, data, NULL);
297       append_to_statement_list (init, &expr);
298     }
299
300   genericize_cp_loop (&loop, EXPR_LOCATION (stmt), FOR_COND (stmt),
301                       FOR_BODY (stmt), FOR_EXPR (stmt), 1, walk_subtrees, data);
302   append_to_statement_list (loop, &expr);
303   if (expr == NULL_TREE)
304     expr = loop;
305   *stmt_p = expr;
306 }
307
308 /* Genericize a WHILE_STMT node *STMT_P.  */
309
310 static void
311 genericize_while_stmt (tree *stmt_p, int *walk_subtrees, void *data)
312 {
313   tree stmt = *stmt_p;
314   genericize_cp_loop (stmt_p, EXPR_LOCATION (stmt), WHILE_COND (stmt),
315                       WHILE_BODY (stmt), NULL_TREE, 1, walk_subtrees, data);
316 }
317
318 /* Genericize a DO_STMT node *STMT_P.  */
319
320 static void
321 genericize_do_stmt (tree *stmt_p, int *walk_subtrees, void *data)
322 {
323   tree stmt = *stmt_p;
324   genericize_cp_loop (stmt_p, EXPR_LOCATION (stmt), DO_COND (stmt),
325                       DO_BODY (stmt), NULL_TREE, 0, walk_subtrees, data);
326 }
327
328 /* Genericize a SWITCH_STMT node *STMT_P by turning it into a SWITCH_EXPR.  */
329
330 static void
331 genericize_switch_stmt (tree *stmt_p, int *walk_subtrees, void *data)
332 {
333   tree stmt = *stmt_p;
334   tree break_block, body, cond, type;
335   location_t stmt_locus = EXPR_LOCATION (stmt);
336
337   break_block = begin_bc_block (bc_break, stmt_locus);
338
339   body = SWITCH_STMT_BODY (stmt);
340   if (!body)
341     body = build_empty_stmt (stmt_locus);
342   cond = SWITCH_STMT_COND (stmt);
343   type = SWITCH_STMT_TYPE (stmt);
344
345   cp_walk_tree (&body, cp_genericize_r, data, NULL);
346   cp_walk_tree (&cond, cp_genericize_r, data, NULL);
347   cp_walk_tree (&type, cp_genericize_r, data, NULL);
348   *walk_subtrees = 0;
349
350   *stmt_p = build3_loc (stmt_locus, SWITCH_EXPR, type, cond, body, NULL_TREE);
351   finish_bc_block (stmt_p, bc_break, break_block);
352 }
353
354 /* Genericize a CONTINUE_STMT node *STMT_P.  */
355
356 static void
357 genericize_continue_stmt (tree *stmt_p)
358 {
359   tree stmt_list = NULL;
360   tree pred = build_predict_expr (PRED_CONTINUE, NOT_TAKEN);
361   tree label = get_bc_label (bc_continue);
362   location_t location = EXPR_LOCATION (*stmt_p);
363   tree jump = build1_loc (location, GOTO_EXPR, void_type_node, label);
364   append_to_statement_list (pred, &stmt_list);
365   append_to_statement_list (jump, &stmt_list);
366   *stmt_p = stmt_list;
367 }
368
369 /* Genericize a BREAK_STMT node *STMT_P.  */
370
371 static void
372 genericize_break_stmt (tree *stmt_p)
373 {
374   tree label = get_bc_label (bc_break);
375   location_t location = EXPR_LOCATION (*stmt_p);
376   *stmt_p = build1_loc (location, GOTO_EXPR, void_type_node, label);
377 }
378
379 /* Genericize a OMP_FOR node *STMT_P.  */
380
381 static void
382 genericize_omp_for_stmt (tree *stmt_p, int *walk_subtrees, void *data)
383 {
384   tree stmt = *stmt_p;
385   location_t locus = EXPR_LOCATION (stmt);
386   tree clab = begin_bc_block (bc_continue, locus);
387
388   cp_walk_tree (&OMP_FOR_BODY (stmt), cp_genericize_r, data, NULL);
389   cp_walk_tree (&OMP_FOR_CLAUSES (stmt), cp_genericize_r, data, NULL);
390   cp_walk_tree (&OMP_FOR_INIT (stmt), cp_genericize_r, data, NULL);
391   cp_walk_tree (&OMP_FOR_COND (stmt), cp_genericize_r, data, NULL);
392   cp_walk_tree (&OMP_FOR_INCR (stmt), cp_genericize_r, data, NULL);
393   cp_walk_tree (&OMP_FOR_PRE_BODY (stmt), cp_genericize_r, data, NULL);
394   *walk_subtrees = 0;
395
396   finish_bc_block (&OMP_FOR_BODY (stmt), bc_continue, clab);
397 }
398
399 /* Hook into the middle of gimplifying an OMP_FOR node.  */
400
401 static enum gimplify_status
402 cp_gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
403 {
404   tree for_stmt = *expr_p;
405   gimple_seq seq = NULL;
406
407   /* Protect ourselves from recursion.  */
408   if (OMP_FOR_GIMPLIFYING_P (for_stmt))
409     return GS_UNHANDLED;
410   OMP_FOR_GIMPLIFYING_P (for_stmt) = 1;
411
412   gimplify_and_add (for_stmt, &seq);
413   gimple_seq_add_seq (pre_p, seq);
414
415   OMP_FOR_GIMPLIFYING_P (for_stmt) = 0;
416
417   return GS_ALL_DONE;
418 }
419
420 /*  Gimplify an EXPR_STMT node.  */
421
422 static void
423 gimplify_expr_stmt (tree *stmt_p)
424 {
425   tree stmt = EXPR_STMT_EXPR (*stmt_p);
426
427   if (stmt == error_mark_node)
428     stmt = NULL;
429
430   /* Gimplification of a statement expression will nullify the
431      statement if all its side effects are moved to *PRE_P and *POST_P.
432
433      In this case we will not want to emit the gimplified statement.
434      However, we may still want to emit a warning, so we do that before
435      gimplification.  */
436   if (stmt && warn_unused_value)
437     {
438       if (!TREE_SIDE_EFFECTS (stmt))
439         {
440           if (!IS_EMPTY_STMT (stmt)
441               && !VOID_TYPE_P (TREE_TYPE (stmt))
442               && !TREE_NO_WARNING (stmt))
443             warning (OPT_Wunused_value, "statement with no effect");
444         }
445       else
446         warn_if_unused_value (stmt, input_location);
447     }
448
449   if (stmt == NULL_TREE)
450     stmt = alloc_stmt_list ();
451
452   *stmt_p = stmt;
453 }
454
455 /* Gimplify initialization from an AGGR_INIT_EXPR.  */
456
457 static void
458 cp_gimplify_init_expr (tree *expr_p)
459 {
460   tree from = TREE_OPERAND (*expr_p, 1);
461   tree to = TREE_OPERAND (*expr_p, 0);
462   tree t;
463
464   /* What about code that pulls out the temp and uses it elsewhere?  I
465      think that such code never uses the TARGET_EXPR as an initializer.  If
466      I'm wrong, we'll abort because the temp won't have any RTL.  In that
467      case, I guess we'll need to replace references somehow.  */
468   if (TREE_CODE (from) == TARGET_EXPR)
469     from = TARGET_EXPR_INITIAL (from);
470
471   /* Look through any COMPOUND_EXPRs, since build_compound_expr pushes them
472      inside the TARGET_EXPR.  */
473   for (t = from; t; )
474     {
475       tree sub = TREE_CODE (t) == COMPOUND_EXPR ? TREE_OPERAND (t, 0) : t;
476
477       /* If we are initializing from an AGGR_INIT_EXPR, drop the INIT_EXPR and
478          replace the slot operand with our target.
479
480          Should we add a target parm to gimplify_expr instead?  No, as in this
481          case we want to replace the INIT_EXPR.  */
482       if (TREE_CODE (sub) == AGGR_INIT_EXPR
483           || TREE_CODE (sub) == VEC_INIT_EXPR)
484         {
485           if (TREE_CODE (sub) == AGGR_INIT_EXPR)
486             AGGR_INIT_EXPR_SLOT (sub) = to;
487           else
488             VEC_INIT_EXPR_SLOT (sub) = to;
489           *expr_p = from;
490
491           /* The initialization is now a side-effect, so the container can
492              become void.  */
493           if (from != sub)
494             TREE_TYPE (from) = void_type_node;
495         }
496
497       if (cxx_dialect >= cxx14 && TREE_CODE (sub) == CONSTRUCTOR)
498         /* Handle aggregate NSDMI.  */
499         replace_placeholders (sub, to);
500
501       if (t == sub)
502         break;
503       else
504         t = TREE_OPERAND (t, 1);
505     }
506
507 }
508
509 /* Gimplify a MUST_NOT_THROW_EXPR.  */
510
511 static enum gimplify_status
512 gimplify_must_not_throw_expr (tree *expr_p, gimple_seq *pre_p)
513 {
514   tree stmt = *expr_p;
515   tree temp = voidify_wrapper_expr (stmt, NULL);
516   tree body = TREE_OPERAND (stmt, 0);
517   gimple_seq try_ = NULL;
518   gimple_seq catch_ = NULL;
519   gimple *mnt;
520
521   gimplify_and_add (body, &try_);
522   mnt = gimple_build_eh_must_not_throw (terminate_node);
523   gimple_seq_add_stmt_without_update (&catch_, mnt);
524   mnt = gimple_build_try (try_, catch_, GIMPLE_TRY_CATCH);
525
526   gimple_seq_add_stmt_without_update (pre_p, mnt);
527   if (temp)
528     {
529       *expr_p = temp;
530       return GS_OK;
531     }
532
533   *expr_p = NULL;
534   return GS_ALL_DONE;
535 }
536
537 /* Return TRUE if an operand (OP) of a given TYPE being copied is
538    really just an empty class copy.
539
540    Check that the operand has a simple form so that TARGET_EXPRs and
541    non-empty CONSTRUCTORs get reduced properly, and we leave the
542    return slot optimization alone because it isn't a copy.  */
543
544 static bool
545 simple_empty_class_p (tree type, tree op)
546 {
547   return
548     ((TREE_CODE (op) == COMPOUND_EXPR
549       && simple_empty_class_p (type, TREE_OPERAND (op, 1)))
550      || is_gimple_lvalue (op)
551      || INDIRECT_REF_P (op)
552      || (TREE_CODE (op) == CONSTRUCTOR
553          && CONSTRUCTOR_NELTS (op) == 0
554          && !TREE_CLOBBER_P (op))
555      || (TREE_CODE (op) == CALL_EXPR
556          && !CALL_EXPR_RETURN_SLOT_OPT (op)))
557     && is_really_empty_class (type);
558 }
559
560 /* Do C++-specific gimplification.  Args are as for gimplify_expr.  */
561
562 int
563 cp_gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
564 {
565   int saved_stmts_are_full_exprs_p = 0;
566   enum tree_code code = TREE_CODE (*expr_p);
567   enum gimplify_status ret;
568
569   if (STATEMENT_CODE_P (code))
570     {
571       saved_stmts_are_full_exprs_p = stmts_are_full_exprs_p ();
572       current_stmt_tree ()->stmts_are_full_exprs_p
573         = STMT_IS_FULL_EXPR_P (*expr_p);
574     }
575
576   switch (code)
577     {
578     case PTRMEM_CST:
579       *expr_p = cplus_expand_constant (*expr_p);
580       ret = GS_OK;
581       break;
582
583     case AGGR_INIT_EXPR:
584       simplify_aggr_init_expr (expr_p);
585       ret = GS_OK;
586       break;
587
588     case VEC_INIT_EXPR:
589       {
590         location_t loc = input_location;
591         tree init = VEC_INIT_EXPR_INIT (*expr_p);
592         int from_array = (init && TREE_CODE (TREE_TYPE (init)) == ARRAY_TYPE);
593         gcc_assert (EXPR_HAS_LOCATION (*expr_p));
594         input_location = EXPR_LOCATION (*expr_p);
595         *expr_p = build_vec_init (VEC_INIT_EXPR_SLOT (*expr_p), NULL_TREE,
596                                   init, VEC_INIT_EXPR_VALUE_INIT (*expr_p),
597                                   from_array,
598                                   tf_warning_or_error);
599         cp_genericize_tree (expr_p);
600         ret = GS_OK;
601         input_location = loc;
602       }
603       break;
604
605     case THROW_EXPR:
606       /* FIXME communicate throw type to back end, probably by moving
607          THROW_EXPR into ../tree.def.  */
608       *expr_p = TREE_OPERAND (*expr_p, 0);
609       ret = GS_OK;
610       break;
611
612     case MUST_NOT_THROW_EXPR:
613       ret = gimplify_must_not_throw_expr (expr_p, pre_p);
614       break;
615
616       /* We used to do this for MODIFY_EXPR as well, but that's unsafe; the
617          LHS of an assignment might also be involved in the RHS, as in bug
618          25979.  */
619     case INIT_EXPR:
620       if (fn_contains_cilk_spawn_p (cfun)
621           && cilk_detect_spawn_and_unwrap (expr_p))
622         {
623           cilk_cp_gimplify_call_params_in_spawned_fn (expr_p, pre_p, post_p);
624           return (enum gimplify_status) gimplify_cilk_spawn (expr_p);
625         }
626       if (seen_error ())
627         return GS_ERROR;
628
629       cp_gimplify_init_expr (expr_p);
630       if (TREE_CODE (*expr_p) != INIT_EXPR)
631         return GS_OK;
632       /* Otherwise fall through.  */
633     case MODIFY_EXPR:
634     modify_expr_case:
635       {
636         if (fn_contains_cilk_spawn_p (cfun)
637             && cilk_detect_spawn_and_unwrap (expr_p)
638             && !seen_error ())
639           {
640             cilk_cp_gimplify_call_params_in_spawned_fn (expr_p, pre_p, post_p);
641             return (enum gimplify_status) gimplify_cilk_spawn (expr_p);
642           }
643         /* If the back end isn't clever enough to know that the lhs and rhs
644            types are the same, add an explicit conversion.  */
645         tree op0 = TREE_OPERAND (*expr_p, 0);
646         tree op1 = TREE_OPERAND (*expr_p, 1);
647
648         if (!error_operand_p (op0)
649             && !error_operand_p (op1)
650             && (TYPE_STRUCTURAL_EQUALITY_P (TREE_TYPE (op0))
651                 || TYPE_STRUCTURAL_EQUALITY_P (TREE_TYPE (op1)))
652             && !useless_type_conversion_p (TREE_TYPE (op1), TREE_TYPE (op0)))
653           TREE_OPERAND (*expr_p, 1) = build1 (VIEW_CONVERT_EXPR,
654                                               TREE_TYPE (op0), op1);
655
656         else if (simple_empty_class_p (TREE_TYPE (op0), op1))
657           {
658             /* Remove any copies of empty classes.  Also drop volatile
659                variables on the RHS to avoid infinite recursion from
660                gimplify_expr trying to load the value.  */
661             gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
662                            is_gimple_lvalue, fb_lvalue);
663             if (TREE_SIDE_EFFECTS (op1))
664               {
665                 if (TREE_THIS_VOLATILE (op1)
666                     && (REFERENCE_CLASS_P (op1) || DECL_P (op1)))
667                   op1 = build_fold_addr_expr (op1);
668
669                 gimplify_and_add (op1, pre_p);
670               }
671             *expr_p = TREE_OPERAND (*expr_p, 0);
672           }
673       }
674       ret = GS_OK;
675       break;
676
677     case EMPTY_CLASS_EXPR:
678       /* We create an empty CONSTRUCTOR with RECORD_TYPE.  */
679       *expr_p = build_constructor (TREE_TYPE (*expr_p), NULL);
680       ret = GS_OK;
681       break;
682
683     case BASELINK:
684       *expr_p = BASELINK_FUNCTIONS (*expr_p);
685       ret = GS_OK;
686       break;
687
688     case TRY_BLOCK:
689       genericize_try_block (expr_p);
690       ret = GS_OK;
691       break;
692
693     case HANDLER:
694       genericize_catch_block (expr_p);
695       ret = GS_OK;
696       break;
697
698     case EH_SPEC_BLOCK:
699       genericize_eh_spec_block (expr_p);
700       ret = GS_OK;
701       break;
702
703     case USING_STMT:
704       gcc_unreachable ();
705
706     case FOR_STMT:
707     case WHILE_STMT:
708     case DO_STMT:
709     case SWITCH_STMT:
710     case CONTINUE_STMT:
711     case BREAK_STMT:
712       gcc_unreachable ();
713
714     case OMP_FOR:
715     case OMP_SIMD:
716     case OMP_DISTRIBUTE:
717     case OMP_TASKLOOP:
718       ret = cp_gimplify_omp_for (expr_p, pre_p);
719       break;
720
721     case EXPR_STMT:
722       gimplify_expr_stmt (expr_p);
723       ret = GS_OK;
724       break;
725
726     case UNARY_PLUS_EXPR:
727       {
728         tree arg = TREE_OPERAND (*expr_p, 0);
729         tree type = TREE_TYPE (*expr_p);
730         *expr_p = (TREE_TYPE (arg) != type) ? fold_convert (type, arg)
731                                             : arg;
732         ret = GS_OK;
733       }
734       break;
735
736     case CILK_SPAWN_STMT:
737       gcc_assert(fn_contains_cilk_spawn_p (cfun)
738                  && cilk_detect_spawn_and_unwrap (expr_p));
739
740       if (!seen_error ())
741         {
742           cilk_cp_gimplify_call_params_in_spawned_fn (expr_p, pre_p, post_p);
743           return (enum gimplify_status) gimplify_cilk_spawn (expr_p);
744         }
745       return GS_ERROR;
746
747     case CALL_EXPR:
748       if (fn_contains_cilk_spawn_p (cfun)
749           && cilk_detect_spawn_and_unwrap (expr_p)
750           && !seen_error ())
751         {
752           cilk_cp_gimplify_call_params_in_spawned_fn (expr_p, pre_p, post_p);
753           return (enum gimplify_status) gimplify_cilk_spawn (expr_p);
754         }
755       /* DR 1030 says that we need to evaluate the elements of an
756          initializer-list in forward order even when it's used as arguments to
757          a constructor.  So if the target wants to evaluate them in reverse
758          order and there's more than one argument other than 'this', gimplify
759          them in order.  */
760       ret = GS_OK;
761       if (PUSH_ARGS_REVERSED && CALL_EXPR_LIST_INIT_P (*expr_p)
762           && call_expr_nargs (*expr_p) > 2)
763         {
764           int nargs = call_expr_nargs (*expr_p);
765           location_t loc = EXPR_LOC_OR_LOC (*expr_p, input_location);
766           for (int i = 1; i < nargs; ++i)
767             {
768               enum gimplify_status t
769                 = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p, loc);
770               if (t == GS_ERROR)
771                 ret = GS_ERROR;
772             }
773         }
774       break;
775
776     case RETURN_EXPR:
777       if (TREE_OPERAND (*expr_p, 0)
778           && (TREE_CODE (TREE_OPERAND (*expr_p, 0)) == INIT_EXPR
779               || TREE_CODE (TREE_OPERAND (*expr_p, 0)) == MODIFY_EXPR))
780         {
781           expr_p = &TREE_OPERAND (*expr_p, 0);
782           code = TREE_CODE (*expr_p);
783           /* Avoid going through the INIT_EXPR case, which can
784              degrade INIT_EXPRs into AGGR_INIT_EXPRs.  */
785           goto modify_expr_case;
786         }
787       /* Fall through.  */
788
789     default:
790       ret = (enum gimplify_status) c_gimplify_expr (expr_p, pre_p, post_p);
791       break;
792     }
793
794   /* Restore saved state.  */
795   if (STATEMENT_CODE_P (code))
796     current_stmt_tree ()->stmts_are_full_exprs_p
797       = saved_stmts_are_full_exprs_p;
798
799   return ret;
800 }
801
802 static inline bool
803 is_invisiref_parm (const_tree t)
804 {
805   return ((TREE_CODE (t) == PARM_DECL || TREE_CODE (t) == RESULT_DECL)
806           && DECL_BY_REFERENCE (t));
807 }
808
809 /* Return true if the uid in both int tree maps are equal.  */
810
811 bool
812 cxx_int_tree_map_hasher::equal (cxx_int_tree_map *a, cxx_int_tree_map *b)
813 {
814   return (a->uid == b->uid);
815 }
816
817 /* Hash a UID in a cxx_int_tree_map.  */
818
819 unsigned int
820 cxx_int_tree_map_hasher::hash (cxx_int_tree_map *item)
821 {
822   return item->uid;
823 }
824
825 /* A stable comparison routine for use with splay trees and DECLs.  */
826
827 static int
828 splay_tree_compare_decl_uid (splay_tree_key xa, splay_tree_key xb)
829 {
830   tree a = (tree) xa;
831   tree b = (tree) xb;
832
833   return DECL_UID (a) - DECL_UID (b);
834 }
835
836 /* OpenMP context during genericization.  */
837
838 struct cp_genericize_omp_taskreg
839 {
840   bool is_parallel;
841   bool default_shared;
842   struct cp_genericize_omp_taskreg *outer;
843   splay_tree variables;
844 };
845
846 /* Return true if genericization should try to determine if
847    DECL is firstprivate or shared within task regions.  */
848
849 static bool
850 omp_var_to_track (tree decl)
851 {
852   tree type = TREE_TYPE (decl);
853   if (is_invisiref_parm (decl))
854     type = TREE_TYPE (type);
855   while (TREE_CODE (type) == ARRAY_TYPE)
856     type = TREE_TYPE (type);
857   if (type == error_mark_node || !CLASS_TYPE_P (type))
858     return false;
859   if (VAR_P (decl) && CP_DECL_THREAD_LOCAL_P (decl))
860     return false;
861   if (cxx_omp_predetermined_sharing (decl) != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
862     return false;
863   return true;
864 }
865
866 /* Note DECL use in OpenMP region OMP_CTX during genericization.  */
867
868 static void
869 omp_cxx_notice_variable (struct cp_genericize_omp_taskreg *omp_ctx, tree decl)
870 {
871   splay_tree_node n = splay_tree_lookup (omp_ctx->variables,
872                                          (splay_tree_key) decl);
873   if (n == NULL)
874     {
875       int flags = OMP_CLAUSE_DEFAULT_SHARED;
876       if (omp_ctx->outer)
877         omp_cxx_notice_variable (omp_ctx->outer, decl);
878       if (!omp_ctx->default_shared)
879         {
880           struct cp_genericize_omp_taskreg *octx;
881
882           for (octx = omp_ctx->outer; octx; octx = octx->outer)
883             {
884               n = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
885               if (n && n->value != OMP_CLAUSE_DEFAULT_SHARED)
886                 {
887                   flags = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
888                   break;
889                 }
890               if (octx->is_parallel)
891                 break;
892             }
893           if (octx == NULL
894               && (TREE_CODE (decl) == PARM_DECL
895                   || (!(TREE_STATIC (decl) || DECL_EXTERNAL (decl))
896                       && DECL_CONTEXT (decl) == current_function_decl)))
897             flags = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
898           if (flags == OMP_CLAUSE_DEFAULT_FIRSTPRIVATE)
899             {
900               /* DECL is implicitly determined firstprivate in
901                  the current task construct.  Ensure copy ctor and
902                  dtor are instantiated, because during gimplification
903                  it will be already too late.  */
904               tree type = TREE_TYPE (decl);
905               if (is_invisiref_parm (decl))
906                 type = TREE_TYPE (type);
907               while (TREE_CODE (type) == ARRAY_TYPE)
908                 type = TREE_TYPE (type);
909               get_copy_ctor (type, tf_none);
910               get_dtor (type, tf_none);
911             }
912         }
913       splay_tree_insert (omp_ctx->variables, (splay_tree_key) decl, flags);
914     }
915 }
916
917 /* Genericization context.  */
918
919 struct cp_genericize_data
920 {
921   hash_set<tree> *p_set;
922   vec<tree> bind_expr_stack;
923   struct cp_genericize_omp_taskreg *omp_ctx;
924   tree try_block;
925   bool no_sanitize_p;
926 };
927
928 /* Perform any pre-gimplification folding of C++ front end trees to
929    GENERIC.
930    Note:  The folding of none-omp cases is something to move into
931      the middle-end.  As for now we have most foldings only on GENERIC
932      in fold-const, we need to perform this before transformation to
933      GIMPLE-form.  */
934
935 static tree
936 cp_fold_r (tree *stmt_p, int *walk_subtrees, void *data)
937 {
938   tree stmt;
939   enum tree_code code;
940
941   *stmt_p = stmt = cp_fold (*stmt_p);
942
943   code = TREE_CODE (stmt);
944   if (code == OMP_FOR || code == OMP_SIMD || code == OMP_DISTRIBUTE
945       || code == OMP_TASKLOOP || code == CILK_FOR || code == CILK_SIMD
946       || code == OACC_LOOP)
947     {
948       tree x;
949       int i, n;
950
951       cp_walk_tree (&OMP_FOR_BODY (stmt), cp_fold_r, data, NULL);
952       cp_walk_tree (&OMP_FOR_CLAUSES (stmt), cp_fold_r, data, NULL);
953       cp_walk_tree (&OMP_FOR_INIT (stmt), cp_fold_r, data, NULL);
954       x = OMP_FOR_COND (stmt);
955       if (x && TREE_CODE_CLASS (TREE_CODE (x)) == tcc_comparison)
956         {
957           cp_walk_tree (&TREE_OPERAND (x, 0), cp_fold_r, data, NULL);
958           cp_walk_tree (&TREE_OPERAND (x, 1), cp_fold_r, data, NULL);
959         }
960       else if (x && TREE_CODE (x) == TREE_VEC)
961         {
962           n = TREE_VEC_LENGTH (x);
963           for (i = 0; i < n; i++)
964             {
965               tree o = TREE_VEC_ELT (x, i);
966               if (o && TREE_CODE_CLASS (TREE_CODE (o)) == tcc_comparison)
967                 cp_walk_tree (&TREE_OPERAND (o, 1), cp_fold_r, data, NULL);
968             }
969         }
970       x = OMP_FOR_INCR (stmt);
971       if (x && TREE_CODE (x) == TREE_VEC)
972         {
973           n = TREE_VEC_LENGTH (x);
974           for (i = 0; i < n; i++)
975             {
976               tree o = TREE_VEC_ELT (x, i);
977               if (o && TREE_CODE (o) == MODIFY_EXPR)
978                 o = TREE_OPERAND (o, 1);
979               if (o && (TREE_CODE (o) == PLUS_EXPR || TREE_CODE (o) == MINUS_EXPR
980                         || TREE_CODE (o) == POINTER_PLUS_EXPR))
981                 {
982                   cp_walk_tree (&TREE_OPERAND (o, 0), cp_fold_r, data, NULL);
983                   cp_walk_tree (&TREE_OPERAND (o, 1), cp_fold_r, data, NULL);
984                 }
985             }
986         }
987       cp_walk_tree (&OMP_FOR_PRE_BODY (stmt), cp_fold_r, data, NULL);
988       *walk_subtrees = 0;
989     }
990
991   return NULL;
992 }
993
994 /* Fold ALL the trees!  FIXME we should be able to remove this, but
995    apparently that still causes optimization regressions.  */
996
997 void
998 cp_fold_function (tree fndecl)
999 {
1000   cp_walk_tree (&DECL_SAVED_TREE (fndecl), cp_fold_r, NULL, NULL);
1001 }
1002
1003 /* Perform any pre-gimplification lowering of C++ front end trees to
1004    GENERIC.  */
1005
1006 static tree
1007 cp_genericize_r (tree *stmt_p, int *walk_subtrees, void *data)
1008 {
1009   tree stmt = *stmt_p;
1010   struct cp_genericize_data *wtd = (struct cp_genericize_data *) data;
1011   hash_set<tree> *p_set = wtd->p_set;
1012
1013   /* If in an OpenMP context, note var uses.  */
1014   if (__builtin_expect (wtd->omp_ctx != NULL, 0)
1015       && (VAR_P (stmt)
1016           || TREE_CODE (stmt) == PARM_DECL
1017           || TREE_CODE (stmt) == RESULT_DECL)
1018       && omp_var_to_track (stmt))
1019     omp_cxx_notice_variable (wtd->omp_ctx, stmt);
1020
1021   if (is_invisiref_parm (stmt)
1022       /* Don't dereference parms in a thunk, pass the references through. */
1023       && !(DECL_THUNK_P (current_function_decl)
1024            && TREE_CODE (stmt) == PARM_DECL))
1025     {
1026       *stmt_p = convert_from_reference (stmt);
1027       *walk_subtrees = 0;
1028       return NULL;
1029     }
1030
1031   /* Map block scope extern declarations to visible declarations with the
1032      same name and type in outer scopes if any.  */
1033   if (cp_function_chain->extern_decl_map
1034       && VAR_OR_FUNCTION_DECL_P (stmt)
1035       && DECL_EXTERNAL (stmt))
1036     {
1037       struct cxx_int_tree_map *h, in;
1038       in.uid = DECL_UID (stmt);
1039       h = cp_function_chain->extern_decl_map->find_with_hash (&in, in.uid);
1040       if (h)
1041         {
1042           *stmt_p = h->to;
1043           *walk_subtrees = 0;
1044           return NULL;
1045         }
1046     }
1047
1048   /* Other than invisiref parms, don't walk the same tree twice.  */
1049   if (p_set->contains (stmt))
1050     {
1051       *walk_subtrees = 0;
1052       return NULL_TREE;
1053     }
1054
1055   if (TREE_CODE (stmt) == ADDR_EXPR
1056       && is_invisiref_parm (TREE_OPERAND (stmt, 0)))
1057     {
1058       /* If in an OpenMP context, note var uses.  */
1059       if (__builtin_expect (wtd->omp_ctx != NULL, 0)
1060           && omp_var_to_track (TREE_OPERAND (stmt, 0)))
1061         omp_cxx_notice_variable (wtd->omp_ctx, TREE_OPERAND (stmt, 0));
1062       *stmt_p = fold_convert (TREE_TYPE (stmt), TREE_OPERAND (stmt, 0));
1063       *walk_subtrees = 0;
1064     }
1065   else if (TREE_CODE (stmt) == RETURN_EXPR
1066            && TREE_OPERAND (stmt, 0)
1067            && is_invisiref_parm (TREE_OPERAND (stmt, 0)))
1068     /* Don't dereference an invisiref RESULT_DECL inside a RETURN_EXPR.  */
1069     *walk_subtrees = 0;
1070   else if (TREE_CODE (stmt) == OMP_CLAUSE)
1071     switch (OMP_CLAUSE_CODE (stmt))
1072       {
1073       case OMP_CLAUSE_LASTPRIVATE:
1074         /* Don't dereference an invisiref in OpenMP clauses.  */
1075         if (is_invisiref_parm (OMP_CLAUSE_DECL (stmt)))
1076           {
1077             *walk_subtrees = 0;
1078             if (OMP_CLAUSE_LASTPRIVATE_STMT (stmt))
1079               cp_walk_tree (&OMP_CLAUSE_LASTPRIVATE_STMT (stmt),
1080                             cp_genericize_r, data, NULL);
1081           }
1082         break;
1083       case OMP_CLAUSE_PRIVATE:
1084         /* Don't dereference an invisiref in OpenMP clauses.  */
1085         if (is_invisiref_parm (OMP_CLAUSE_DECL (stmt)))
1086           *walk_subtrees = 0;
1087         else if (wtd->omp_ctx != NULL)
1088           {
1089             /* Private clause doesn't cause any references to the
1090                var in outer contexts, avoid calling
1091                omp_cxx_notice_variable for it.  */
1092             struct cp_genericize_omp_taskreg *old = wtd->omp_ctx;
1093             wtd->omp_ctx = NULL;
1094             cp_walk_tree (&OMP_CLAUSE_DECL (stmt), cp_genericize_r,
1095                           data, NULL);
1096             wtd->omp_ctx = old;
1097             *walk_subtrees = 0;
1098           }
1099         break;
1100       case OMP_CLAUSE_SHARED:
1101       case OMP_CLAUSE_FIRSTPRIVATE:
1102       case OMP_CLAUSE_COPYIN:
1103       case OMP_CLAUSE_COPYPRIVATE:
1104         /* Don't dereference an invisiref in OpenMP clauses.  */
1105         if (is_invisiref_parm (OMP_CLAUSE_DECL (stmt)))
1106           *walk_subtrees = 0;
1107         break;
1108       case OMP_CLAUSE_REDUCTION:
1109         /* Don't dereference an invisiref in reduction clause's
1110            OMP_CLAUSE_DECL either.  OMP_CLAUSE_REDUCTION_{INIT,MERGE}
1111            still needs to be genericized.  */
1112         if (is_invisiref_parm (OMP_CLAUSE_DECL (stmt)))
1113           {
1114             *walk_subtrees = 0;
1115             if (OMP_CLAUSE_REDUCTION_INIT (stmt))
1116               cp_walk_tree (&OMP_CLAUSE_REDUCTION_INIT (stmt),
1117                             cp_genericize_r, data, NULL);
1118             if (OMP_CLAUSE_REDUCTION_MERGE (stmt))
1119               cp_walk_tree (&OMP_CLAUSE_REDUCTION_MERGE (stmt),
1120                             cp_genericize_r, data, NULL);
1121           }
1122         break;
1123       default:
1124         break;
1125       }
1126   else if (IS_TYPE_OR_DECL_P (stmt))
1127     *walk_subtrees = 0;
1128
1129   /* Due to the way voidify_wrapper_expr is written, we don't get a chance
1130      to lower this construct before scanning it, so we need to lower these
1131      before doing anything else.  */
1132   else if (TREE_CODE (stmt) == CLEANUP_STMT)
1133     *stmt_p = build2_loc (EXPR_LOCATION (stmt),
1134                           CLEANUP_EH_ONLY (stmt) ? TRY_CATCH_EXPR
1135                                                  : TRY_FINALLY_EXPR,
1136                           void_type_node,
1137                           CLEANUP_BODY (stmt),
1138                           CLEANUP_EXPR (stmt));
1139
1140   else if (TREE_CODE (stmt) == IF_STMT)
1141     {
1142       genericize_if_stmt (stmt_p);
1143       /* *stmt_p has changed, tail recurse to handle it again.  */
1144       return cp_genericize_r (stmt_p, walk_subtrees, data);
1145     }
1146
1147   /* COND_EXPR might have incompatible types in branches if one or both
1148      arms are bitfields.  Fix it up now.  */
1149   else if (TREE_CODE (stmt) == COND_EXPR)
1150     {
1151       tree type_left
1152         = (TREE_OPERAND (stmt, 1)
1153            ? is_bitfield_expr_with_lowered_type (TREE_OPERAND (stmt, 1))
1154            : NULL_TREE);
1155       tree type_right
1156         = (TREE_OPERAND (stmt, 2)
1157            ? is_bitfield_expr_with_lowered_type (TREE_OPERAND (stmt, 2))
1158            : NULL_TREE);
1159       if (type_left
1160           && !useless_type_conversion_p (TREE_TYPE (stmt),
1161                                          TREE_TYPE (TREE_OPERAND (stmt, 1))))
1162         {
1163           TREE_OPERAND (stmt, 1)
1164             = fold_convert (type_left, TREE_OPERAND (stmt, 1));
1165           gcc_assert (useless_type_conversion_p (TREE_TYPE (stmt),
1166                                                  type_left));
1167         }
1168       if (type_right
1169           && !useless_type_conversion_p (TREE_TYPE (stmt),
1170                                          TREE_TYPE (TREE_OPERAND (stmt, 2))))
1171         {
1172           TREE_OPERAND (stmt, 2)
1173             = fold_convert (type_right, TREE_OPERAND (stmt, 2));
1174           gcc_assert (useless_type_conversion_p (TREE_TYPE (stmt),
1175                                                  type_right));
1176         }
1177     }
1178
1179   else if (TREE_CODE (stmt) == BIND_EXPR)
1180     {
1181       if (__builtin_expect (wtd->omp_ctx != NULL, 0))
1182         {
1183           tree decl;
1184           for (decl = BIND_EXPR_VARS (stmt); decl; decl = DECL_CHAIN (decl))
1185             if (VAR_P (decl)
1186                 && !DECL_EXTERNAL (decl)
1187                 && omp_var_to_track (decl))
1188               {
1189                 splay_tree_node n
1190                   = splay_tree_lookup (wtd->omp_ctx->variables,
1191                                        (splay_tree_key) decl);
1192                 if (n == NULL)
1193                   splay_tree_insert (wtd->omp_ctx->variables,
1194                                      (splay_tree_key) decl,
1195                                      TREE_STATIC (decl)
1196                                      ? OMP_CLAUSE_DEFAULT_SHARED
1197                                      : OMP_CLAUSE_DEFAULT_PRIVATE);
1198               }
1199         }
1200       if (flag_sanitize
1201           & (SANITIZE_NULL | SANITIZE_ALIGNMENT | SANITIZE_VPTR))
1202         {
1203           /* The point here is to not sanitize static initializers.  */
1204           bool no_sanitize_p = wtd->no_sanitize_p;
1205           wtd->no_sanitize_p = true;
1206           for (tree decl = BIND_EXPR_VARS (stmt);
1207                decl;
1208                decl = DECL_CHAIN (decl))
1209             if (VAR_P (decl)
1210                 && TREE_STATIC (decl)
1211                 && DECL_INITIAL (decl))
1212               cp_walk_tree (&DECL_INITIAL (decl), cp_genericize_r, data, NULL);
1213           wtd->no_sanitize_p = no_sanitize_p;
1214         }
1215       wtd->bind_expr_stack.safe_push (stmt);
1216       cp_walk_tree (&BIND_EXPR_BODY (stmt),
1217                     cp_genericize_r, data, NULL);
1218       wtd->bind_expr_stack.pop ();
1219     }
1220
1221   else if (TREE_CODE (stmt) == USING_STMT)
1222     {
1223       tree block = NULL_TREE;
1224
1225       /* Get the innermost inclosing GIMPLE_BIND that has a non NULL
1226          BLOCK, and append an IMPORTED_DECL to its
1227          BLOCK_VARS chained list.  */
1228       if (wtd->bind_expr_stack.exists ())
1229         {
1230           int i;
1231           for (i = wtd->bind_expr_stack.length () - 1; i >= 0; i--)
1232             if ((block = BIND_EXPR_BLOCK (wtd->bind_expr_stack[i])))
1233               break;
1234         }
1235       if (block)
1236         {
1237           tree using_directive;
1238           gcc_assert (TREE_OPERAND (stmt, 0));
1239
1240           using_directive = make_node (IMPORTED_DECL);
1241           TREE_TYPE (using_directive) = void_type_node;
1242
1243           IMPORTED_DECL_ASSOCIATED_DECL (using_directive)
1244             = TREE_OPERAND (stmt, 0);
1245           DECL_CHAIN (using_directive) = BLOCK_VARS (block);
1246           BLOCK_VARS (block) = using_directive;
1247         }
1248       /* The USING_STMT won't appear in GENERIC.  */
1249       *stmt_p = build1 (NOP_EXPR, void_type_node, integer_zero_node);
1250       *walk_subtrees = 0;
1251     }
1252
1253   else if (TREE_CODE (stmt) == DECL_EXPR
1254            && TREE_CODE (DECL_EXPR_DECL (stmt)) == USING_DECL)
1255     {
1256       /* Using decls inside DECL_EXPRs are just dropped on the floor.  */
1257       *stmt_p = build1 (NOP_EXPR, void_type_node, integer_zero_node);
1258       *walk_subtrees = 0;
1259     }
1260   else if (TREE_CODE (stmt) == DECL_EXPR)
1261     {
1262       tree d = DECL_EXPR_DECL (stmt);
1263       if (TREE_CODE (d) == VAR_DECL)
1264         gcc_assert (CP_DECL_THREAD_LOCAL_P (d) == DECL_THREAD_LOCAL_P (d));
1265     }
1266   else if (TREE_CODE (stmt) == OMP_PARALLEL || TREE_CODE (stmt) == OMP_TASK)
1267     {
1268       struct cp_genericize_omp_taskreg omp_ctx;
1269       tree c, decl;
1270       splay_tree_node n;
1271
1272       *walk_subtrees = 0;
1273       cp_walk_tree (&OMP_CLAUSES (stmt), cp_genericize_r, data, NULL);
1274       omp_ctx.is_parallel = TREE_CODE (stmt) == OMP_PARALLEL;
1275       omp_ctx.default_shared = omp_ctx.is_parallel;
1276       omp_ctx.outer = wtd->omp_ctx;
1277       omp_ctx.variables = splay_tree_new (splay_tree_compare_decl_uid, 0, 0);
1278       wtd->omp_ctx = &omp_ctx;
1279       for (c = OMP_CLAUSES (stmt); c; c = OMP_CLAUSE_CHAIN (c))
1280         switch (OMP_CLAUSE_CODE (c))
1281           {
1282           case OMP_CLAUSE_SHARED:
1283           case OMP_CLAUSE_PRIVATE:
1284           case OMP_CLAUSE_FIRSTPRIVATE:
1285           case OMP_CLAUSE_LASTPRIVATE:
1286             decl = OMP_CLAUSE_DECL (c);
1287             if (decl == error_mark_node || !omp_var_to_track (decl))
1288               break;
1289             n = splay_tree_lookup (omp_ctx.variables, (splay_tree_key) decl);
1290             if (n != NULL)
1291               break;
1292             splay_tree_insert (omp_ctx.variables, (splay_tree_key) decl,
1293                                OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
1294                                ? OMP_CLAUSE_DEFAULT_SHARED
1295                                : OMP_CLAUSE_DEFAULT_PRIVATE);
1296             if (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_PRIVATE
1297                 && omp_ctx.outer)
1298               omp_cxx_notice_variable (omp_ctx.outer, decl);
1299             break;
1300           case OMP_CLAUSE_DEFAULT:
1301             if (OMP_CLAUSE_DEFAULT_KIND (c) == OMP_CLAUSE_DEFAULT_SHARED)
1302               omp_ctx.default_shared = true;
1303           default:
1304             break;
1305           }
1306       cp_walk_tree (&OMP_BODY (stmt), cp_genericize_r, data, NULL);
1307       wtd->omp_ctx = omp_ctx.outer;
1308       splay_tree_delete (omp_ctx.variables);
1309     }
1310   else if (TREE_CODE (stmt) == TRY_BLOCK)
1311     {
1312       *walk_subtrees = 0;
1313       tree try_block = wtd->try_block;
1314       wtd->try_block = stmt;
1315       cp_walk_tree (&TRY_STMTS (stmt), cp_genericize_r, data, NULL);
1316       wtd->try_block = try_block;
1317       cp_walk_tree (&TRY_HANDLERS (stmt), cp_genericize_r, data, NULL);
1318     }
1319   else if (TREE_CODE (stmt) == MUST_NOT_THROW_EXPR)
1320     {
1321       /* MUST_NOT_THROW_COND might be something else with TM.  */
1322       if (MUST_NOT_THROW_COND (stmt) == NULL_TREE)
1323         {
1324           *walk_subtrees = 0;
1325           tree try_block = wtd->try_block;
1326           wtd->try_block = stmt;
1327           cp_walk_tree (&TREE_OPERAND (stmt, 0), cp_genericize_r, data, NULL);
1328           wtd->try_block = try_block;
1329         }
1330     }
1331   else if (TREE_CODE (stmt) == THROW_EXPR)
1332     {
1333       location_t loc = location_of (stmt);
1334       if (TREE_NO_WARNING (stmt))
1335         /* Never mind.  */;
1336       else if (wtd->try_block)
1337         {
1338           if (TREE_CODE (wtd->try_block) == MUST_NOT_THROW_EXPR
1339               && warning_at (loc, OPT_Wterminate,
1340                              "throw will always call terminate()")
1341               && cxx_dialect >= cxx11
1342               && DECL_DESTRUCTOR_P (current_function_decl))
1343             inform (loc, "in C++11 destructors default to noexcept");
1344         }
1345       else
1346         {
1347           if (warn_cxx11_compat && cxx_dialect < cxx11
1348               && DECL_DESTRUCTOR_P (current_function_decl)
1349               && (TYPE_RAISES_EXCEPTIONS (TREE_TYPE (current_function_decl))
1350                   == NULL_TREE)
1351               && (get_defaulted_eh_spec (current_function_decl)
1352                   == empty_except_spec))
1353             warning_at (loc, OPT_Wc__11_compat,
1354                         "in C++11 this throw will terminate because "
1355                         "destructors default to noexcept");
1356         }
1357     }
1358   else if (TREE_CODE (stmt) == CONVERT_EXPR)
1359     gcc_assert (!CONVERT_EXPR_VBASE_PATH (stmt));
1360   else if (TREE_CODE (stmt) == FOR_STMT)
1361     genericize_for_stmt (stmt_p, walk_subtrees, data);
1362   else if (TREE_CODE (stmt) == WHILE_STMT)
1363     genericize_while_stmt (stmt_p, walk_subtrees, data);
1364   else if (TREE_CODE (stmt) == DO_STMT)
1365     genericize_do_stmt (stmt_p, walk_subtrees, data);
1366   else if (TREE_CODE (stmt) == SWITCH_STMT)
1367     genericize_switch_stmt (stmt_p, walk_subtrees, data);
1368   else if (TREE_CODE (stmt) == CONTINUE_STMT)
1369     genericize_continue_stmt (stmt_p);
1370   else if (TREE_CODE (stmt) == BREAK_STMT)
1371     genericize_break_stmt (stmt_p);
1372   else if (TREE_CODE (stmt) == OMP_FOR
1373            || TREE_CODE (stmt) == OMP_SIMD
1374            || TREE_CODE (stmt) == OMP_DISTRIBUTE
1375            || TREE_CODE (stmt) == OMP_TASKLOOP)
1376     genericize_omp_for_stmt (stmt_p, walk_subtrees, data);
1377   else if ((flag_sanitize
1378             & (SANITIZE_NULL | SANITIZE_ALIGNMENT | SANITIZE_VPTR))
1379            && !wtd->no_sanitize_p)
1380     {
1381       if ((flag_sanitize & (SANITIZE_NULL | SANITIZE_ALIGNMENT))
1382           && TREE_CODE (stmt) == NOP_EXPR
1383           && TREE_CODE (TREE_TYPE (stmt)) == REFERENCE_TYPE)
1384         ubsan_maybe_instrument_reference (stmt);
1385       else if (TREE_CODE (stmt) == CALL_EXPR)
1386         {
1387           tree fn = CALL_EXPR_FN (stmt);
1388           if (fn != NULL_TREE
1389               && !error_operand_p (fn)
1390               && POINTER_TYPE_P (TREE_TYPE (fn))
1391               && TREE_CODE (TREE_TYPE (TREE_TYPE (fn))) == METHOD_TYPE)
1392             {
1393               bool is_ctor
1394                 = TREE_CODE (fn) == ADDR_EXPR
1395                   && TREE_CODE (TREE_OPERAND (fn, 0)) == FUNCTION_DECL
1396                   && DECL_CONSTRUCTOR_P (TREE_OPERAND (fn, 0));
1397               if (flag_sanitize & (SANITIZE_NULL | SANITIZE_ALIGNMENT))
1398                 ubsan_maybe_instrument_member_call (stmt, is_ctor);
1399               if ((flag_sanitize & SANITIZE_VPTR) && !is_ctor)
1400                 cp_ubsan_maybe_instrument_member_call (stmt);
1401             }
1402         }
1403     }
1404
1405   p_set->add (*stmt_p);
1406
1407   return NULL;
1408 }
1409
1410 /* Lower C++ front end trees to GENERIC in T_P.  */
1411
1412 static void
1413 cp_genericize_tree (tree* t_p)
1414 {
1415   struct cp_genericize_data wtd;
1416
1417   wtd.p_set = new hash_set<tree>;
1418   wtd.bind_expr_stack.create (0);
1419   wtd.omp_ctx = NULL;
1420   wtd.try_block = NULL_TREE;
1421   wtd.no_sanitize_p = false;
1422   cp_walk_tree (t_p, cp_genericize_r, &wtd, NULL);
1423   delete wtd.p_set;
1424   wtd.bind_expr_stack.release ();
1425   if (flag_sanitize & SANITIZE_VPTR)
1426     cp_ubsan_instrument_member_accesses (t_p);
1427 }
1428
1429 /* If a function that should end with a return in non-void
1430    function doesn't obviously end with return, add ubsan
1431    instrumentation code to verify it at runtime.  */
1432
1433 static void
1434 cp_ubsan_maybe_instrument_return (tree fndecl)
1435 {
1436   if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fndecl)))
1437       || DECL_CONSTRUCTOR_P (fndecl)
1438       || DECL_DESTRUCTOR_P (fndecl)
1439       || !targetm.warn_func_return (fndecl))
1440     return;
1441
1442   tree t = DECL_SAVED_TREE (fndecl);
1443   while (t)
1444     {
1445       switch (TREE_CODE (t))
1446         {
1447         case BIND_EXPR:
1448           t = BIND_EXPR_BODY (t);
1449           continue;
1450         case TRY_FINALLY_EXPR:
1451           t = TREE_OPERAND (t, 0);
1452           continue;
1453         case STATEMENT_LIST:
1454           {
1455             tree_stmt_iterator i = tsi_last (t);
1456             if (!tsi_end_p (i))
1457               {
1458                 t = tsi_stmt (i);
1459                 continue;
1460               }
1461           }
1462           break;
1463         case RETURN_EXPR:
1464           return;
1465         default:
1466           break;
1467         }
1468       break;
1469     }
1470   if (t == NULL_TREE)
1471     return;
1472   t = DECL_SAVED_TREE (fndecl);
1473   if (TREE_CODE (t) == BIND_EXPR
1474       && TREE_CODE (BIND_EXPR_BODY (t)) == STATEMENT_LIST)
1475     {
1476       tree_stmt_iterator i = tsi_last (BIND_EXPR_BODY (t));
1477       t = ubsan_instrument_return (DECL_SOURCE_LOCATION (fndecl));
1478       tsi_link_after (&i, t, TSI_NEW_STMT);
1479     }
1480 }
1481
1482 void
1483 cp_genericize (tree fndecl)
1484 {
1485   tree t;
1486
1487   /* Fix up the types of parms passed by invisible reference.  */
1488   for (t = DECL_ARGUMENTS (fndecl); t; t = DECL_CHAIN (t))
1489     if (TREE_ADDRESSABLE (TREE_TYPE (t)))
1490       {
1491         /* If a function's arguments are copied to create a thunk,
1492            then DECL_BY_REFERENCE will be set -- but the type of the
1493            argument will be a pointer type, so we will never get
1494            here.  */
1495         gcc_assert (!DECL_BY_REFERENCE (t));
1496         gcc_assert (DECL_ARG_TYPE (t) != TREE_TYPE (t));
1497         TREE_TYPE (t) = DECL_ARG_TYPE (t);
1498         DECL_BY_REFERENCE (t) = 1;
1499         TREE_ADDRESSABLE (t) = 0;
1500         relayout_decl (t);
1501       }
1502
1503   /* Do the same for the return value.  */
1504   if (TREE_ADDRESSABLE (TREE_TYPE (DECL_RESULT (fndecl))))
1505     {
1506       t = DECL_RESULT (fndecl);
1507       TREE_TYPE (t) = build_reference_type (TREE_TYPE (t));
1508       DECL_BY_REFERENCE (t) = 1;
1509       TREE_ADDRESSABLE (t) = 0;
1510       relayout_decl (t);
1511       if (DECL_NAME (t))
1512         {
1513           /* Adjust DECL_VALUE_EXPR of the original var.  */
1514           tree outer = outer_curly_brace_block (current_function_decl);
1515           tree var;
1516
1517           if (outer)
1518             for (var = BLOCK_VARS (outer); var; var = DECL_CHAIN (var))
1519               if (DECL_NAME (t) == DECL_NAME (var)
1520                   && DECL_HAS_VALUE_EXPR_P (var)
1521                   && DECL_VALUE_EXPR (var) == t)
1522                 {
1523                   tree val = convert_from_reference (t);
1524                   SET_DECL_VALUE_EXPR (var, val);
1525                   break;
1526                 }
1527         }
1528     }
1529
1530   /* If we're a clone, the body is already GIMPLE.  */
1531   if (DECL_CLONED_FUNCTION_P (fndecl))
1532     return;
1533
1534   /* Expand all the array notations here.  */
1535   if (flag_cilkplus 
1536       && contains_array_notation_expr (DECL_SAVED_TREE (fndecl)))
1537     DECL_SAVED_TREE (fndecl) = 
1538       expand_array_notation_exprs (DECL_SAVED_TREE (fndecl));
1539
1540   /* We do want to see every occurrence of the parms, so we can't just use
1541      walk_tree's hash functionality.  */
1542   cp_genericize_tree (&DECL_SAVED_TREE (fndecl));
1543
1544   if (flag_sanitize & SANITIZE_RETURN
1545       && do_ubsan_in_current_function ())
1546     cp_ubsan_maybe_instrument_return (fndecl);
1547
1548   /* Do everything else.  */
1549   c_genericize (fndecl);
1550
1551   gcc_assert (bc_label[bc_break] == NULL);
1552   gcc_assert (bc_label[bc_continue] == NULL);
1553 }
1554 \f
1555 /* Build code to apply FN to each member of ARG1 and ARG2.  FN may be
1556    NULL if there is in fact nothing to do.  ARG2 may be null if FN
1557    actually only takes one argument.  */
1558
1559 static tree
1560 cxx_omp_clause_apply_fn (tree fn, tree arg1, tree arg2)
1561 {
1562   tree defparm, parm, t;
1563   int i = 0;
1564   int nargs;
1565   tree *argarray;
1566
1567   if (fn == NULL)
1568     return NULL;
1569
1570   nargs = list_length (DECL_ARGUMENTS (fn));
1571   argarray = XALLOCAVEC (tree, nargs);
1572
1573   defparm = TREE_CHAIN (TYPE_ARG_TYPES (TREE_TYPE (fn)));
1574   if (arg2)
1575     defparm = TREE_CHAIN (defparm);
1576
1577   if (TREE_CODE (TREE_TYPE (arg1)) == ARRAY_TYPE)
1578     {
1579       tree inner_type = TREE_TYPE (arg1);
1580       tree start1, end1, p1;
1581       tree start2 = NULL, p2 = NULL;
1582       tree ret = NULL, lab;
1583
1584       start1 = arg1;
1585       start2 = arg2;
1586       do
1587         {
1588           inner_type = TREE_TYPE (inner_type);
1589           start1 = build4 (ARRAY_REF, inner_type, start1,
1590                            size_zero_node, NULL, NULL);
1591           if (arg2)
1592             start2 = build4 (ARRAY_REF, inner_type, start2,
1593                              size_zero_node, NULL, NULL);
1594         }
1595       while (TREE_CODE (inner_type) == ARRAY_TYPE);
1596       start1 = build_fold_addr_expr_loc (input_location, start1);
1597       if (arg2)
1598         start2 = build_fold_addr_expr_loc (input_location, start2);
1599
1600       end1 = TYPE_SIZE_UNIT (TREE_TYPE (arg1));
1601       end1 = fold_build_pointer_plus (start1, end1);
1602
1603       p1 = create_tmp_var (TREE_TYPE (start1));
1604       t = build2 (MODIFY_EXPR, TREE_TYPE (p1), p1, start1);
1605       append_to_statement_list (t, &ret);
1606
1607       if (arg2)
1608         {
1609           p2 = create_tmp_var (TREE_TYPE (start2));
1610           t = build2 (MODIFY_EXPR, TREE_TYPE (p2), p2, start2);
1611           append_to_statement_list (t, &ret);
1612         }
1613
1614       lab = create_artificial_label (input_location);
1615       t = build1 (LABEL_EXPR, void_type_node, lab);
1616       append_to_statement_list (t, &ret);
1617
1618       argarray[i++] = p1;
1619       if (arg2)
1620         argarray[i++] = p2;
1621       /* Handle default arguments.  */
1622       for (parm = defparm; parm && parm != void_list_node;
1623            parm = TREE_CHAIN (parm), i++)
1624         argarray[i] = convert_default_arg (TREE_VALUE (parm),
1625                                            TREE_PURPOSE (parm), fn, i,
1626                                            tf_warning_or_error);
1627       t = build_call_a (fn, i, argarray);
1628       t = fold_convert (void_type_node, t);
1629       t = fold_build_cleanup_point_expr (TREE_TYPE (t), t);
1630       append_to_statement_list (t, &ret);
1631
1632       t = fold_build_pointer_plus (p1, TYPE_SIZE_UNIT (inner_type));
1633       t = build2 (MODIFY_EXPR, TREE_TYPE (p1), p1, t);
1634       append_to_statement_list (t, &ret);
1635
1636       if (arg2)
1637         {
1638           t = fold_build_pointer_plus (p2, TYPE_SIZE_UNIT (inner_type));
1639           t = build2 (MODIFY_EXPR, TREE_TYPE (p2), p2, t);
1640           append_to_statement_list (t, &ret);
1641         }
1642
1643       t = build2 (NE_EXPR, boolean_type_node, p1, end1);
1644       t = build3 (COND_EXPR, void_type_node, t, build_and_jump (&lab), NULL);
1645       append_to_statement_list (t, &ret);
1646
1647       return ret;
1648     }
1649   else
1650     {
1651       argarray[i++] = build_fold_addr_expr_loc (input_location, arg1);
1652       if (arg2)
1653         argarray[i++] = build_fold_addr_expr_loc (input_location, arg2);
1654       /* Handle default arguments.  */
1655       for (parm = defparm; parm && parm != void_list_node;
1656            parm = TREE_CHAIN (parm), i++)
1657         argarray[i] = convert_default_arg (TREE_VALUE (parm),
1658                                            TREE_PURPOSE (parm),
1659                                            fn, i, tf_warning_or_error);
1660       t = build_call_a (fn, i, argarray);
1661       t = fold_convert (void_type_node, t);
1662       return fold_build_cleanup_point_expr (TREE_TYPE (t), t);
1663     }
1664 }
1665
1666 /* Return code to initialize DECL with its default constructor, or
1667    NULL if there's nothing to do.  */
1668
1669 tree
1670 cxx_omp_clause_default_ctor (tree clause, tree decl, tree /*outer*/)
1671 {
1672   tree info = CP_OMP_CLAUSE_INFO (clause);
1673   tree ret = NULL;
1674
1675   if (info)
1676     ret = cxx_omp_clause_apply_fn (TREE_VEC_ELT (info, 0), decl, NULL);
1677
1678   return ret;
1679 }
1680
1681 /* Return code to initialize DST with a copy constructor from SRC.  */
1682
1683 tree
1684 cxx_omp_clause_copy_ctor (tree clause, tree dst, tree src)
1685 {
1686   tree info = CP_OMP_CLAUSE_INFO (clause);
1687   tree ret = NULL;
1688
1689   if (info)
1690     ret = cxx_omp_clause_apply_fn (TREE_VEC_ELT (info, 0), dst, src);
1691   if (ret == NULL)
1692     ret = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
1693
1694   return ret;
1695 }
1696
1697 /* Similarly, except use an assignment operator instead.  */
1698
1699 tree
1700 cxx_omp_clause_assign_op (tree clause, tree dst, tree src)
1701 {
1702   tree info = CP_OMP_CLAUSE_INFO (clause);
1703   tree ret = NULL;
1704
1705   if (info)
1706     ret = cxx_omp_clause_apply_fn (TREE_VEC_ELT (info, 2), dst, src);
1707   if (ret == NULL)
1708     ret = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
1709
1710   return ret;
1711 }
1712
1713 /* Return code to destroy DECL.  */
1714
1715 tree
1716 cxx_omp_clause_dtor (tree clause, tree decl)
1717 {
1718   tree info = CP_OMP_CLAUSE_INFO (clause);
1719   tree ret = NULL;
1720
1721   if (info)
1722     ret = cxx_omp_clause_apply_fn (TREE_VEC_ELT (info, 1), decl, NULL);
1723
1724   return ret;
1725 }
1726
1727 /* True if OpenMP should privatize what this DECL points to rather
1728    than the DECL itself.  */
1729
1730 bool
1731 cxx_omp_privatize_by_reference (const_tree decl)
1732 {
1733   return (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
1734           || is_invisiref_parm (decl));
1735 }
1736
1737 /* Return true if DECL is const qualified var having no mutable member.  */
1738 bool
1739 cxx_omp_const_qual_no_mutable (tree decl)
1740 {
1741   tree type = TREE_TYPE (decl);
1742   if (TREE_CODE (type) == REFERENCE_TYPE)
1743     {
1744       if (!is_invisiref_parm (decl))
1745         return false;
1746       type = TREE_TYPE (type);
1747
1748       if (TREE_CODE (decl) == RESULT_DECL && DECL_NAME (decl))
1749         {
1750           /* NVR doesn't preserve const qualification of the
1751              variable's type.  */
1752           tree outer = outer_curly_brace_block (current_function_decl);
1753           tree var;
1754
1755           if (outer)
1756             for (var = BLOCK_VARS (outer); var; var = DECL_CHAIN (var))
1757               if (DECL_NAME (decl) == DECL_NAME (var)
1758                   && (TYPE_MAIN_VARIANT (type)
1759                       == TYPE_MAIN_VARIANT (TREE_TYPE (var))))
1760                 {
1761                   if (TYPE_READONLY (TREE_TYPE (var)))
1762                     type = TREE_TYPE (var);
1763                   break;
1764                 }
1765         }
1766     }
1767
1768   if (type == error_mark_node)
1769     return false;
1770
1771   /* Variables with const-qualified type having no mutable member
1772      are predetermined shared.  */
1773   if (TYPE_READONLY (type) && !cp_has_mutable_p (type))
1774     return true;
1775
1776   return false;
1777 }
1778
1779 /* True if OpenMP sharing attribute of DECL is predetermined.  */
1780
1781 enum omp_clause_default_kind
1782 cxx_omp_predetermined_sharing (tree decl)
1783 {
1784   /* Static data members are predetermined shared.  */
1785   if (TREE_STATIC (decl))
1786     {
1787       tree ctx = CP_DECL_CONTEXT (decl);
1788       if (TYPE_P (ctx) && MAYBE_CLASS_TYPE_P (ctx))
1789         return OMP_CLAUSE_DEFAULT_SHARED;
1790     }
1791
1792   /* Const qualified vars having no mutable member are predetermined
1793      shared.  */
1794   if (cxx_omp_const_qual_no_mutable (decl))
1795     return OMP_CLAUSE_DEFAULT_SHARED;
1796
1797   return OMP_CLAUSE_DEFAULT_UNSPECIFIED;
1798 }
1799
1800 /* Finalize an implicitly determined clause.  */
1801
1802 void
1803 cxx_omp_finish_clause (tree c, gimple_seq *)
1804 {
1805   tree decl, inner_type;
1806   bool make_shared = false;
1807
1808   if (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_FIRSTPRIVATE)
1809     return;
1810
1811   decl = OMP_CLAUSE_DECL (c);
1812   decl = require_complete_type (decl);
1813   inner_type = TREE_TYPE (decl);
1814   if (decl == error_mark_node)
1815     make_shared = true;
1816   else if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE)
1817     inner_type = TREE_TYPE (inner_type);
1818
1819   /* We're interested in the base element, not arrays.  */
1820   while (TREE_CODE (inner_type) == ARRAY_TYPE)
1821     inner_type = TREE_TYPE (inner_type);
1822
1823   /* Check for special function availability by building a call to one.
1824      Save the results, because later we won't be in the right context
1825      for making these queries.  */
1826   if (!make_shared
1827       && CLASS_TYPE_P (inner_type)
1828       && cxx_omp_create_clause_info (c, inner_type, false, true, false, true))
1829     make_shared = true;
1830
1831   if (make_shared)
1832     OMP_CLAUSE_CODE (c) = OMP_CLAUSE_SHARED;
1833 }
1834
1835 /* Return true if DECL's DECL_VALUE_EXPR (if any) should be
1836    disregarded in OpenMP construct, because it is going to be
1837    remapped during OpenMP lowering.  SHARED is true if DECL
1838    is going to be shared, false if it is going to be privatized.  */
1839
1840 bool
1841 cxx_omp_disregard_value_expr (tree decl, bool shared)
1842 {
1843   return !shared
1844          && VAR_P (decl)
1845          && DECL_HAS_VALUE_EXPR_P (decl)
1846          && DECL_ARTIFICIAL (decl)
1847          && DECL_LANG_SPECIFIC (decl)
1848          && DECL_OMP_PRIVATIZED_MEMBER (decl);
1849 }
1850
1851 /* Callback for walk_tree, looking for LABEL_EXPR.  Return *TP if it is
1852    a LABEL_EXPR; otherwise return NULL_TREE.  Do not check the subtrees
1853    of GOTO_EXPR.  */
1854
1855 static tree
1856 contains_label_1 (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1857 {
1858   switch (TREE_CODE (*tp))
1859     {
1860     case LABEL_EXPR:
1861       return *tp;
1862
1863     case GOTO_EXPR:
1864       *walk_subtrees = 0;
1865
1866       /* ... fall through ...  */
1867
1868     default:
1869       return NULL_TREE;
1870     }
1871 }
1872
1873 /* Return whether the sub-tree ST contains a label which is accessible from
1874    outside the sub-tree.  */
1875
1876 static bool
1877 contains_label_p (tree st)
1878 {
1879   return
1880    walk_tree_without_duplicates (&st, contains_label_1 , NULL) != NULL_TREE;
1881 }
1882
1883 /* Perform folding on expression X.  */
1884
1885 tree
1886 cp_fully_fold (tree x)
1887 {
1888   return cp_fold (x);
1889 }
1890
1891 /* Fold expression X which is used as an rvalue if RVAL is true.  */
1892
1893 static tree
1894 cp_fold_maybe_rvalue (tree x, bool rval)
1895 {
1896   if (rval && DECL_P (x))
1897     {
1898       tree v = decl_constant_value (x);
1899       if (v != error_mark_node)
1900         x = v;
1901     }
1902   return cp_fold (x);
1903 }
1904
1905 /* Fold expression X which is used as an rvalue.  */
1906
1907 static tree
1908 cp_fold_rvalue (tree x)
1909 {
1910   return cp_fold_maybe_rvalue (x, true);
1911 }
1912
1913 /* c-common interface to cp_fold.  If IN_INIT, this is in a static initializer
1914    and certain changes are made to the folding done.  Or should be (FIXME).  We
1915    never touch maybe_const, as it is only used for the C front-end
1916    C_MAYBE_CONST_EXPR.  */
1917
1918 tree
1919 c_fully_fold (tree x, bool /*in_init*/, bool */*maybe_const*/)
1920 {
1921   /* c_fully_fold is only used on rvalues, and we need to fold CONST_DECL to
1922      INTEGER_CST.  */
1923   return cp_fold_rvalue (x);
1924 }
1925
1926 static GTY((cache, deletable)) cache_map fold_cache;
1927
1928 /*  This function tries to fold an expression X.
1929     To avoid combinatorial explosion, folding results are kept in fold_cache.
1930     If we are processing a template or X is invalid, we don't fold at all.
1931     For performance reasons we don't cache expressions representing a
1932     declaration or constant.
1933     Function returns X or its folded variant.  */
1934
1935 static tree
1936 cp_fold (tree x)
1937 {
1938   tree op0, op1, op2, op3;
1939   tree org_x = x, r = NULL_TREE;
1940   enum tree_code code;
1941   location_t loc;
1942   bool rval_ops = true;
1943
1944   if (!x || x == error_mark_node)
1945     return x;
1946
1947   if (processing_template_decl
1948       || (EXPR_P (x) && (!TREE_TYPE (x) || TREE_TYPE (x) == error_mark_node)))
1949     return x;
1950
1951   /* Don't bother to cache DECLs or constants.  */
1952   if (DECL_P (x) || CONSTANT_CLASS_P (x))
1953     return x;
1954
1955   if (tree cached = fold_cache.get (x))
1956     return cached;
1957
1958   code = TREE_CODE (x);
1959   switch (code)
1960     {
1961     case SIZEOF_EXPR:
1962       x = fold_sizeof_expr (x);
1963       break;
1964
1965     case VIEW_CONVERT_EXPR:
1966       rval_ops = false;
1967     case CONVERT_EXPR:
1968     case NOP_EXPR:
1969     case NON_LVALUE_EXPR:
1970
1971       if (VOID_TYPE_P (TREE_TYPE (x)))
1972         return x;
1973
1974       if (!TREE_OPERAND (x, 0)
1975           || TREE_CODE (TREE_OPERAND (x, 0)) == NON_LVALUE_EXPR)
1976         return x;
1977
1978       loc = EXPR_LOCATION (x);
1979       op0 = TREE_OPERAND (x, 0);
1980
1981       if (TREE_CODE (x) == NOP_EXPR
1982           && TREE_OVERFLOW_P (op0)
1983           && TREE_TYPE (x) == TREE_TYPE (op0))
1984         return x;
1985
1986       op0 = cp_fold_maybe_rvalue (op0, rval_ops);
1987
1988       if (op0 != TREE_OPERAND (x, 0))
1989         x = fold_build1_loc (loc, code, TREE_TYPE (x), op0);
1990       else
1991         x = fold (x);
1992
1993       /* Conversion of an out-of-range value has implementation-defined
1994          behavior; the language considers it different from arithmetic
1995          overflow, which is undefined.  */
1996       if (TREE_CODE (op0) == INTEGER_CST
1997           && TREE_OVERFLOW_P (x) && !TREE_OVERFLOW_P (op0))
1998         TREE_OVERFLOW (x) = false;
1999
2000       break;
2001
2002     case ADDR_EXPR:
2003     case REALPART_EXPR:
2004     case IMAGPART_EXPR:
2005       rval_ops = false;
2006     case CONJ_EXPR:
2007     case FIX_TRUNC_EXPR:
2008     case FLOAT_EXPR:
2009     case NEGATE_EXPR:
2010     case ABS_EXPR:
2011     case BIT_NOT_EXPR:
2012     case TRUTH_NOT_EXPR:
2013     case FIXED_CONVERT_EXPR:
2014     case UNARY_PLUS_EXPR:
2015     case INDIRECT_REF:
2016
2017       loc = EXPR_LOCATION (x);
2018       op0 = cp_fold_maybe_rvalue (TREE_OPERAND (x, 0), rval_ops);
2019
2020       if (op0 != TREE_OPERAND (x, 0))
2021         x = fold_build1_loc (loc, code, TREE_TYPE (x), op0);
2022       else
2023         x = fold (x);
2024
2025       gcc_assert (TREE_CODE (x) != COND_EXPR
2026                   || !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (x, 0))));
2027       break;
2028
2029     case POSTDECREMENT_EXPR:
2030     case POSTINCREMENT_EXPR:
2031     case INIT_EXPR:
2032
2033         loc = EXPR_LOCATION (x);
2034         op0 = cp_fold (TREE_OPERAND (x, 0));
2035         op1 = cp_fold_rvalue (TREE_OPERAND (x, 1));
2036
2037         if (TREE_OPERAND (x, 0) != op0 || TREE_OPERAND (x, 1) != op1)
2038           x = build2_loc (loc, code, TREE_TYPE (x), op0, op1);
2039
2040         break;
2041
2042     case PREDECREMENT_EXPR:
2043     case PREINCREMENT_EXPR:
2044     case COMPOUND_EXPR:
2045     case MODIFY_EXPR:
2046       rval_ops = false;
2047     case POINTER_PLUS_EXPR:
2048     case PLUS_EXPR:
2049     case MINUS_EXPR:
2050     case MULT_EXPR:
2051     case TRUNC_DIV_EXPR:
2052     case CEIL_DIV_EXPR:
2053     case FLOOR_DIV_EXPR:
2054     case ROUND_DIV_EXPR:
2055     case TRUNC_MOD_EXPR:
2056     case CEIL_MOD_EXPR:
2057     case ROUND_MOD_EXPR:
2058     case RDIV_EXPR:
2059     case EXACT_DIV_EXPR:
2060     case MIN_EXPR:
2061     case MAX_EXPR:
2062     case LSHIFT_EXPR:
2063     case RSHIFT_EXPR:
2064     case LROTATE_EXPR:
2065     case RROTATE_EXPR:
2066     case BIT_AND_EXPR:
2067     case BIT_IOR_EXPR:
2068     case BIT_XOR_EXPR:
2069     case TRUTH_AND_EXPR:
2070     case TRUTH_ANDIF_EXPR:
2071     case TRUTH_OR_EXPR:
2072     case TRUTH_ORIF_EXPR:
2073     case TRUTH_XOR_EXPR:
2074     case LT_EXPR: case LE_EXPR:
2075     case GT_EXPR: case GE_EXPR:
2076     case EQ_EXPR: case NE_EXPR:
2077     case UNORDERED_EXPR: case ORDERED_EXPR:
2078     case UNLT_EXPR: case UNLE_EXPR:
2079     case UNGT_EXPR: case UNGE_EXPR:
2080     case UNEQ_EXPR: case LTGT_EXPR:
2081     case RANGE_EXPR: case COMPLEX_EXPR:
2082
2083       loc = EXPR_LOCATION (x);
2084       op0 = cp_fold_maybe_rvalue (TREE_OPERAND (x, 0), rval_ops);
2085       op1 = cp_fold_rvalue (TREE_OPERAND (x, 1));
2086       if ((code == COMPOUND_EXPR || code == MODIFY_EXPR)
2087           && ((op1 && TREE_SIDE_EFFECTS (op1))
2088                || (op0 && TREE_SIDE_EFFECTS (op0))))
2089         break;
2090       if (TREE_CODE (x) == COMPOUND_EXPR && !op0)
2091         op0 = build_empty_stmt (loc);
2092
2093       if (op0 != TREE_OPERAND (x, 0) || op1 != TREE_OPERAND (x, 1))
2094         x = fold_build2_loc (loc, code, TREE_TYPE (x), op0, op1);
2095       else
2096         x = fold (x);
2097
2098       if (TREE_CODE (x) == COMPOUND_EXPR && TREE_OPERAND (x, 0) == NULL_TREE
2099           && TREE_OPERAND (x, 1))
2100         return TREE_OPERAND (x, 1);
2101       break;
2102
2103     case VEC_COND_EXPR:
2104     case COND_EXPR:
2105
2106       loc = EXPR_LOCATION (x);
2107       op0 = cp_fold_rvalue (TREE_OPERAND (x, 0));
2108
2109       if (TREE_SIDE_EFFECTS (op0))
2110         break;
2111
2112       op1 = cp_fold (TREE_OPERAND (x, 1));
2113       op2 = cp_fold (TREE_OPERAND (x, 2));
2114
2115       if (TREE_CODE (op0) == INTEGER_CST)
2116         {
2117           tree un;
2118
2119           if (integer_zerop (op0))
2120             {
2121               un = op1;
2122               r = op2;
2123             }
2124           else
2125             {
2126               un = op2;
2127               r = op1;
2128             }
2129
2130           if ((!TREE_SIDE_EFFECTS (un) || !contains_label_p (un))
2131               && (! VOID_TYPE_P (TREE_TYPE (r)) || VOID_TYPE_P (x)))
2132             {
2133               if (CAN_HAVE_LOCATION_P (r)
2134                   && EXPR_LOCATION (r) != loc
2135                   && !(TREE_CODE (r) == SAVE_EXPR
2136                        || TREE_CODE (r) == TARGET_EXPR
2137                        || TREE_CODE (r) == BIND_EXPR))
2138                 {
2139                   r = copy_node (r);
2140                   SET_EXPR_LOCATION (r, loc);
2141                 }
2142               x = r;
2143             }
2144
2145           break;
2146         }
2147
2148       if (VOID_TYPE_P (TREE_TYPE (x)))
2149         break;
2150
2151       x = build3_loc (loc, code, TREE_TYPE (x), op0, op1, op2);
2152
2153       if (code != COND_EXPR)
2154         x = fold (x);
2155
2156       break;
2157
2158     case CALL_EXPR:
2159       {
2160         int i, m, sv = optimize, nw = sv, changed = 0;
2161         tree callee = get_callee_fndecl (x);
2162
2163         /* Some built-in function calls will be evaluated at compile-time in
2164            fold ().  Set optimize to 1 when folding __builtin_constant_p inside
2165            a constexpr function so that fold_builtin_1 doesn't fold it to 0.  */
2166         if (callee && DECL_BUILT_IN (callee) && !optimize
2167             && DECL_IS_BUILTIN_CONSTANT_P (callee)
2168             && current_function_decl
2169             && DECL_DECLARED_CONSTEXPR_P (current_function_decl))
2170           nw = 1;
2171
2172         x = copy_node (x);
2173
2174         m = call_expr_nargs (x);
2175         for (i = 0; i < m; i++)
2176           {
2177             r = cp_fold (CALL_EXPR_ARG (x, i));
2178             if (r != CALL_EXPR_ARG (x, i))
2179               changed = 1;
2180             CALL_EXPR_ARG (x, i) = r;
2181           }
2182
2183         optimize = nw;
2184         r = fold (x);
2185         optimize = sv;
2186
2187         if (TREE_CODE (r) != CALL_EXPR)
2188           {
2189             x = cp_fold (r);
2190             break;
2191           }
2192
2193         optimize = nw;
2194
2195         /* Invoke maybe_constant_value for functions declared
2196            constexpr and not called with AGGR_INIT_EXPRs.
2197            TODO:
2198            Do constexpr expansion of expressions where the call itself is not
2199            constant, but the call followed by an INDIRECT_REF is.  */
2200         if (callee && DECL_DECLARED_CONSTEXPR_P (callee))
2201           r = maybe_constant_value (x);
2202         optimize = sv;
2203
2204         if (TREE_CODE (r) != CALL_EXPR)
2205           {
2206             x = r;
2207             break;
2208           }
2209
2210         if (!changed)
2211           x = org_x;
2212         break;
2213       }
2214
2215     case CONSTRUCTOR:
2216       {
2217         unsigned i;
2218         constructor_elt *p;
2219         vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (x);
2220         FOR_EACH_VEC_SAFE_ELT (elts, i, p)
2221           p->value = cp_fold (p->value);
2222         break;
2223       }
2224     case TREE_VEC:
2225       {
2226         bool changed = false;
2227         vec<tree, va_gc> *vec = make_tree_vector ();
2228         int i, n = TREE_VEC_LENGTH (x);
2229         vec_safe_reserve (vec, n);
2230
2231         for (i = 0; i < n; i++)
2232           {
2233             tree op = cp_fold (TREE_VEC_ELT (x, i));
2234             vec->quick_push (op);
2235             if (op != TREE_VEC_ELT (x, i))
2236               changed = true;
2237           }
2238
2239         if (changed)
2240           {
2241             r = copy_node (x);
2242             for (i = 0; i < n; i++)
2243               TREE_VEC_ELT (r, i) = (*vec)[i];
2244             x = r;
2245           }
2246
2247         release_tree_vector (vec);
2248       }
2249
2250       break;
2251
2252     case ARRAY_REF:
2253     case ARRAY_RANGE_REF:
2254
2255       loc = EXPR_LOCATION (x);
2256       op0 = cp_fold (TREE_OPERAND (x, 0));
2257       op1 = cp_fold (TREE_OPERAND (x, 1));
2258       op2 = cp_fold (TREE_OPERAND (x, 2));
2259       op3 = cp_fold (TREE_OPERAND (x, 3));
2260
2261       if (op0 != TREE_OPERAND (x, 0) || op1 != TREE_OPERAND (x, 1)
2262           || op2 != TREE_OPERAND (x, 2) || op3 != TREE_OPERAND (x, 3))
2263         x = build4_loc (loc, code, TREE_TYPE (x), op0, op1, op2, op3);
2264
2265       x = fold (x);
2266       break;
2267
2268     default:
2269       return org_x;
2270     }
2271
2272   fold_cache.put (org_x, x);
2273   /* Prevent that we try to fold an already folded result again.  */
2274   if (x != org_x)
2275     fold_cache.put (x, x);
2276
2277   return x;
2278 }
2279
2280 #include "gt-cp-cp-gimplify.h"