PR c++/29733
[official-gcc.git] / gcc / cp / cp-gimplify.c
blobbdb2edf2f41687863194706d9da73b88ecfbcdad
1 /* C++-specific tree lowering bits; see also c-gimplify.c and tree-gimple.c.
3 Copyright (C) 2002, 2003, 2004, 2005, 2006 Free Software Foundation, Inc.
4 Contributed by Jason Merrill <jason@redhat.com>
6 This file is part of GCC.
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 2, or (at your option) any later
11 version.
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.
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING. If not, write to the Free
20 Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
21 02110-1301, USA. */
23 #include "config.h"
24 #include "system.h"
25 #include "coretypes.h"
26 #include "tm.h"
27 #include "tree.h"
28 #include "cp-tree.h"
29 #include "c-common.h"
30 #include "toplev.h"
31 #include "tree-gimple.h"
32 #include "hashtab.h"
33 #include "pointer-set.h"
34 #include "flags.h"
36 /* Local declarations. */
38 enum bc_t { bc_break = 0, bc_continue = 1 };
40 /* Stack of labels which are targets for "break" or "continue",
41 linked through TREE_CHAIN. */
42 static tree bc_label[2];
44 /* Begin a scope which can be exited by a break or continue statement. BC
45 indicates which.
47 Just creates a label and pushes it into the current context. */
49 static tree
50 begin_bc_block (enum bc_t bc)
52 tree label = create_artificial_label ();
53 TREE_CHAIN (label) = bc_label[bc];
54 bc_label[bc] = label;
55 return label;
58 /* Finish a scope which can be exited by a break or continue statement.
59 LABEL was returned from the most recent call to begin_bc_block. BODY is
60 an expression for the contents of the scope.
62 If we saw a break (or continue) in the scope, append a LABEL_EXPR to
63 body. Otherwise, just forget the label. */
65 static tree
66 finish_bc_block (enum bc_t bc, tree label, tree body)
68 gcc_assert (label == bc_label[bc]);
70 if (TREE_USED (label))
72 tree t, sl = NULL;
74 t = build1 (LABEL_EXPR, void_type_node, label);
76 append_to_statement_list (body, &sl);
77 append_to_statement_list (t, &sl);
78 body = sl;
81 bc_label[bc] = TREE_CHAIN (label);
82 TREE_CHAIN (label) = NULL_TREE;
83 return body;
86 /* Build a GOTO_EXPR to represent a break or continue statement. BC
87 indicates which. */
89 static tree
90 build_bc_goto (enum bc_t bc)
92 tree label = bc_label[bc];
94 if (label == NULL_TREE)
96 if (bc == bc_break)
97 error ("break statement not within loop or switch");
98 else
99 error ("continue statement not within loop or switch");
101 return NULL_TREE;
104 /* Mark the label used for finish_bc_block. */
105 TREE_USED (label) = 1;
106 return build1 (GOTO_EXPR, void_type_node, label);
109 /* Genericize a TRY_BLOCK. */
111 static void
112 genericize_try_block (tree *stmt_p)
114 tree body = TRY_STMTS (*stmt_p);
115 tree cleanup = TRY_HANDLERS (*stmt_p);
117 gimplify_stmt (&body);
119 if (CLEANUP_P (*stmt_p))
120 /* A cleanup is an expression, so it doesn't need to be genericized. */;
121 else
122 gimplify_stmt (&cleanup);
124 *stmt_p = build2 (TRY_CATCH_EXPR, void_type_node, body, cleanup);
127 /* Genericize a HANDLER by converting to a CATCH_EXPR. */
129 static void
130 genericize_catch_block (tree *stmt_p)
132 tree type = HANDLER_TYPE (*stmt_p);
133 tree body = HANDLER_BODY (*stmt_p);
135 gimplify_stmt (&body);
137 /* FIXME should the caught type go in TREE_TYPE? */
138 *stmt_p = build2 (CATCH_EXPR, void_type_node, type, body);
141 /* Genericize an EH_SPEC_BLOCK by converting it to a
142 TRY_CATCH_EXPR/EH_FILTER_EXPR pair. */
144 static void
145 genericize_eh_spec_block (tree *stmt_p)
147 tree body = EH_SPEC_STMTS (*stmt_p);
148 tree allowed = EH_SPEC_RAISES (*stmt_p);
149 tree failure = build_call (call_unexpected_node,
150 tree_cons (NULL_TREE, build_exc_ptr (),
151 NULL_TREE));
152 gimplify_stmt (&body);
154 *stmt_p = gimple_build_eh_filter (body, allowed, failure);
157 /* Genericize an IF_STMT by turning it into a COND_EXPR. */
159 static void
160 gimplify_if_stmt (tree *stmt_p)
162 tree stmt, cond, then_, else_;
164 stmt = *stmt_p;
165 cond = IF_COND (stmt);
166 then_ = THEN_CLAUSE (stmt);
167 else_ = ELSE_CLAUSE (stmt);
169 if (!then_)
170 then_ = build_empty_stmt ();
171 if (!else_)
172 else_ = build_empty_stmt ();
174 if (integer_nonzerop (cond) && !TREE_SIDE_EFFECTS (else_))
175 stmt = then_;
176 else if (integer_zerop (cond) && !TREE_SIDE_EFFECTS (then_))
177 stmt = else_;
178 else
179 stmt = build3 (COND_EXPR, void_type_node, cond, then_, else_);
180 *stmt_p = stmt;
183 /* Build a generic representation of one of the C loop forms. COND is the
184 loop condition or NULL_TREE. BODY is the (possibly compound) statement
185 controlled by the loop. INCR is the increment expression of a for-loop,
186 or NULL_TREE. COND_IS_FIRST indicates whether the condition is
187 evaluated before the loop body as in while and for loops, or after the
188 loop body as in do-while loops. */
190 static tree
191 gimplify_cp_loop (tree cond, tree body, tree incr, bool cond_is_first)
193 tree top, entry, exit, cont_block, break_block, stmt_list, t;
194 location_t stmt_locus;
196 stmt_locus = input_location;
197 stmt_list = NULL_TREE;
198 entry = NULL_TREE;
200 break_block = begin_bc_block (bc_break);
201 cont_block = begin_bc_block (bc_continue);
203 /* If condition is zero don't generate a loop construct. */
204 if (cond && integer_zerop (cond))
206 top = NULL_TREE;
207 exit = NULL_TREE;
208 if (cond_is_first)
210 t = build_bc_goto (bc_break);
211 append_to_statement_list (t, &stmt_list);
214 else
216 /* If we use a LOOP_EXPR here, we have to feed the whole thing
217 back through the main gimplifier to lower it. Given that we
218 have to gimplify the loop body NOW so that we can resolve
219 break/continue stmts, seems easier to just expand to gotos. */
220 top = build1 (LABEL_EXPR, void_type_node, NULL_TREE);
222 /* If we have an exit condition, then we build an IF with gotos either
223 out of the loop, or to the top of it. If there's no exit condition,
224 then we just build a jump back to the top. */
225 exit = build_and_jump (&LABEL_EXPR_LABEL (top));
226 if (cond && !integer_nonzerop (cond))
228 t = build_bc_goto (bc_break);
229 exit = fold_build3 (COND_EXPR, void_type_node, cond, exit, t);
230 gimplify_stmt (&exit);
232 if (cond_is_first)
234 if (incr)
236 entry = build1 (LABEL_EXPR, void_type_node, NULL_TREE);
237 t = build_and_jump (&LABEL_EXPR_LABEL (entry));
239 else
240 t = build_bc_goto (bc_continue);
241 append_to_statement_list (t, &stmt_list);
246 gimplify_stmt (&body);
247 gimplify_stmt (&incr);
249 body = finish_bc_block (bc_continue, cont_block, body);
251 append_to_statement_list (top, &stmt_list);
252 append_to_statement_list (body, &stmt_list);
253 append_to_statement_list (incr, &stmt_list);
254 append_to_statement_list (entry, &stmt_list);
255 append_to_statement_list (exit, &stmt_list);
257 annotate_all_with_locus (&stmt_list, stmt_locus);
259 return finish_bc_block (bc_break, break_block, stmt_list);
262 /* Gimplify a FOR_STMT node. Move the stuff in the for-init-stmt into the
263 prequeue and hand off to gimplify_cp_loop. */
265 static void
266 gimplify_for_stmt (tree *stmt_p, tree *pre_p)
268 tree stmt = *stmt_p;
270 if (FOR_INIT_STMT (stmt))
271 gimplify_and_add (FOR_INIT_STMT (stmt), pre_p);
273 *stmt_p = gimplify_cp_loop (FOR_COND (stmt), FOR_BODY (stmt),
274 FOR_EXPR (stmt), 1);
277 /* Gimplify a WHILE_STMT node. */
279 static void
280 gimplify_while_stmt (tree *stmt_p)
282 tree stmt = *stmt_p;
283 *stmt_p = gimplify_cp_loop (WHILE_COND (stmt), WHILE_BODY (stmt),
284 NULL_TREE, 1);
287 /* Gimplify a DO_STMT node. */
289 static void
290 gimplify_do_stmt (tree *stmt_p)
292 tree stmt = *stmt_p;
293 *stmt_p = gimplify_cp_loop (DO_COND (stmt), DO_BODY (stmt),
294 NULL_TREE, 0);
297 /* Genericize a SWITCH_STMT by turning it into a SWITCH_EXPR. */
299 static void
300 gimplify_switch_stmt (tree *stmt_p)
302 tree stmt = *stmt_p;
303 tree break_block, body;
304 location_t stmt_locus = input_location;
306 break_block = begin_bc_block (bc_break);
308 body = SWITCH_STMT_BODY (stmt);
309 if (!body)
310 body = build_empty_stmt ();
312 *stmt_p = build3 (SWITCH_EXPR, SWITCH_STMT_TYPE (stmt),
313 SWITCH_STMT_COND (stmt), body, NULL_TREE);
314 SET_EXPR_LOCATION (*stmt_p, stmt_locus);
315 gimplify_stmt (stmt_p);
317 *stmt_p = finish_bc_block (bc_break, break_block, *stmt_p);
320 /* Hook into the middle of gimplifying an OMP_FOR node. This is required
321 in order to properly gimplify CONTINUE statements. Here we merely
322 manage the continue stack; the rest of the job is performed by the
323 regular gimplifier. */
325 static enum gimplify_status
326 cp_gimplify_omp_for (tree *expr_p)
328 tree for_stmt = *expr_p;
329 tree cont_block;
331 /* Protect ourselves from recursion. */
332 if (OMP_FOR_GIMPLIFYING_P (for_stmt))
333 return GS_UNHANDLED;
334 OMP_FOR_GIMPLIFYING_P (for_stmt) = 1;
336 /* Note that while technically the continue label is enabled too soon
337 here, we should have already diagnosed invalid continues nested within
338 statement expressions within the INIT, COND, or INCR expressions. */
339 cont_block = begin_bc_block (bc_continue);
341 gimplify_stmt (expr_p);
343 OMP_FOR_BODY (for_stmt)
344 = finish_bc_block (bc_continue, cont_block, OMP_FOR_BODY (for_stmt));
345 OMP_FOR_GIMPLIFYING_P (for_stmt) = 0;
347 return GS_ALL_DONE;
350 /* Gimplify an EXPR_STMT node. */
352 static void
353 gimplify_expr_stmt (tree *stmt_p)
355 tree stmt = EXPR_STMT_EXPR (*stmt_p);
357 if (stmt == error_mark_node)
358 stmt = NULL;
360 /* Gimplification of a statement expression will nullify the
361 statement if all its side effects are moved to *PRE_P and *POST_P.
363 In this case we will not want to emit the gimplified statement.
364 However, we may still want to emit a warning, so we do that before
365 gimplification. */
366 if (stmt && (extra_warnings || warn_unused_value))
368 if (!TREE_SIDE_EFFECTS (stmt))
370 if (!IS_EMPTY_STMT (stmt)
371 && !VOID_TYPE_P (TREE_TYPE (stmt))
372 && !TREE_NO_WARNING (stmt))
373 warning (OPT_Wextra, "statement with no effect");
375 else if (warn_unused_value)
376 warn_if_unused_value (stmt, input_location);
379 if (stmt == NULL_TREE)
380 stmt = alloc_stmt_list ();
382 *stmt_p = stmt;
385 /* Gimplify initialization from an AGGR_INIT_EXPR. */
387 static void
388 cp_gimplify_init_expr (tree *expr_p, tree *pre_p, tree *post_p)
390 tree from = TREE_OPERAND (*expr_p, 1);
391 tree to = TREE_OPERAND (*expr_p, 0);
392 tree sub;
394 /* What about code that pulls out the temp and uses it elsewhere? I
395 think that such code never uses the TARGET_EXPR as an initializer. If
396 I'm wrong, we'll abort because the temp won't have any RTL. In that
397 case, I guess we'll need to replace references somehow. */
398 if (TREE_CODE (from) == TARGET_EXPR)
399 from = TARGET_EXPR_INITIAL (from);
401 /* Look through any COMPOUND_EXPRs, since build_compound_expr pushes them
402 inside the TARGET_EXPR. */
403 sub = expr_last (from);
405 /* If we are initializing from an AGGR_INIT_EXPR, drop the INIT_EXPR and
406 replace the slot operand with our target.
408 Should we add a target parm to gimplify_expr instead? No, as in this
409 case we want to replace the INIT_EXPR. */
410 if (TREE_CODE (sub) == AGGR_INIT_EXPR)
412 gimplify_expr (&to, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
413 TREE_OPERAND (sub, 2) = to;
414 *expr_p = from;
416 /* The initialization is now a side-effect, so the container can
417 become void. */
418 if (from != sub)
419 TREE_TYPE (from) = void_type_node;
423 /* Gimplify a MUST_NOT_THROW_EXPR. */
425 static void
426 gimplify_must_not_throw_expr (tree *expr_p, tree *pre_p)
428 tree stmt = *expr_p;
429 tree temp = voidify_wrapper_expr (stmt, NULL);
430 tree body = TREE_OPERAND (stmt, 0);
432 gimplify_stmt (&body);
434 stmt = gimple_build_eh_filter (body, NULL_TREE,
435 build_call (terminate_node, NULL_TREE));
437 if (temp)
439 append_to_statement_list (stmt, pre_p);
440 *expr_p = temp;
442 else
443 *expr_p = stmt;
446 /* Do C++-specific gimplification. Args are as for gimplify_expr. */
449 cp_gimplify_expr (tree *expr_p, tree *pre_p, tree *post_p)
451 int saved_stmts_are_full_exprs_p = 0;
452 enum tree_code code = TREE_CODE (*expr_p);
453 enum gimplify_status ret;
455 if (STATEMENT_CODE_P (code))
457 saved_stmts_are_full_exprs_p = stmts_are_full_exprs_p ();
458 current_stmt_tree ()->stmts_are_full_exprs_p
459 = STMT_IS_FULL_EXPR_P (*expr_p);
462 switch (code)
464 case PTRMEM_CST:
465 *expr_p = cplus_expand_constant (*expr_p);
466 ret = GS_OK;
467 break;
469 case AGGR_INIT_EXPR:
470 simplify_aggr_init_expr (expr_p);
471 ret = GS_OK;
472 break;
474 case THROW_EXPR:
475 /* FIXME communicate throw type to backend, probably by moving
476 THROW_EXPR into ../tree.def. */
477 *expr_p = TREE_OPERAND (*expr_p, 0);
478 ret = GS_OK;
479 break;
481 case MUST_NOT_THROW_EXPR:
482 gimplify_must_not_throw_expr (expr_p, pre_p);
483 ret = GS_OK;
484 break;
486 /* We used to do this for MODIFY_EXPR as well, but that's unsafe; the
487 LHS of an assignment might also be involved in the RHS, as in bug
488 25979. */
489 case INIT_EXPR:
490 cp_gimplify_init_expr (expr_p, pre_p, post_p);
491 ret = GS_OK;
492 break;
494 case EMPTY_CLASS_EXPR:
495 /* We create an empty CONSTRUCTOR with RECORD_TYPE. */
496 *expr_p = build_constructor (TREE_TYPE (*expr_p), NULL);
497 ret = GS_OK;
498 break;
500 case BASELINK:
501 *expr_p = BASELINK_FUNCTIONS (*expr_p);
502 ret = GS_OK;
503 break;
505 case TRY_BLOCK:
506 genericize_try_block (expr_p);
507 ret = GS_OK;
508 break;
510 case HANDLER:
511 genericize_catch_block (expr_p);
512 ret = GS_OK;
513 break;
515 case EH_SPEC_BLOCK:
516 genericize_eh_spec_block (expr_p);
517 ret = GS_OK;
518 break;
520 case USING_STMT:
521 /* Just ignore for now. Eventually we will want to pass this on to
522 the debugger. */
523 *expr_p = build_empty_stmt ();
524 ret = GS_ALL_DONE;
525 break;
527 case IF_STMT:
528 gimplify_if_stmt (expr_p);
529 ret = GS_OK;
530 break;
532 case FOR_STMT:
533 gimplify_for_stmt (expr_p, pre_p);
534 ret = GS_ALL_DONE;
535 break;
537 case WHILE_STMT:
538 gimplify_while_stmt (expr_p);
539 ret = GS_ALL_DONE;
540 break;
542 case DO_STMT:
543 gimplify_do_stmt (expr_p);
544 ret = GS_ALL_DONE;
545 break;
547 case SWITCH_STMT:
548 gimplify_switch_stmt (expr_p);
549 ret = GS_ALL_DONE;
550 break;
552 case OMP_FOR:
553 ret = cp_gimplify_omp_for (expr_p);
554 break;
556 case CONTINUE_STMT:
557 *expr_p = build_bc_goto (bc_continue);
558 ret = GS_ALL_DONE;
559 break;
561 case BREAK_STMT:
562 *expr_p = build_bc_goto (bc_break);
563 ret = GS_ALL_DONE;
564 break;
566 case EXPR_STMT:
567 gimplify_expr_stmt (expr_p);
568 ret = GS_OK;
569 break;
571 case UNARY_PLUS_EXPR:
573 tree arg = TREE_OPERAND (*expr_p, 0);
574 tree type = TREE_TYPE (*expr_p);
575 *expr_p = (TREE_TYPE (arg) != type) ? fold_convert (type, arg)
576 : arg;
577 ret = GS_OK;
579 break;
581 default:
582 ret = c_gimplify_expr (expr_p, pre_p, post_p);
583 break;
586 /* Restore saved state. */
587 if (STATEMENT_CODE_P (code))
588 current_stmt_tree ()->stmts_are_full_exprs_p
589 = saved_stmts_are_full_exprs_p;
591 return ret;
594 static inline bool
595 is_invisiref_parm (tree t)
597 return ((TREE_CODE (t) == PARM_DECL || TREE_CODE (t) == RESULT_DECL)
598 && DECL_BY_REFERENCE (t));
601 /* Return true if the uid in both int tree maps are equal. */
604 cxx_int_tree_map_eq (const void *va, const void *vb)
606 const struct cxx_int_tree_map *a = (const struct cxx_int_tree_map *) va;
607 const struct cxx_int_tree_map *b = (const struct cxx_int_tree_map *) vb;
608 return (a->uid == b->uid);
611 /* Hash a UID in a cxx_int_tree_map. */
613 unsigned int
614 cxx_int_tree_map_hash (const void *item)
616 return ((const struct cxx_int_tree_map *)item)->uid;
619 /* Perform any pre-gimplification lowering of C++ front end trees to
620 GENERIC. */
622 static tree
623 cp_genericize_r (tree *stmt_p, int *walk_subtrees, void *data)
625 tree stmt = *stmt_p;
626 struct pointer_set_t *p_set = (struct pointer_set_t*) data;
628 if (is_invisiref_parm (stmt)
629 /* Don't dereference parms in a thunk, pass the references through. */
630 && !(DECL_THUNK_P (current_function_decl)
631 && TREE_CODE (stmt) == PARM_DECL))
633 *stmt_p = convert_from_reference (stmt);
634 *walk_subtrees = 0;
635 return NULL;
638 /* Map block scope extern declarations to visible declarations with the
639 same name and type in outer scopes if any. */
640 if (cp_function_chain->extern_decl_map
641 && (TREE_CODE (stmt) == FUNCTION_DECL || TREE_CODE (stmt) == VAR_DECL)
642 && DECL_EXTERNAL (stmt))
644 struct cxx_int_tree_map *h, in;
645 in.uid = DECL_UID (stmt);
646 h = (struct cxx_int_tree_map *)
647 htab_find_with_hash (cp_function_chain->extern_decl_map,
648 &in, in.uid);
649 if (h)
651 *stmt_p = h->to;
652 *walk_subtrees = 0;
653 return NULL;
657 /* Other than invisiref parms, don't walk the same tree twice. */
658 if (pointer_set_contains (p_set, stmt))
660 *walk_subtrees = 0;
661 return NULL_TREE;
664 if (TREE_CODE (stmt) == ADDR_EXPR
665 && is_invisiref_parm (TREE_OPERAND (stmt, 0)))
667 *stmt_p = convert (TREE_TYPE (stmt), TREE_OPERAND (stmt, 0));
668 *walk_subtrees = 0;
670 else if (TREE_CODE (stmt) == RETURN_EXPR
671 && TREE_OPERAND (stmt, 0)
672 && is_invisiref_parm (TREE_OPERAND (stmt, 0)))
673 /* Don't dereference an invisiref RESULT_DECL inside a RETURN_EXPR. */
674 *walk_subtrees = 0;
675 else if (IS_TYPE_OR_DECL_P (stmt))
676 *walk_subtrees = 0;
678 /* Due to the way voidify_wrapper_expr is written, we don't get a chance
679 to lower this construct before scanning it, so we need to lower these
680 before doing anything else. */
681 else if (TREE_CODE (stmt) == CLEANUP_STMT)
682 *stmt_p = build2 (CLEANUP_EH_ONLY (stmt) ? TRY_CATCH_EXPR
683 : TRY_FINALLY_EXPR,
684 void_type_node,
685 CLEANUP_BODY (stmt),
686 CLEANUP_EXPR (stmt));
688 pointer_set_insert (p_set, *stmt_p);
690 return NULL;
693 void
694 cp_genericize (tree fndecl)
696 tree t;
697 struct pointer_set_t *p_set;
699 /* Fix up the types of parms passed by invisible reference. */
700 for (t = DECL_ARGUMENTS (fndecl); t; t = TREE_CHAIN (t))
701 if (TREE_ADDRESSABLE (TREE_TYPE (t)))
703 /* If a function's arguments are copied to create a thunk,
704 then DECL_BY_REFERENCE will be set -- but the type of the
705 argument will be a pointer type, so we will never get
706 here. */
707 gcc_assert (!DECL_BY_REFERENCE (t));
708 gcc_assert (DECL_ARG_TYPE (t) != TREE_TYPE (t));
709 TREE_TYPE (t) = DECL_ARG_TYPE (t);
710 DECL_BY_REFERENCE (t) = 1;
711 TREE_ADDRESSABLE (t) = 0;
712 relayout_decl (t);
715 /* Do the same for the return value. */
716 if (TREE_ADDRESSABLE (TREE_TYPE (DECL_RESULT (fndecl))))
718 t = DECL_RESULT (fndecl);
719 TREE_TYPE (t) = build_reference_type (TREE_TYPE (t));
720 DECL_BY_REFERENCE (t) = 1;
721 TREE_ADDRESSABLE (t) = 0;
722 relayout_decl (t);
725 /* If we're a clone, the body is already GIMPLE. */
726 if (DECL_CLONED_FUNCTION_P (fndecl))
727 return;
729 /* We do want to see every occurrence of the parms, so we can't just use
730 walk_tree's hash functionality. */
731 p_set = pointer_set_create ();
732 walk_tree (&DECL_SAVED_TREE (fndecl), cp_genericize_r, p_set, NULL);
733 pointer_set_destroy (p_set);
735 /* Do everything else. */
736 c_genericize (fndecl);
738 gcc_assert (bc_label[bc_break] == NULL);
739 gcc_assert (bc_label[bc_continue] == NULL);
742 /* Build code to apply FN to each member of ARG1 and ARG2. FN may be
743 NULL if there is in fact nothing to do. ARG2 may be null if FN
744 actually only takes one argument. */
746 static tree
747 cxx_omp_clause_apply_fn (tree fn, tree arg1, tree arg2)
749 tree defparm, parm;
750 int i;
752 if (fn == NULL)
753 return NULL;
755 defparm = TREE_CHAIN (TYPE_ARG_TYPES (TREE_TYPE (fn)));
756 if (arg2)
757 defparm = TREE_CHAIN (defparm);
759 if (TREE_CODE (TREE_TYPE (arg1)) == ARRAY_TYPE)
761 tree inner_type = TREE_TYPE (arg1);
762 tree start1, end1, p1;
763 tree start2 = NULL, p2 = NULL;
764 tree ret = NULL, lab, t;
766 start1 = arg1;
767 start2 = arg2;
770 inner_type = TREE_TYPE (inner_type);
771 start1 = build4 (ARRAY_REF, inner_type, start1,
772 size_zero_node, NULL, NULL);
773 if (arg2)
774 start2 = build4 (ARRAY_REF, inner_type, start2,
775 size_zero_node, NULL, NULL);
777 while (TREE_CODE (inner_type) == ARRAY_TYPE);
778 start1 = build_fold_addr_expr (start1);
779 if (arg2)
780 start2 = build_fold_addr_expr (start2);
782 end1 = TYPE_SIZE_UNIT (TREE_TYPE (arg1));
783 end1 = fold_convert (TREE_TYPE (start1), end1);
784 end1 = build2 (PLUS_EXPR, TREE_TYPE (start1), start1, end1);
786 p1 = create_tmp_var (TREE_TYPE (start1), NULL);
787 t = build2 (MODIFY_EXPR, void_type_node, p1, start1);
788 append_to_statement_list (t, &ret);
790 if (arg2)
792 p2 = create_tmp_var (TREE_TYPE (start2), NULL);
793 t = build2 (MODIFY_EXPR, void_type_node, p2, start2);
794 append_to_statement_list (t, &ret);
797 lab = create_artificial_label ();
798 t = build1 (LABEL_EXPR, void_type_node, lab);
799 append_to_statement_list (t, &ret);
801 t = tree_cons (NULL, p1, NULL);
802 if (arg2)
803 t = tree_cons (NULL, p2, t);
804 /* Handle default arguments. */
805 i = 1 + (arg2 != NULL);
806 for (parm = defparm; parm != void_list_node; parm = TREE_CHAIN (parm))
807 t = tree_cons (NULL, convert_default_arg (TREE_VALUE (parm),
808 TREE_PURPOSE (parm),
809 fn, i++), t);
810 t = build_call (fn, nreverse (t));
811 append_to_statement_list (t, &ret);
813 t = fold_convert (TREE_TYPE (p1), TYPE_SIZE_UNIT (inner_type));
814 t = build2 (PLUS_EXPR, TREE_TYPE (p1), p1, t);
815 t = build2 (MODIFY_EXPR, void_type_node, p1, t);
816 append_to_statement_list (t, &ret);
818 if (arg2)
820 t = fold_convert (TREE_TYPE (p2), TYPE_SIZE_UNIT (inner_type));
821 t = build2 (PLUS_EXPR, TREE_TYPE (p2), p2, t);
822 t = build2 (MODIFY_EXPR, void_type_node, p2, t);
823 append_to_statement_list (t, &ret);
826 t = build2 (NE_EXPR, boolean_type_node, p1, end1);
827 t = build3 (COND_EXPR, void_type_node, t, build_and_jump (&lab), NULL);
828 append_to_statement_list (t, &ret);
830 return ret;
832 else
834 tree t = tree_cons (NULL, build_fold_addr_expr (arg1), NULL);
835 if (arg2)
836 t = tree_cons (NULL, build_fold_addr_expr (arg2), t);
837 /* Handle default arguments. */
838 i = 1 + (arg2 != NULL);
839 for (parm = defparm; parm != void_list_node; parm = TREE_CHAIN (parm))
840 t = tree_cons (NULL, convert_default_arg (TREE_VALUE (parm),
841 TREE_PURPOSE (parm),
842 fn, i++), t);
843 return build_call (fn, nreverse (t));
847 /* Return code to initialize DECL with its default constructor, or
848 NULL if there's nothing to do. */
850 tree
851 cxx_omp_clause_default_ctor (tree clause, tree decl)
853 tree info = CP_OMP_CLAUSE_INFO (clause);
854 tree ret = NULL;
856 if (info)
857 ret = cxx_omp_clause_apply_fn (TREE_VEC_ELT (info, 0), decl, NULL);
859 return ret;
862 /* Return code to initialize DST with a copy constructor from SRC. */
864 tree
865 cxx_omp_clause_copy_ctor (tree clause, tree dst, tree src)
867 tree info = CP_OMP_CLAUSE_INFO (clause);
868 tree ret = NULL;
870 if (info)
871 ret = cxx_omp_clause_apply_fn (TREE_VEC_ELT (info, 0), dst, src);
872 if (ret == NULL)
873 ret = build2 (MODIFY_EXPR, void_type_node, dst, src);
875 return ret;
878 /* Similarly, except use an assignment operator instead. */
880 tree
881 cxx_omp_clause_assign_op (tree clause, tree dst, tree src)
883 tree info = CP_OMP_CLAUSE_INFO (clause);
884 tree ret = NULL;
886 if (info)
887 ret = cxx_omp_clause_apply_fn (TREE_VEC_ELT (info, 2), dst, src);
888 if (ret == NULL)
889 ret = build2 (MODIFY_EXPR, void_type_node, dst, src);
891 return ret;
894 /* Return code to destroy DECL. */
896 tree
897 cxx_omp_clause_dtor (tree clause, tree decl)
899 tree info = CP_OMP_CLAUSE_INFO (clause);
900 tree ret = NULL;
902 if (info)
903 ret = cxx_omp_clause_apply_fn (TREE_VEC_ELT (info, 1), decl, NULL);
905 return ret;
908 /* True if OpenMP should privatize what this DECL points to rather
909 than the DECL itself. */
911 bool
912 cxx_omp_privatize_by_reference (tree decl)
914 return TREE_CODE (decl) == RESULT_DECL && DECL_BY_REFERENCE (decl);