1 /* Tree lowering pass. This pass converts the GENERIC functions-as-trees
2 tree representation into the GIMPLE form.
3 Copyright (C) 2002-2015 Free Software Foundation, Inc.
4 Major work done by Sebastian Pop <s.pop@laposte.net>,
5 Diego Novillo <dnovillo@redhat.com> and Jason Merrill <jason@redhat.com>.
7 This file is part of GCC.
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 3, or (at your option) any later
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING3. If not see
21 <http://www.gnu.org/licenses/>. */
25 #include "coretypes.h"
31 #include "gimple-predict.h"
32 #include "tree-pass.h" /* FIXME: only for PROP_gimple_any */
35 #include "tree-pretty-print.h"
36 #include "diagnostic-core.h"
38 #include "fold-const.h"
43 #include "gimple-fold.h"
46 #include "gimple-iterator.h"
47 #include "stor-layout.h"
48 #include "print-tree.h"
49 #include "tree-iterator.h"
50 #include "tree-inline.h"
51 #include "langhooks.h"
55 #include "gimple-low.h"
57 #include "gomp-constants.h"
58 #include "tree-dump.h"
59 #include "gimple-walk.h"
60 #include "langhooks-def.h" /* FIXME: for lhd_set_decl_assembler_name */
63 enum gimplify_omp_var_data
69 GOVD_FIRSTPRIVATE
= 16,
70 GOVD_LASTPRIVATE
= 32,
74 GOVD_DEBUG_PRIVATE
= 512,
75 GOVD_PRIVATE_OUTER_REF
= 1024,
79 /* Flag for GOVD_MAP: don't copy back. */
80 GOVD_MAP_TO_ONLY
= 8192,
82 /* Flag for GOVD_LINEAR or GOVD_LASTPRIVATE: no outer reference. */
83 GOVD_LINEAR_LASTPRIVATE_NO_OUTER
= 16384,
85 GOVD_MAP_0LEN_ARRAY
= 32768,
87 /* Flag for GOVD_MAP, if it is always, to or always, tofrom mapping. */
88 GOVD_MAP_ALWAYS_TO
= 65536,
90 /* Flag for shared vars that are or might be stored to in the region. */
91 GOVD_WRITTEN
= 131072,
93 /* Flag for GOVD_MAP, if it is a forced mapping. */
94 GOVD_MAP_FORCE
= 262144,
96 GOVD_DATA_SHARE_CLASS
= (GOVD_SHARED
| GOVD_PRIVATE
| GOVD_FIRSTPRIVATE
97 | GOVD_LASTPRIVATE
| GOVD_REDUCTION
| GOVD_LINEAR
104 ORT_WORKSHARE
= 0x00,
108 ORT_COMBINED_PARALLEL
= 0x03,
111 ORT_UNTIED_TASK
= 0x05,
114 ORT_COMBINED_TEAMS
= 0x09,
117 ORT_TARGET_DATA
= 0x10,
119 /* Data region with offloading. */
121 ORT_COMBINED_TARGET
= 0x21,
123 /* OpenACC variants. */
124 ORT_ACC
= 0x40, /* A generic OpenACC region. */
125 ORT_ACC_DATA
= ORT_ACC
| ORT_TARGET_DATA
, /* Data construct. */
126 ORT_ACC_PARALLEL
= ORT_ACC
| ORT_TARGET
, /* Parallel construct */
127 ORT_ACC_KERNELS
= ORT_ACC
| ORT_TARGET
| 0x80, /* Kernels construct. */
128 ORT_ACC_HOST_DATA
= ORT_ACC
| ORT_TARGET_DATA
| 0x80, /* Host data. */
130 /* Dummy OpenMP region, used to disable expansion of
131 DECL_VALUE_EXPRs in taskloop pre body. */
135 /* Gimplify hashtable helper. */
137 struct gimplify_hasher
: free_ptr_hash
<elt_t
>
139 static inline hashval_t
hash (const elt_t
*);
140 static inline bool equal (const elt_t
*, const elt_t
*);
145 struct gimplify_ctx
*prev_context
;
147 vec
<gbind
*> bind_expr_stack
;
149 gimple_seq conditional_cleanups
;
153 vec
<tree
> case_labels
;
154 /* The formal temporary table. Should this be persistent? */
155 hash_table
<gimplify_hasher
> *temp_htab
;
160 bool allow_rhs_cond_expr
;
161 bool in_cleanup_point_expr
;
164 struct gimplify_omp_ctx
166 struct gimplify_omp_ctx
*outer_context
;
167 splay_tree variables
;
168 hash_set
<tree
> *privatized_types
;
169 /* Iteration variables in an OMP_FOR. */
170 vec
<tree
> loop_iter_var
;
172 enum omp_clause_default_kind default_kind
;
173 enum omp_region_type region_type
;
176 bool target_map_scalars_firstprivate
;
177 bool target_map_pointers_as_0len_arrays
;
178 bool target_firstprivatize_array_bases
;
181 static struct gimplify_ctx
*gimplify_ctxp
;
182 static struct gimplify_omp_ctx
*gimplify_omp_ctxp
;
184 /* Forward declaration. */
185 static enum gimplify_status
gimplify_compound_expr (tree
*, gimple_seq
*, bool);
186 static hash_map
<tree
, tree
> *oacc_declare_returns
;
188 /* Shorter alias name for the above function for use in gimplify.c
192 gimplify_seq_add_stmt (gimple_seq
*seq_p
, gimple
*gs
)
194 gimple_seq_add_stmt_without_update (seq_p
, gs
);
197 /* Append sequence SRC to the end of sequence *DST_P. If *DST_P is
198 NULL, a new sequence is allocated. This function is
199 similar to gimple_seq_add_seq, but does not scan the operands.
200 During gimplification, we need to manipulate statement sequences
201 before the def/use vectors have been constructed. */
204 gimplify_seq_add_seq (gimple_seq
*dst_p
, gimple_seq src
)
206 gimple_stmt_iterator si
;
211 si
= gsi_last (*dst_p
);
212 gsi_insert_seq_after_without_update (&si
, src
, GSI_NEW_STMT
);
216 /* Pointer to a list of allocated gimplify_ctx structs to be used for pushing
217 and popping gimplify contexts. */
219 static struct gimplify_ctx
*ctx_pool
= NULL
;
221 /* Return a gimplify context struct from the pool. */
223 static inline struct gimplify_ctx
*
226 struct gimplify_ctx
* c
= ctx_pool
;
229 ctx_pool
= c
->prev_context
;
231 c
= XNEW (struct gimplify_ctx
);
233 memset (c
, '\0', sizeof (*c
));
237 /* Put gimplify context C back into the pool. */
240 ctx_free (struct gimplify_ctx
*c
)
242 c
->prev_context
= ctx_pool
;
246 /* Free allocated ctx stack memory. */
249 free_gimplify_stack (void)
251 struct gimplify_ctx
*c
;
253 while ((c
= ctx_pool
))
255 ctx_pool
= c
->prev_context
;
261 /* Set up a context for the gimplifier. */
264 push_gimplify_context (bool in_ssa
, bool rhs_cond_ok
)
266 struct gimplify_ctx
*c
= ctx_alloc ();
268 c
->prev_context
= gimplify_ctxp
;
270 gimplify_ctxp
->into_ssa
= in_ssa
;
271 gimplify_ctxp
->allow_rhs_cond_expr
= rhs_cond_ok
;
274 /* Tear down a context for the gimplifier. If BODY is non-null, then
275 put the temporaries into the outer BIND_EXPR. Otherwise, put them
278 BODY is not a sequence, but the first tuple in a sequence. */
281 pop_gimplify_context (gimple
*body
)
283 struct gimplify_ctx
*c
= gimplify_ctxp
;
286 && (!c
->bind_expr_stack
.exists ()
287 || c
->bind_expr_stack
.is_empty ()));
288 c
->bind_expr_stack
.release ();
289 gimplify_ctxp
= c
->prev_context
;
292 declare_vars (c
->temps
, body
, false);
294 record_vars (c
->temps
);
301 /* Push a GIMPLE_BIND tuple onto the stack of bindings. */
304 gimple_push_bind_expr (gbind
*bind_stmt
)
306 gimplify_ctxp
->bind_expr_stack
.reserve (8);
307 gimplify_ctxp
->bind_expr_stack
.safe_push (bind_stmt
);
310 /* Pop the first element off the stack of bindings. */
313 gimple_pop_bind_expr (void)
315 gimplify_ctxp
->bind_expr_stack
.pop ();
318 /* Return the first element of the stack of bindings. */
321 gimple_current_bind_expr (void)
323 return gimplify_ctxp
->bind_expr_stack
.last ();
326 /* Return the stack of bindings created during gimplification. */
329 gimple_bind_expr_stack (void)
331 return gimplify_ctxp
->bind_expr_stack
;
334 /* Return true iff there is a COND_EXPR between us and the innermost
335 CLEANUP_POINT_EXPR. This info is used by gimple_push_cleanup. */
338 gimple_conditional_context (void)
340 return gimplify_ctxp
->conditions
> 0;
343 /* Note that we've entered a COND_EXPR. */
346 gimple_push_condition (void)
348 #ifdef ENABLE_GIMPLE_CHECKING
349 if (gimplify_ctxp
->conditions
== 0)
350 gcc_assert (gimple_seq_empty_p (gimplify_ctxp
->conditional_cleanups
));
352 ++(gimplify_ctxp
->conditions
);
355 /* Note that we've left a COND_EXPR. If we're back at unconditional scope
356 now, add any conditional cleanups we've seen to the prequeue. */
359 gimple_pop_condition (gimple_seq
*pre_p
)
361 int conds
= --(gimplify_ctxp
->conditions
);
363 gcc_assert (conds
>= 0);
366 gimplify_seq_add_seq (pre_p
, gimplify_ctxp
->conditional_cleanups
);
367 gimplify_ctxp
->conditional_cleanups
= NULL
;
371 /* A stable comparison routine for use with splay trees and DECLs. */
374 splay_tree_compare_decl_uid (splay_tree_key xa
, splay_tree_key xb
)
379 return DECL_UID (a
) - DECL_UID (b
);
382 /* Create a new omp construct that deals with variable remapping. */
384 static struct gimplify_omp_ctx
*
385 new_omp_context (enum omp_region_type region_type
)
387 struct gimplify_omp_ctx
*c
;
389 c
= XCNEW (struct gimplify_omp_ctx
);
390 c
->outer_context
= gimplify_omp_ctxp
;
391 c
->variables
= splay_tree_new (splay_tree_compare_decl_uid
, 0, 0);
392 c
->privatized_types
= new hash_set
<tree
>;
393 c
->location
= input_location
;
394 c
->region_type
= region_type
;
395 if ((region_type
& ORT_TASK
) == 0)
396 c
->default_kind
= OMP_CLAUSE_DEFAULT_SHARED
;
398 c
->default_kind
= OMP_CLAUSE_DEFAULT_UNSPECIFIED
;
403 /* Destroy an omp construct that deals with variable remapping. */
406 delete_omp_context (struct gimplify_omp_ctx
*c
)
408 splay_tree_delete (c
->variables
);
409 delete c
->privatized_types
;
410 c
->loop_iter_var
.release ();
414 static void omp_add_variable (struct gimplify_omp_ctx
*, tree
, unsigned int);
415 static bool omp_notice_variable (struct gimplify_omp_ctx
*, tree
, bool);
417 /* Both gimplify the statement T and append it to *SEQ_P. This function
418 behaves exactly as gimplify_stmt, but you don't have to pass T as a
422 gimplify_and_add (tree t
, gimple_seq
*seq_p
)
424 gimplify_stmt (&t
, seq_p
);
427 /* Gimplify statement T into sequence *SEQ_P, and return the first
428 tuple in the sequence of generated tuples for this statement.
429 Return NULL if gimplifying T produced no tuples. */
432 gimplify_and_return_first (tree t
, gimple_seq
*seq_p
)
434 gimple_stmt_iterator last
= gsi_last (*seq_p
);
436 gimplify_and_add (t
, seq_p
);
438 if (!gsi_end_p (last
))
441 return gsi_stmt (last
);
444 return gimple_seq_first_stmt (*seq_p
);
447 /* Returns true iff T is a valid RHS for an assignment to an un-renamed
448 LHS, or for a call argument. */
451 is_gimple_mem_rhs (tree t
)
453 /* If we're dealing with a renamable type, either source or dest must be
454 a renamed variable. */
455 if (is_gimple_reg_type (TREE_TYPE (t
)))
456 return is_gimple_val (t
);
458 return is_gimple_val (t
) || is_gimple_lvalue (t
);
461 /* Return true if T is a CALL_EXPR or an expression that can be
462 assigned to a temporary. Note that this predicate should only be
463 used during gimplification. See the rationale for this in
464 gimplify_modify_expr. */
467 is_gimple_reg_rhs_or_call (tree t
)
469 return (get_gimple_rhs_class (TREE_CODE (t
)) != GIMPLE_INVALID_RHS
470 || TREE_CODE (t
) == CALL_EXPR
);
473 /* Return true if T is a valid memory RHS or a CALL_EXPR. Note that
474 this predicate should only be used during gimplification. See the
475 rationale for this in gimplify_modify_expr. */
478 is_gimple_mem_rhs_or_call (tree t
)
480 /* If we're dealing with a renamable type, either source or dest must be
481 a renamed variable. */
482 if (is_gimple_reg_type (TREE_TYPE (t
)))
483 return is_gimple_val (t
);
485 return (is_gimple_val (t
) || is_gimple_lvalue (t
)
486 || TREE_CODE (t
) == CALL_EXPR
);
489 /* Create a temporary with a name derived from VAL. Subroutine of
490 lookup_tmp_var; nobody else should call this function. */
493 create_tmp_from_val (tree val
)
495 /* Drop all qualifiers and address-space information from the value type. */
496 tree type
= TYPE_MAIN_VARIANT (TREE_TYPE (val
));
497 tree var
= create_tmp_var (type
, get_name (val
));
498 if (TREE_CODE (TREE_TYPE (var
)) == COMPLEX_TYPE
499 || TREE_CODE (TREE_TYPE (var
)) == VECTOR_TYPE
)
500 DECL_GIMPLE_REG_P (var
) = 1;
504 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
505 an existing expression temporary. */
508 lookup_tmp_var (tree val
, bool is_formal
)
512 /* If not optimizing, never really reuse a temporary. local-alloc
513 won't allocate any variable that is used in more than one basic
514 block, which means it will go into memory, causing much extra
515 work in reload and final and poorer code generation, outweighing
516 the extra memory allocation here. */
517 if (!optimize
|| !is_formal
|| TREE_SIDE_EFFECTS (val
))
518 ret
= create_tmp_from_val (val
);
525 if (!gimplify_ctxp
->temp_htab
)
526 gimplify_ctxp
->temp_htab
= new hash_table
<gimplify_hasher
> (1000);
527 slot
= gimplify_ctxp
->temp_htab
->find_slot (&elt
, INSERT
);
530 elt_p
= XNEW (elt_t
);
532 elt_p
->temp
= ret
= create_tmp_from_val (val
);
545 /* Helper for get_formal_tmp_var and get_initialized_tmp_var. */
548 internal_get_tmp_var (tree val
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
553 /* Notice that we explicitly allow VAL to be a CALL_EXPR so that we
554 can create an INIT_EXPR and convert it into a GIMPLE_CALL below. */
555 gimplify_expr (&val
, pre_p
, post_p
, is_gimple_reg_rhs_or_call
,
558 if (gimplify_ctxp
->into_ssa
559 && is_gimple_reg_type (TREE_TYPE (val
)))
560 t
= make_ssa_name (TYPE_MAIN_VARIANT (TREE_TYPE (val
)));
562 t
= lookup_tmp_var (val
, is_formal
);
564 mod
= build2 (INIT_EXPR
, TREE_TYPE (t
), t
, unshare_expr (val
));
566 SET_EXPR_LOCATION (mod
, EXPR_LOC_OR_LOC (val
, input_location
));
568 /* gimplify_modify_expr might want to reduce this further. */
569 gimplify_and_add (mod
, pre_p
);
575 /* Return a formal temporary variable initialized with VAL. PRE_P is as
576 in gimplify_expr. Only use this function if:
578 1) The value of the unfactored expression represented by VAL will not
579 change between the initialization and use of the temporary, and
580 2) The temporary will not be otherwise modified.
582 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
583 and #2 means it is inappropriate for && temps.
585 For other cases, use get_initialized_tmp_var instead. */
588 get_formal_tmp_var (tree val
, gimple_seq
*pre_p
)
590 return internal_get_tmp_var (val
, pre_p
, NULL
, true);
593 /* Return a temporary variable initialized with VAL. PRE_P and POST_P
594 are as in gimplify_expr. */
597 get_initialized_tmp_var (tree val
, gimple_seq
*pre_p
, gimple_seq
*post_p
)
599 return internal_get_tmp_var (val
, pre_p
, post_p
, false);
602 /* Declare all the variables in VARS in SCOPE. If DEBUG_INFO is true,
603 generate debug info for them; otherwise don't. */
606 declare_vars (tree vars
, gimple
*gs
, bool debug_info
)
613 gbind
*scope
= as_a
<gbind
*> (gs
);
615 temps
= nreverse (last
);
617 block
= gimple_bind_block (scope
);
618 gcc_assert (!block
|| TREE_CODE (block
) == BLOCK
);
619 if (!block
|| !debug_info
)
621 DECL_CHAIN (last
) = gimple_bind_vars (scope
);
622 gimple_bind_set_vars (scope
, temps
);
626 /* We need to attach the nodes both to the BIND_EXPR and to its
627 associated BLOCK for debugging purposes. The key point here
628 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
629 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
630 if (BLOCK_VARS (block
))
631 BLOCK_VARS (block
) = chainon (BLOCK_VARS (block
), temps
);
634 gimple_bind_set_vars (scope
,
635 chainon (gimple_bind_vars (scope
), temps
));
636 BLOCK_VARS (block
) = temps
;
642 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
643 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
644 no such upper bound can be obtained. */
647 force_constant_size (tree var
)
649 /* The only attempt we make is by querying the maximum size of objects
650 of the variable's type. */
652 HOST_WIDE_INT max_size
;
654 gcc_assert (TREE_CODE (var
) == VAR_DECL
);
656 max_size
= max_int_size_in_bytes (TREE_TYPE (var
));
658 gcc_assert (max_size
>= 0);
661 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var
)), max_size
);
663 = build_int_cst (TREE_TYPE (DECL_SIZE (var
)), max_size
* BITS_PER_UNIT
);
666 /* Push the temporary variable TMP into the current binding. */
669 gimple_add_tmp_var_fn (struct function
*fn
, tree tmp
)
671 gcc_assert (!DECL_CHAIN (tmp
) && !DECL_SEEN_IN_BIND_EXPR_P (tmp
));
673 /* Later processing assumes that the object size is constant, which might
674 not be true at this point. Force the use of a constant upper bound in
676 if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (tmp
)))
677 force_constant_size (tmp
);
679 DECL_CONTEXT (tmp
) = fn
->decl
;
680 DECL_SEEN_IN_BIND_EXPR_P (tmp
) = 1;
682 record_vars_into (tmp
, fn
->decl
);
685 /* Push the temporary variable TMP into the current binding. */
688 gimple_add_tmp_var (tree tmp
)
690 gcc_assert (!DECL_CHAIN (tmp
) && !DECL_SEEN_IN_BIND_EXPR_P (tmp
));
692 /* Later processing assumes that the object size is constant, which might
693 not be true at this point. Force the use of a constant upper bound in
695 if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (tmp
)))
696 force_constant_size (tmp
);
698 DECL_CONTEXT (tmp
) = current_function_decl
;
699 DECL_SEEN_IN_BIND_EXPR_P (tmp
) = 1;
703 DECL_CHAIN (tmp
) = gimplify_ctxp
->temps
;
704 gimplify_ctxp
->temps
= tmp
;
706 /* Mark temporaries local within the nearest enclosing parallel. */
707 if (gimplify_omp_ctxp
)
709 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
711 && (ctx
->region_type
== ORT_WORKSHARE
712 || ctx
->region_type
== ORT_SIMD
713 || ctx
->region_type
== ORT_ACC
))
714 ctx
= ctx
->outer_context
;
716 omp_add_variable (ctx
, tmp
, GOVD_LOCAL
| GOVD_SEEN
);
725 /* This case is for nested functions. We need to expose the locals
727 body_seq
= gimple_body (current_function_decl
);
728 declare_vars (tmp
, gimple_seq_first_stmt (body_seq
), false);
734 /* This page contains routines to unshare tree nodes, i.e. to duplicate tree
735 nodes that are referenced more than once in GENERIC functions. This is
736 necessary because gimplification (translation into GIMPLE) is performed
737 by modifying tree nodes in-place, so gimplication of a shared node in a
738 first context could generate an invalid GIMPLE form in a second context.
740 This is achieved with a simple mark/copy/unmark algorithm that walks the
741 GENERIC representation top-down, marks nodes with TREE_VISITED the first
742 time it encounters them, duplicates them if they already have TREE_VISITED
743 set, and finally removes the TREE_VISITED marks it has set.
745 The algorithm works only at the function level, i.e. it generates a GENERIC
746 representation of a function with no nodes shared within the function when
747 passed a GENERIC function (except for nodes that are allowed to be shared).
749 At the global level, it is also necessary to unshare tree nodes that are
750 referenced in more than one function, for the same aforementioned reason.
751 This requires some cooperation from the front-end. There are 2 strategies:
753 1. Manual unsharing. The front-end needs to call unshare_expr on every
754 expression that might end up being shared across functions.
756 2. Deep unsharing. This is an extension of regular unsharing. Instead
757 of calling unshare_expr on expressions that might be shared across
758 functions, the front-end pre-marks them with TREE_VISITED. This will
759 ensure that they are unshared on the first reference within functions
760 when the regular unsharing algorithm runs. The counterpart is that
761 this algorithm must look deeper than for manual unsharing, which is
762 specified by LANG_HOOKS_DEEP_UNSHARING.
764 If there are only few specific cases of node sharing across functions, it is
765 probably easier for a front-end to unshare the expressions manually. On the
766 contrary, if the expressions generated at the global level are as widespread
767 as expressions generated within functions, deep unsharing is very likely the
770 /* Similar to copy_tree_r but do not copy SAVE_EXPR or TARGET_EXPR nodes.
771 These nodes model computations that must be done once. If we were to
772 unshare something like SAVE_EXPR(i++), the gimplification process would
773 create wrong code. However, if DATA is non-null, it must hold a pointer
774 set that is used to unshare the subtrees of these nodes. */
777 mostly_copy_tree_r (tree
*tp
, int *walk_subtrees
, void *data
)
780 enum tree_code code
= TREE_CODE (t
);
782 /* Do not copy SAVE_EXPR, TARGET_EXPR or BIND_EXPR nodes themselves, but
783 copy their subtrees if we can make sure to do it only once. */
784 if (code
== SAVE_EXPR
|| code
== TARGET_EXPR
|| code
== BIND_EXPR
)
786 if (data
&& !((hash_set
<tree
> *)data
)->add (t
))
792 /* Stop at types, decls, constants like copy_tree_r. */
793 else if (TREE_CODE_CLASS (code
) == tcc_type
794 || TREE_CODE_CLASS (code
) == tcc_declaration
795 || TREE_CODE_CLASS (code
) == tcc_constant
796 /* We can't do anything sensible with a BLOCK used as an
797 expression, but we also can't just die when we see it
798 because of non-expression uses. So we avert our eyes
799 and cross our fingers. Silly Java. */
803 /* Cope with the statement expression extension. */
804 else if (code
== STATEMENT_LIST
)
807 /* Leave the bulk of the work to copy_tree_r itself. */
809 copy_tree_r (tp
, walk_subtrees
, NULL
);
814 /* Callback for walk_tree to unshare most of the shared trees rooted at *TP.
815 If *TP has been visited already, then *TP is deeply copied by calling
816 mostly_copy_tree_r. DATA is passed to mostly_copy_tree_r unmodified. */
819 copy_if_shared_r (tree
*tp
, int *walk_subtrees
, void *data
)
822 enum tree_code code
= TREE_CODE (t
);
824 /* Skip types, decls, and constants. But we do want to look at their
825 types and the bounds of types. Mark them as visited so we properly
826 unmark their subtrees on the unmark pass. If we've already seen them,
827 don't look down further. */
828 if (TREE_CODE_CLASS (code
) == tcc_type
829 || TREE_CODE_CLASS (code
) == tcc_declaration
830 || TREE_CODE_CLASS (code
) == tcc_constant
)
832 if (TREE_VISITED (t
))
835 TREE_VISITED (t
) = 1;
838 /* If this node has been visited already, unshare it and don't look
840 else if (TREE_VISITED (t
))
842 walk_tree (tp
, mostly_copy_tree_r
, data
, NULL
);
846 /* Otherwise, mark the node as visited and keep looking. */
848 TREE_VISITED (t
) = 1;
853 /* Unshare most of the shared trees rooted at *TP. DATA is passed to the
854 copy_if_shared_r callback unmodified. */
857 copy_if_shared (tree
*tp
, void *data
)
859 walk_tree (tp
, copy_if_shared_r
, data
, NULL
);
862 /* Unshare all the trees in the body of FNDECL, as well as in the bodies of
863 any nested functions. */
866 unshare_body (tree fndecl
)
868 struct cgraph_node
*cgn
= cgraph_node::get (fndecl
);
869 /* If the language requires deep unsharing, we need a pointer set to make
870 sure we don't repeatedly unshare subtrees of unshareable nodes. */
871 hash_set
<tree
> *visited
872 = lang_hooks
.deep_unsharing
? new hash_set
<tree
> : NULL
;
874 copy_if_shared (&DECL_SAVED_TREE (fndecl
), visited
);
875 copy_if_shared (&DECL_SIZE (DECL_RESULT (fndecl
)), visited
);
876 copy_if_shared (&DECL_SIZE_UNIT (DECL_RESULT (fndecl
)), visited
);
881 for (cgn
= cgn
->nested
; cgn
; cgn
= cgn
->next_nested
)
882 unshare_body (cgn
->decl
);
885 /* Callback for walk_tree to unmark the visited trees rooted at *TP.
886 Subtrees are walked until the first unvisited node is encountered. */
889 unmark_visited_r (tree
*tp
, int *walk_subtrees
, void *data ATTRIBUTE_UNUSED
)
893 /* If this node has been visited, unmark it and keep looking. */
894 if (TREE_VISITED (t
))
895 TREE_VISITED (t
) = 0;
897 /* Otherwise, don't look any deeper. */
904 /* Unmark the visited trees rooted at *TP. */
907 unmark_visited (tree
*tp
)
909 walk_tree (tp
, unmark_visited_r
, NULL
, NULL
);
912 /* Likewise, but mark all trees as not visited. */
915 unvisit_body (tree fndecl
)
917 struct cgraph_node
*cgn
= cgraph_node::get (fndecl
);
919 unmark_visited (&DECL_SAVED_TREE (fndecl
));
920 unmark_visited (&DECL_SIZE (DECL_RESULT (fndecl
)));
921 unmark_visited (&DECL_SIZE_UNIT (DECL_RESULT (fndecl
)));
924 for (cgn
= cgn
->nested
; cgn
; cgn
= cgn
->next_nested
)
925 unvisit_body (cgn
->decl
);
928 /* Unconditionally make an unshared copy of EXPR. This is used when using
929 stored expressions which span multiple functions, such as BINFO_VTABLE,
930 as the normal unsharing process can't tell that they're shared. */
933 unshare_expr (tree expr
)
935 walk_tree (&expr
, mostly_copy_tree_r
, NULL
, NULL
);
939 /* Worker for unshare_expr_without_location. */
942 prune_expr_location (tree
*tp
, int *walk_subtrees
, void *)
945 SET_EXPR_LOCATION (*tp
, UNKNOWN_LOCATION
);
951 /* Similar to unshare_expr but also prune all expression locations
955 unshare_expr_without_location (tree expr
)
957 walk_tree (&expr
, mostly_copy_tree_r
, NULL
, NULL
);
959 walk_tree (&expr
, prune_expr_location
, NULL
, NULL
);
963 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
964 contain statements and have a value. Assign its value to a temporary
965 and give it void_type_node. Return the temporary, or NULL_TREE if
966 WRAPPER was already void. */
969 voidify_wrapper_expr (tree wrapper
, tree temp
)
971 tree type
= TREE_TYPE (wrapper
);
972 if (type
&& !VOID_TYPE_P (type
))
976 /* Set p to point to the body of the wrapper. Loop until we find
977 something that isn't a wrapper. */
978 for (p
= &wrapper
; p
&& *p
; )
980 switch (TREE_CODE (*p
))
983 TREE_SIDE_EFFECTS (*p
) = 1;
984 TREE_TYPE (*p
) = void_type_node
;
985 /* For a BIND_EXPR, the body is operand 1. */
986 p
= &BIND_EXPR_BODY (*p
);
989 case CLEANUP_POINT_EXPR
:
990 case TRY_FINALLY_EXPR
:
992 TREE_SIDE_EFFECTS (*p
) = 1;
993 TREE_TYPE (*p
) = void_type_node
;
994 p
= &TREE_OPERAND (*p
, 0);
999 tree_stmt_iterator i
= tsi_last (*p
);
1000 TREE_SIDE_EFFECTS (*p
) = 1;
1001 TREE_TYPE (*p
) = void_type_node
;
1002 p
= tsi_end_p (i
) ? NULL
: tsi_stmt_ptr (i
);
1007 /* Advance to the last statement. Set all container types to
1009 for (; TREE_CODE (*p
) == COMPOUND_EXPR
; p
= &TREE_OPERAND (*p
, 1))
1011 TREE_SIDE_EFFECTS (*p
) = 1;
1012 TREE_TYPE (*p
) = void_type_node
;
1016 case TRANSACTION_EXPR
:
1017 TREE_SIDE_EFFECTS (*p
) = 1;
1018 TREE_TYPE (*p
) = void_type_node
;
1019 p
= &TRANSACTION_EXPR_BODY (*p
);
1023 /* Assume that any tree upon which voidify_wrapper_expr is
1024 directly called is a wrapper, and that its body is op0. */
1027 TREE_SIDE_EFFECTS (*p
) = 1;
1028 TREE_TYPE (*p
) = void_type_node
;
1029 p
= &TREE_OPERAND (*p
, 0);
1037 if (p
== NULL
|| IS_EMPTY_STMT (*p
))
1041 /* The wrapper is on the RHS of an assignment that we're pushing
1043 gcc_assert (TREE_CODE (temp
) == INIT_EXPR
1044 || TREE_CODE (temp
) == MODIFY_EXPR
);
1045 TREE_OPERAND (temp
, 1) = *p
;
1050 temp
= create_tmp_var (type
, "retval");
1051 *p
= build2 (INIT_EXPR
, type
, temp
, *p
);
1060 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1061 a temporary through which they communicate. */
1064 build_stack_save_restore (gcall
**save
, gcall
**restore
)
1068 *save
= gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_SAVE
), 0);
1069 tmp_var
= create_tmp_var (ptr_type_node
, "saved_stack");
1070 gimple_call_set_lhs (*save
, tmp_var
);
1073 = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_RESTORE
),
1077 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1079 static enum gimplify_status
1080 gimplify_bind_expr (tree
*expr_p
, gimple_seq
*pre_p
)
1082 tree bind_expr
= *expr_p
;
1083 bool old_save_stack
= gimplify_ctxp
->save_stack
;
1086 gimple_seq body
, cleanup
;
1088 location_t start_locus
= 0, end_locus
= 0;
1089 tree ret_clauses
= NULL
;
1091 tree temp
= voidify_wrapper_expr (bind_expr
, NULL
);
1093 /* Mark variables seen in this bind expr. */
1094 for (t
= BIND_EXPR_VARS (bind_expr
); t
; t
= DECL_CHAIN (t
))
1096 if (TREE_CODE (t
) == VAR_DECL
)
1098 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
1100 /* Mark variable as local. */
1101 if (ctx
&& ctx
->region_type
!= ORT_NONE
&& !DECL_EXTERNAL (t
)
1102 && (! DECL_SEEN_IN_BIND_EXPR_P (t
)
1103 || splay_tree_lookup (ctx
->variables
,
1104 (splay_tree_key
) t
) == NULL
))
1106 if (ctx
->region_type
== ORT_SIMD
1107 && TREE_ADDRESSABLE (t
)
1108 && !TREE_STATIC (t
))
1109 omp_add_variable (ctx
, t
, GOVD_PRIVATE
| GOVD_SEEN
);
1111 omp_add_variable (ctx
, t
, GOVD_LOCAL
| GOVD_SEEN
);
1114 DECL_SEEN_IN_BIND_EXPR_P (t
) = 1;
1116 if (DECL_HARD_REGISTER (t
) && !is_global_var (t
) && cfun
)
1117 cfun
->has_local_explicit_reg_vars
= true;
1120 /* Preliminarily mark non-addressed complex variables as eligible
1121 for promotion to gimple registers. We'll transform their uses
1123 if ((TREE_CODE (TREE_TYPE (t
)) == COMPLEX_TYPE
1124 || TREE_CODE (TREE_TYPE (t
)) == VECTOR_TYPE
)
1125 && !TREE_THIS_VOLATILE (t
)
1126 && (TREE_CODE (t
) == VAR_DECL
&& !DECL_HARD_REGISTER (t
))
1127 && !needs_to_live_in_memory (t
))
1128 DECL_GIMPLE_REG_P (t
) = 1;
1131 bind_stmt
= gimple_build_bind (BIND_EXPR_VARS (bind_expr
), NULL
,
1132 BIND_EXPR_BLOCK (bind_expr
));
1133 gimple_push_bind_expr (bind_stmt
);
1135 gimplify_ctxp
->save_stack
= false;
1137 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1139 gimplify_stmt (&BIND_EXPR_BODY (bind_expr
), &body
);
1140 gimple_bind_set_body (bind_stmt
, body
);
1142 /* Source location wise, the cleanup code (stack_restore and clobbers)
1143 belongs to the end of the block, so propagate what we have. The
1144 stack_save operation belongs to the beginning of block, which we can
1145 infer from the bind_expr directly if the block has no explicit
1147 if (BIND_EXPR_BLOCK (bind_expr
))
1149 end_locus
= BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr
));
1150 start_locus
= BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr
));
1152 if (start_locus
== 0)
1153 start_locus
= EXPR_LOCATION (bind_expr
);
1157 if (gimplify_ctxp
->save_stack
)
1159 gcall
*stack_restore
;
1161 /* Save stack on entry and restore it on exit. Add a try_finally
1162 block to achieve this. */
1163 build_stack_save_restore (&stack_save
, &stack_restore
);
1165 gimple_set_location (stack_save
, start_locus
);
1166 gimple_set_location (stack_restore
, end_locus
);
1168 gimplify_seq_add_stmt (&cleanup
, stack_restore
);
1171 /* Add clobbers for all variables that go out of scope. */
1172 for (t
= BIND_EXPR_VARS (bind_expr
); t
; t
= DECL_CHAIN (t
))
1174 if (TREE_CODE (t
) == VAR_DECL
1175 && !is_global_var (t
)
1176 && DECL_CONTEXT (t
) == current_function_decl
1177 && !DECL_HARD_REGISTER (t
)
1178 && !TREE_THIS_VOLATILE (t
)
1179 && !DECL_HAS_VALUE_EXPR_P (t
)
1180 /* Only care for variables that have to be in memory. Others
1181 will be rewritten into SSA names, hence moved to the top-level. */
1182 && !is_gimple_reg (t
)
1183 && flag_stack_reuse
!= SR_NONE
)
1185 tree clobber
= build_constructor (TREE_TYPE (t
), NULL
);
1186 gimple
*clobber_stmt
;
1187 TREE_THIS_VOLATILE (clobber
) = 1;
1188 clobber_stmt
= gimple_build_assign (t
, clobber
);
1189 gimple_set_location (clobber_stmt
, end_locus
);
1190 gimplify_seq_add_stmt (&cleanup
, clobber_stmt
);
1192 if (flag_openacc
&& oacc_declare_returns
!= NULL
)
1194 tree
*c
= oacc_declare_returns
->get (t
);
1198 OMP_CLAUSE_CHAIN (*c
) = ret_clauses
;
1202 oacc_declare_returns
->remove (t
);
1204 if (oacc_declare_returns
->elements () == 0)
1206 delete oacc_declare_returns
;
1207 oacc_declare_returns
= NULL
;
1217 gimple_stmt_iterator si
= gsi_start (cleanup
);
1219 stmt
= gimple_build_omp_target (NULL
, GF_OMP_TARGET_KIND_OACC_DECLARE
,
1221 gsi_insert_seq_before_without_update (&si
, stmt
, GSI_NEW_STMT
);
1227 gimple_seq new_body
;
1230 gs
= gimple_build_try (gimple_bind_body (bind_stmt
), cleanup
,
1231 GIMPLE_TRY_FINALLY
);
1234 gimplify_seq_add_stmt (&new_body
, stack_save
);
1235 gimplify_seq_add_stmt (&new_body
, gs
);
1236 gimple_bind_set_body (bind_stmt
, new_body
);
1239 gimplify_ctxp
->save_stack
= old_save_stack
;
1240 gimple_pop_bind_expr ();
1242 gimplify_seq_add_stmt (pre_p
, bind_stmt
);
1250 *expr_p
= NULL_TREE
;
1254 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1255 GIMPLE value, it is assigned to a new temporary and the statement is
1256 re-written to return the temporary.
1258 PRE_P points to the sequence where side effects that must happen before
1259 STMT should be stored. */
1261 static enum gimplify_status
1262 gimplify_return_expr (tree stmt
, gimple_seq
*pre_p
)
1265 tree ret_expr
= TREE_OPERAND (stmt
, 0);
1266 tree result_decl
, result
;
1268 if (ret_expr
== error_mark_node
)
1271 /* Implicit _Cilk_sync must be inserted right before any return statement
1272 if there is a _Cilk_spawn in the function. If the user has provided a
1273 _Cilk_sync, the optimizer should remove this duplicate one. */
1274 if (fn_contains_cilk_spawn_p (cfun
))
1276 tree impl_sync
= build0 (CILK_SYNC_STMT
, void_type_node
);
1277 gimplify_and_add (impl_sync
, pre_p
);
1281 || TREE_CODE (ret_expr
) == RESULT_DECL
1282 || ret_expr
== error_mark_node
)
1284 greturn
*ret
= gimple_build_return (ret_expr
);
1285 gimple_set_no_warning (ret
, TREE_NO_WARNING (stmt
));
1286 gimplify_seq_add_stmt (pre_p
, ret
);
1290 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl
))))
1291 result_decl
= NULL_TREE
;
1294 result_decl
= TREE_OPERAND (ret_expr
, 0);
1296 /* See through a return by reference. */
1297 if (TREE_CODE (result_decl
) == INDIRECT_REF
)
1298 result_decl
= TREE_OPERAND (result_decl
, 0);
1300 gcc_assert ((TREE_CODE (ret_expr
) == MODIFY_EXPR
1301 || TREE_CODE (ret_expr
) == INIT_EXPR
)
1302 && TREE_CODE (result_decl
) == RESULT_DECL
);
1305 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1306 Recall that aggregate_value_p is FALSE for any aggregate type that is
1307 returned in registers. If we're returning values in registers, then
1308 we don't want to extend the lifetime of the RESULT_DECL, particularly
1309 across another call. In addition, for those aggregates for which
1310 hard_function_value generates a PARALLEL, we'll die during normal
1311 expansion of structure assignments; there's special code in expand_return
1312 to handle this case that does not exist in expand_expr. */
1315 else if (aggregate_value_p (result_decl
, TREE_TYPE (current_function_decl
)))
1317 if (TREE_CODE (DECL_SIZE (result_decl
)) != INTEGER_CST
)
1319 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl
)))
1320 gimplify_type_sizes (TREE_TYPE (result_decl
), pre_p
);
1321 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1322 should be effectively allocated by the caller, i.e. all calls to
1323 this function must be subject to the Return Slot Optimization. */
1324 gimplify_one_sizepos (&DECL_SIZE (result_decl
), pre_p
);
1325 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl
), pre_p
);
1327 result
= result_decl
;
1329 else if (gimplify_ctxp
->return_temp
)
1330 result
= gimplify_ctxp
->return_temp
;
1333 result
= create_tmp_reg (TREE_TYPE (result_decl
));
1335 /* ??? With complex control flow (usually involving abnormal edges),
1336 we can wind up warning about an uninitialized value for this. Due
1337 to how this variable is constructed and initialized, this is never
1338 true. Give up and never warn. */
1339 TREE_NO_WARNING (result
) = 1;
1341 gimplify_ctxp
->return_temp
= result
;
1344 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1345 Then gimplify the whole thing. */
1346 if (result
!= result_decl
)
1347 TREE_OPERAND (ret_expr
, 0) = result
;
1349 gimplify_and_add (TREE_OPERAND (stmt
, 0), pre_p
);
1351 ret
= gimple_build_return (result
);
1352 gimple_set_no_warning (ret
, TREE_NO_WARNING (stmt
));
1353 gimplify_seq_add_stmt (pre_p
, ret
);
1358 /* Gimplify a variable-length array DECL. */
1361 gimplify_vla_decl (tree decl
, gimple_seq
*seq_p
)
1363 /* This is a variable-sized decl. Simplify its size and mark it
1364 for deferred expansion. */
1365 tree t
, addr
, ptr_type
;
1367 gimplify_one_sizepos (&DECL_SIZE (decl
), seq_p
);
1368 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl
), seq_p
);
1370 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1371 if (DECL_HAS_VALUE_EXPR_P (decl
))
1374 /* All occurrences of this decl in final gimplified code will be
1375 replaced by indirection. Setting DECL_VALUE_EXPR does two
1376 things: First, it lets the rest of the gimplifier know what
1377 replacement to use. Second, it lets the debug info know
1378 where to find the value. */
1379 ptr_type
= build_pointer_type (TREE_TYPE (decl
));
1380 addr
= create_tmp_var (ptr_type
, get_name (decl
));
1381 DECL_IGNORED_P (addr
) = 0;
1382 t
= build_fold_indirect_ref (addr
);
1383 TREE_THIS_NOTRAP (t
) = 1;
1384 SET_DECL_VALUE_EXPR (decl
, t
);
1385 DECL_HAS_VALUE_EXPR_P (decl
) = 1;
1387 t
= builtin_decl_explicit (BUILT_IN_ALLOCA_WITH_ALIGN
);
1388 t
= build_call_expr (t
, 2, DECL_SIZE_UNIT (decl
),
1389 size_int (DECL_ALIGN (decl
)));
1390 /* The call has been built for a variable-sized object. */
1391 CALL_ALLOCA_FOR_VAR_P (t
) = 1;
1392 t
= fold_convert (ptr_type
, t
);
1393 t
= build2 (MODIFY_EXPR
, TREE_TYPE (addr
), addr
, t
);
1395 gimplify_and_add (t
, seq_p
);
1397 /* Indicate that we need to restore the stack level when the
1398 enclosing BIND_EXPR is exited. */
1399 gimplify_ctxp
->save_stack
= true;
1402 /* A helper function to be called via walk_tree. Mark all labels under *TP
1403 as being forced. To be called for DECL_INITIAL of static variables. */
1406 force_labels_r (tree
*tp
, int *walk_subtrees
, void *data ATTRIBUTE_UNUSED
)
1410 if (TREE_CODE (*tp
) == LABEL_DECL
)
1411 FORCED_LABEL (*tp
) = 1;
1416 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
1417 and initialization explicit. */
1419 static enum gimplify_status
1420 gimplify_decl_expr (tree
*stmt_p
, gimple_seq
*seq_p
)
1422 tree stmt
= *stmt_p
;
1423 tree decl
= DECL_EXPR_DECL (stmt
);
1425 *stmt_p
= NULL_TREE
;
1427 if (TREE_TYPE (decl
) == error_mark_node
)
1430 if ((TREE_CODE (decl
) == TYPE_DECL
1431 || TREE_CODE (decl
) == VAR_DECL
)
1432 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl
)))
1433 gimplify_type_sizes (TREE_TYPE (decl
), seq_p
);
1435 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
1436 in case its size expressions contain problematic nodes like CALL_EXPR. */
1437 if (TREE_CODE (decl
) == TYPE_DECL
1438 && DECL_ORIGINAL_TYPE (decl
)
1439 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl
)))
1440 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl
), seq_p
);
1442 if (TREE_CODE (decl
) == VAR_DECL
&& !DECL_EXTERNAL (decl
))
1444 tree init
= DECL_INITIAL (decl
);
1446 if (TREE_CODE (DECL_SIZE_UNIT (decl
)) != INTEGER_CST
1447 || (!TREE_STATIC (decl
)
1448 && flag_stack_check
== GENERIC_STACK_CHECK
1449 && compare_tree_int (DECL_SIZE_UNIT (decl
),
1450 STACK_CHECK_MAX_VAR_SIZE
) > 0))
1451 gimplify_vla_decl (decl
, seq_p
);
1453 /* Some front ends do not explicitly declare all anonymous
1454 artificial variables. We compensate here by declaring the
1455 variables, though it would be better if the front ends would
1456 explicitly declare them. */
1457 if (!DECL_SEEN_IN_BIND_EXPR_P (decl
)
1458 && DECL_ARTIFICIAL (decl
) && DECL_NAME (decl
) == NULL_TREE
)
1459 gimple_add_tmp_var (decl
);
1461 if (init
&& init
!= error_mark_node
)
1463 if (!TREE_STATIC (decl
))
1465 DECL_INITIAL (decl
) = NULL_TREE
;
1466 init
= build2 (INIT_EXPR
, void_type_node
, decl
, init
);
1467 gimplify_and_add (init
, seq_p
);
1471 /* We must still examine initializers for static variables
1472 as they may contain a label address. */
1473 walk_tree (&init
, force_labels_r
, NULL
, NULL
);
1480 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1481 and replacing the LOOP_EXPR with goto, but if the loop contains an
1482 EXIT_EXPR, we need to append a label for it to jump to. */
1484 static enum gimplify_status
1485 gimplify_loop_expr (tree
*expr_p
, gimple_seq
*pre_p
)
1487 tree saved_label
= gimplify_ctxp
->exit_label
;
1488 tree start_label
= create_artificial_label (UNKNOWN_LOCATION
);
1490 gimplify_seq_add_stmt (pre_p
, gimple_build_label (start_label
));
1492 gimplify_ctxp
->exit_label
= NULL_TREE
;
1494 gimplify_and_add (LOOP_EXPR_BODY (*expr_p
), pre_p
);
1496 gimplify_seq_add_stmt (pre_p
, gimple_build_goto (start_label
));
1498 if (gimplify_ctxp
->exit_label
)
1499 gimplify_seq_add_stmt (pre_p
,
1500 gimple_build_label (gimplify_ctxp
->exit_label
));
1502 gimplify_ctxp
->exit_label
= saved_label
;
1508 /* Gimplify a statement list onto a sequence. These may be created either
1509 by an enlightened front-end, or by shortcut_cond_expr. */
1511 static enum gimplify_status
1512 gimplify_statement_list (tree
*expr_p
, gimple_seq
*pre_p
)
1514 tree temp
= voidify_wrapper_expr (*expr_p
, NULL
);
1516 tree_stmt_iterator i
= tsi_start (*expr_p
);
1518 while (!tsi_end_p (i
))
1520 gimplify_stmt (tsi_stmt_ptr (i
), pre_p
);
1534 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
1537 static enum gimplify_status
1538 gimplify_switch_expr (tree
*expr_p
, gimple_seq
*pre_p
)
1540 tree switch_expr
= *expr_p
;
1541 gimple_seq switch_body_seq
= NULL
;
1542 enum gimplify_status ret
;
1543 tree index_type
= TREE_TYPE (switch_expr
);
1544 if (index_type
== NULL_TREE
)
1545 index_type
= TREE_TYPE (SWITCH_COND (switch_expr
));
1547 ret
= gimplify_expr (&SWITCH_COND (switch_expr
), pre_p
, NULL
, is_gimple_val
,
1549 if (ret
== GS_ERROR
|| ret
== GS_UNHANDLED
)
1552 if (SWITCH_BODY (switch_expr
))
1555 vec
<tree
> saved_labels
;
1556 tree default_case
= NULL_TREE
;
1557 gswitch
*switch_stmt
;
1559 /* If someone can be bothered to fill in the labels, they can
1560 be bothered to null out the body too. */
1561 gcc_assert (!SWITCH_LABELS (switch_expr
));
1563 /* Save old labels, get new ones from body, then restore the old
1564 labels. Save all the things from the switch body to append after. */
1565 saved_labels
= gimplify_ctxp
->case_labels
;
1566 gimplify_ctxp
->case_labels
.create (8);
1568 gimplify_stmt (&SWITCH_BODY (switch_expr
), &switch_body_seq
);
1569 labels
= gimplify_ctxp
->case_labels
;
1570 gimplify_ctxp
->case_labels
= saved_labels
;
1572 preprocess_case_label_vec_for_gimple (labels
, index_type
,
1577 glabel
*new_default
;
1580 = build_case_label (NULL_TREE
, NULL_TREE
,
1581 create_artificial_label (UNKNOWN_LOCATION
));
1582 new_default
= gimple_build_label (CASE_LABEL (default_case
));
1583 gimplify_seq_add_stmt (&switch_body_seq
, new_default
);
1586 switch_stmt
= gimple_build_switch (SWITCH_COND (switch_expr
),
1587 default_case
, labels
);
1588 gimplify_seq_add_stmt (pre_p
, switch_stmt
);
1589 gimplify_seq_add_seq (pre_p
, switch_body_seq
);
1593 gcc_assert (SWITCH_LABELS (switch_expr
));
1598 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
1600 static enum gimplify_status
1601 gimplify_case_label_expr (tree
*expr_p
, gimple_seq
*pre_p
)
1603 struct gimplify_ctx
*ctxp
;
1606 /* Invalid programs can play Duff's Device type games with, for example,
1607 #pragma omp parallel. At least in the C front end, we don't
1608 detect such invalid branches until after gimplification, in the
1609 diagnose_omp_blocks pass. */
1610 for (ctxp
= gimplify_ctxp
; ; ctxp
= ctxp
->prev_context
)
1611 if (ctxp
->case_labels
.exists ())
1614 label_stmt
= gimple_build_label (CASE_LABEL (*expr_p
));
1615 ctxp
->case_labels
.safe_push (*expr_p
);
1616 gimplify_seq_add_stmt (pre_p
, label_stmt
);
1621 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
1625 build_and_jump (tree
*label_p
)
1627 if (label_p
== NULL
)
1628 /* If there's nowhere to jump, just fall through. */
1631 if (*label_p
== NULL_TREE
)
1633 tree label
= create_artificial_label (UNKNOWN_LOCATION
);
1637 return build1 (GOTO_EXPR
, void_type_node
, *label_p
);
1640 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
1641 This also involves building a label to jump to and communicating it to
1642 gimplify_loop_expr through gimplify_ctxp->exit_label. */
1644 static enum gimplify_status
1645 gimplify_exit_expr (tree
*expr_p
)
1647 tree cond
= TREE_OPERAND (*expr_p
, 0);
1650 expr
= build_and_jump (&gimplify_ctxp
->exit_label
);
1651 expr
= build3 (COND_EXPR
, void_type_node
, cond
, expr
, NULL_TREE
);
1657 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
1658 different from its canonical type, wrap the whole thing inside a
1659 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
1662 The canonical type of a COMPONENT_REF is the type of the field being
1663 referenced--unless the field is a bit-field which can be read directly
1664 in a smaller mode, in which case the canonical type is the
1665 sign-appropriate type corresponding to that mode. */
1668 canonicalize_component_ref (tree
*expr_p
)
1670 tree expr
= *expr_p
;
1673 gcc_assert (TREE_CODE (expr
) == COMPONENT_REF
);
1675 if (INTEGRAL_TYPE_P (TREE_TYPE (expr
)))
1676 type
= TREE_TYPE (get_unwidened (expr
, NULL_TREE
));
1678 type
= TREE_TYPE (TREE_OPERAND (expr
, 1));
1680 /* One could argue that all the stuff below is not necessary for
1681 the non-bitfield case and declare it a FE error if type
1682 adjustment would be needed. */
1683 if (TREE_TYPE (expr
) != type
)
1685 #ifdef ENABLE_TYPES_CHECKING
1686 tree old_type
= TREE_TYPE (expr
);
1690 /* We need to preserve qualifiers and propagate them from
1692 type_quals
= TYPE_QUALS (type
)
1693 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr
, 0)));
1694 if (TYPE_QUALS (type
) != type_quals
)
1695 type
= build_qualified_type (TYPE_MAIN_VARIANT (type
), type_quals
);
1697 /* Set the type of the COMPONENT_REF to the underlying type. */
1698 TREE_TYPE (expr
) = type
;
1700 #ifdef ENABLE_TYPES_CHECKING
1701 /* It is now a FE error, if the conversion from the canonical
1702 type to the original expression type is not useless. */
1703 gcc_assert (useless_type_conversion_p (old_type
, type
));
1708 /* If a NOP conversion is changing a pointer to array of foo to a pointer
1709 to foo, embed that change in the ADDR_EXPR by converting
1714 where L is the lower bound. For simplicity, only do this for constant
1716 The constraint is that the type of &array[L] is trivially convertible
1720 canonicalize_addr_expr (tree
*expr_p
)
1722 tree expr
= *expr_p
;
1723 tree addr_expr
= TREE_OPERAND (expr
, 0);
1724 tree datype
, ddatype
, pddatype
;
1726 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
1727 if (!POINTER_TYPE_P (TREE_TYPE (expr
))
1728 || TREE_CODE (addr_expr
) != ADDR_EXPR
)
1731 /* The addr_expr type should be a pointer to an array. */
1732 datype
= TREE_TYPE (TREE_TYPE (addr_expr
));
1733 if (TREE_CODE (datype
) != ARRAY_TYPE
)
1736 /* The pointer to element type shall be trivially convertible to
1737 the expression pointer type. */
1738 ddatype
= TREE_TYPE (datype
);
1739 pddatype
= build_pointer_type (ddatype
);
1740 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr
)),
1744 /* The lower bound and element sizes must be constant. */
1745 if (!TYPE_SIZE_UNIT (ddatype
)
1746 || TREE_CODE (TYPE_SIZE_UNIT (ddatype
)) != INTEGER_CST
1747 || !TYPE_DOMAIN (datype
) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype
))
1748 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype
))) != INTEGER_CST
)
1751 /* All checks succeeded. Build a new node to merge the cast. */
1752 *expr_p
= build4 (ARRAY_REF
, ddatype
, TREE_OPERAND (addr_expr
, 0),
1753 TYPE_MIN_VALUE (TYPE_DOMAIN (datype
)),
1754 NULL_TREE
, NULL_TREE
);
1755 *expr_p
= build1 (ADDR_EXPR
, pddatype
, *expr_p
);
1757 /* We can have stripped a required restrict qualifier above. */
1758 if (!useless_type_conversion_p (TREE_TYPE (expr
), TREE_TYPE (*expr_p
)))
1759 *expr_p
= fold_convert (TREE_TYPE (expr
), *expr_p
);
1762 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
1763 underneath as appropriate. */
1765 static enum gimplify_status
1766 gimplify_conversion (tree
*expr_p
)
1768 location_t loc
= EXPR_LOCATION (*expr_p
);
1769 gcc_assert (CONVERT_EXPR_P (*expr_p
));
1771 /* Then strip away all but the outermost conversion. */
1772 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p
, 0));
1774 /* And remove the outermost conversion if it's useless. */
1775 if (tree_ssa_useless_type_conversion (*expr_p
))
1776 *expr_p
= TREE_OPERAND (*expr_p
, 0);
1778 /* If we still have a conversion at the toplevel,
1779 then canonicalize some constructs. */
1780 if (CONVERT_EXPR_P (*expr_p
))
1782 tree sub
= TREE_OPERAND (*expr_p
, 0);
1784 /* If a NOP conversion is changing the type of a COMPONENT_REF
1785 expression, then canonicalize its type now in order to expose more
1786 redundant conversions. */
1787 if (TREE_CODE (sub
) == COMPONENT_REF
)
1788 canonicalize_component_ref (&TREE_OPERAND (*expr_p
, 0));
1790 /* If a NOP conversion is changing a pointer to array of foo
1791 to a pointer to foo, embed that change in the ADDR_EXPR. */
1792 else if (TREE_CODE (sub
) == ADDR_EXPR
)
1793 canonicalize_addr_expr (expr_p
);
1796 /* If we have a conversion to a non-register type force the
1797 use of a VIEW_CONVERT_EXPR instead. */
1798 if (CONVERT_EXPR_P (*expr_p
) && !is_gimple_reg_type (TREE_TYPE (*expr_p
)))
1799 *expr_p
= fold_build1_loc (loc
, VIEW_CONVERT_EXPR
, TREE_TYPE (*expr_p
),
1800 TREE_OPERAND (*expr_p
, 0));
1802 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
1803 if (TREE_CODE (*expr_p
) == CONVERT_EXPR
)
1804 TREE_SET_CODE (*expr_p
, NOP_EXPR
);
1809 /* Nonlocal VLAs seen in the current function. */
1810 static hash_set
<tree
> *nonlocal_vlas
;
1812 /* The VAR_DECLs created for nonlocal VLAs for debug info purposes. */
1813 static tree nonlocal_vla_vars
;
1815 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
1816 DECL_VALUE_EXPR, and it's worth re-examining things. */
1818 static enum gimplify_status
1819 gimplify_var_or_parm_decl (tree
*expr_p
)
1821 tree decl
= *expr_p
;
1823 /* ??? If this is a local variable, and it has not been seen in any
1824 outer BIND_EXPR, then it's probably the result of a duplicate
1825 declaration, for which we've already issued an error. It would
1826 be really nice if the front end wouldn't leak these at all.
1827 Currently the only known culprit is C++ destructors, as seen
1828 in g++.old-deja/g++.jason/binding.C. */
1829 if (TREE_CODE (decl
) == VAR_DECL
1830 && !DECL_SEEN_IN_BIND_EXPR_P (decl
)
1831 && !TREE_STATIC (decl
) && !DECL_EXTERNAL (decl
)
1832 && decl_function_context (decl
) == current_function_decl
)
1834 gcc_assert (seen_error ());
1838 /* When within an OMP context, notice uses of variables. */
1839 if (gimplify_omp_ctxp
&& omp_notice_variable (gimplify_omp_ctxp
, decl
, true))
1842 /* If the decl is an alias for another expression, substitute it now. */
1843 if (DECL_HAS_VALUE_EXPR_P (decl
))
1845 tree value_expr
= DECL_VALUE_EXPR (decl
);
1847 /* For referenced nonlocal VLAs add a decl for debugging purposes
1848 to the current function. */
1849 if (TREE_CODE (decl
) == VAR_DECL
1850 && TREE_CODE (DECL_SIZE_UNIT (decl
)) != INTEGER_CST
1851 && nonlocal_vlas
!= NULL
1852 && TREE_CODE (value_expr
) == INDIRECT_REF
1853 && TREE_CODE (TREE_OPERAND (value_expr
, 0)) == VAR_DECL
1854 && decl_function_context (decl
) != current_function_decl
)
1856 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
1858 && (ctx
->region_type
== ORT_WORKSHARE
1859 || ctx
->region_type
== ORT_SIMD
1860 || ctx
->region_type
== ORT_ACC
))
1861 ctx
= ctx
->outer_context
;
1862 if (!ctx
&& !nonlocal_vlas
->add (decl
))
1864 tree copy
= copy_node (decl
);
1866 lang_hooks
.dup_lang_specific_decl (copy
);
1867 SET_DECL_RTL (copy
, 0);
1868 TREE_USED (copy
) = 1;
1869 DECL_CHAIN (copy
) = nonlocal_vla_vars
;
1870 nonlocal_vla_vars
= copy
;
1871 SET_DECL_VALUE_EXPR (copy
, unshare_expr (value_expr
));
1872 DECL_HAS_VALUE_EXPR_P (copy
) = 1;
1876 *expr_p
= unshare_expr (value_expr
);
1883 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
1886 recalculate_side_effects (tree t
)
1888 enum tree_code code
= TREE_CODE (t
);
1889 int len
= TREE_OPERAND_LENGTH (t
);
1892 switch (TREE_CODE_CLASS (code
))
1894 case tcc_expression
:
1900 case PREDECREMENT_EXPR
:
1901 case PREINCREMENT_EXPR
:
1902 case POSTDECREMENT_EXPR
:
1903 case POSTINCREMENT_EXPR
:
1904 /* All of these have side-effects, no matter what their
1913 case tcc_comparison
: /* a comparison expression */
1914 case tcc_unary
: /* a unary arithmetic expression */
1915 case tcc_binary
: /* a binary arithmetic expression */
1916 case tcc_reference
: /* a reference */
1917 case tcc_vl_exp
: /* a function call */
1918 TREE_SIDE_EFFECTS (t
) = TREE_THIS_VOLATILE (t
);
1919 for (i
= 0; i
< len
; ++i
)
1921 tree op
= TREE_OPERAND (t
, i
);
1922 if (op
&& TREE_SIDE_EFFECTS (op
))
1923 TREE_SIDE_EFFECTS (t
) = 1;
1928 /* No side-effects. */
1936 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
1940 : min_lval '[' val ']'
1942 | compound_lval '[' val ']'
1943 | compound_lval '.' ID
1945 This is not part of the original SIMPLE definition, which separates
1946 array and member references, but it seems reasonable to handle them
1947 together. Also, this way we don't run into problems with union
1948 aliasing; gcc requires that for accesses through a union to alias, the
1949 union reference must be explicit, which was not always the case when we
1950 were splitting up array and member refs.
1952 PRE_P points to the sequence where side effects that must happen before
1953 *EXPR_P should be stored.
1955 POST_P points to the sequence where side effects that must happen after
1956 *EXPR_P should be stored. */
1958 static enum gimplify_status
1959 gimplify_compound_lval (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
1960 fallback_t fallback
)
1963 enum gimplify_status ret
= GS_ALL_DONE
, tret
;
1965 location_t loc
= EXPR_LOCATION (*expr_p
);
1966 tree expr
= *expr_p
;
1968 /* Create a stack of the subexpressions so later we can walk them in
1969 order from inner to outer. */
1970 auto_vec
<tree
, 10> expr_stack
;
1972 /* We can handle anything that get_inner_reference can deal with. */
1973 for (p
= expr_p
; ; p
= &TREE_OPERAND (*p
, 0))
1976 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
1977 if (TREE_CODE (*p
) == INDIRECT_REF
)
1978 *p
= fold_indirect_ref_loc (loc
, *p
);
1980 if (handled_component_p (*p
))
1982 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
1983 additional COMPONENT_REFs. */
1984 else if ((TREE_CODE (*p
) == VAR_DECL
|| TREE_CODE (*p
) == PARM_DECL
)
1985 && gimplify_var_or_parm_decl (p
) == GS_OK
)
1990 expr_stack
.safe_push (*p
);
1993 gcc_assert (expr_stack
.length ());
1995 /* Now EXPR_STACK is a stack of pointers to all the refs we've
1996 walked through and P points to the innermost expression.
1998 Java requires that we elaborated nodes in source order. That
1999 means we must gimplify the inner expression followed by each of
2000 the indices, in order. But we can't gimplify the inner
2001 expression until we deal with any variable bounds, sizes, or
2002 positions in order to deal with PLACEHOLDER_EXPRs.
2004 So we do this in three steps. First we deal with the annotations
2005 for any variables in the components, then we gimplify the base,
2006 then we gimplify any indices, from left to right. */
2007 for (i
= expr_stack
.length () - 1; i
>= 0; i
--)
2009 tree t
= expr_stack
[i
];
2011 if (TREE_CODE (t
) == ARRAY_REF
|| TREE_CODE (t
) == ARRAY_RANGE_REF
)
2013 /* Gimplify the low bound and element type size and put them into
2014 the ARRAY_REF. If these values are set, they have already been
2016 if (TREE_OPERAND (t
, 2) == NULL_TREE
)
2018 tree low
= unshare_expr (array_ref_low_bound (t
));
2019 if (!is_gimple_min_invariant (low
))
2021 TREE_OPERAND (t
, 2) = low
;
2022 tret
= gimplify_expr (&TREE_OPERAND (t
, 2), pre_p
,
2023 post_p
, is_gimple_reg
,
2025 ret
= MIN (ret
, tret
);
2030 tret
= gimplify_expr (&TREE_OPERAND (t
, 2), pre_p
, post_p
,
2031 is_gimple_reg
, fb_rvalue
);
2032 ret
= MIN (ret
, tret
);
2035 if (TREE_OPERAND (t
, 3) == NULL_TREE
)
2037 tree elmt_type
= TREE_TYPE (TREE_TYPE (TREE_OPERAND (t
, 0)));
2038 tree elmt_size
= unshare_expr (array_ref_element_size (t
));
2039 tree factor
= size_int (TYPE_ALIGN_UNIT (elmt_type
));
2041 /* Divide the element size by the alignment of the element
2044 = size_binop_loc (loc
, EXACT_DIV_EXPR
, elmt_size
, factor
);
2046 if (!is_gimple_min_invariant (elmt_size
))
2048 TREE_OPERAND (t
, 3) = elmt_size
;
2049 tret
= gimplify_expr (&TREE_OPERAND (t
, 3), pre_p
,
2050 post_p
, is_gimple_reg
,
2052 ret
= MIN (ret
, tret
);
2057 tret
= gimplify_expr (&TREE_OPERAND (t
, 3), pre_p
, post_p
,
2058 is_gimple_reg
, fb_rvalue
);
2059 ret
= MIN (ret
, tret
);
2062 else if (TREE_CODE (t
) == COMPONENT_REF
)
2064 /* Set the field offset into T and gimplify it. */
2065 if (TREE_OPERAND (t
, 2) == NULL_TREE
)
2067 tree offset
= unshare_expr (component_ref_field_offset (t
));
2068 tree field
= TREE_OPERAND (t
, 1);
2070 = size_int (DECL_OFFSET_ALIGN (field
) / BITS_PER_UNIT
);
2072 /* Divide the offset by its alignment. */
2073 offset
= size_binop_loc (loc
, EXACT_DIV_EXPR
, offset
, factor
);
2075 if (!is_gimple_min_invariant (offset
))
2077 TREE_OPERAND (t
, 2) = offset
;
2078 tret
= gimplify_expr (&TREE_OPERAND (t
, 2), pre_p
,
2079 post_p
, is_gimple_reg
,
2081 ret
= MIN (ret
, tret
);
2086 tret
= gimplify_expr (&TREE_OPERAND (t
, 2), pre_p
, post_p
,
2087 is_gimple_reg
, fb_rvalue
);
2088 ret
= MIN (ret
, tret
);
2093 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
2094 so as to match the min_lval predicate. Failure to do so may result
2095 in the creation of large aggregate temporaries. */
2096 tret
= gimplify_expr (p
, pre_p
, post_p
, is_gimple_min_lval
,
2097 fallback
| fb_lvalue
);
2098 ret
= MIN (ret
, tret
);
2100 /* And finally, the indices and operands of ARRAY_REF. During this
2101 loop we also remove any useless conversions. */
2102 for (; expr_stack
.length () > 0; )
2104 tree t
= expr_stack
.pop ();
2106 if (TREE_CODE (t
) == ARRAY_REF
|| TREE_CODE (t
) == ARRAY_RANGE_REF
)
2108 /* Gimplify the dimension. */
2109 if (!is_gimple_min_invariant (TREE_OPERAND (t
, 1)))
2111 tret
= gimplify_expr (&TREE_OPERAND (t
, 1), pre_p
, post_p
,
2112 is_gimple_val
, fb_rvalue
);
2113 ret
= MIN (ret
, tret
);
2117 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t
, 0));
2119 /* The innermost expression P may have originally had
2120 TREE_SIDE_EFFECTS set which would have caused all the outer
2121 expressions in *EXPR_P leading to P to also have had
2122 TREE_SIDE_EFFECTS set. */
2123 recalculate_side_effects (t
);
2126 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
2127 if ((fallback
& fb_rvalue
) && TREE_CODE (*expr_p
) == COMPONENT_REF
)
2129 canonicalize_component_ref (expr_p
);
2132 expr_stack
.release ();
2134 gcc_assert (*expr_p
== expr
|| ret
!= GS_ALL_DONE
);
2139 /* Gimplify the self modifying expression pointed to by EXPR_P
2142 PRE_P points to the list where side effects that must happen before
2143 *EXPR_P should be stored.
2145 POST_P points to the list where side effects that must happen after
2146 *EXPR_P should be stored.
2148 WANT_VALUE is nonzero iff we want to use the value of this expression
2149 in another expression.
2151 ARITH_TYPE is the type the computation should be performed in. */
2153 enum gimplify_status
2154 gimplify_self_mod_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
2155 bool want_value
, tree arith_type
)
2157 enum tree_code code
;
2158 tree lhs
, lvalue
, rhs
, t1
;
2159 gimple_seq post
= NULL
, *orig_post_p
= post_p
;
2161 enum tree_code arith_code
;
2162 enum gimplify_status ret
;
2163 location_t loc
= EXPR_LOCATION (*expr_p
);
2165 code
= TREE_CODE (*expr_p
);
2167 gcc_assert (code
== POSTINCREMENT_EXPR
|| code
== POSTDECREMENT_EXPR
2168 || code
== PREINCREMENT_EXPR
|| code
== PREDECREMENT_EXPR
);
2170 /* Prefix or postfix? */
2171 if (code
== POSTINCREMENT_EXPR
|| code
== POSTDECREMENT_EXPR
)
2172 /* Faster to treat as prefix if result is not used. */
2173 postfix
= want_value
;
2177 /* For postfix, make sure the inner expression's post side effects
2178 are executed after side effects from this expression. */
2182 /* Add or subtract? */
2183 if (code
== PREINCREMENT_EXPR
|| code
== POSTINCREMENT_EXPR
)
2184 arith_code
= PLUS_EXPR
;
2186 arith_code
= MINUS_EXPR
;
2188 /* Gimplify the LHS into a GIMPLE lvalue. */
2189 lvalue
= TREE_OPERAND (*expr_p
, 0);
2190 ret
= gimplify_expr (&lvalue
, pre_p
, post_p
, is_gimple_lvalue
, fb_lvalue
);
2191 if (ret
== GS_ERROR
)
2194 /* Extract the operands to the arithmetic operation. */
2196 rhs
= TREE_OPERAND (*expr_p
, 1);
2198 /* For postfix operator, we evaluate the LHS to an rvalue and then use
2199 that as the result value and in the postqueue operation. */
2202 ret
= gimplify_expr (&lhs
, pre_p
, post_p
, is_gimple_val
, fb_rvalue
);
2203 if (ret
== GS_ERROR
)
2206 lhs
= get_initialized_tmp_var (lhs
, pre_p
, NULL
);
2209 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
2210 if (POINTER_TYPE_P (TREE_TYPE (lhs
)))
2212 rhs
= convert_to_ptrofftype_loc (loc
, rhs
);
2213 if (arith_code
== MINUS_EXPR
)
2214 rhs
= fold_build1_loc (loc
, NEGATE_EXPR
, TREE_TYPE (rhs
), rhs
);
2215 t1
= fold_build2 (POINTER_PLUS_EXPR
, TREE_TYPE (*expr_p
), lhs
, rhs
);
2218 t1
= fold_convert (TREE_TYPE (*expr_p
),
2219 fold_build2 (arith_code
, arith_type
,
2220 fold_convert (arith_type
, lhs
),
2221 fold_convert (arith_type
, rhs
)));
2225 gimplify_assign (lvalue
, t1
, pre_p
);
2226 gimplify_seq_add_seq (orig_post_p
, post
);
2232 *expr_p
= build2 (MODIFY_EXPR
, TREE_TYPE (lvalue
), lvalue
, t1
);
2237 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
2240 maybe_with_size_expr (tree
*expr_p
)
2242 tree expr
= *expr_p
;
2243 tree type
= TREE_TYPE (expr
);
2246 /* If we've already wrapped this or the type is error_mark_node, we can't do
2248 if (TREE_CODE (expr
) == WITH_SIZE_EXPR
2249 || type
== error_mark_node
)
2252 /* If the size isn't known or is a constant, we have nothing to do. */
2253 size
= TYPE_SIZE_UNIT (type
);
2254 if (!size
|| TREE_CODE (size
) == INTEGER_CST
)
2257 /* Otherwise, make a WITH_SIZE_EXPR. */
2258 size
= unshare_expr (size
);
2259 size
= SUBSTITUTE_PLACEHOLDER_IN_EXPR (size
, expr
);
2260 *expr_p
= build2 (WITH_SIZE_EXPR
, type
, expr
, size
);
2263 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
2264 Store any side-effects in PRE_P. CALL_LOCATION is the location of
2267 enum gimplify_status
2268 gimplify_arg (tree
*arg_p
, gimple_seq
*pre_p
, location_t call_location
)
2270 bool (*test
) (tree
);
2273 /* In general, we allow lvalues for function arguments to avoid
2274 extra overhead of copying large aggregates out of even larger
2275 aggregates into temporaries only to copy the temporaries to
2276 the argument list. Make optimizers happy by pulling out to
2277 temporaries those types that fit in registers. */
2278 if (is_gimple_reg_type (TREE_TYPE (*arg_p
)))
2279 test
= is_gimple_val
, fb
= fb_rvalue
;
2282 test
= is_gimple_lvalue
, fb
= fb_either
;
2283 /* Also strip a TARGET_EXPR that would force an extra copy. */
2284 if (TREE_CODE (*arg_p
) == TARGET_EXPR
)
2286 tree init
= TARGET_EXPR_INITIAL (*arg_p
);
2288 && !VOID_TYPE_P (TREE_TYPE (init
)))
2293 /* If this is a variable sized type, we must remember the size. */
2294 maybe_with_size_expr (arg_p
);
2296 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
2297 /* Make sure arguments have the same location as the function call
2299 protected_set_expr_location (*arg_p
, call_location
);
2301 /* There is a sequence point before a function call. Side effects in
2302 the argument list must occur before the actual call. So, when
2303 gimplifying arguments, force gimplify_expr to use an internal
2304 post queue which is then appended to the end of PRE_P. */
2305 return gimplify_expr (arg_p
, pre_p
, NULL
, test
, fb
);
2308 /* Don't fold inside offloading or taskreg regions: it can break code by
2309 adding decl references that weren't in the source. We'll do it during
2310 omplower pass instead. */
2313 maybe_fold_stmt (gimple_stmt_iterator
*gsi
)
2315 struct gimplify_omp_ctx
*ctx
;
2316 for (ctx
= gimplify_omp_ctxp
; ctx
; ctx
= ctx
->outer_context
)
2317 if ((ctx
->region_type
& (ORT_TARGET
| ORT_PARALLEL
| ORT_TASK
)) != 0)
2319 return fold_stmt (gsi
);
2322 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
2323 WANT_VALUE is true if the result of the call is desired. */
2325 static enum gimplify_status
2326 gimplify_call_expr (tree
*expr_p
, gimple_seq
*pre_p
, bool want_value
)
2328 tree fndecl
, parms
, p
, fnptrtype
;
2329 enum gimplify_status ret
;
2332 bool builtin_va_start_p
= false;
2333 location_t loc
= EXPR_LOCATION (*expr_p
);
2335 gcc_assert (TREE_CODE (*expr_p
) == CALL_EXPR
);
2337 /* For reliable diagnostics during inlining, it is necessary that
2338 every call_expr be annotated with file and line. */
2339 if (! EXPR_HAS_LOCATION (*expr_p
))
2340 SET_EXPR_LOCATION (*expr_p
, input_location
);
2342 /* Gimplify internal functions created in the FEs. */
2343 if (CALL_EXPR_FN (*expr_p
) == NULL_TREE
)
2348 nargs
= call_expr_nargs (*expr_p
);
2349 enum internal_fn ifn
= CALL_EXPR_IFN (*expr_p
);
2350 auto_vec
<tree
> vargs (nargs
);
2352 for (i
= 0; i
< nargs
; i
++)
2354 gimplify_arg (&CALL_EXPR_ARG (*expr_p
, i
), pre_p
,
2355 EXPR_LOCATION (*expr_p
));
2356 vargs
.quick_push (CALL_EXPR_ARG (*expr_p
, i
));
2358 gimple
*call
= gimple_build_call_internal_vec (ifn
, vargs
);
2359 gimplify_seq_add_stmt (pre_p
, call
);
2363 /* This may be a call to a builtin function.
2365 Builtin function calls may be transformed into different
2366 (and more efficient) builtin function calls under certain
2367 circumstances. Unfortunately, gimplification can muck things
2368 up enough that the builtin expanders are not aware that certain
2369 transformations are still valid.
2371 So we attempt transformation/gimplification of the call before
2372 we gimplify the CALL_EXPR. At this time we do not manage to
2373 transform all calls in the same manner as the expanders do, but
2374 we do transform most of them. */
2375 fndecl
= get_callee_fndecl (*expr_p
);
2377 && DECL_BUILT_IN_CLASS (fndecl
) == BUILT_IN_NORMAL
)
2378 switch (DECL_FUNCTION_CODE (fndecl
))
2380 case BUILT_IN_VA_START
:
2382 builtin_va_start_p
= TRUE
;
2383 if (call_expr_nargs (*expr_p
) < 2)
2385 error ("too few arguments to function %<va_start%>");
2386 *expr_p
= build_empty_stmt (EXPR_LOCATION (*expr_p
));
2390 if (fold_builtin_next_arg (*expr_p
, true))
2392 *expr_p
= build_empty_stmt (EXPR_LOCATION (*expr_p
));
2399 *expr_p
= build_int_cst (TREE_TYPE (*expr_p
),
2400 LOCATION_LINE (EXPR_LOCATION (*expr_p
)));
2405 const char *locfile
= LOCATION_FILE (EXPR_LOCATION (*expr_p
));
2406 *expr_p
= build_string_literal (strlen (locfile
) + 1, locfile
);
2409 case BUILT_IN_FUNCTION
:
2411 const char *function
;
2412 function
= IDENTIFIER_POINTER (DECL_NAME (current_function_decl
));
2413 *expr_p
= build_string_literal (strlen (function
) + 1, function
);
2419 if (fndecl
&& DECL_BUILT_IN (fndecl
))
2421 tree new_tree
= fold_call_expr (input_location
, *expr_p
, !want_value
);
2422 if (new_tree
&& new_tree
!= *expr_p
)
2424 /* There was a transformation of this call which computes the
2425 same value, but in a more efficient way. Return and try
2432 /* Remember the original function pointer type. */
2433 fnptrtype
= TREE_TYPE (CALL_EXPR_FN (*expr_p
));
2435 /* There is a sequence point before the call, so any side effects in
2436 the calling expression must occur before the actual call. Force
2437 gimplify_expr to use an internal post queue. */
2438 ret
= gimplify_expr (&CALL_EXPR_FN (*expr_p
), pre_p
, NULL
,
2439 is_gimple_call_addr
, fb_rvalue
);
2441 nargs
= call_expr_nargs (*expr_p
);
2443 /* Get argument types for verification. */
2444 fndecl
= get_callee_fndecl (*expr_p
);
2447 parms
= TYPE_ARG_TYPES (TREE_TYPE (fndecl
));
2449 parms
= TYPE_ARG_TYPES (TREE_TYPE (fnptrtype
));
2451 if (fndecl
&& DECL_ARGUMENTS (fndecl
))
2452 p
= DECL_ARGUMENTS (fndecl
);
2457 for (i
= 0; i
< nargs
&& p
; i
++, p
= TREE_CHAIN (p
))
2460 /* If the last argument is __builtin_va_arg_pack () and it is not
2461 passed as a named argument, decrease the number of CALL_EXPR
2462 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
2465 && TREE_CODE (CALL_EXPR_ARG (*expr_p
, nargs
- 1)) == CALL_EXPR
)
2467 tree last_arg
= CALL_EXPR_ARG (*expr_p
, nargs
- 1);
2468 tree last_arg_fndecl
= get_callee_fndecl (last_arg
);
2471 && TREE_CODE (last_arg_fndecl
) == FUNCTION_DECL
2472 && DECL_BUILT_IN_CLASS (last_arg_fndecl
) == BUILT_IN_NORMAL
2473 && DECL_FUNCTION_CODE (last_arg_fndecl
) == BUILT_IN_VA_ARG_PACK
)
2475 tree call
= *expr_p
;
2478 *expr_p
= build_call_array_loc (loc
, TREE_TYPE (call
),
2479 CALL_EXPR_FN (call
),
2480 nargs
, CALL_EXPR_ARGP (call
));
2482 /* Copy all CALL_EXPR flags, location and block, except
2483 CALL_EXPR_VA_ARG_PACK flag. */
2484 CALL_EXPR_STATIC_CHAIN (*expr_p
) = CALL_EXPR_STATIC_CHAIN (call
);
2485 CALL_EXPR_TAILCALL (*expr_p
) = CALL_EXPR_TAILCALL (call
);
2486 CALL_EXPR_RETURN_SLOT_OPT (*expr_p
)
2487 = CALL_EXPR_RETURN_SLOT_OPT (call
);
2488 CALL_FROM_THUNK_P (*expr_p
) = CALL_FROM_THUNK_P (call
);
2489 SET_EXPR_LOCATION (*expr_p
, EXPR_LOCATION (call
));
2491 /* Set CALL_EXPR_VA_ARG_PACK. */
2492 CALL_EXPR_VA_ARG_PACK (*expr_p
) = 1;
2496 /* Gimplify the function arguments. */
2499 for (i
= (PUSH_ARGS_REVERSED
? nargs
- 1 : 0);
2500 PUSH_ARGS_REVERSED
? i
>= 0 : i
< nargs
;
2501 PUSH_ARGS_REVERSED
? i
-- : i
++)
2503 enum gimplify_status t
;
2505 /* Avoid gimplifying the second argument to va_start, which needs to
2506 be the plain PARM_DECL. */
2507 if ((i
!= 1) || !builtin_va_start_p
)
2509 t
= gimplify_arg (&CALL_EXPR_ARG (*expr_p
, i
), pre_p
,
2510 EXPR_LOCATION (*expr_p
));
2518 /* Gimplify the static chain. */
2519 if (CALL_EXPR_STATIC_CHAIN (*expr_p
))
2521 if (fndecl
&& !DECL_STATIC_CHAIN (fndecl
))
2522 CALL_EXPR_STATIC_CHAIN (*expr_p
) = NULL
;
2525 enum gimplify_status t
;
2526 t
= gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p
), pre_p
,
2527 EXPR_LOCATION (*expr_p
));
2533 /* Verify the function result. */
2534 if (want_value
&& fndecl
2535 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype
))))
2537 error_at (loc
, "using result of function returning %<void%>");
2541 /* Try this again in case gimplification exposed something. */
2542 if (ret
!= GS_ERROR
)
2544 tree new_tree
= fold_call_expr (input_location
, *expr_p
, !want_value
);
2546 if (new_tree
&& new_tree
!= *expr_p
)
2548 /* There was a transformation of this call which computes the
2549 same value, but in a more efficient way. Return and try
2557 *expr_p
= error_mark_node
;
2561 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
2562 decl. This allows us to eliminate redundant or useless
2563 calls to "const" functions. */
2564 if (TREE_CODE (*expr_p
) == CALL_EXPR
)
2566 int flags
= call_expr_flags (*expr_p
);
2567 if (flags
& (ECF_CONST
| ECF_PURE
)
2568 /* An infinite loop is considered a side effect. */
2569 && !(flags
& (ECF_LOOPING_CONST_OR_PURE
)))
2570 TREE_SIDE_EFFECTS (*expr_p
) = 0;
2573 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
2574 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
2575 form and delegate the creation of a GIMPLE_CALL to
2576 gimplify_modify_expr. This is always possible because when
2577 WANT_VALUE is true, the caller wants the result of this call into
2578 a temporary, which means that we will emit an INIT_EXPR in
2579 internal_get_tmp_var which will then be handled by
2580 gimplify_modify_expr. */
2583 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
2584 have to do is replicate it as a GIMPLE_CALL tuple. */
2585 gimple_stmt_iterator gsi
;
2586 call
= gimple_build_call_from_tree (*expr_p
);
2587 gimple_call_set_fntype (call
, TREE_TYPE (fnptrtype
));
2588 notice_special_calls (call
);
2589 gimplify_seq_add_stmt (pre_p
, call
);
2590 gsi
= gsi_last (*pre_p
);
2591 maybe_fold_stmt (&gsi
);
2592 *expr_p
= NULL_TREE
;
2595 /* Remember the original function type. */
2596 CALL_EXPR_FN (*expr_p
) = build1 (NOP_EXPR
, fnptrtype
,
2597 CALL_EXPR_FN (*expr_p
));
2602 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
2603 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
2605 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
2606 condition is true or false, respectively. If null, we should generate
2607 our own to skip over the evaluation of this specific expression.
2609 LOCUS is the source location of the COND_EXPR.
2611 This function is the tree equivalent of do_jump.
2613 shortcut_cond_r should only be called by shortcut_cond_expr. */
2616 shortcut_cond_r (tree pred
, tree
*true_label_p
, tree
*false_label_p
,
2619 tree local_label
= NULL_TREE
;
2620 tree t
, expr
= NULL
;
2622 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
2623 retain the shortcut semantics. Just insert the gotos here;
2624 shortcut_cond_expr will append the real blocks later. */
2625 if (TREE_CODE (pred
) == TRUTH_ANDIF_EXPR
)
2627 location_t new_locus
;
2629 /* Turn if (a && b) into
2631 if (a); else goto no;
2632 if (b) goto yes; else goto no;
2635 if (false_label_p
== NULL
)
2636 false_label_p
= &local_label
;
2638 /* Keep the original source location on the first 'if'. */
2639 t
= shortcut_cond_r (TREE_OPERAND (pred
, 0), NULL
, false_label_p
, locus
);
2640 append_to_statement_list (t
, &expr
);
2642 /* Set the source location of the && on the second 'if'. */
2643 new_locus
= EXPR_HAS_LOCATION (pred
) ? EXPR_LOCATION (pred
) : locus
;
2644 t
= shortcut_cond_r (TREE_OPERAND (pred
, 1), true_label_p
, false_label_p
,
2646 append_to_statement_list (t
, &expr
);
2648 else if (TREE_CODE (pred
) == TRUTH_ORIF_EXPR
)
2650 location_t new_locus
;
2652 /* Turn if (a || b) into
2655 if (b) goto yes; else goto no;
2658 if (true_label_p
== NULL
)
2659 true_label_p
= &local_label
;
2661 /* Keep the original source location on the first 'if'. */
2662 t
= shortcut_cond_r (TREE_OPERAND (pred
, 0), true_label_p
, NULL
, locus
);
2663 append_to_statement_list (t
, &expr
);
2665 /* Set the source location of the || on the second 'if'. */
2666 new_locus
= EXPR_HAS_LOCATION (pred
) ? EXPR_LOCATION (pred
) : locus
;
2667 t
= shortcut_cond_r (TREE_OPERAND (pred
, 1), true_label_p
, false_label_p
,
2669 append_to_statement_list (t
, &expr
);
2671 else if (TREE_CODE (pred
) == COND_EXPR
2672 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred
, 1)))
2673 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred
, 2))))
2675 location_t new_locus
;
2677 /* As long as we're messing with gotos, turn if (a ? b : c) into
2679 if (b) goto yes; else goto no;
2681 if (c) goto yes; else goto no;
2683 Don't do this if one of the arms has void type, which can happen
2684 in C++ when the arm is throw. */
2686 /* Keep the original source location on the first 'if'. Set the source
2687 location of the ? on the second 'if'. */
2688 new_locus
= EXPR_HAS_LOCATION (pred
) ? EXPR_LOCATION (pred
) : locus
;
2689 expr
= build3 (COND_EXPR
, void_type_node
, TREE_OPERAND (pred
, 0),
2690 shortcut_cond_r (TREE_OPERAND (pred
, 1), true_label_p
,
2691 false_label_p
, locus
),
2692 shortcut_cond_r (TREE_OPERAND (pred
, 2), true_label_p
,
2693 false_label_p
, new_locus
));
2697 expr
= build3 (COND_EXPR
, void_type_node
, pred
,
2698 build_and_jump (true_label_p
),
2699 build_and_jump (false_label_p
));
2700 SET_EXPR_LOCATION (expr
, locus
);
2705 t
= build1 (LABEL_EXPR
, void_type_node
, local_label
);
2706 append_to_statement_list (t
, &expr
);
2712 /* Given a conditional expression EXPR with short-circuit boolean
2713 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
2714 predicate apart into the equivalent sequence of conditionals. */
2717 shortcut_cond_expr (tree expr
)
2719 tree pred
= TREE_OPERAND (expr
, 0);
2720 tree then_
= TREE_OPERAND (expr
, 1);
2721 tree else_
= TREE_OPERAND (expr
, 2);
2722 tree true_label
, false_label
, end_label
, t
;
2724 tree
*false_label_p
;
2725 bool emit_end
, emit_false
, jump_over_else
;
2726 bool then_se
= then_
&& TREE_SIDE_EFFECTS (then_
);
2727 bool else_se
= else_
&& TREE_SIDE_EFFECTS (else_
);
2729 /* First do simple transformations. */
2732 /* If there is no 'else', turn
2735 if (a) if (b) then c. */
2736 while (TREE_CODE (pred
) == TRUTH_ANDIF_EXPR
)
2738 /* Keep the original source location on the first 'if'. */
2739 location_t locus
= EXPR_LOC_OR_LOC (expr
, input_location
);
2740 TREE_OPERAND (expr
, 0) = TREE_OPERAND (pred
, 1);
2741 /* Set the source location of the && on the second 'if'. */
2742 if (EXPR_HAS_LOCATION (pred
))
2743 SET_EXPR_LOCATION (expr
, EXPR_LOCATION (pred
));
2744 then_
= shortcut_cond_expr (expr
);
2745 then_se
= then_
&& TREE_SIDE_EFFECTS (then_
);
2746 pred
= TREE_OPERAND (pred
, 0);
2747 expr
= build3 (COND_EXPR
, void_type_node
, pred
, then_
, NULL_TREE
);
2748 SET_EXPR_LOCATION (expr
, locus
);
2754 /* If there is no 'then', turn
2757 if (a); else if (b); else d. */
2758 while (TREE_CODE (pred
) == TRUTH_ORIF_EXPR
)
2760 /* Keep the original source location on the first 'if'. */
2761 location_t locus
= EXPR_LOC_OR_LOC (expr
, input_location
);
2762 TREE_OPERAND (expr
, 0) = TREE_OPERAND (pred
, 1);
2763 /* Set the source location of the || on the second 'if'. */
2764 if (EXPR_HAS_LOCATION (pred
))
2765 SET_EXPR_LOCATION (expr
, EXPR_LOCATION (pred
));
2766 else_
= shortcut_cond_expr (expr
);
2767 else_se
= else_
&& TREE_SIDE_EFFECTS (else_
);
2768 pred
= TREE_OPERAND (pred
, 0);
2769 expr
= build3 (COND_EXPR
, void_type_node
, pred
, NULL_TREE
, else_
);
2770 SET_EXPR_LOCATION (expr
, locus
);
2774 /* If we're done, great. */
2775 if (TREE_CODE (pred
) != TRUTH_ANDIF_EXPR
2776 && TREE_CODE (pred
) != TRUTH_ORIF_EXPR
)
2779 /* Otherwise we need to mess with gotos. Change
2782 if (a); else goto no;
2785 and recursively gimplify the condition. */
2787 true_label
= false_label
= end_label
= NULL_TREE
;
2789 /* If our arms just jump somewhere, hijack those labels so we don't
2790 generate jumps to jumps. */
2793 && TREE_CODE (then_
) == GOTO_EXPR
2794 && TREE_CODE (GOTO_DESTINATION (then_
)) == LABEL_DECL
)
2796 true_label
= GOTO_DESTINATION (then_
);
2802 && TREE_CODE (else_
) == GOTO_EXPR
2803 && TREE_CODE (GOTO_DESTINATION (else_
)) == LABEL_DECL
)
2805 false_label
= GOTO_DESTINATION (else_
);
2810 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
2812 true_label_p
= &true_label
;
2814 true_label_p
= NULL
;
2816 /* The 'else' branch also needs a label if it contains interesting code. */
2817 if (false_label
|| else_se
)
2818 false_label_p
= &false_label
;
2820 false_label_p
= NULL
;
2822 /* If there was nothing else in our arms, just forward the label(s). */
2823 if (!then_se
&& !else_se
)
2824 return shortcut_cond_r (pred
, true_label_p
, false_label_p
,
2825 EXPR_LOC_OR_LOC (expr
, input_location
));
2827 /* If our last subexpression already has a terminal label, reuse it. */
2829 t
= expr_last (else_
);
2831 t
= expr_last (then_
);
2834 if (t
&& TREE_CODE (t
) == LABEL_EXPR
)
2835 end_label
= LABEL_EXPR_LABEL (t
);
2837 /* If we don't care about jumping to the 'else' branch, jump to the end
2838 if the condition is false. */
2840 false_label_p
= &end_label
;
2842 /* We only want to emit these labels if we aren't hijacking them. */
2843 emit_end
= (end_label
== NULL_TREE
);
2844 emit_false
= (false_label
== NULL_TREE
);
2846 /* We only emit the jump over the else clause if we have to--if the
2847 then clause may fall through. Otherwise we can wind up with a
2848 useless jump and a useless label at the end of gimplified code,
2849 which will cause us to think that this conditional as a whole
2850 falls through even if it doesn't. If we then inline a function
2851 which ends with such a condition, that can cause us to issue an
2852 inappropriate warning about control reaching the end of a
2853 non-void function. */
2854 jump_over_else
= block_may_fallthru (then_
);
2856 pred
= shortcut_cond_r (pred
, true_label_p
, false_label_p
,
2857 EXPR_LOC_OR_LOC (expr
, input_location
));
2860 append_to_statement_list (pred
, &expr
);
2862 append_to_statement_list (then_
, &expr
);
2867 tree last
= expr_last (expr
);
2868 t
= build_and_jump (&end_label
);
2869 if (EXPR_HAS_LOCATION (last
))
2870 SET_EXPR_LOCATION (t
, EXPR_LOCATION (last
));
2871 append_to_statement_list (t
, &expr
);
2875 t
= build1 (LABEL_EXPR
, void_type_node
, false_label
);
2876 append_to_statement_list (t
, &expr
);
2878 append_to_statement_list (else_
, &expr
);
2880 if (emit_end
&& end_label
)
2882 t
= build1 (LABEL_EXPR
, void_type_node
, end_label
);
2883 append_to_statement_list (t
, &expr
);
2889 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
2892 gimple_boolify (tree expr
)
2894 tree type
= TREE_TYPE (expr
);
2895 location_t loc
= EXPR_LOCATION (expr
);
2897 if (TREE_CODE (expr
) == NE_EXPR
2898 && TREE_CODE (TREE_OPERAND (expr
, 0)) == CALL_EXPR
2899 && integer_zerop (TREE_OPERAND (expr
, 1)))
2901 tree call
= TREE_OPERAND (expr
, 0);
2902 tree fn
= get_callee_fndecl (call
);
2904 /* For __builtin_expect ((long) (x), y) recurse into x as well
2905 if x is truth_value_p. */
2907 && DECL_BUILT_IN_CLASS (fn
) == BUILT_IN_NORMAL
2908 && DECL_FUNCTION_CODE (fn
) == BUILT_IN_EXPECT
2909 && call_expr_nargs (call
) == 2)
2911 tree arg
= CALL_EXPR_ARG (call
, 0);
2914 if (TREE_CODE (arg
) == NOP_EXPR
2915 && TREE_TYPE (arg
) == TREE_TYPE (call
))
2916 arg
= TREE_OPERAND (arg
, 0);
2917 if (truth_value_p (TREE_CODE (arg
)))
2919 arg
= gimple_boolify (arg
);
2920 CALL_EXPR_ARG (call
, 0)
2921 = fold_convert_loc (loc
, TREE_TYPE (call
), arg
);
2927 switch (TREE_CODE (expr
))
2929 case TRUTH_AND_EXPR
:
2931 case TRUTH_XOR_EXPR
:
2932 case TRUTH_ANDIF_EXPR
:
2933 case TRUTH_ORIF_EXPR
:
2934 /* Also boolify the arguments of truth exprs. */
2935 TREE_OPERAND (expr
, 1) = gimple_boolify (TREE_OPERAND (expr
, 1));
2938 case TRUTH_NOT_EXPR
:
2939 TREE_OPERAND (expr
, 0) = gimple_boolify (TREE_OPERAND (expr
, 0));
2941 /* These expressions always produce boolean results. */
2942 if (TREE_CODE (type
) != BOOLEAN_TYPE
)
2943 TREE_TYPE (expr
) = boolean_type_node
;
2947 switch ((enum annot_expr_kind
) TREE_INT_CST_LOW (TREE_OPERAND (expr
, 1)))
2949 case annot_expr_ivdep_kind
:
2950 case annot_expr_no_vector_kind
:
2951 case annot_expr_vector_kind
:
2952 TREE_OPERAND (expr
, 0) = gimple_boolify (TREE_OPERAND (expr
, 0));
2953 if (TREE_CODE (type
) != BOOLEAN_TYPE
)
2954 TREE_TYPE (expr
) = boolean_type_node
;
2961 if (COMPARISON_CLASS_P (expr
))
2963 /* There expressions always prduce boolean results. */
2964 if (TREE_CODE (type
) != BOOLEAN_TYPE
)
2965 TREE_TYPE (expr
) = boolean_type_node
;
2968 /* Other expressions that get here must have boolean values, but
2969 might need to be converted to the appropriate mode. */
2970 if (TREE_CODE (type
) == BOOLEAN_TYPE
)
2972 return fold_convert_loc (loc
, boolean_type_node
, expr
);
2976 /* Given a conditional expression *EXPR_P without side effects, gimplify
2977 its operands. New statements are inserted to PRE_P. */
2979 static enum gimplify_status
2980 gimplify_pure_cond_expr (tree
*expr_p
, gimple_seq
*pre_p
)
2982 tree expr
= *expr_p
, cond
;
2983 enum gimplify_status ret
, tret
;
2984 enum tree_code code
;
2986 cond
= gimple_boolify (COND_EXPR_COND (expr
));
2988 /* We need to handle && and || specially, as their gimplification
2989 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
2990 code
= TREE_CODE (cond
);
2991 if (code
== TRUTH_ANDIF_EXPR
)
2992 TREE_SET_CODE (cond
, TRUTH_AND_EXPR
);
2993 else if (code
== TRUTH_ORIF_EXPR
)
2994 TREE_SET_CODE (cond
, TRUTH_OR_EXPR
);
2995 ret
= gimplify_expr (&cond
, pre_p
, NULL
, is_gimple_condexpr
, fb_rvalue
);
2996 COND_EXPR_COND (*expr_p
) = cond
;
2998 tret
= gimplify_expr (&COND_EXPR_THEN (expr
), pre_p
, NULL
,
2999 is_gimple_val
, fb_rvalue
);
3000 ret
= MIN (ret
, tret
);
3001 tret
= gimplify_expr (&COND_EXPR_ELSE (expr
), pre_p
, NULL
,
3002 is_gimple_val
, fb_rvalue
);
3004 return MIN (ret
, tret
);
3007 /* Return true if evaluating EXPR could trap.
3008 EXPR is GENERIC, while tree_could_trap_p can be called
3012 generic_expr_could_trap_p (tree expr
)
3016 if (!expr
|| is_gimple_val (expr
))
3019 if (!EXPR_P (expr
) || tree_could_trap_p (expr
))
3022 n
= TREE_OPERAND_LENGTH (expr
);
3023 for (i
= 0; i
< n
; i
++)
3024 if (generic_expr_could_trap_p (TREE_OPERAND (expr
, i
)))
3030 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
3039 The second form is used when *EXPR_P is of type void.
3041 PRE_P points to the list where side effects that must happen before
3042 *EXPR_P should be stored. */
3044 static enum gimplify_status
3045 gimplify_cond_expr (tree
*expr_p
, gimple_seq
*pre_p
, fallback_t fallback
)
3047 tree expr
= *expr_p
;
3048 tree type
= TREE_TYPE (expr
);
3049 location_t loc
= EXPR_LOCATION (expr
);
3050 tree tmp
, arm1
, arm2
;
3051 enum gimplify_status ret
;
3052 tree label_true
, label_false
, label_cont
;
3053 bool have_then_clause_p
, have_else_clause_p
;
3055 enum tree_code pred_code
;
3056 gimple_seq seq
= NULL
;
3058 /* If this COND_EXPR has a value, copy the values into a temporary within
3060 if (!VOID_TYPE_P (type
))
3062 tree then_
= TREE_OPERAND (expr
, 1), else_
= TREE_OPERAND (expr
, 2);
3065 /* If either an rvalue is ok or we do not require an lvalue, create the
3066 temporary. But we cannot do that if the type is addressable. */
3067 if (((fallback
& fb_rvalue
) || !(fallback
& fb_lvalue
))
3068 && !TREE_ADDRESSABLE (type
))
3070 if (gimplify_ctxp
->allow_rhs_cond_expr
3071 /* If either branch has side effects or could trap, it can't be
3072 evaluated unconditionally. */
3073 && !TREE_SIDE_EFFECTS (then_
)
3074 && !generic_expr_could_trap_p (then_
)
3075 && !TREE_SIDE_EFFECTS (else_
)
3076 && !generic_expr_could_trap_p (else_
))
3077 return gimplify_pure_cond_expr (expr_p
, pre_p
);
3079 tmp
= create_tmp_var (type
, "iftmp");
3083 /* Otherwise, only create and copy references to the values. */
3086 type
= build_pointer_type (type
);
3088 if (!VOID_TYPE_P (TREE_TYPE (then_
)))
3089 then_
= build_fold_addr_expr_loc (loc
, then_
);
3091 if (!VOID_TYPE_P (TREE_TYPE (else_
)))
3092 else_
= build_fold_addr_expr_loc (loc
, else_
);
3095 = build3 (COND_EXPR
, type
, TREE_OPERAND (expr
, 0), then_
, else_
);
3097 tmp
= create_tmp_var (type
, "iftmp");
3098 result
= build_simple_mem_ref_loc (loc
, tmp
);
3101 /* Build the new then clause, `tmp = then_;'. But don't build the
3102 assignment if the value is void; in C++ it can be if it's a throw. */
3103 if (!VOID_TYPE_P (TREE_TYPE (then_
)))
3104 TREE_OPERAND (expr
, 1) = build2 (MODIFY_EXPR
, type
, tmp
, then_
);
3106 /* Similarly, build the new else clause, `tmp = else_;'. */
3107 if (!VOID_TYPE_P (TREE_TYPE (else_
)))
3108 TREE_OPERAND (expr
, 2) = build2 (MODIFY_EXPR
, type
, tmp
, else_
);
3110 TREE_TYPE (expr
) = void_type_node
;
3111 recalculate_side_effects (expr
);
3113 /* Move the COND_EXPR to the prequeue. */
3114 gimplify_stmt (&expr
, pre_p
);
3120 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
3121 STRIP_TYPE_NOPS (TREE_OPERAND (expr
, 0));
3122 if (TREE_CODE (TREE_OPERAND (expr
, 0)) == COMPOUND_EXPR
)
3123 gimplify_compound_expr (&TREE_OPERAND (expr
, 0), pre_p
, true);
3125 /* Make sure the condition has BOOLEAN_TYPE. */
3126 TREE_OPERAND (expr
, 0) = gimple_boolify (TREE_OPERAND (expr
, 0));
3128 /* Break apart && and || conditions. */
3129 if (TREE_CODE (TREE_OPERAND (expr
, 0)) == TRUTH_ANDIF_EXPR
3130 || TREE_CODE (TREE_OPERAND (expr
, 0)) == TRUTH_ORIF_EXPR
)
3132 expr
= shortcut_cond_expr (expr
);
3134 if (expr
!= *expr_p
)
3138 /* We can't rely on gimplify_expr to re-gimplify the expanded
3139 form properly, as cleanups might cause the target labels to be
3140 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
3141 set up a conditional context. */
3142 gimple_push_condition ();
3143 gimplify_stmt (expr_p
, &seq
);
3144 gimple_pop_condition (pre_p
);
3145 gimple_seq_add_seq (pre_p
, seq
);
3151 /* Now do the normal gimplification. */
3153 /* Gimplify condition. */
3154 ret
= gimplify_expr (&TREE_OPERAND (expr
, 0), pre_p
, NULL
, is_gimple_condexpr
,
3156 if (ret
== GS_ERROR
)
3158 gcc_assert (TREE_OPERAND (expr
, 0) != NULL_TREE
);
3160 gimple_push_condition ();
3162 have_then_clause_p
= have_else_clause_p
= false;
3163 if (TREE_OPERAND (expr
, 1) != NULL
3164 && TREE_CODE (TREE_OPERAND (expr
, 1)) == GOTO_EXPR
3165 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr
, 1))) == LABEL_DECL
3166 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr
, 1)))
3167 == current_function_decl
)
3168 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
3169 have different locations, otherwise we end up with incorrect
3170 location information on the branches. */
3172 || !EXPR_HAS_LOCATION (expr
)
3173 || !EXPR_HAS_LOCATION (TREE_OPERAND (expr
, 1))
3174 || EXPR_LOCATION (expr
) == EXPR_LOCATION (TREE_OPERAND (expr
, 1))))
3176 label_true
= GOTO_DESTINATION (TREE_OPERAND (expr
, 1));
3177 have_then_clause_p
= true;
3180 label_true
= create_artificial_label (UNKNOWN_LOCATION
);
3181 if (TREE_OPERAND (expr
, 2) != NULL
3182 && TREE_CODE (TREE_OPERAND (expr
, 2)) == GOTO_EXPR
3183 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr
, 2))) == LABEL_DECL
3184 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr
, 2)))
3185 == current_function_decl
)
3186 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
3187 have different locations, otherwise we end up with incorrect
3188 location information on the branches. */
3190 || !EXPR_HAS_LOCATION (expr
)
3191 || !EXPR_HAS_LOCATION (TREE_OPERAND (expr
, 2))
3192 || EXPR_LOCATION (expr
) == EXPR_LOCATION (TREE_OPERAND (expr
, 2))))
3194 label_false
= GOTO_DESTINATION (TREE_OPERAND (expr
, 2));
3195 have_else_clause_p
= true;
3198 label_false
= create_artificial_label (UNKNOWN_LOCATION
);
3200 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr
), &pred_code
, &arm1
,
3202 cond_stmt
= gimple_build_cond (pred_code
, arm1
, arm2
, label_true
,
3204 gimplify_seq_add_stmt (&seq
, cond_stmt
);
3205 gimple_stmt_iterator gsi
= gsi_last (seq
);
3206 maybe_fold_stmt (&gsi
);
3208 label_cont
= NULL_TREE
;
3209 if (!have_then_clause_p
)
3211 /* For if (...) {} else { code; } put label_true after
3213 if (TREE_OPERAND (expr
, 1) == NULL_TREE
3214 && !have_else_clause_p
3215 && TREE_OPERAND (expr
, 2) != NULL_TREE
)
3216 label_cont
= label_true
;
3219 gimplify_seq_add_stmt (&seq
, gimple_build_label (label_true
));
3220 have_then_clause_p
= gimplify_stmt (&TREE_OPERAND (expr
, 1), &seq
);
3221 /* For if (...) { code; } else {} or
3222 if (...) { code; } else goto label; or
3223 if (...) { code; return; } else { ... }
3224 label_cont isn't needed. */
3225 if (!have_else_clause_p
3226 && TREE_OPERAND (expr
, 2) != NULL_TREE
3227 && gimple_seq_may_fallthru (seq
))
3230 label_cont
= create_artificial_label (UNKNOWN_LOCATION
);
3232 g
= gimple_build_goto (label_cont
);
3234 /* GIMPLE_COND's are very low level; they have embedded
3235 gotos. This particular embedded goto should not be marked
3236 with the location of the original COND_EXPR, as it would
3237 correspond to the COND_EXPR's condition, not the ELSE or the
3238 THEN arms. To avoid marking it with the wrong location, flag
3239 it as "no location". */
3240 gimple_set_do_not_emit_location (g
);
3242 gimplify_seq_add_stmt (&seq
, g
);
3246 if (!have_else_clause_p
)
3248 gimplify_seq_add_stmt (&seq
, gimple_build_label (label_false
));
3249 have_else_clause_p
= gimplify_stmt (&TREE_OPERAND (expr
, 2), &seq
);
3252 gimplify_seq_add_stmt (&seq
, gimple_build_label (label_cont
));
3254 gimple_pop_condition (pre_p
);
3255 gimple_seq_add_seq (pre_p
, seq
);
3257 if (ret
== GS_ERROR
)
3259 else if (have_then_clause_p
|| have_else_clause_p
)
3263 /* Both arms are empty; replace the COND_EXPR with its predicate. */
3264 expr
= TREE_OPERAND (expr
, 0);
3265 gimplify_stmt (&expr
, pre_p
);
3272 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
3273 to be marked addressable.
3275 We cannot rely on such an expression being directly markable if a temporary
3276 has been created by the gimplification. In this case, we create another
3277 temporary and initialize it with a copy, which will become a store after we
3278 mark it addressable. This can happen if the front-end passed us something
3279 that it could not mark addressable yet, like a Fortran pass-by-reference
3280 parameter (int) floatvar. */
3283 prepare_gimple_addressable (tree
*expr_p
, gimple_seq
*seq_p
)
3285 while (handled_component_p (*expr_p
))
3286 expr_p
= &TREE_OPERAND (*expr_p
, 0);
3287 if (is_gimple_reg (*expr_p
))
3289 tree var
= get_initialized_tmp_var (*expr_p
, seq_p
, NULL
);
3290 DECL_GIMPLE_REG_P (var
) = 0;
3295 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
3296 a call to __builtin_memcpy. */
3298 static enum gimplify_status
3299 gimplify_modify_expr_to_memcpy (tree
*expr_p
, tree size
, bool want_value
,
3302 tree t
, to
, to_ptr
, from
, from_ptr
;
3304 location_t loc
= EXPR_LOCATION (*expr_p
);
3306 to
= TREE_OPERAND (*expr_p
, 0);
3307 from
= TREE_OPERAND (*expr_p
, 1);
3309 /* Mark the RHS addressable. Beware that it may not be possible to do so
3310 directly if a temporary has been created by the gimplification. */
3311 prepare_gimple_addressable (&from
, seq_p
);
3313 mark_addressable (from
);
3314 from_ptr
= build_fold_addr_expr_loc (loc
, from
);
3315 gimplify_arg (&from_ptr
, seq_p
, loc
);
3317 mark_addressable (to
);
3318 to_ptr
= build_fold_addr_expr_loc (loc
, to
);
3319 gimplify_arg (&to_ptr
, seq_p
, loc
);
3321 t
= builtin_decl_implicit (BUILT_IN_MEMCPY
);
3323 gs
= gimple_build_call (t
, 3, to_ptr
, from_ptr
, size
);
3327 /* tmp = memcpy() */
3328 t
= create_tmp_var (TREE_TYPE (to_ptr
));
3329 gimple_call_set_lhs (gs
, t
);
3330 gimplify_seq_add_stmt (seq_p
, gs
);
3332 *expr_p
= build_simple_mem_ref (t
);
3336 gimplify_seq_add_stmt (seq_p
, gs
);
3341 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
3342 a call to __builtin_memset. In this case we know that the RHS is
3343 a CONSTRUCTOR with an empty element list. */
3345 static enum gimplify_status
3346 gimplify_modify_expr_to_memset (tree
*expr_p
, tree size
, bool want_value
,
3349 tree t
, from
, to
, to_ptr
;
3351 location_t loc
= EXPR_LOCATION (*expr_p
);
3353 /* Assert our assumptions, to abort instead of producing wrong code
3354 silently if they are not met. Beware that the RHS CONSTRUCTOR might
3355 not be immediately exposed. */
3356 from
= TREE_OPERAND (*expr_p
, 1);
3357 if (TREE_CODE (from
) == WITH_SIZE_EXPR
)
3358 from
= TREE_OPERAND (from
, 0);
3360 gcc_assert (TREE_CODE (from
) == CONSTRUCTOR
3361 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from
)));
3364 to
= TREE_OPERAND (*expr_p
, 0);
3366 to_ptr
= build_fold_addr_expr_loc (loc
, to
);
3367 gimplify_arg (&to_ptr
, seq_p
, loc
);
3368 t
= builtin_decl_implicit (BUILT_IN_MEMSET
);
3370 gs
= gimple_build_call (t
, 3, to_ptr
, integer_zero_node
, size
);
3374 /* tmp = memset() */
3375 t
= create_tmp_var (TREE_TYPE (to_ptr
));
3376 gimple_call_set_lhs (gs
, t
);
3377 gimplify_seq_add_stmt (seq_p
, gs
);
3379 *expr_p
= build1 (INDIRECT_REF
, TREE_TYPE (to
), t
);
3383 gimplify_seq_add_stmt (seq_p
, gs
);
3388 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
3389 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
3390 assignment. Return non-null if we detect a potential overlap. */
3392 struct gimplify_init_ctor_preeval_data
3394 /* The base decl of the lhs object. May be NULL, in which case we
3395 have to assume the lhs is indirect. */
3398 /* The alias set of the lhs object. */
3399 alias_set_type lhs_alias_set
;
3403 gimplify_init_ctor_preeval_1 (tree
*tp
, int *walk_subtrees
, void *xdata
)
3405 struct gimplify_init_ctor_preeval_data
*data
3406 = (struct gimplify_init_ctor_preeval_data
*) xdata
;
3409 /* If we find the base object, obviously we have overlap. */
3410 if (data
->lhs_base_decl
== t
)
3413 /* If the constructor component is indirect, determine if we have a
3414 potential overlap with the lhs. The only bits of information we
3415 have to go on at this point are addressability and alias sets. */
3416 if ((INDIRECT_REF_P (t
)
3417 || TREE_CODE (t
) == MEM_REF
)
3418 && (!data
->lhs_base_decl
|| TREE_ADDRESSABLE (data
->lhs_base_decl
))
3419 && alias_sets_conflict_p (data
->lhs_alias_set
, get_alias_set (t
)))
3422 /* If the constructor component is a call, determine if it can hide a
3423 potential overlap with the lhs through an INDIRECT_REF like above.
3424 ??? Ugh - this is completely broken. In fact this whole analysis
3425 doesn't look conservative. */
3426 if (TREE_CODE (t
) == CALL_EXPR
)
3428 tree type
, fntype
= TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t
)));
3430 for (type
= TYPE_ARG_TYPES (fntype
); type
; type
= TREE_CHAIN (type
))
3431 if (POINTER_TYPE_P (TREE_VALUE (type
))
3432 && (!data
->lhs_base_decl
|| TREE_ADDRESSABLE (data
->lhs_base_decl
))
3433 && alias_sets_conflict_p (data
->lhs_alias_set
,
3435 (TREE_TYPE (TREE_VALUE (type
)))))
3439 if (IS_TYPE_OR_DECL_P (t
))
3444 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
3445 force values that overlap with the lhs (as described by *DATA)
3446 into temporaries. */
3449 gimplify_init_ctor_preeval (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
3450 struct gimplify_init_ctor_preeval_data
*data
)
3452 enum gimplify_status one
;
3454 /* If the value is constant, then there's nothing to pre-evaluate. */
3455 if (TREE_CONSTANT (*expr_p
))
3457 /* Ensure it does not have side effects, it might contain a reference to
3458 the object we're initializing. */
3459 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p
));
3463 /* If the type has non-trivial constructors, we can't pre-evaluate. */
3464 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p
)))
3467 /* Recurse for nested constructors. */
3468 if (TREE_CODE (*expr_p
) == CONSTRUCTOR
)
3470 unsigned HOST_WIDE_INT ix
;
3471 constructor_elt
*ce
;
3472 vec
<constructor_elt
, va_gc
> *v
= CONSTRUCTOR_ELTS (*expr_p
);
3474 FOR_EACH_VEC_SAFE_ELT (v
, ix
, ce
)
3475 gimplify_init_ctor_preeval (&ce
->value
, pre_p
, post_p
, data
);
3480 /* If this is a variable sized type, we must remember the size. */
3481 maybe_with_size_expr (expr_p
);
3483 /* Gimplify the constructor element to something appropriate for the rhs
3484 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
3485 the gimplifier will consider this a store to memory. Doing this
3486 gimplification now means that we won't have to deal with complicated
3487 language-specific trees, nor trees like SAVE_EXPR that can induce
3488 exponential search behavior. */
3489 one
= gimplify_expr (expr_p
, pre_p
, post_p
, is_gimple_mem_rhs
, fb_rvalue
);
3490 if (one
== GS_ERROR
)
3496 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
3497 with the lhs, since "a = { .x=a }" doesn't make sense. This will
3498 always be true for all scalars, since is_gimple_mem_rhs insists on a
3499 temporary variable for them. */
3500 if (DECL_P (*expr_p
))
3503 /* If this is of variable size, we have no choice but to assume it doesn't
3504 overlap since we can't make a temporary for it. */
3505 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p
))) != INTEGER_CST
)
3508 /* Otherwise, we must search for overlap ... */
3509 if (!walk_tree (expr_p
, gimplify_init_ctor_preeval_1
, data
, NULL
))
3512 /* ... and if found, force the value into a temporary. */
3513 *expr_p
= get_formal_tmp_var (*expr_p
, pre_p
);
3516 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
3517 a RANGE_EXPR in a CONSTRUCTOR for an array.
3521 object[var] = value;
3528 We increment var _after_ the loop exit check because we might otherwise
3529 fail if upper == TYPE_MAX_VALUE (type for upper).
3531 Note that we never have to deal with SAVE_EXPRs here, because this has
3532 already been taken care of for us, in gimplify_init_ctor_preeval(). */
3534 static void gimplify_init_ctor_eval (tree
, vec
<constructor_elt
, va_gc
> *,
3535 gimple_seq
*, bool);
3538 gimplify_init_ctor_eval_range (tree object
, tree lower
, tree upper
,
3539 tree value
, tree array_elt_type
,
3540 gimple_seq
*pre_p
, bool cleared
)
3542 tree loop_entry_label
, loop_exit_label
, fall_thru_label
;
3543 tree var
, var_type
, cref
, tmp
;
3545 loop_entry_label
= create_artificial_label (UNKNOWN_LOCATION
);
3546 loop_exit_label
= create_artificial_label (UNKNOWN_LOCATION
);
3547 fall_thru_label
= create_artificial_label (UNKNOWN_LOCATION
);
3549 /* Create and initialize the index variable. */
3550 var_type
= TREE_TYPE (upper
);
3551 var
= create_tmp_var (var_type
);
3552 gimplify_seq_add_stmt (pre_p
, gimple_build_assign (var
, lower
));
3554 /* Add the loop entry label. */
3555 gimplify_seq_add_stmt (pre_p
, gimple_build_label (loop_entry_label
));
3557 /* Build the reference. */
3558 cref
= build4 (ARRAY_REF
, array_elt_type
, unshare_expr (object
),
3559 var
, NULL_TREE
, NULL_TREE
);
3561 /* If we are a constructor, just call gimplify_init_ctor_eval to do
3562 the store. Otherwise just assign value to the reference. */
3564 if (TREE_CODE (value
) == CONSTRUCTOR
)
3565 /* NB we might have to call ourself recursively through
3566 gimplify_init_ctor_eval if the value is a constructor. */
3567 gimplify_init_ctor_eval (cref
, CONSTRUCTOR_ELTS (value
),
3570 gimplify_seq_add_stmt (pre_p
, gimple_build_assign (cref
, value
));
3572 /* We exit the loop when the index var is equal to the upper bound. */
3573 gimplify_seq_add_stmt (pre_p
,
3574 gimple_build_cond (EQ_EXPR
, var
, upper
,
3575 loop_exit_label
, fall_thru_label
));
3577 gimplify_seq_add_stmt (pre_p
, gimple_build_label (fall_thru_label
));
3579 /* Otherwise, increment the index var... */
3580 tmp
= build2 (PLUS_EXPR
, var_type
, var
,
3581 fold_convert (var_type
, integer_one_node
));
3582 gimplify_seq_add_stmt (pre_p
, gimple_build_assign (var
, tmp
));
3584 /* ...and jump back to the loop entry. */
3585 gimplify_seq_add_stmt (pre_p
, gimple_build_goto (loop_entry_label
));
3587 /* Add the loop exit label. */
3588 gimplify_seq_add_stmt (pre_p
, gimple_build_label (loop_exit_label
));
3591 /* Return true if FDECL is accessing a field that is zero sized. */
3594 zero_sized_field_decl (const_tree fdecl
)
3596 if (TREE_CODE (fdecl
) == FIELD_DECL
&& DECL_SIZE (fdecl
)
3597 && integer_zerop (DECL_SIZE (fdecl
)))
3602 /* Return true if TYPE is zero sized. */
3605 zero_sized_type (const_tree type
)
3607 if (AGGREGATE_TYPE_P (type
) && TYPE_SIZE (type
)
3608 && integer_zerop (TYPE_SIZE (type
)))
3613 /* A subroutine of gimplify_init_constructor. Generate individual
3614 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
3615 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
3616 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
3620 gimplify_init_ctor_eval (tree object
, vec
<constructor_elt
, va_gc
> *elts
,
3621 gimple_seq
*pre_p
, bool cleared
)
3623 tree array_elt_type
= NULL
;
3624 unsigned HOST_WIDE_INT ix
;
3625 tree purpose
, value
;
3627 if (TREE_CODE (TREE_TYPE (object
)) == ARRAY_TYPE
)
3628 array_elt_type
= TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object
)));
3630 FOR_EACH_CONSTRUCTOR_ELT (elts
, ix
, purpose
, value
)
3634 /* NULL values are created above for gimplification errors. */
3638 if (cleared
&& initializer_zerop (value
))
3641 /* ??? Here's to hoping the front end fills in all of the indices,
3642 so we don't have to figure out what's missing ourselves. */
3643 gcc_assert (purpose
);
3645 /* Skip zero-sized fields, unless value has side-effects. This can
3646 happen with calls to functions returning a zero-sized type, which
3647 we shouldn't discard. As a number of downstream passes don't
3648 expect sets of zero-sized fields, we rely on the gimplification of
3649 the MODIFY_EXPR we make below to drop the assignment statement. */
3650 if (! TREE_SIDE_EFFECTS (value
) && zero_sized_field_decl (purpose
))
3653 /* If we have a RANGE_EXPR, we have to build a loop to assign the
3655 if (TREE_CODE (purpose
) == RANGE_EXPR
)
3657 tree lower
= TREE_OPERAND (purpose
, 0);
3658 tree upper
= TREE_OPERAND (purpose
, 1);
3660 /* If the lower bound is equal to upper, just treat it as if
3661 upper was the index. */
3662 if (simple_cst_equal (lower
, upper
))
3666 gimplify_init_ctor_eval_range (object
, lower
, upper
, value
,
3667 array_elt_type
, pre_p
, cleared
);
3674 /* Do not use bitsizetype for ARRAY_REF indices. */
3675 if (TYPE_DOMAIN (TREE_TYPE (object
)))
3677 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object
))),
3679 cref
= build4 (ARRAY_REF
, array_elt_type
, unshare_expr (object
),
3680 purpose
, NULL_TREE
, NULL_TREE
);
3684 gcc_assert (TREE_CODE (purpose
) == FIELD_DECL
);
3685 cref
= build3 (COMPONENT_REF
, TREE_TYPE (purpose
),
3686 unshare_expr (object
), purpose
, NULL_TREE
);
3689 if (TREE_CODE (value
) == CONSTRUCTOR
3690 && TREE_CODE (TREE_TYPE (value
)) != VECTOR_TYPE
)
3691 gimplify_init_ctor_eval (cref
, CONSTRUCTOR_ELTS (value
),
3695 tree init
= build2 (INIT_EXPR
, TREE_TYPE (cref
), cref
, value
);
3696 gimplify_and_add (init
, pre_p
);
3702 /* Return the appropriate RHS predicate for this LHS. */
3705 rhs_predicate_for (tree lhs
)
3707 if (is_gimple_reg (lhs
))
3708 return is_gimple_reg_rhs_or_call
;
3710 return is_gimple_mem_rhs_or_call
;
3713 /* Gimplify a C99 compound literal expression. This just means adding
3714 the DECL_EXPR before the current statement and using its anonymous
3717 static enum gimplify_status
3718 gimplify_compound_literal_expr (tree
*expr_p
, gimple_seq
*pre_p
,
3719 bool (*gimple_test_f
) (tree
),
3720 fallback_t fallback
)
3722 tree decl_s
= COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p
);
3723 tree decl
= DECL_EXPR_DECL (decl_s
);
3724 tree init
= DECL_INITIAL (decl
);
3725 /* Mark the decl as addressable if the compound literal
3726 expression is addressable now, otherwise it is marked too late
3727 after we gimplify the initialization expression. */
3728 if (TREE_ADDRESSABLE (*expr_p
))
3729 TREE_ADDRESSABLE (decl
) = 1;
3730 /* Otherwise, if we don't need an lvalue and have a literal directly
3731 substitute it. Check if it matches the gimple predicate, as
3732 otherwise we'd generate a new temporary, and we can as well just
3733 use the decl we already have. */
3734 else if (!TREE_ADDRESSABLE (decl
)
3736 && (fallback
& fb_lvalue
) == 0
3737 && gimple_test_f (init
))
3743 /* Preliminarily mark non-addressed complex variables as eligible
3744 for promotion to gimple registers. We'll transform their uses
3746 if ((TREE_CODE (TREE_TYPE (decl
)) == COMPLEX_TYPE
3747 || TREE_CODE (TREE_TYPE (decl
)) == VECTOR_TYPE
)
3748 && !TREE_THIS_VOLATILE (decl
)
3749 && !needs_to_live_in_memory (decl
))
3750 DECL_GIMPLE_REG_P (decl
) = 1;
3752 /* If the decl is not addressable, then it is being used in some
3753 expression or on the right hand side of a statement, and it can
3754 be put into a readonly data section. */
3755 if (!TREE_ADDRESSABLE (decl
) && (fallback
& fb_lvalue
) == 0)
3756 TREE_READONLY (decl
) = 1;
3758 /* This decl isn't mentioned in the enclosing block, so add it to the
3759 list of temps. FIXME it seems a bit of a kludge to say that
3760 anonymous artificial vars aren't pushed, but everything else is. */
3761 if (DECL_NAME (decl
) == NULL_TREE
&& !DECL_SEEN_IN_BIND_EXPR_P (decl
))
3762 gimple_add_tmp_var (decl
);
3764 gimplify_and_add (decl_s
, pre_p
);
3769 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
3770 return a new CONSTRUCTOR if something changed. */
3773 optimize_compound_literals_in_ctor (tree orig_ctor
)
3775 tree ctor
= orig_ctor
;
3776 vec
<constructor_elt
, va_gc
> *elts
= CONSTRUCTOR_ELTS (ctor
);
3777 unsigned int idx
, num
= vec_safe_length (elts
);
3779 for (idx
= 0; idx
< num
; idx
++)
3781 tree value
= (*elts
)[idx
].value
;
3782 tree newval
= value
;
3783 if (TREE_CODE (value
) == CONSTRUCTOR
)
3784 newval
= optimize_compound_literals_in_ctor (value
);
3785 else if (TREE_CODE (value
) == COMPOUND_LITERAL_EXPR
)
3787 tree decl_s
= COMPOUND_LITERAL_EXPR_DECL_EXPR (value
);
3788 tree decl
= DECL_EXPR_DECL (decl_s
);
3789 tree init
= DECL_INITIAL (decl
);
3791 if (!TREE_ADDRESSABLE (value
)
3792 && !TREE_ADDRESSABLE (decl
)
3794 && TREE_CODE (init
) == CONSTRUCTOR
)
3795 newval
= optimize_compound_literals_in_ctor (init
);
3797 if (newval
== value
)
3800 if (ctor
== orig_ctor
)
3802 ctor
= copy_node (orig_ctor
);
3803 CONSTRUCTOR_ELTS (ctor
) = vec_safe_copy (elts
);
3804 elts
= CONSTRUCTOR_ELTS (ctor
);
3806 (*elts
)[idx
].value
= newval
;
3811 /* A subroutine of gimplify_modify_expr. Break out elements of a
3812 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
3814 Note that we still need to clear any elements that don't have explicit
3815 initializers, so if not all elements are initialized we keep the
3816 original MODIFY_EXPR, we just remove all of the constructor elements.
3818 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
3819 GS_ERROR if we would have to create a temporary when gimplifying
3820 this constructor. Otherwise, return GS_OK.
3822 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
3824 static enum gimplify_status
3825 gimplify_init_constructor (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
3826 bool want_value
, bool notify_temp_creation
)
3828 tree object
, ctor
, type
;
3829 enum gimplify_status ret
;
3830 vec
<constructor_elt
, va_gc
> *elts
;
3832 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p
, 1)) == CONSTRUCTOR
);
3834 if (!notify_temp_creation
)
3836 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
3837 is_gimple_lvalue
, fb_lvalue
);
3838 if (ret
== GS_ERROR
)
3842 object
= TREE_OPERAND (*expr_p
, 0);
3843 ctor
= TREE_OPERAND (*expr_p
, 1) =
3844 optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p
, 1));
3845 type
= TREE_TYPE (ctor
);
3846 elts
= CONSTRUCTOR_ELTS (ctor
);
3849 switch (TREE_CODE (type
))
3853 case QUAL_UNION_TYPE
:
3856 struct gimplify_init_ctor_preeval_data preeval_data
;
3857 HOST_WIDE_INT num_ctor_elements
, num_nonzero_elements
;
3858 bool cleared
, complete_p
, valid_const_initializer
;
3860 /* Aggregate types must lower constructors to initialization of
3861 individual elements. The exception is that a CONSTRUCTOR node
3862 with no elements indicates zero-initialization of the whole. */
3863 if (vec_safe_is_empty (elts
))
3865 if (notify_temp_creation
)
3870 /* Fetch information about the constructor to direct later processing.
3871 We might want to make static versions of it in various cases, and
3872 can only do so if it known to be a valid constant initializer. */
3873 valid_const_initializer
3874 = categorize_ctor_elements (ctor
, &num_nonzero_elements
,
3875 &num_ctor_elements
, &complete_p
);
3877 /* If a const aggregate variable is being initialized, then it
3878 should never be a lose to promote the variable to be static. */
3879 if (valid_const_initializer
3880 && num_nonzero_elements
> 1
3881 && TREE_READONLY (object
)
3882 && TREE_CODE (object
) == VAR_DECL
3883 && (flag_merge_constants
>= 2 || !TREE_ADDRESSABLE (object
)))
3885 if (notify_temp_creation
)
3887 DECL_INITIAL (object
) = ctor
;
3888 TREE_STATIC (object
) = 1;
3889 if (!DECL_NAME (object
))
3890 DECL_NAME (object
) = create_tmp_var_name ("C");
3891 walk_tree (&DECL_INITIAL (object
), force_labels_r
, NULL
, NULL
);
3893 /* ??? C++ doesn't automatically append a .<number> to the
3894 assembler name, and even when it does, it looks at FE private
3895 data structures to figure out what that number should be,
3896 which are not set for this variable. I suppose this is
3897 important for local statics for inline functions, which aren't
3898 "local" in the object file sense. So in order to get a unique
3899 TU-local symbol, we must invoke the lhd version now. */
3900 lhd_set_decl_assembler_name (object
);
3902 *expr_p
= NULL_TREE
;
3906 /* If there are "lots" of initialized elements, even discounting
3907 those that are not address constants (and thus *must* be
3908 computed at runtime), then partition the constructor into
3909 constant and non-constant parts. Block copy the constant
3910 parts in, then generate code for the non-constant parts. */
3911 /* TODO. There's code in cp/typeck.c to do this. */
3913 if (int_size_in_bytes (TREE_TYPE (ctor
)) < 0)
3914 /* store_constructor will ignore the clearing of variable-sized
3915 objects. Initializers for such objects must explicitly set
3916 every field that needs to be set. */
3918 else if (!complete_p
&& !CONSTRUCTOR_NO_CLEARING (ctor
))
3919 /* If the constructor isn't complete, clear the whole object
3920 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
3922 ??? This ought not to be needed. For any element not present
3923 in the initializer, we should simply set them to zero. Except
3924 we'd need to *find* the elements that are not present, and that
3925 requires trickery to avoid quadratic compile-time behavior in
3926 large cases or excessive memory use in small cases. */
3928 else if (num_ctor_elements
- num_nonzero_elements
3929 > CLEAR_RATIO (optimize_function_for_speed_p (cfun
))
3930 && num_nonzero_elements
< num_ctor_elements
/ 4)
3931 /* If there are "lots" of zeros, it's more efficient to clear
3932 the memory and then set the nonzero elements. */
3937 /* If there are "lots" of initialized elements, and all of them
3938 are valid address constants, then the entire initializer can
3939 be dropped to memory, and then memcpy'd out. Don't do this
3940 for sparse arrays, though, as it's more efficient to follow
3941 the standard CONSTRUCTOR behavior of memset followed by
3942 individual element initialization. Also don't do this for small
3943 all-zero initializers (which aren't big enough to merit
3944 clearing), and don't try to make bitwise copies of
3945 TREE_ADDRESSABLE types.
3947 We cannot apply such transformation when compiling chkp static
3948 initializer because creation of initializer image in the memory
3949 will require static initialization of bounds for it. It should
3950 result in another gimplification of similar initializer and we
3951 may fall into infinite loop. */
3952 if (valid_const_initializer
3953 && !(cleared
|| num_nonzero_elements
== 0)
3954 && !TREE_ADDRESSABLE (type
)
3955 && (!current_function_decl
3956 || !lookup_attribute ("chkp ctor",
3957 DECL_ATTRIBUTES (current_function_decl
))))
3959 HOST_WIDE_INT size
= int_size_in_bytes (type
);
3962 /* ??? We can still get unbounded array types, at least
3963 from the C++ front end. This seems wrong, but attempt
3964 to work around it for now. */
3967 size
= int_size_in_bytes (TREE_TYPE (object
));
3969 TREE_TYPE (ctor
) = type
= TREE_TYPE (object
);
3972 /* Find the maximum alignment we can assume for the object. */
3973 /* ??? Make use of DECL_OFFSET_ALIGN. */
3974 if (DECL_P (object
))
3975 align
= DECL_ALIGN (object
);
3977 align
= TYPE_ALIGN (type
);
3979 /* Do a block move either if the size is so small as to make
3980 each individual move a sub-unit move on average, or if it
3981 is so large as to make individual moves inefficient. */
3983 && num_nonzero_elements
> 1
3984 && (size
< num_nonzero_elements
3985 || !can_move_by_pieces (size
, align
)))
3987 if (notify_temp_creation
)
3990 walk_tree (&ctor
, force_labels_r
, NULL
, NULL
);
3991 ctor
= tree_output_constant_def (ctor
);
3992 if (!useless_type_conversion_p (type
, TREE_TYPE (ctor
)))
3993 ctor
= build1 (VIEW_CONVERT_EXPR
, type
, ctor
);
3994 TREE_OPERAND (*expr_p
, 1) = ctor
;
3996 /* This is no longer an assignment of a CONSTRUCTOR, but
3997 we still may have processing to do on the LHS. So
3998 pretend we didn't do anything here to let that happen. */
3999 return GS_UNHANDLED
;
4003 /* If the target is volatile, we have non-zero elements and more than
4004 one field to assign, initialize the target from a temporary. */
4005 if (TREE_THIS_VOLATILE (object
)
4006 && !TREE_ADDRESSABLE (type
)
4007 && num_nonzero_elements
> 0
4008 && vec_safe_length (elts
) > 1)
4010 tree temp
= create_tmp_var (TYPE_MAIN_VARIANT (type
));
4011 TREE_OPERAND (*expr_p
, 0) = temp
;
4012 *expr_p
= build2 (COMPOUND_EXPR
, TREE_TYPE (*expr_p
),
4014 build2 (MODIFY_EXPR
, void_type_node
,
4019 if (notify_temp_creation
)
4022 /* If there are nonzero elements and if needed, pre-evaluate to capture
4023 elements overlapping with the lhs into temporaries. We must do this
4024 before clearing to fetch the values before they are zeroed-out. */
4025 if (num_nonzero_elements
> 0 && TREE_CODE (*expr_p
) != INIT_EXPR
)
4027 preeval_data
.lhs_base_decl
= get_base_address (object
);
4028 if (!DECL_P (preeval_data
.lhs_base_decl
))
4029 preeval_data
.lhs_base_decl
= NULL
;
4030 preeval_data
.lhs_alias_set
= get_alias_set (object
);
4032 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p
, 1),
4033 pre_p
, post_p
, &preeval_data
);
4036 bool ctor_has_side_effects_p
4037 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p
, 1));
4041 /* Zap the CONSTRUCTOR element list, which simplifies this case.
4042 Note that we still have to gimplify, in order to handle the
4043 case of variable sized types. Avoid shared tree structures. */
4044 CONSTRUCTOR_ELTS (ctor
) = NULL
;
4045 TREE_SIDE_EFFECTS (ctor
) = 0;
4046 object
= unshare_expr (object
);
4047 gimplify_stmt (expr_p
, pre_p
);
4050 /* If we have not block cleared the object, or if there are nonzero
4051 elements in the constructor, or if the constructor has side effects,
4052 add assignments to the individual scalar fields of the object. */
4054 || num_nonzero_elements
> 0
4055 || ctor_has_side_effects_p
)
4056 gimplify_init_ctor_eval (object
, elts
, pre_p
, cleared
);
4058 *expr_p
= NULL_TREE
;
4066 if (notify_temp_creation
)
4069 /* Extract the real and imaginary parts out of the ctor. */
4070 gcc_assert (elts
->length () == 2);
4071 r
= (*elts
)[0].value
;
4072 i
= (*elts
)[1].value
;
4073 if (r
== NULL
|| i
== NULL
)
4075 tree zero
= build_zero_cst (TREE_TYPE (type
));
4082 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
4083 represent creation of a complex value. */
4084 if (TREE_CONSTANT (r
) && TREE_CONSTANT (i
))
4086 ctor
= build_complex (type
, r
, i
);
4087 TREE_OPERAND (*expr_p
, 1) = ctor
;
4091 ctor
= build2 (COMPLEX_EXPR
, type
, r
, i
);
4092 TREE_OPERAND (*expr_p
, 1) = ctor
;
4093 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 1),
4096 rhs_predicate_for (TREE_OPERAND (*expr_p
, 0)),
4104 unsigned HOST_WIDE_INT ix
;
4105 constructor_elt
*ce
;
4107 if (notify_temp_creation
)
4110 /* Go ahead and simplify constant constructors to VECTOR_CST. */
4111 if (TREE_CONSTANT (ctor
))
4113 bool constant_p
= true;
4116 /* Even when ctor is constant, it might contain non-*_CST
4117 elements, such as addresses or trapping values like
4118 1.0/0.0 - 1.0/0.0. Such expressions don't belong
4119 in VECTOR_CST nodes. */
4120 FOR_EACH_CONSTRUCTOR_VALUE (elts
, ix
, value
)
4121 if (!CONSTANT_CLASS_P (value
))
4129 TREE_OPERAND (*expr_p
, 1) = build_vector_from_ctor (type
, elts
);
4133 TREE_CONSTANT (ctor
) = 0;
4136 /* Vector types use CONSTRUCTOR all the way through gimple
4137 compilation as a general initializer. */
4138 FOR_EACH_VEC_SAFE_ELT (elts
, ix
, ce
)
4140 enum gimplify_status tret
;
4141 tret
= gimplify_expr (&ce
->value
, pre_p
, post_p
, is_gimple_val
,
4143 if (tret
== GS_ERROR
)
4146 if (!is_gimple_reg (TREE_OPERAND (*expr_p
, 0)))
4147 TREE_OPERAND (*expr_p
, 1) = get_formal_tmp_var (ctor
, pre_p
);
4152 /* So how did we get a CONSTRUCTOR for a scalar type? */
4156 if (ret
== GS_ERROR
)
4158 else if (want_value
)
4165 /* If we have gimplified both sides of the initializer but have
4166 not emitted an assignment, do so now. */
4169 tree lhs
= TREE_OPERAND (*expr_p
, 0);
4170 tree rhs
= TREE_OPERAND (*expr_p
, 1);
4171 gassign
*init
= gimple_build_assign (lhs
, rhs
);
4172 gimplify_seq_add_stmt (pre_p
, init
);
4180 /* Given a pointer value OP0, return a simplified version of an
4181 indirection through OP0, or NULL_TREE if no simplification is
4182 possible. This may only be applied to a rhs of an expression.
4183 Note that the resulting type may be different from the type pointed
4184 to in the sense that it is still compatible from the langhooks
4188 gimple_fold_indirect_ref_rhs (tree t
)
4190 return gimple_fold_indirect_ref (t
);
4193 /* Subroutine of gimplify_modify_expr to do simplifications of
4194 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
4195 something changes. */
4197 static enum gimplify_status
4198 gimplify_modify_expr_rhs (tree
*expr_p
, tree
*from_p
, tree
*to_p
,
4199 gimple_seq
*pre_p
, gimple_seq
*post_p
,
4202 enum gimplify_status ret
= GS_UNHANDLED
;
4208 switch (TREE_CODE (*from_p
))
4211 /* If we're assigning from a read-only variable initialized with
4212 a constructor, do the direct assignment from the constructor,
4213 but only if neither source nor target are volatile since this
4214 latter assignment might end up being done on a per-field basis. */
4215 if (DECL_INITIAL (*from_p
)
4216 && TREE_READONLY (*from_p
)
4217 && !TREE_THIS_VOLATILE (*from_p
)
4218 && !TREE_THIS_VOLATILE (*to_p
)
4219 && TREE_CODE (DECL_INITIAL (*from_p
)) == CONSTRUCTOR
)
4221 tree old_from
= *from_p
;
4222 enum gimplify_status subret
;
4224 /* Move the constructor into the RHS. */
4225 *from_p
= unshare_expr (DECL_INITIAL (*from_p
));
4227 /* Let's see if gimplify_init_constructor will need to put
4229 subret
= gimplify_init_constructor (expr_p
, NULL
, NULL
,
4231 if (subret
== GS_ERROR
)
4233 /* If so, revert the change. */
4245 /* If we have code like
4249 where the type of "x" is a (possibly cv-qualified variant
4250 of "A"), treat the entire expression as identical to "x".
4251 This kind of code arises in C++ when an object is bound
4252 to a const reference, and if "x" is a TARGET_EXPR we want
4253 to take advantage of the optimization below. */
4254 bool volatile_p
= TREE_THIS_VOLATILE (*from_p
);
4255 tree t
= gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p
, 0));
4258 if (TREE_THIS_VOLATILE (t
) != volatile_p
)
4261 t
= build_simple_mem_ref_loc (EXPR_LOCATION (*from_p
),
4262 build_fold_addr_expr (t
));
4263 if (REFERENCE_CLASS_P (t
))
4264 TREE_THIS_VOLATILE (t
) = volatile_p
;
4275 /* If we are initializing something from a TARGET_EXPR, strip the
4276 TARGET_EXPR and initialize it directly, if possible. This can't
4277 be done if the initializer is void, since that implies that the
4278 temporary is set in some non-trivial way.
4280 ??? What about code that pulls out the temp and uses it
4281 elsewhere? I think that such code never uses the TARGET_EXPR as
4282 an initializer. If I'm wrong, we'll die because the temp won't
4283 have any RTL. In that case, I guess we'll need to replace
4284 references somehow. */
4285 tree init
= TARGET_EXPR_INITIAL (*from_p
);
4288 && !VOID_TYPE_P (TREE_TYPE (init
)))
4298 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
4300 gimplify_compound_expr (from_p
, pre_p
, true);
4306 /* If we already made some changes, let the front end have a
4307 crack at this before we break it down. */
4308 if (ret
!= GS_UNHANDLED
)
4310 /* If we're initializing from a CONSTRUCTOR, break this into
4311 individual MODIFY_EXPRs. */
4312 return gimplify_init_constructor (expr_p
, pre_p
, post_p
, want_value
,
4316 /* If we're assigning to a non-register type, push the assignment
4317 down into the branches. This is mandatory for ADDRESSABLE types,
4318 since we cannot generate temporaries for such, but it saves a
4319 copy in other cases as well. */
4320 if (!is_gimple_reg_type (TREE_TYPE (*from_p
)))
4322 /* This code should mirror the code in gimplify_cond_expr. */
4323 enum tree_code code
= TREE_CODE (*expr_p
);
4324 tree cond
= *from_p
;
4325 tree result
= *to_p
;
4327 ret
= gimplify_expr (&result
, pre_p
, post_p
,
4328 is_gimple_lvalue
, fb_lvalue
);
4329 if (ret
!= GS_ERROR
)
4332 if (TREE_TYPE (TREE_OPERAND (cond
, 1)) != void_type_node
)
4333 TREE_OPERAND (cond
, 1)
4334 = build2 (code
, void_type_node
, result
,
4335 TREE_OPERAND (cond
, 1));
4336 if (TREE_TYPE (TREE_OPERAND (cond
, 2)) != void_type_node
)
4337 TREE_OPERAND (cond
, 2)
4338 = build2 (code
, void_type_node
, unshare_expr (result
),
4339 TREE_OPERAND (cond
, 2));
4341 TREE_TYPE (cond
) = void_type_node
;
4342 recalculate_side_effects (cond
);
4346 gimplify_and_add (cond
, pre_p
);
4347 *expr_p
= unshare_expr (result
);
4356 /* For calls that return in memory, give *to_p as the CALL_EXPR's
4357 return slot so that we don't generate a temporary. */
4358 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p
)
4359 && aggregate_value_p (*from_p
, *from_p
))
4363 if (!(rhs_predicate_for (*to_p
))(*from_p
))
4364 /* If we need a temporary, *to_p isn't accurate. */
4366 /* It's OK to use the return slot directly unless it's an NRV. */
4367 else if (TREE_CODE (*to_p
) == RESULT_DECL
4368 && DECL_NAME (*to_p
) == NULL_TREE
4369 && needs_to_live_in_memory (*to_p
))
4371 else if (is_gimple_reg_type (TREE_TYPE (*to_p
))
4372 || (DECL_P (*to_p
) && DECL_REGISTER (*to_p
)))
4373 /* Don't force regs into memory. */
4375 else if (TREE_CODE (*expr_p
) == INIT_EXPR
)
4376 /* It's OK to use the target directly if it's being
4379 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p
)))
4381 /* Always use the target and thus RSO for variable-sized types.
4382 GIMPLE cannot deal with a variable-sized assignment
4383 embedded in a call statement. */
4385 else if (TREE_CODE (*to_p
) != SSA_NAME
4386 && (!is_gimple_variable (*to_p
)
4387 || needs_to_live_in_memory (*to_p
)))
4388 /* Don't use the original target if it's already addressable;
4389 if its address escapes, and the called function uses the
4390 NRV optimization, a conforming program could see *to_p
4391 change before the called function returns; see c++/19317.
4392 When optimizing, the return_slot pass marks more functions
4393 as safe after we have escape info. */
4400 CALL_EXPR_RETURN_SLOT_OPT (*from_p
) = 1;
4401 mark_addressable (*to_p
);
4406 case WITH_SIZE_EXPR
:
4407 /* Likewise for calls that return an aggregate of non-constant size,
4408 since we would not be able to generate a temporary at all. */
4409 if (TREE_CODE (TREE_OPERAND (*from_p
, 0)) == CALL_EXPR
)
4411 *from_p
= TREE_OPERAND (*from_p
, 0);
4412 /* We don't change ret in this case because the
4413 WITH_SIZE_EXPR might have been added in
4414 gimplify_modify_expr, so returning GS_OK would lead to an
4420 /* If we're initializing from a container, push the initialization
4422 case CLEANUP_POINT_EXPR
:
4424 case STATEMENT_LIST
:
4426 tree wrap
= *from_p
;
4429 ret
= gimplify_expr (to_p
, pre_p
, post_p
, is_gimple_min_lval
,
4431 if (ret
!= GS_ERROR
)
4434 t
= voidify_wrapper_expr (wrap
, *expr_p
);
4435 gcc_assert (t
== *expr_p
);
4439 gimplify_and_add (wrap
, pre_p
);
4440 *expr_p
= unshare_expr (*to_p
);
4447 case COMPOUND_LITERAL_EXPR
:
4449 tree complit
= TREE_OPERAND (*expr_p
, 1);
4450 tree decl_s
= COMPOUND_LITERAL_EXPR_DECL_EXPR (complit
);
4451 tree decl
= DECL_EXPR_DECL (decl_s
);
4452 tree init
= DECL_INITIAL (decl
);
4454 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
4455 into struct T x = { 0, 1, 2 } if the address of the
4456 compound literal has never been taken. */
4457 if (!TREE_ADDRESSABLE (complit
)
4458 && !TREE_ADDRESSABLE (decl
)
4461 *expr_p
= copy_node (*expr_p
);
4462 TREE_OPERAND (*expr_p
, 1) = init
;
4477 /* Return true if T looks like a valid GIMPLE statement. */
4480 is_gimple_stmt (tree t
)
4482 const enum tree_code code
= TREE_CODE (t
);
4487 /* The only valid NOP_EXPR is the empty statement. */
4488 return IS_EMPTY_STMT (t
);
4492 /* These are only valid if they're void. */
4493 return TREE_TYPE (t
) == NULL
|| VOID_TYPE_P (TREE_TYPE (t
));
4499 case CASE_LABEL_EXPR
:
4500 case TRY_CATCH_EXPR
:
4501 case TRY_FINALLY_EXPR
:
4502 case EH_FILTER_EXPR
:
4505 case STATEMENT_LIST
:
4509 case OACC_HOST_DATA
:
4512 case OACC_ENTER_DATA
:
4513 case OACC_EXIT_DATA
:
4519 case OMP_DISTRIBUTE
:
4530 case OMP_TARGET_DATA
:
4531 case OMP_TARGET_UPDATE
:
4532 case OMP_TARGET_ENTER_DATA
:
4533 case OMP_TARGET_EXIT_DATA
:
4536 /* These are always void. */
4542 /* These are valid regardless of their type. */
4551 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
4552 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a variable with
4553 DECL_GIMPLE_REG_P set.
4555 IMPORTANT NOTE: This promotion is performed by introducing a load of the
4556 other, unmodified part of the complex object just before the total store.
4557 As a consequence, if the object is still uninitialized, an undefined value
4558 will be loaded into a register, which may result in a spurious exception
4559 if the register is floating-point and the value happens to be a signaling
4560 NaN for example. Then the fully-fledged complex operations lowering pass
4561 followed by a DCE pass are necessary in order to fix things up. */
4563 static enum gimplify_status
4564 gimplify_modify_expr_complex_part (tree
*expr_p
, gimple_seq
*pre_p
,
4567 enum tree_code code
, ocode
;
4568 tree lhs
, rhs
, new_rhs
, other
, realpart
, imagpart
;
4570 lhs
= TREE_OPERAND (*expr_p
, 0);
4571 rhs
= TREE_OPERAND (*expr_p
, 1);
4572 code
= TREE_CODE (lhs
);
4573 lhs
= TREE_OPERAND (lhs
, 0);
4575 ocode
= code
== REALPART_EXPR
? IMAGPART_EXPR
: REALPART_EXPR
;
4576 other
= build1 (ocode
, TREE_TYPE (rhs
), lhs
);
4577 TREE_NO_WARNING (other
) = 1;
4578 other
= get_formal_tmp_var (other
, pre_p
);
4580 realpart
= code
== REALPART_EXPR
? rhs
: other
;
4581 imagpart
= code
== REALPART_EXPR
? other
: rhs
;
4583 if (TREE_CONSTANT (realpart
) && TREE_CONSTANT (imagpart
))
4584 new_rhs
= build_complex (TREE_TYPE (lhs
), realpart
, imagpart
);
4586 new_rhs
= build2 (COMPLEX_EXPR
, TREE_TYPE (lhs
), realpart
, imagpart
);
4588 gimplify_seq_add_stmt (pre_p
, gimple_build_assign (lhs
, new_rhs
));
4589 *expr_p
= (want_value
) ? rhs
: NULL_TREE
;
4594 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
4600 PRE_P points to the list where side effects that must happen before
4601 *EXPR_P should be stored.
4603 POST_P points to the list where side effects that must happen after
4604 *EXPR_P should be stored.
4606 WANT_VALUE is nonzero iff we want to use the value of this expression
4607 in another expression. */
4609 static enum gimplify_status
4610 gimplify_modify_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
4613 tree
*from_p
= &TREE_OPERAND (*expr_p
, 1);
4614 tree
*to_p
= &TREE_OPERAND (*expr_p
, 0);
4615 enum gimplify_status ret
= GS_UNHANDLED
;
4617 location_t loc
= EXPR_LOCATION (*expr_p
);
4618 gimple_stmt_iterator gsi
;
4620 gcc_assert (TREE_CODE (*expr_p
) == MODIFY_EXPR
4621 || TREE_CODE (*expr_p
) == INIT_EXPR
);
4623 /* Trying to simplify a clobber using normal logic doesn't work,
4624 so handle it here. */
4625 if (TREE_CLOBBER_P (*from_p
))
4627 ret
= gimplify_expr (to_p
, pre_p
, post_p
, is_gimple_lvalue
, fb_lvalue
);
4628 if (ret
== GS_ERROR
)
4630 gcc_assert (!want_value
4631 && (TREE_CODE (*to_p
) == VAR_DECL
4632 || TREE_CODE (*to_p
) == MEM_REF
));
4633 gimplify_seq_add_stmt (pre_p
, gimple_build_assign (*to_p
, *from_p
));
4638 /* Insert pointer conversions required by the middle-end that are not
4639 required by the frontend. This fixes middle-end type checking for
4640 for example gcc.dg/redecl-6.c. */
4641 if (POINTER_TYPE_P (TREE_TYPE (*to_p
)))
4643 STRIP_USELESS_TYPE_CONVERSION (*from_p
);
4644 if (!useless_type_conversion_p (TREE_TYPE (*to_p
), TREE_TYPE (*from_p
)))
4645 *from_p
= fold_convert_loc (loc
, TREE_TYPE (*to_p
), *from_p
);
4648 /* See if any simplifications can be done based on what the RHS is. */
4649 ret
= gimplify_modify_expr_rhs (expr_p
, from_p
, to_p
, pre_p
, post_p
,
4651 if (ret
!= GS_UNHANDLED
)
4654 /* For zero sized types only gimplify the left hand side and right hand
4655 side as statements and throw away the assignment. Do this after
4656 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
4658 if (zero_sized_type (TREE_TYPE (*from_p
)) && !want_value
)
4660 gimplify_stmt (from_p
, pre_p
);
4661 gimplify_stmt (to_p
, pre_p
);
4662 *expr_p
= NULL_TREE
;
4666 /* If the value being copied is of variable width, compute the length
4667 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
4668 before gimplifying any of the operands so that we can resolve any
4669 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
4670 the size of the expression to be copied, not of the destination, so
4671 that is what we must do here. */
4672 maybe_with_size_expr (from_p
);
4674 ret
= gimplify_expr (to_p
, pre_p
, post_p
, is_gimple_lvalue
, fb_lvalue
);
4675 if (ret
== GS_ERROR
)
4678 /* As a special case, we have to temporarily allow for assignments
4679 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
4680 a toplevel statement, when gimplifying the GENERIC expression
4681 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
4682 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
4684 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
4685 prevent gimplify_expr from trying to create a new temporary for
4686 foo's LHS, we tell it that it should only gimplify until it
4687 reaches the CALL_EXPR. On return from gimplify_expr, the newly
4688 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
4689 and all we need to do here is set 'a' to be its LHS. */
4690 ret
= gimplify_expr (from_p
, pre_p
, post_p
, rhs_predicate_for (*to_p
),
4692 if (ret
== GS_ERROR
)
4695 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
4696 size as argument to the call. */
4697 if (TREE_CODE (*from_p
) == WITH_SIZE_EXPR
)
4699 tree call
= TREE_OPERAND (*from_p
, 0);
4700 tree vlasize
= TREE_OPERAND (*from_p
, 1);
4702 if (TREE_CODE (call
) == CALL_EXPR
4703 && CALL_EXPR_IFN (call
) == IFN_VA_ARG
)
4705 int nargs
= call_expr_nargs (call
);
4706 tree type
= TREE_TYPE (call
);
4707 tree ap
= CALL_EXPR_ARG (call
, 0);
4708 tree tag
= CALL_EXPR_ARG (call
, 1);
4709 tree newcall
= build_call_expr_internal_loc (EXPR_LOCATION (call
),
4713 tree
*call_p
= &(TREE_OPERAND (*from_p
, 0));
4718 /* Now see if the above changed *from_p to something we handle specially. */
4719 ret
= gimplify_modify_expr_rhs (expr_p
, from_p
, to_p
, pre_p
, post_p
,
4721 if (ret
!= GS_UNHANDLED
)
4724 /* If we've got a variable sized assignment between two lvalues (i.e. does
4725 not involve a call), then we can make things a bit more straightforward
4726 by converting the assignment to memcpy or memset. */
4727 if (TREE_CODE (*from_p
) == WITH_SIZE_EXPR
)
4729 tree from
= TREE_OPERAND (*from_p
, 0);
4730 tree size
= TREE_OPERAND (*from_p
, 1);
4732 if (TREE_CODE (from
) == CONSTRUCTOR
)
4733 return gimplify_modify_expr_to_memset (expr_p
, size
, want_value
, pre_p
);
4735 if (is_gimple_addressable (from
))
4738 return gimplify_modify_expr_to_memcpy (expr_p
, size
, want_value
,
4743 /* Transform partial stores to non-addressable complex variables into
4744 total stores. This allows us to use real instead of virtual operands
4745 for these variables, which improves optimization. */
4746 if ((TREE_CODE (*to_p
) == REALPART_EXPR
4747 || TREE_CODE (*to_p
) == IMAGPART_EXPR
)
4748 && is_gimple_reg (TREE_OPERAND (*to_p
, 0)))
4749 return gimplify_modify_expr_complex_part (expr_p
, pre_p
, want_value
);
4751 /* Try to alleviate the effects of the gimplification creating artificial
4752 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
4753 make sure not to create DECL_DEBUG_EXPR links across functions. */
4754 if (!gimplify_ctxp
->into_ssa
4755 && TREE_CODE (*from_p
) == VAR_DECL
4756 && DECL_IGNORED_P (*from_p
)
4758 && !DECL_IGNORED_P (*to_p
)
4759 && decl_function_context (*to_p
) == current_function_decl
)
4761 if (!DECL_NAME (*from_p
) && DECL_NAME (*to_p
))
4763 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p
)));
4764 DECL_HAS_DEBUG_EXPR_P (*from_p
) = 1;
4765 SET_DECL_DEBUG_EXPR (*from_p
, *to_p
);
4768 if (want_value
&& TREE_THIS_VOLATILE (*to_p
))
4769 *from_p
= get_initialized_tmp_var (*from_p
, pre_p
, post_p
);
4771 if (TREE_CODE (*from_p
) == CALL_EXPR
)
4773 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
4774 instead of a GIMPLE_ASSIGN. */
4776 if (CALL_EXPR_FN (*from_p
) == NULL_TREE
)
4778 /* Gimplify internal functions created in the FEs. */
4779 int nargs
= call_expr_nargs (*from_p
), i
;
4780 enum internal_fn ifn
= CALL_EXPR_IFN (*from_p
);
4781 auto_vec
<tree
> vargs (nargs
);
4783 for (i
= 0; i
< nargs
; i
++)
4785 gimplify_arg (&CALL_EXPR_ARG (*from_p
, i
), pre_p
,
4786 EXPR_LOCATION (*from_p
));
4787 vargs
.quick_push (CALL_EXPR_ARG (*from_p
, i
));
4789 call_stmt
= gimple_build_call_internal_vec (ifn
, vargs
);
4790 gimple_set_location (call_stmt
, EXPR_LOCATION (*expr_p
));
4794 tree fnptrtype
= TREE_TYPE (CALL_EXPR_FN (*from_p
));
4795 CALL_EXPR_FN (*from_p
) = TREE_OPERAND (CALL_EXPR_FN (*from_p
), 0);
4796 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p
));
4797 tree fndecl
= get_callee_fndecl (*from_p
);
4799 && DECL_BUILT_IN_CLASS (fndecl
) == BUILT_IN_NORMAL
4800 && DECL_FUNCTION_CODE (fndecl
) == BUILT_IN_EXPECT
4801 && call_expr_nargs (*from_p
) == 3)
4802 call_stmt
= gimple_build_call_internal (IFN_BUILTIN_EXPECT
, 3,
4803 CALL_EXPR_ARG (*from_p
, 0),
4804 CALL_EXPR_ARG (*from_p
, 1),
4805 CALL_EXPR_ARG (*from_p
, 2));
4808 call_stmt
= gimple_build_call_from_tree (*from_p
);
4809 gimple_call_set_fntype (call_stmt
, TREE_TYPE (fnptrtype
));
4812 notice_special_calls (call_stmt
);
4813 if (!gimple_call_noreturn_p (call_stmt
))
4814 gimple_call_set_lhs (call_stmt
, *to_p
);
4819 assign
= gimple_build_assign (*to_p
, *from_p
);
4820 gimple_set_location (assign
, EXPR_LOCATION (*expr_p
));
4823 if (gimplify_ctxp
->into_ssa
&& is_gimple_reg (*to_p
))
4825 /* We should have got an SSA name from the start. */
4826 gcc_assert (TREE_CODE (*to_p
) == SSA_NAME
);
4829 gimplify_seq_add_stmt (pre_p
, assign
);
4830 gsi
= gsi_last (*pre_p
);
4831 maybe_fold_stmt (&gsi
);
4835 *expr_p
= TREE_THIS_VOLATILE (*to_p
) ? *from_p
: unshare_expr (*to_p
);
4844 /* Gimplify a comparison between two variable-sized objects. Do this
4845 with a call to BUILT_IN_MEMCMP. */
4847 static enum gimplify_status
4848 gimplify_variable_sized_compare (tree
*expr_p
)
4850 location_t loc
= EXPR_LOCATION (*expr_p
);
4851 tree op0
= TREE_OPERAND (*expr_p
, 0);
4852 tree op1
= TREE_OPERAND (*expr_p
, 1);
4853 tree t
, arg
, dest
, src
, expr
;
4855 arg
= TYPE_SIZE_UNIT (TREE_TYPE (op0
));
4856 arg
= unshare_expr (arg
);
4857 arg
= SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg
, op0
);
4858 src
= build_fold_addr_expr_loc (loc
, op1
);
4859 dest
= build_fold_addr_expr_loc (loc
, op0
);
4860 t
= builtin_decl_implicit (BUILT_IN_MEMCMP
);
4861 t
= build_call_expr_loc (loc
, t
, 3, dest
, src
, arg
);
4864 = build2 (TREE_CODE (*expr_p
), TREE_TYPE (*expr_p
), t
, integer_zero_node
);
4865 SET_EXPR_LOCATION (expr
, loc
);
4871 /* Gimplify a comparison between two aggregate objects of integral scalar
4872 mode as a comparison between the bitwise equivalent scalar values. */
4874 static enum gimplify_status
4875 gimplify_scalar_mode_aggregate_compare (tree
*expr_p
)
4877 location_t loc
= EXPR_LOCATION (*expr_p
);
4878 tree op0
= TREE_OPERAND (*expr_p
, 0);
4879 tree op1
= TREE_OPERAND (*expr_p
, 1);
4881 tree type
= TREE_TYPE (op0
);
4882 tree scalar_type
= lang_hooks
.types
.type_for_mode (TYPE_MODE (type
), 1);
4884 op0
= fold_build1_loc (loc
, VIEW_CONVERT_EXPR
, scalar_type
, op0
);
4885 op1
= fold_build1_loc (loc
, VIEW_CONVERT_EXPR
, scalar_type
, op1
);
4888 = fold_build2_loc (loc
, TREE_CODE (*expr_p
), TREE_TYPE (*expr_p
), op0
, op1
);
4893 /* Gimplify an expression sequence. This function gimplifies each
4894 expression and rewrites the original expression with the last
4895 expression of the sequence in GIMPLE form.
4897 PRE_P points to the list where the side effects for all the
4898 expressions in the sequence will be emitted.
4900 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
4902 static enum gimplify_status
4903 gimplify_compound_expr (tree
*expr_p
, gimple_seq
*pre_p
, bool want_value
)
4909 tree
*sub_p
= &TREE_OPERAND (t
, 0);
4911 if (TREE_CODE (*sub_p
) == COMPOUND_EXPR
)
4912 gimplify_compound_expr (sub_p
, pre_p
, false);
4914 gimplify_stmt (sub_p
, pre_p
);
4916 t
= TREE_OPERAND (t
, 1);
4918 while (TREE_CODE (t
) == COMPOUND_EXPR
);
4925 gimplify_stmt (expr_p
, pre_p
);
4930 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
4931 gimplify. After gimplification, EXPR_P will point to a new temporary
4932 that holds the original value of the SAVE_EXPR node.
4934 PRE_P points to the list where side effects that must happen before
4935 *EXPR_P should be stored. */
4937 static enum gimplify_status
4938 gimplify_save_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
)
4940 enum gimplify_status ret
= GS_ALL_DONE
;
4943 gcc_assert (TREE_CODE (*expr_p
) == SAVE_EXPR
);
4944 val
= TREE_OPERAND (*expr_p
, 0);
4946 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
4947 if (!SAVE_EXPR_RESOLVED_P (*expr_p
))
4949 /* The operand may be a void-valued expression such as SAVE_EXPRs
4950 generated by the Java frontend for class initialization. It is
4951 being executed only for its side-effects. */
4952 if (TREE_TYPE (val
) == void_type_node
)
4954 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
4955 is_gimple_stmt
, fb_none
);
4959 val
= get_initialized_tmp_var (val
, pre_p
, post_p
);
4961 TREE_OPERAND (*expr_p
, 0) = val
;
4962 SAVE_EXPR_RESOLVED_P (*expr_p
) = 1;
4970 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
4977 PRE_P points to the list where side effects that must happen before
4978 *EXPR_P should be stored.
4980 POST_P points to the list where side effects that must happen after
4981 *EXPR_P should be stored. */
4983 static enum gimplify_status
4984 gimplify_addr_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
)
4986 tree expr
= *expr_p
;
4987 tree op0
= TREE_OPERAND (expr
, 0);
4988 enum gimplify_status ret
;
4989 location_t loc
= EXPR_LOCATION (*expr_p
);
4991 switch (TREE_CODE (op0
))
4995 /* Check if we are dealing with an expression of the form '&*ptr'.
4996 While the front end folds away '&*ptr' into 'ptr', these
4997 expressions may be generated internally by the compiler (e.g.,
4998 builtins like __builtin_va_end). */
4999 /* Caution: the silent array decomposition semantics we allow for
5000 ADDR_EXPR means we can't always discard the pair. */
5001 /* Gimplification of the ADDR_EXPR operand may drop
5002 cv-qualification conversions, so make sure we add them if
5005 tree op00
= TREE_OPERAND (op0
, 0);
5006 tree t_expr
= TREE_TYPE (expr
);
5007 tree t_op00
= TREE_TYPE (op00
);
5009 if (!useless_type_conversion_p (t_expr
, t_op00
))
5010 op00
= fold_convert_loc (loc
, TREE_TYPE (expr
), op00
);
5016 case VIEW_CONVERT_EXPR
:
5017 /* Take the address of our operand and then convert it to the type of
5020 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
5021 all clear. The impact of this transformation is even less clear. */
5023 /* If the operand is a useless conversion, look through it. Doing so
5024 guarantees that the ADDR_EXPR and its operand will remain of the
5026 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0
, 0)))
5027 op0
= TREE_OPERAND (op0
, 0);
5029 *expr_p
= fold_convert_loc (loc
, TREE_TYPE (expr
),
5030 build_fold_addr_expr_loc (loc
,
5031 TREE_OPERAND (op0
, 0)));
5036 if (integer_zerop (TREE_OPERAND (op0
, 1)))
5037 goto do_indirect_ref
;
5039 /* ... fall through ... */
5042 /* If we see a call to a declared builtin or see its address
5043 being taken (we can unify those cases here) then we can mark
5044 the builtin for implicit generation by GCC. */
5045 if (TREE_CODE (op0
) == FUNCTION_DECL
5046 && DECL_BUILT_IN_CLASS (op0
) == BUILT_IN_NORMAL
5047 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0
)))
5048 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0
), true);
5050 /* We use fb_either here because the C frontend sometimes takes
5051 the address of a call that returns a struct; see
5052 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
5053 the implied temporary explicit. */
5055 /* Make the operand addressable. */
5056 ret
= gimplify_expr (&TREE_OPERAND (expr
, 0), pre_p
, post_p
,
5057 is_gimple_addressable
, fb_either
);
5058 if (ret
== GS_ERROR
)
5061 /* Then mark it. Beware that it may not be possible to do so directly
5062 if a temporary has been created by the gimplification. */
5063 prepare_gimple_addressable (&TREE_OPERAND (expr
, 0), pre_p
);
5065 op0
= TREE_OPERAND (expr
, 0);
5067 /* For various reasons, the gimplification of the expression
5068 may have made a new INDIRECT_REF. */
5069 if (TREE_CODE (op0
) == INDIRECT_REF
)
5070 goto do_indirect_ref
;
5072 mark_addressable (TREE_OPERAND (expr
, 0));
5074 /* The FEs may end up building ADDR_EXPRs early on a decl with
5075 an incomplete type. Re-build ADDR_EXPRs in canonical form
5077 if (!types_compatible_p (TREE_TYPE (op0
), TREE_TYPE (TREE_TYPE (expr
))))
5078 *expr_p
= build_fold_addr_expr (op0
);
5080 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
5081 recompute_tree_invariant_for_addr_expr (*expr_p
);
5083 /* If we re-built the ADDR_EXPR add a conversion to the original type
5085 if (!useless_type_conversion_p (TREE_TYPE (expr
), TREE_TYPE (*expr_p
)))
5086 *expr_p
= fold_convert (TREE_TYPE (expr
), *expr_p
);
5094 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
5095 value; output operands should be a gimple lvalue. */
5097 static enum gimplify_status
5098 gimplify_asm_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
)
5102 const char **oconstraints
;
5105 const char *constraint
;
5106 bool allows_mem
, allows_reg
, is_inout
;
5107 enum gimplify_status ret
, tret
;
5109 vec
<tree
, va_gc
> *inputs
;
5110 vec
<tree
, va_gc
> *outputs
;
5111 vec
<tree
, va_gc
> *clobbers
;
5112 vec
<tree
, va_gc
> *labels
;
5116 noutputs
= list_length (ASM_OUTPUTS (expr
));
5117 oconstraints
= (const char **) alloca ((noutputs
) * sizeof (const char *));
5125 link_next
= NULL_TREE
;
5126 for (i
= 0, link
= ASM_OUTPUTS (expr
); link
; ++i
, link
= link_next
)
5129 size_t constraint_len
;
5131 link_next
= TREE_CHAIN (link
);
5135 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link
)));
5136 constraint_len
= strlen (constraint
);
5137 if (constraint_len
== 0)
5140 ok
= parse_output_constraint (&constraint
, i
, 0, 0,
5141 &allows_mem
, &allows_reg
, &is_inout
);
5148 if (!allows_reg
&& allows_mem
)
5149 mark_addressable (TREE_VALUE (link
));
5151 tret
= gimplify_expr (&TREE_VALUE (link
), pre_p
, post_p
,
5152 is_inout
? is_gimple_min_lval
: is_gimple_lvalue
,
5153 fb_lvalue
| fb_mayfail
);
5154 if (tret
== GS_ERROR
)
5156 error ("invalid lvalue in asm output %d", i
);
5160 vec_safe_push (outputs
, link
);
5161 TREE_CHAIN (link
) = NULL_TREE
;
5165 /* An input/output operand. To give the optimizers more
5166 flexibility, split it into separate input and output
5171 /* Turn the in/out constraint into an output constraint. */
5172 char *p
= xstrdup (constraint
);
5174 TREE_VALUE (TREE_PURPOSE (link
)) = build_string (constraint_len
, p
);
5176 /* And add a matching input constraint. */
5179 sprintf (buf
, "%d", i
);
5181 /* If there are multiple alternatives in the constraint,
5182 handle each of them individually. Those that allow register
5183 will be replaced with operand number, the others will stay
5185 if (strchr (p
, ',') != NULL
)
5187 size_t len
= 0, buflen
= strlen (buf
);
5188 char *beg
, *end
, *str
, *dst
;
5192 end
= strchr (beg
, ',');
5194 end
= strchr (beg
, '\0');
5195 if ((size_t) (end
- beg
) < buflen
)
5198 len
+= end
- beg
+ 1;
5205 str
= (char *) alloca (len
);
5206 for (beg
= p
+ 1, dst
= str
;;)
5209 bool mem_p
, reg_p
, inout_p
;
5211 end
= strchr (beg
, ',');
5216 parse_output_constraint (&tem
, i
, 0, 0,
5217 &mem_p
, ®_p
, &inout_p
);
5222 memcpy (dst
, buf
, buflen
);
5231 memcpy (dst
, beg
, len
);
5240 input
= build_string (dst
- str
, str
);
5243 input
= build_string (strlen (buf
), buf
);
5246 input
= build_string (constraint_len
- 1, constraint
+ 1);
5250 input
= build_tree_list (build_tree_list (NULL_TREE
, input
),
5251 unshare_expr (TREE_VALUE (link
)));
5252 ASM_INPUTS (expr
) = chainon (ASM_INPUTS (expr
), input
);
5256 link_next
= NULL_TREE
;
5257 for (link
= ASM_INPUTS (expr
); link
; ++i
, link
= link_next
)
5259 link_next
= TREE_CHAIN (link
);
5260 constraint
= TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link
)));
5261 parse_input_constraint (&constraint
, 0, 0, noutputs
, 0,
5262 oconstraints
, &allows_mem
, &allows_reg
);
5264 /* If we can't make copies, we can only accept memory. */
5265 if (TREE_ADDRESSABLE (TREE_TYPE (TREE_VALUE (link
))))
5271 error ("impossible constraint in %<asm%>");
5272 error ("non-memory input %d must stay in memory", i
);
5277 /* If the operand is a memory input, it should be an lvalue. */
5278 if (!allows_reg
&& allows_mem
)
5280 tree inputv
= TREE_VALUE (link
);
5281 STRIP_NOPS (inputv
);
5282 if (TREE_CODE (inputv
) == PREDECREMENT_EXPR
5283 || TREE_CODE (inputv
) == PREINCREMENT_EXPR
5284 || TREE_CODE (inputv
) == POSTDECREMENT_EXPR
5285 || TREE_CODE (inputv
) == POSTINCREMENT_EXPR
5286 || TREE_CODE (inputv
) == MODIFY_EXPR
)
5287 TREE_VALUE (link
) = error_mark_node
;
5288 tret
= gimplify_expr (&TREE_VALUE (link
), pre_p
, post_p
,
5289 is_gimple_lvalue
, fb_lvalue
| fb_mayfail
);
5290 mark_addressable (TREE_VALUE (link
));
5291 if (tret
== GS_ERROR
)
5293 if (EXPR_HAS_LOCATION (TREE_VALUE (link
)))
5294 input_location
= EXPR_LOCATION (TREE_VALUE (link
));
5295 error ("memory input %d is not directly addressable", i
);
5301 tret
= gimplify_expr (&TREE_VALUE (link
), pre_p
, post_p
,
5302 is_gimple_asm_val
, fb_rvalue
);
5303 if (tret
== GS_ERROR
)
5307 TREE_CHAIN (link
) = NULL_TREE
;
5308 vec_safe_push (inputs
, link
);
5311 link_next
= NULL_TREE
;
5312 for (link
= ASM_CLOBBERS (expr
); link
; ++i
, link
= link_next
)
5314 link_next
= TREE_CHAIN (link
);
5315 TREE_CHAIN (link
) = NULL_TREE
;
5316 vec_safe_push (clobbers
, link
);
5319 link_next
= NULL_TREE
;
5320 for (link
= ASM_LABELS (expr
); link
; ++i
, link
= link_next
)
5322 link_next
= TREE_CHAIN (link
);
5323 TREE_CHAIN (link
) = NULL_TREE
;
5324 vec_safe_push (labels
, link
);
5327 /* Do not add ASMs with errors to the gimple IL stream. */
5328 if (ret
!= GS_ERROR
)
5330 stmt
= gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr
)),
5331 inputs
, outputs
, clobbers
, labels
);
5333 gimple_asm_set_volatile (stmt
, ASM_VOLATILE_P (expr
) || noutputs
== 0);
5334 gimple_asm_set_input (stmt
, ASM_INPUT_P (expr
));
5336 gimplify_seq_add_stmt (pre_p
, stmt
);
5342 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
5343 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
5344 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
5345 return to this function.
5347 FIXME should we complexify the prequeue handling instead? Or use flags
5348 for all the cleanups and let the optimizer tighten them up? The current
5349 code seems pretty fragile; it will break on a cleanup within any
5350 non-conditional nesting. But any such nesting would be broken, anyway;
5351 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
5352 and continues out of it. We can do that at the RTL level, though, so
5353 having an optimizer to tighten up try/finally regions would be a Good
5356 static enum gimplify_status
5357 gimplify_cleanup_point_expr (tree
*expr_p
, gimple_seq
*pre_p
)
5359 gimple_stmt_iterator iter
;
5360 gimple_seq body_sequence
= NULL
;
5362 tree temp
= voidify_wrapper_expr (*expr_p
, NULL
);
5364 /* We only care about the number of conditions between the innermost
5365 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
5366 any cleanups collected outside the CLEANUP_POINT_EXPR. */
5367 int old_conds
= gimplify_ctxp
->conditions
;
5368 gimple_seq old_cleanups
= gimplify_ctxp
->conditional_cleanups
;
5369 bool old_in_cleanup_point_expr
= gimplify_ctxp
->in_cleanup_point_expr
;
5370 gimplify_ctxp
->conditions
= 0;
5371 gimplify_ctxp
->conditional_cleanups
= NULL
;
5372 gimplify_ctxp
->in_cleanup_point_expr
= true;
5374 gimplify_stmt (&TREE_OPERAND (*expr_p
, 0), &body_sequence
);
5376 gimplify_ctxp
->conditions
= old_conds
;
5377 gimplify_ctxp
->conditional_cleanups
= old_cleanups
;
5378 gimplify_ctxp
->in_cleanup_point_expr
= old_in_cleanup_point_expr
;
5380 for (iter
= gsi_start (body_sequence
); !gsi_end_p (iter
); )
5382 gimple
*wce
= gsi_stmt (iter
);
5384 if (gimple_code (wce
) == GIMPLE_WITH_CLEANUP_EXPR
)
5386 if (gsi_one_before_end_p (iter
))
5388 /* Note that gsi_insert_seq_before and gsi_remove do not
5389 scan operands, unlike some other sequence mutators. */
5390 if (!gimple_wce_cleanup_eh_only (wce
))
5391 gsi_insert_seq_before_without_update (&iter
,
5392 gimple_wce_cleanup (wce
),
5394 gsi_remove (&iter
, true);
5401 enum gimple_try_flags kind
;
5403 if (gimple_wce_cleanup_eh_only (wce
))
5404 kind
= GIMPLE_TRY_CATCH
;
5406 kind
= GIMPLE_TRY_FINALLY
;
5407 seq
= gsi_split_seq_after (iter
);
5409 gtry
= gimple_build_try (seq
, gimple_wce_cleanup (wce
), kind
);
5410 /* Do not use gsi_replace here, as it may scan operands.
5411 We want to do a simple structural modification only. */
5412 gsi_set_stmt (&iter
, gtry
);
5413 iter
= gsi_start (gtry
->eval
);
5420 gimplify_seq_add_seq (pre_p
, body_sequence
);
5433 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
5434 is the cleanup action required. EH_ONLY is true if the cleanup should
5435 only be executed if an exception is thrown, not on normal exit. */
5438 gimple_push_cleanup (tree var
, tree cleanup
, bool eh_only
, gimple_seq
*pre_p
)
5441 gimple_seq cleanup_stmts
= NULL
;
5443 /* Errors can result in improperly nested cleanups. Which results in
5444 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
5448 if (gimple_conditional_context ())
5450 /* If we're in a conditional context, this is more complex. We only
5451 want to run the cleanup if we actually ran the initialization that
5452 necessitates it, but we want to run it after the end of the
5453 conditional context. So we wrap the try/finally around the
5454 condition and use a flag to determine whether or not to actually
5455 run the destructor. Thus
5459 becomes (approximately)
5463 if (test) { A::A(temp); flag = 1; val = f(temp); }
5466 if (flag) A::~A(temp);
5470 tree flag
= create_tmp_var (boolean_type_node
, "cleanup");
5471 gassign
*ffalse
= gimple_build_assign (flag
, boolean_false_node
);
5472 gassign
*ftrue
= gimple_build_assign (flag
, boolean_true_node
);
5474 cleanup
= build3 (COND_EXPR
, void_type_node
, flag
, cleanup
, NULL
);
5475 gimplify_stmt (&cleanup
, &cleanup_stmts
);
5476 wce
= gimple_build_wce (cleanup_stmts
);
5478 gimplify_seq_add_stmt (&gimplify_ctxp
->conditional_cleanups
, ffalse
);
5479 gimplify_seq_add_stmt (&gimplify_ctxp
->conditional_cleanups
, wce
);
5480 gimplify_seq_add_stmt (pre_p
, ftrue
);
5482 /* Because of this manipulation, and the EH edges that jump
5483 threading cannot redirect, the temporary (VAR) will appear
5484 to be used uninitialized. Don't warn. */
5485 TREE_NO_WARNING (var
) = 1;
5489 gimplify_stmt (&cleanup
, &cleanup_stmts
);
5490 wce
= gimple_build_wce (cleanup_stmts
);
5491 gimple_wce_set_cleanup_eh_only (wce
, eh_only
);
5492 gimplify_seq_add_stmt (pre_p
, wce
);
5496 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
5498 static enum gimplify_status
5499 gimplify_target_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
)
5501 tree targ
= *expr_p
;
5502 tree temp
= TARGET_EXPR_SLOT (targ
);
5503 tree init
= TARGET_EXPR_INITIAL (targ
);
5504 enum gimplify_status ret
;
5508 tree cleanup
= NULL_TREE
;
5510 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
5511 to the temps list. Handle also variable length TARGET_EXPRs. */
5512 if (TREE_CODE (DECL_SIZE (temp
)) != INTEGER_CST
)
5514 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp
)))
5515 gimplify_type_sizes (TREE_TYPE (temp
), pre_p
);
5516 gimplify_vla_decl (temp
, pre_p
);
5519 gimple_add_tmp_var (temp
);
5521 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
5522 expression is supposed to initialize the slot. */
5523 if (VOID_TYPE_P (TREE_TYPE (init
)))
5524 ret
= gimplify_expr (&init
, pre_p
, post_p
, is_gimple_stmt
, fb_none
);
5527 tree init_expr
= build2 (INIT_EXPR
, void_type_node
, temp
, init
);
5529 ret
= gimplify_expr (&init
, pre_p
, post_p
, is_gimple_stmt
, fb_none
);
5531 ggc_free (init_expr
);
5533 if (ret
== GS_ERROR
)
5535 /* PR c++/28266 Make sure this is expanded only once. */
5536 TARGET_EXPR_INITIAL (targ
) = NULL_TREE
;
5540 gimplify_and_add (init
, pre_p
);
5542 /* If needed, push the cleanup for the temp. */
5543 if (TARGET_EXPR_CLEANUP (targ
))
5545 if (CLEANUP_EH_ONLY (targ
))
5546 gimple_push_cleanup (temp
, TARGET_EXPR_CLEANUP (targ
),
5547 CLEANUP_EH_ONLY (targ
), pre_p
);
5549 cleanup
= TARGET_EXPR_CLEANUP (targ
);
5552 /* Add a clobber for the temporary going out of scope, like
5553 gimplify_bind_expr. */
5554 if (gimplify_ctxp
->in_cleanup_point_expr
5555 && needs_to_live_in_memory (temp
)
5556 && flag_stack_reuse
== SR_ALL
)
5558 tree clobber
= build_constructor (TREE_TYPE (temp
),
5560 TREE_THIS_VOLATILE (clobber
) = true;
5561 clobber
= build2 (MODIFY_EXPR
, TREE_TYPE (temp
), temp
, clobber
);
5563 cleanup
= build2 (COMPOUND_EXPR
, void_type_node
, cleanup
,
5570 gimple_push_cleanup (temp
, cleanup
, false, pre_p
);
5572 /* Only expand this once. */
5573 TREE_OPERAND (targ
, 3) = init
;
5574 TARGET_EXPR_INITIAL (targ
) = NULL_TREE
;
5577 /* We should have expanded this before. */
5578 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp
));
5584 /* Gimplification of expression trees. */
5586 /* Gimplify an expression which appears at statement context. The
5587 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
5588 NULL, a new sequence is allocated.
5590 Return true if we actually added a statement to the queue. */
5593 gimplify_stmt (tree
*stmt_p
, gimple_seq
*seq_p
)
5595 gimple_seq_node last
;
5597 last
= gimple_seq_last (*seq_p
);
5598 gimplify_expr (stmt_p
, seq_p
, NULL
, is_gimple_stmt
, fb_none
);
5599 return last
!= gimple_seq_last (*seq_p
);
5602 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
5603 to CTX. If entries already exist, force them to be some flavor of private.
5604 If there is no enclosing parallel, do nothing. */
5607 omp_firstprivatize_variable (struct gimplify_omp_ctx
*ctx
, tree decl
)
5611 if (decl
== NULL
|| !DECL_P (decl
) || ctx
->region_type
== ORT_NONE
)
5616 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
5619 if (n
->value
& GOVD_SHARED
)
5620 n
->value
= GOVD_FIRSTPRIVATE
| (n
->value
& GOVD_SEEN
);
5621 else if (n
->value
& GOVD_MAP
)
5622 n
->value
|= GOVD_MAP_TO_ONLY
;
5626 else if ((ctx
->region_type
& ORT_TARGET
) != 0)
5628 if (ctx
->target_map_scalars_firstprivate
)
5629 omp_add_variable (ctx
, decl
, GOVD_FIRSTPRIVATE
);
5631 omp_add_variable (ctx
, decl
, GOVD_MAP
| GOVD_MAP_TO_ONLY
);
5633 else if (ctx
->region_type
!= ORT_WORKSHARE
5634 && ctx
->region_type
!= ORT_SIMD
5635 && ctx
->region_type
!= ORT_ACC
5636 && !(ctx
->region_type
& ORT_TARGET_DATA
))
5637 omp_add_variable (ctx
, decl
, GOVD_FIRSTPRIVATE
);
5639 ctx
= ctx
->outer_context
;
5644 /* Similarly for each of the type sizes of TYPE. */
5647 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx
*ctx
, tree type
)
5649 if (type
== NULL
|| type
== error_mark_node
)
5651 type
= TYPE_MAIN_VARIANT (type
);
5653 if (ctx
->privatized_types
->add (type
))
5656 switch (TREE_CODE (type
))
5662 case FIXED_POINT_TYPE
:
5663 omp_firstprivatize_variable (ctx
, TYPE_MIN_VALUE (type
));
5664 omp_firstprivatize_variable (ctx
, TYPE_MAX_VALUE (type
));
5668 omp_firstprivatize_type_sizes (ctx
, TREE_TYPE (type
));
5669 omp_firstprivatize_type_sizes (ctx
, TYPE_DOMAIN (type
));
5674 case QUAL_UNION_TYPE
:
5677 for (field
= TYPE_FIELDS (type
); field
; field
= DECL_CHAIN (field
))
5678 if (TREE_CODE (field
) == FIELD_DECL
)
5680 omp_firstprivatize_variable (ctx
, DECL_FIELD_OFFSET (field
));
5681 omp_firstprivatize_type_sizes (ctx
, TREE_TYPE (field
));
5687 case REFERENCE_TYPE
:
5688 omp_firstprivatize_type_sizes (ctx
, TREE_TYPE (type
));
5695 omp_firstprivatize_variable (ctx
, TYPE_SIZE (type
));
5696 omp_firstprivatize_variable (ctx
, TYPE_SIZE_UNIT (type
));
5697 lang_hooks
.types
.omp_firstprivatize_type_sizes (ctx
, type
);
5700 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
5703 omp_add_variable (struct gimplify_omp_ctx
*ctx
, tree decl
, unsigned int flags
)
5706 unsigned int nflags
;
5709 if (error_operand_p (decl
) || ctx
->region_type
== ORT_NONE
)
5712 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
5713 there are constructors involved somewhere. */
5714 if (TREE_ADDRESSABLE (TREE_TYPE (decl
))
5715 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl
)))
5718 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
5719 if (n
!= NULL
&& (n
->value
& GOVD_DATA_SHARE_CLASS
) != 0)
5721 /* We shouldn't be re-adding the decl with the same data
5723 gcc_assert ((n
->value
& GOVD_DATA_SHARE_CLASS
& flags
) == 0);
5724 nflags
= n
->value
| flags
;
5725 /* The only combination of data sharing classes we should see is
5726 FIRSTPRIVATE and LASTPRIVATE. However, OpenACC permits
5727 reduction variables to be used in data sharing clauses. */
5728 gcc_assert ((ctx
->region_type
& ORT_ACC
) != 0
5729 || ((nflags
& GOVD_DATA_SHARE_CLASS
)
5730 == (GOVD_FIRSTPRIVATE
| GOVD_LASTPRIVATE
))
5731 || (flags
& GOVD_DATA_SHARE_CLASS
) == 0);
5736 /* When adding a variable-sized variable, we have to handle all sorts
5737 of additional bits of data: the pointer replacement variable, and
5738 the parameters of the type. */
5739 if (DECL_SIZE (decl
) && TREE_CODE (DECL_SIZE (decl
)) != INTEGER_CST
)
5741 /* Add the pointer replacement variable as PRIVATE if the variable
5742 replacement is private, else FIRSTPRIVATE since we'll need the
5743 address of the original variable either for SHARED, or for the
5744 copy into or out of the context. */
5745 if (!(flags
& GOVD_LOCAL
))
5747 if (flags
& GOVD_MAP
)
5748 nflags
= GOVD_MAP
| GOVD_MAP_TO_ONLY
| GOVD_EXPLICIT
;
5749 else if (flags
& GOVD_PRIVATE
)
5750 nflags
= GOVD_PRIVATE
;
5751 else if ((ctx
->region_type
& (ORT_TARGET
| ORT_TARGET_DATA
)) != 0
5752 && (flags
& GOVD_FIRSTPRIVATE
))
5753 nflags
= GOVD_PRIVATE
| GOVD_EXPLICIT
;
5755 nflags
= GOVD_FIRSTPRIVATE
;
5756 nflags
|= flags
& GOVD_SEEN
;
5757 t
= DECL_VALUE_EXPR (decl
);
5758 gcc_assert (TREE_CODE (t
) == INDIRECT_REF
);
5759 t
= TREE_OPERAND (t
, 0);
5760 gcc_assert (DECL_P (t
));
5761 omp_add_variable (ctx
, t
, nflags
);
5764 /* Add all of the variable and type parameters (which should have
5765 been gimplified to a formal temporary) as FIRSTPRIVATE. */
5766 omp_firstprivatize_variable (ctx
, DECL_SIZE_UNIT (decl
));
5767 omp_firstprivatize_variable (ctx
, DECL_SIZE (decl
));
5768 omp_firstprivatize_type_sizes (ctx
, TREE_TYPE (decl
));
5770 /* The variable-sized variable itself is never SHARED, only some form
5771 of PRIVATE. The sharing would take place via the pointer variable
5772 which we remapped above. */
5773 if (flags
& GOVD_SHARED
)
5774 flags
= GOVD_PRIVATE
| GOVD_DEBUG_PRIVATE
5775 | (flags
& (GOVD_SEEN
| GOVD_EXPLICIT
));
5777 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
5778 alloca statement we generate for the variable, so make sure it
5779 is available. This isn't automatically needed for the SHARED
5780 case, since we won't be allocating local storage then.
5781 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
5782 in this case omp_notice_variable will be called later
5783 on when it is gimplified. */
5784 else if (! (flags
& (GOVD_LOCAL
| GOVD_MAP
))
5785 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl
))))
5786 omp_notice_variable (ctx
, TYPE_SIZE_UNIT (TREE_TYPE (decl
)), true);
5788 else if ((flags
& (GOVD_MAP
| GOVD_LOCAL
)) == 0
5789 && lang_hooks
.decls
.omp_privatize_by_reference (decl
))
5791 omp_firstprivatize_type_sizes (ctx
, TREE_TYPE (decl
));
5793 /* Similar to the direct variable sized case above, we'll need the
5794 size of references being privatized. */
5795 if ((flags
& GOVD_SHARED
) == 0)
5797 t
= TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl
)));
5799 omp_notice_variable (ctx
, t
, true);
5806 splay_tree_insert (ctx
->variables
, (splay_tree_key
)decl
, flags
);
5809 /* Notice a threadprivate variable DECL used in OMP context CTX.
5810 This just prints out diagnostics about threadprivate variable uses
5811 in untied tasks. If DECL2 is non-NULL, prevent this warning
5812 on that variable. */
5815 omp_notice_threadprivate_variable (struct gimplify_omp_ctx
*ctx
, tree decl
,
5819 struct gimplify_omp_ctx
*octx
;
5821 for (octx
= ctx
; octx
; octx
= octx
->outer_context
)
5822 if ((octx
->region_type
& ORT_TARGET
) != 0)
5824 n
= splay_tree_lookup (octx
->variables
, (splay_tree_key
)decl
);
5827 error ("threadprivate variable %qE used in target region",
5829 error_at (octx
->location
, "enclosing target region");
5830 splay_tree_insert (octx
->variables
, (splay_tree_key
)decl
, 0);
5833 splay_tree_insert (octx
->variables
, (splay_tree_key
)decl2
, 0);
5836 if (ctx
->region_type
!= ORT_UNTIED_TASK
)
5838 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
5841 error ("threadprivate variable %qE used in untied task",
5843 error_at (ctx
->location
, "enclosing task");
5844 splay_tree_insert (ctx
->variables
, (splay_tree_key
)decl
, 0);
5847 splay_tree_insert (ctx
->variables
, (splay_tree_key
)decl2
, 0);
5851 /* Return true if global var DECL is device resident. */
5854 device_resident_p (tree decl
)
5856 tree attr
= lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (decl
));
5861 for (tree t
= TREE_VALUE (attr
); t
; t
= TREE_PURPOSE (t
))
5863 tree c
= TREE_VALUE (t
);
5864 if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_DEVICE_RESIDENT
)
5871 /* Determine outer default flags for DECL mentioned in an OMP region
5872 but not declared in an enclosing clause.
5874 ??? Some compiler-generated variables (like SAVE_EXPRs) could be
5875 remapped firstprivate instead of shared. To some extent this is
5876 addressed in omp_firstprivatize_type_sizes, but not
5880 omp_default_clause (struct gimplify_omp_ctx
*ctx
, tree decl
,
5881 bool in_code
, unsigned flags
)
5883 enum omp_clause_default_kind default_kind
= ctx
->default_kind
;
5884 enum omp_clause_default_kind kind
;
5886 kind
= lang_hooks
.decls
.omp_predetermined_sharing (decl
);
5887 if (kind
!= OMP_CLAUSE_DEFAULT_UNSPECIFIED
)
5888 default_kind
= kind
;
5890 switch (default_kind
)
5892 case OMP_CLAUSE_DEFAULT_NONE
:
5896 if (ctx
->region_type
& ORT_PARALLEL
)
5898 else if (ctx
->region_type
& ORT_TASK
)
5900 else if (ctx
->region_type
& ORT_TEAMS
)
5905 error ("%qE not specified in enclosing %s",
5906 DECL_NAME (lang_hooks
.decls
.omp_report_decl (decl
)), rtype
);
5907 error_at (ctx
->location
, "enclosing %s", rtype
);
5910 case OMP_CLAUSE_DEFAULT_SHARED
:
5911 flags
|= GOVD_SHARED
;
5913 case OMP_CLAUSE_DEFAULT_PRIVATE
:
5914 flags
|= GOVD_PRIVATE
;
5916 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE
:
5917 flags
|= GOVD_FIRSTPRIVATE
;
5919 case OMP_CLAUSE_DEFAULT_UNSPECIFIED
:
5920 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
5921 gcc_assert ((ctx
->region_type
& ORT_TASK
) != 0);
5922 if (struct gimplify_omp_ctx
*octx
= ctx
->outer_context
)
5924 omp_notice_variable (octx
, decl
, in_code
);
5925 for (; octx
; octx
= octx
->outer_context
)
5929 n2
= splay_tree_lookup (octx
->variables
, (splay_tree_key
) decl
);
5930 if ((octx
->region_type
& (ORT_TARGET_DATA
| ORT_TARGET
)) != 0
5931 && (n2
== NULL
|| (n2
->value
& GOVD_DATA_SHARE_CLASS
) == 0))
5933 if (n2
&& (n2
->value
& GOVD_DATA_SHARE_CLASS
) != GOVD_SHARED
)
5935 flags
|= GOVD_FIRSTPRIVATE
;
5938 if ((octx
->region_type
& (ORT_PARALLEL
| ORT_TEAMS
)) != 0)
5940 flags
|= GOVD_SHARED
;
5946 if (TREE_CODE (decl
) == PARM_DECL
5947 || (!is_global_var (decl
)
5948 && DECL_CONTEXT (decl
) == current_function_decl
))
5949 flags
|= GOVD_FIRSTPRIVATE
;
5951 flags
|= GOVD_SHARED
;
5963 /* Determine outer default flags for DECL mentioned in an OACC region
5964 but not declared in an enclosing clause. */
5967 oacc_default_clause (struct gimplify_omp_ctx
*ctx
, tree decl
, unsigned flags
)
5970 bool on_device
= false;
5972 if ((ctx
->region_type
& (ORT_ACC_PARALLEL
| ORT_ACC_KERNELS
)) != 0
5973 && is_global_var (decl
)
5974 && device_resident_p (decl
))
5977 flags
|= GOVD_MAP_TO_ONLY
;
5980 switch (ctx
->region_type
)
5985 case ORT_ACC_KERNELS
:
5986 /* Scalars are default 'copy' under kernels, non-scalars are default
5987 'present_or_copy'. */
5989 if (!AGGREGATE_TYPE_P (TREE_TYPE (decl
)))
5990 flags
|= GOVD_MAP_FORCE
;
5995 case ORT_ACC_PARALLEL
:
5997 tree type
= TREE_TYPE (decl
);
5999 if (TREE_CODE (type
) == REFERENCE_TYPE
6000 || POINTER_TYPE_P (type
))
6001 type
= TREE_TYPE (type
);
6003 if (on_device
|| AGGREGATE_TYPE_P (type
))
6004 /* Aggregates default to 'present_or_copy'. */
6007 /* Scalars default to 'firstprivate'. */
6008 flags
|= GOVD_FIRSTPRIVATE
;
6014 if (DECL_ARTIFICIAL (decl
))
6015 ; /* We can get compiler-generated decls, and should not complain
6017 else if (ctx
->default_kind
== OMP_CLAUSE_DEFAULT_NONE
)
6019 error ("%qE not specified in enclosing OpenACC %qs construct",
6020 DECL_NAME (lang_hooks
.decls
.omp_report_decl (decl
)), rkind
);
6021 inform (ctx
->location
, "enclosing OpenACC %qs construct", rkind
);
6024 gcc_checking_assert (ctx
->default_kind
== OMP_CLAUSE_DEFAULT_SHARED
);
6029 /* Record the fact that DECL was used within the OMP context CTX.
6030 IN_CODE is true when real code uses DECL, and false when we should
6031 merely emit default(none) errors. Return true if DECL is going to
6032 be remapped and thus DECL shouldn't be gimplified into its
6033 DECL_VALUE_EXPR (if any). */
6036 omp_notice_variable (struct gimplify_omp_ctx
*ctx
, tree decl
, bool in_code
)
6039 unsigned flags
= in_code
? GOVD_SEEN
: 0;
6040 bool ret
= false, shared
;
6042 if (error_operand_p (decl
))
6045 if (ctx
->region_type
== ORT_NONE
)
6046 return lang_hooks
.decls
.omp_disregard_value_expr (decl
, false);
6048 /* Threadprivate variables are predetermined. */
6049 if (is_global_var (decl
))
6051 if (DECL_THREAD_LOCAL_P (decl
))
6052 return omp_notice_threadprivate_variable (ctx
, decl
, NULL_TREE
);
6054 if (DECL_HAS_VALUE_EXPR_P (decl
))
6056 tree value
= get_base_address (DECL_VALUE_EXPR (decl
));
6058 if (value
&& DECL_P (value
) && DECL_THREAD_LOCAL_P (value
))
6059 return omp_notice_threadprivate_variable (ctx
, decl
, value
);
6063 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
6064 if ((ctx
->region_type
& ORT_TARGET
) != 0)
6066 ret
= lang_hooks
.decls
.omp_disregard_value_expr (decl
, true);
6069 unsigned nflags
= flags
;
6070 if (ctx
->target_map_pointers_as_0len_arrays
6071 || ctx
->target_map_scalars_firstprivate
)
6073 bool is_declare_target
= false;
6074 bool is_scalar
= false;
6075 if (is_global_var (decl
)
6076 && varpool_node::get_create (decl
)->offloadable
)
6078 struct gimplify_omp_ctx
*octx
;
6079 for (octx
= ctx
->outer_context
;
6080 octx
; octx
= octx
->outer_context
)
6082 n
= splay_tree_lookup (octx
->variables
,
6083 (splay_tree_key
)decl
);
6085 && (n
->value
& GOVD_DATA_SHARE_CLASS
) != GOVD_SHARED
6086 && (n
->value
& GOVD_DATA_SHARE_CLASS
) != 0)
6089 is_declare_target
= octx
== NULL
;
6091 if (!is_declare_target
&& ctx
->target_map_scalars_firstprivate
)
6093 tree type
= TREE_TYPE (decl
);
6094 if (TREE_CODE (type
) == REFERENCE_TYPE
)
6095 type
= TREE_TYPE (type
);
6096 if (TREE_CODE (type
) == COMPLEX_TYPE
)
6097 type
= TREE_TYPE (type
);
6098 if (INTEGRAL_TYPE_P (type
)
6099 || SCALAR_FLOAT_TYPE_P (type
)
6100 || TREE_CODE (type
) == POINTER_TYPE
)
6103 if (is_declare_target
)
6105 else if (ctx
->target_map_pointers_as_0len_arrays
6106 && (TREE_CODE (TREE_TYPE (decl
)) == POINTER_TYPE
6107 || (TREE_CODE (TREE_TYPE (decl
)) == REFERENCE_TYPE
6108 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl
)))
6110 nflags
|= GOVD_MAP
| GOVD_MAP_0LEN_ARRAY
;
6112 nflags
|= GOVD_FIRSTPRIVATE
;
6115 struct gimplify_omp_ctx
*octx
= ctx
->outer_context
;
6116 if ((ctx
->region_type
& ORT_ACC
) && octx
)
6118 /* Look in outer OpenACC contexts, to see if there's a
6119 data attribute for this variable. */
6120 omp_notice_variable (octx
, decl
, in_code
);
6122 for (; octx
; octx
= octx
->outer_context
)
6124 if (!(octx
->region_type
& (ORT_TARGET_DATA
| ORT_TARGET
)))
6127 = splay_tree_lookup (octx
->variables
,
6128 (splay_tree_key
) decl
);
6131 if (octx
->region_type
== ORT_ACC_HOST_DATA
)
6132 error ("variable %qE declared in enclosing "
6133 "%<host_data%> region", DECL_NAME (decl
));
6141 tree type
= TREE_TYPE (decl
);
6144 && gimplify_omp_ctxp
->target_firstprivatize_array_bases
6145 && lang_hooks
.decls
.omp_privatize_by_reference (decl
))
6146 type
= TREE_TYPE (type
);
6148 && !lang_hooks
.types
.omp_mappable_type (type
))
6150 error ("%qD referenced in target region does not have "
6151 "a mappable type", decl
);
6152 nflags
|= GOVD_MAP
| GOVD_EXPLICIT
;
6154 else if (nflags
== flags
)
6156 if ((ctx
->region_type
& ORT_ACC
) != 0)
6157 nflags
= oacc_default_clause (ctx
, decl
, flags
);
6163 omp_add_variable (ctx
, decl
, nflags
);
6167 /* If nothing changed, there's nothing left to do. */
6168 if ((n
->value
& flags
) == flags
)
6178 if (ctx
->region_type
== ORT_WORKSHARE
6179 || ctx
->region_type
== ORT_SIMD
6180 || ctx
->region_type
== ORT_ACC
6181 || (ctx
->region_type
& ORT_TARGET_DATA
) != 0)
6184 flags
= omp_default_clause (ctx
, decl
, in_code
, flags
);
6186 if ((flags
& GOVD_PRIVATE
)
6187 && lang_hooks
.decls
.omp_private_outer_ref (decl
))
6188 flags
|= GOVD_PRIVATE_OUTER_REF
;
6190 omp_add_variable (ctx
, decl
, flags
);
6192 shared
= (flags
& GOVD_SHARED
) != 0;
6193 ret
= lang_hooks
.decls
.omp_disregard_value_expr (decl
, shared
);
6197 if ((n
->value
& (GOVD_SEEN
| GOVD_LOCAL
)) == 0
6198 && (flags
& (GOVD_SEEN
| GOVD_LOCAL
)) == GOVD_SEEN
6200 && TREE_CODE (DECL_SIZE (decl
)) != INTEGER_CST
)
6203 tree t
= DECL_VALUE_EXPR (decl
);
6204 gcc_assert (TREE_CODE (t
) == INDIRECT_REF
);
6205 t
= TREE_OPERAND (t
, 0);
6206 gcc_assert (DECL_P (t
));
6207 n2
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) t
);
6208 n2
->value
|= GOVD_SEEN
;
6211 shared
= ((flags
| n
->value
) & GOVD_SHARED
) != 0;
6212 ret
= lang_hooks
.decls
.omp_disregard_value_expr (decl
, shared
);
6214 /* If nothing changed, there's nothing left to do. */
6215 if ((n
->value
& flags
) == flags
)
6221 /* If the variable is private in the current context, then we don't
6222 need to propagate anything to an outer context. */
6223 if ((flags
& GOVD_PRIVATE
) && !(flags
& GOVD_PRIVATE_OUTER_REF
))
6225 if ((flags
& (GOVD_LINEAR
| GOVD_LINEAR_LASTPRIVATE_NO_OUTER
))
6226 == (GOVD_LINEAR
| GOVD_LINEAR_LASTPRIVATE_NO_OUTER
))
6228 if ((flags
& (GOVD_FIRSTPRIVATE
| GOVD_LASTPRIVATE
6229 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER
))
6230 == (GOVD_LASTPRIVATE
| GOVD_LINEAR_LASTPRIVATE_NO_OUTER
))
6232 if (ctx
->outer_context
6233 && omp_notice_variable (ctx
->outer_context
, decl
, in_code
))
6238 /* Verify that DECL is private within CTX. If there's specific information
6239 to the contrary in the innermost scope, generate an error. */
6242 omp_is_private (struct gimplify_omp_ctx
*ctx
, tree decl
, int simd
)
6246 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
6249 if (n
->value
& GOVD_SHARED
)
6251 if (ctx
== gimplify_omp_ctxp
)
6254 error ("iteration variable %qE is predetermined linear",
6257 error ("iteration variable %qE should be private",
6259 n
->value
= GOVD_PRIVATE
;
6265 else if ((n
->value
& GOVD_EXPLICIT
) != 0
6266 && (ctx
== gimplify_omp_ctxp
6267 || (ctx
->region_type
== ORT_COMBINED_PARALLEL
6268 && gimplify_omp_ctxp
->outer_context
== ctx
)))
6270 if ((n
->value
& GOVD_FIRSTPRIVATE
) != 0)
6271 error ("iteration variable %qE should not be firstprivate",
6273 else if ((n
->value
& GOVD_REDUCTION
) != 0)
6274 error ("iteration variable %qE should not be reduction",
6276 else if (simd
== 0 && (n
->value
& GOVD_LINEAR
) != 0)
6277 error ("iteration variable %qE should not be linear",
6279 else if (simd
== 1 && (n
->value
& GOVD_LASTPRIVATE
) != 0)
6280 error ("iteration variable %qE should not be lastprivate",
6282 else if (simd
&& (n
->value
& GOVD_PRIVATE
) != 0)
6283 error ("iteration variable %qE should not be private",
6285 else if (simd
== 2 && (n
->value
& GOVD_LINEAR
) != 0)
6286 error ("iteration variable %qE is predetermined linear",
6289 return (ctx
== gimplify_omp_ctxp
6290 || (ctx
->region_type
== ORT_COMBINED_PARALLEL
6291 && gimplify_omp_ctxp
->outer_context
== ctx
));
6294 if (ctx
->region_type
!= ORT_WORKSHARE
6295 && ctx
->region_type
!= ORT_SIMD
6296 && ctx
->region_type
!= ORT_ACC
)
6298 else if (ctx
->outer_context
)
6299 return omp_is_private (ctx
->outer_context
, decl
, simd
);
6303 /* Return true if DECL is private within a parallel region
6304 that binds to the current construct's context or in parallel
6305 region's REDUCTION clause. */
6308 omp_check_private (struct gimplify_omp_ctx
*ctx
, tree decl
, bool copyprivate
)
6314 ctx
= ctx
->outer_context
;
6317 if (is_global_var (decl
))
6320 /* References might be private, but might be shared too,
6321 when checking for copyprivate, assume they might be
6322 private, otherwise assume they might be shared. */
6326 if (lang_hooks
.decls
.omp_privatize_by_reference (decl
))
6329 /* Treat C++ privatized non-static data members outside
6330 of the privatization the same. */
6331 if (omp_member_access_dummy_var (decl
))
6337 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
6339 if ((ctx
->region_type
& (ORT_TARGET
| ORT_TARGET_DATA
)) != 0
6340 && (n
== NULL
|| (n
->value
& GOVD_DATA_SHARE_CLASS
) == 0))
6345 if ((n
->value
& GOVD_LOCAL
) != 0
6346 && omp_member_access_dummy_var (decl
))
6348 return (n
->value
& GOVD_SHARED
) == 0;
6351 while (ctx
->region_type
== ORT_WORKSHARE
6352 || ctx
->region_type
== ORT_SIMD
6353 || ctx
->region_type
== ORT_ACC
);
6357 /* Return true if the CTX is combined with distribute and thus
6358 lastprivate can't be supported. */
6361 omp_no_lastprivate (struct gimplify_omp_ctx
*ctx
)
6365 if (ctx
->outer_context
== NULL
)
6367 ctx
= ctx
->outer_context
;
6368 switch (ctx
->region_type
)
6371 if (!ctx
->combined_loop
)
6373 if (ctx
->distribute
)
6374 return lang_GNU_Fortran ();
6376 case ORT_COMBINED_PARALLEL
:
6378 case ORT_COMBINED_TEAMS
:
6379 return lang_GNU_Fortran ();
6387 /* Callback for walk_tree to find a DECL_EXPR for the given DECL. */
6390 find_decl_expr (tree
*tp
, int *walk_subtrees
, void *data
)
6394 /* If this node has been visited, unmark it and keep looking. */
6395 if (TREE_CODE (t
) == DECL_EXPR
&& DECL_EXPR_DECL (t
) == (tree
) data
)
6398 if (IS_TYPE_OR_DECL_P (t
))
6403 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
6404 and previous omp contexts. */
6407 gimplify_scan_omp_clauses (tree
*list_p
, gimple_seq
*pre_p
,
6408 enum omp_region_type region_type
,
6409 enum tree_code code
)
6411 struct gimplify_omp_ctx
*ctx
, *outer_ctx
;
6413 hash_map
<tree
, tree
> *struct_map_to_clause
= NULL
;
6414 tree
*prev_list_p
= NULL
;
6416 ctx
= new_omp_context (region_type
);
6417 outer_ctx
= ctx
->outer_context
;
6418 if (code
== OMP_TARGET
&& !lang_GNU_Fortran ())
6420 ctx
->target_map_pointers_as_0len_arrays
= true;
6421 /* FIXME: For Fortran we want to set this too, when
6422 the Fortran FE is updated to OpenMP 4.5. */
6423 ctx
->target_map_scalars_firstprivate
= true;
6425 if (!lang_GNU_Fortran ())
6429 case OMP_TARGET_DATA
:
6430 case OMP_TARGET_ENTER_DATA
:
6431 case OMP_TARGET_EXIT_DATA
:
6432 case OACC_HOST_DATA
:
6433 ctx
->target_firstprivatize_array_bases
= true;
6438 while ((c
= *list_p
) != NULL
)
6440 bool remove
= false;
6441 bool notice_outer
= true;
6442 const char *check_non_private
= NULL
;
6446 switch (OMP_CLAUSE_CODE (c
))
6448 case OMP_CLAUSE_PRIVATE
:
6449 flags
= GOVD_PRIVATE
| GOVD_EXPLICIT
;
6450 if (lang_hooks
.decls
.omp_private_outer_ref (OMP_CLAUSE_DECL (c
)))
6452 flags
|= GOVD_PRIVATE_OUTER_REF
;
6453 OMP_CLAUSE_PRIVATE_OUTER_REF (c
) = 1;
6456 notice_outer
= false;
6458 case OMP_CLAUSE_SHARED
:
6459 flags
= GOVD_SHARED
| GOVD_EXPLICIT
;
6461 case OMP_CLAUSE_FIRSTPRIVATE
:
6462 flags
= GOVD_FIRSTPRIVATE
| GOVD_EXPLICIT
;
6463 check_non_private
= "firstprivate";
6465 case OMP_CLAUSE_LASTPRIVATE
:
6466 flags
= GOVD_LASTPRIVATE
| GOVD_SEEN
| GOVD_EXPLICIT
;
6467 check_non_private
= "lastprivate";
6468 decl
= OMP_CLAUSE_DECL (c
);
6469 if (omp_no_lastprivate (ctx
))
6471 notice_outer
= false;
6472 flags
|= GOVD_LINEAR_LASTPRIVATE_NO_OUTER
;
6474 else if (error_operand_p (decl
))
6477 && (outer_ctx
->region_type
== ORT_COMBINED_PARALLEL
6478 || outer_ctx
->region_type
== ORT_COMBINED_TEAMS
)
6479 && splay_tree_lookup (outer_ctx
->variables
,
6480 (splay_tree_key
) decl
) == NULL
)
6482 omp_add_variable (outer_ctx
, decl
, GOVD_SHARED
| GOVD_SEEN
);
6483 if (outer_ctx
->outer_context
)
6484 omp_notice_variable (outer_ctx
->outer_context
, decl
, true);
6487 && (outer_ctx
->region_type
& ORT_TASK
) != 0
6488 && outer_ctx
->combined_loop
6489 && splay_tree_lookup (outer_ctx
->variables
,
6490 (splay_tree_key
) decl
) == NULL
)
6492 omp_add_variable (outer_ctx
, decl
, GOVD_LASTPRIVATE
| GOVD_SEEN
);
6493 if (outer_ctx
->outer_context
)
6494 omp_notice_variable (outer_ctx
->outer_context
, decl
, true);
6497 && (outer_ctx
->region_type
== ORT_WORKSHARE
6498 || outer_ctx
->region_type
== ORT_ACC
)
6499 && outer_ctx
->combined_loop
6500 && splay_tree_lookup (outer_ctx
->variables
,
6501 (splay_tree_key
) decl
) == NULL
6502 && !omp_check_private (outer_ctx
, decl
, false))
6504 omp_add_variable (outer_ctx
, decl
, GOVD_LASTPRIVATE
| GOVD_SEEN
);
6505 if (outer_ctx
->outer_context
6506 && (outer_ctx
->outer_context
->region_type
6507 == ORT_COMBINED_PARALLEL
)
6508 && splay_tree_lookup (outer_ctx
->outer_context
->variables
,
6509 (splay_tree_key
) decl
) == NULL
)
6511 struct gimplify_omp_ctx
*octx
= outer_ctx
->outer_context
;
6512 omp_add_variable (octx
, decl
, GOVD_SHARED
| GOVD_SEEN
);
6513 if (octx
->outer_context
)
6514 omp_notice_variable (octx
->outer_context
, decl
, true);
6516 else if (outer_ctx
->outer_context
)
6517 omp_notice_variable (outer_ctx
->outer_context
, decl
, true);
6520 case OMP_CLAUSE_REDUCTION
:
6521 flags
= GOVD_REDUCTION
| GOVD_SEEN
| GOVD_EXPLICIT
;
6522 /* OpenACC permits reductions on private variables. */
6523 if (!(region_type
& ORT_ACC
))
6524 check_non_private
= "reduction";
6525 decl
= OMP_CLAUSE_DECL (c
);
6526 if (TREE_CODE (decl
) == MEM_REF
)
6528 tree type
= TREE_TYPE (decl
);
6529 if (gimplify_expr (&TYPE_MAX_VALUE (TYPE_DOMAIN (type
)), pre_p
,
6530 NULL
, is_gimple_val
, fb_rvalue
) == GS_ERROR
)
6535 tree v
= TYPE_MAX_VALUE (TYPE_DOMAIN (type
));
6538 omp_firstprivatize_variable (ctx
, v
);
6539 omp_notice_variable (ctx
, v
, true);
6541 decl
= TREE_OPERAND (decl
, 0);
6542 if (TREE_CODE (decl
) == POINTER_PLUS_EXPR
)
6544 if (gimplify_expr (&TREE_OPERAND (decl
, 1), pre_p
,
6545 NULL
, is_gimple_val
, fb_rvalue
)
6551 v
= TREE_OPERAND (decl
, 1);
6554 omp_firstprivatize_variable (ctx
, v
);
6555 omp_notice_variable (ctx
, v
, true);
6557 decl
= TREE_OPERAND (decl
, 0);
6559 if (TREE_CODE (decl
) == ADDR_EXPR
6560 || TREE_CODE (decl
) == INDIRECT_REF
)
6561 decl
= TREE_OPERAND (decl
, 0);
6564 case OMP_CLAUSE_LINEAR
:
6565 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c
), pre_p
, NULL
,
6566 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
6573 if (code
== OMP_SIMD
6574 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c
))
6576 struct gimplify_omp_ctx
*octx
= outer_ctx
;
6578 && octx
->region_type
== ORT_WORKSHARE
6579 && octx
->combined_loop
6580 && !octx
->distribute
)
6582 if (octx
->outer_context
6583 && (octx
->outer_context
->region_type
6584 == ORT_COMBINED_PARALLEL
))
6585 octx
= octx
->outer_context
->outer_context
;
6587 octx
= octx
->outer_context
;
6590 && octx
->region_type
== ORT_WORKSHARE
6591 && octx
->combined_loop
6593 && !lang_GNU_Fortran ())
6595 error_at (OMP_CLAUSE_LOCATION (c
),
6596 "%<linear%> clause for variable other than "
6597 "loop iterator specified on construct "
6598 "combined with %<distribute%>");
6603 /* For combined #pragma omp parallel for simd, need to put
6604 lastprivate and perhaps firstprivate too on the
6605 parallel. Similarly for #pragma omp for simd. */
6606 struct gimplify_omp_ctx
*octx
= outer_ctx
;
6608 if (omp_no_lastprivate (ctx
))
6609 OMP_CLAUSE_LINEAR_NO_COPYOUT (c
) = 1;
6612 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c
)
6613 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c
))
6615 decl
= OMP_CLAUSE_DECL (c
);
6616 if (error_operand_p (decl
))
6622 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c
))
6623 flags
|= GOVD_FIRSTPRIVATE
;
6624 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c
))
6625 flags
|= GOVD_LASTPRIVATE
;
6627 && octx
->region_type
== ORT_WORKSHARE
6628 && octx
->combined_loop
)
6630 if (octx
->outer_context
6631 && (octx
->outer_context
->region_type
6632 == ORT_COMBINED_PARALLEL
))
6633 octx
= octx
->outer_context
;
6634 else if (omp_check_private (octx
, decl
, false))
6638 && (octx
->region_type
& ORT_TASK
) != 0
6639 && octx
->combined_loop
)
6642 && octx
->region_type
== ORT_COMBINED_PARALLEL
6643 && ctx
->region_type
== ORT_WORKSHARE
6644 && octx
== outer_ctx
)
6645 flags
= GOVD_SEEN
| GOVD_SHARED
;
6647 && octx
->region_type
== ORT_COMBINED_TEAMS
)
6648 flags
= GOVD_SEEN
| GOVD_SHARED
;
6650 && octx
->region_type
== ORT_COMBINED_TARGET
)
6652 flags
&= ~GOVD_LASTPRIVATE
;
6653 if (flags
== GOVD_SEEN
)
6659 = splay_tree_lookup (octx
->variables
,
6660 (splay_tree_key
) decl
);
6661 if (on
&& (on
->value
& GOVD_DATA_SHARE_CLASS
) != 0)
6666 omp_add_variable (octx
, decl
, flags
);
6667 if (octx
->outer_context
== NULL
)
6669 octx
= octx
->outer_context
;
6674 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c
)
6675 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c
)))
6676 omp_notice_variable (octx
, decl
, true);
6678 flags
= GOVD_LINEAR
| GOVD_EXPLICIT
;
6679 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c
)
6680 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c
))
6682 notice_outer
= false;
6683 flags
|= GOVD_LINEAR_LASTPRIVATE_NO_OUTER
;
6687 case OMP_CLAUSE_MAP
:
6688 decl
= OMP_CLAUSE_DECL (c
);
6689 if (error_operand_p (decl
))
6695 case OMP_TARGET_DATA
:
6696 case OMP_TARGET_ENTER_DATA
:
6697 case OMP_TARGET_EXIT_DATA
:
6698 case OACC_HOST_DATA
:
6699 if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_FIRSTPRIVATE_POINTER
6700 || (OMP_CLAUSE_MAP_KIND (c
)
6701 == GOMP_MAP_FIRSTPRIVATE_REFERENCE
))
6702 /* For target {,enter ,exit }data only the array slice is
6703 mapped, but not the pointer to it. */
6711 if (DECL_P (decl
) && outer_ctx
&& (region_type
& ORT_ACC
))
6713 struct gimplify_omp_ctx
*octx
;
6714 for (octx
= outer_ctx
; octx
; octx
= octx
->outer_context
)
6716 if (octx
->region_type
!= ORT_ACC_HOST_DATA
)
6719 = splay_tree_lookup (octx
->variables
,
6720 (splay_tree_key
) decl
);
6722 error_at (OMP_CLAUSE_LOCATION (c
), "variable %qE "
6723 "declared in enclosing %<host_data%> region",
6727 if (OMP_CLAUSE_SIZE (c
) == NULL_TREE
)
6728 OMP_CLAUSE_SIZE (c
) = DECL_P (decl
) ? DECL_SIZE_UNIT (decl
)
6729 : TYPE_SIZE_UNIT (TREE_TYPE (decl
));
6730 if (gimplify_expr (&OMP_CLAUSE_SIZE (c
), pre_p
,
6731 NULL
, is_gimple_val
, fb_rvalue
) == GS_ERROR
)
6736 else if ((OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_FIRSTPRIVATE_POINTER
6737 || (OMP_CLAUSE_MAP_KIND (c
)
6738 == GOMP_MAP_FIRSTPRIVATE_REFERENCE
))
6739 && TREE_CODE (OMP_CLAUSE_SIZE (c
)) != INTEGER_CST
)
6742 = get_initialized_tmp_var (OMP_CLAUSE_SIZE (c
), pre_p
, NULL
);
6743 omp_add_variable (ctx
, OMP_CLAUSE_SIZE (c
),
6744 GOVD_FIRSTPRIVATE
| GOVD_SEEN
);
6749 if (TREE_CODE (d
) == ARRAY_REF
)
6751 while (TREE_CODE (d
) == ARRAY_REF
)
6752 d
= TREE_OPERAND (d
, 0);
6753 if (TREE_CODE (d
) == COMPONENT_REF
6754 && TREE_CODE (TREE_TYPE (d
)) == ARRAY_TYPE
)
6757 pd
= &OMP_CLAUSE_DECL (c
);
6759 && TREE_CODE (decl
) == INDIRECT_REF
6760 && TREE_CODE (TREE_OPERAND (decl
, 0)) == COMPONENT_REF
6761 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl
, 0)))
6764 pd
= &TREE_OPERAND (decl
, 0);
6765 decl
= TREE_OPERAND (decl
, 0);
6767 if (TREE_CODE (decl
) == COMPONENT_REF
)
6769 while (TREE_CODE (decl
) == COMPONENT_REF
)
6770 decl
= TREE_OPERAND (decl
, 0);
6772 if (gimplify_expr (pd
, pre_p
, NULL
, is_gimple_lvalue
, fb_lvalue
)
6780 if (error_operand_p (decl
))
6786 if (TYPE_SIZE_UNIT (TREE_TYPE (decl
)) == NULL
6787 || (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (decl
)))
6790 error_at (OMP_CLAUSE_LOCATION (c
),
6791 "mapping field %qE of variable length "
6792 "structure", OMP_CLAUSE_DECL (c
));
6797 if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_ALWAYS_POINTER
)
6799 /* Error recovery. */
6800 if (prev_list_p
== NULL
)
6805 if (OMP_CLAUSE_CHAIN (*prev_list_p
) != c
)
6807 tree ch
= OMP_CLAUSE_CHAIN (*prev_list_p
);
6808 if (ch
== NULL_TREE
|| OMP_CLAUSE_CHAIN (ch
) != c
)
6817 HOST_WIDE_INT bitsize
, bitpos
;
6819 int unsignedp
, reversep
, volatilep
= 0;
6820 tree base
= OMP_CLAUSE_DECL (c
);
6821 while (TREE_CODE (base
) == ARRAY_REF
)
6822 base
= TREE_OPERAND (base
, 0);
6823 if (TREE_CODE (base
) == INDIRECT_REF
)
6824 base
= TREE_OPERAND (base
, 0);
6825 base
= get_inner_reference (base
, &bitsize
, &bitpos
, &offset
,
6826 &mode
, &unsignedp
, &reversep
,
6828 gcc_assert (base
== decl
6829 && (offset
== NULL_TREE
6830 || TREE_CODE (offset
) == INTEGER_CST
));
6833 = splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
6834 bool ptr
= (OMP_CLAUSE_MAP_KIND (c
)
6835 == GOMP_MAP_ALWAYS_POINTER
);
6836 if (n
== NULL
|| (n
->value
& GOVD_MAP
) == 0)
6838 tree l
= build_omp_clause (OMP_CLAUSE_LOCATION (c
),
6840 OMP_CLAUSE_SET_MAP_KIND (l
, GOMP_MAP_STRUCT
);
6841 OMP_CLAUSE_DECL (l
) = decl
;
6842 OMP_CLAUSE_SIZE (l
) = size_int (1);
6843 if (struct_map_to_clause
== NULL
)
6844 struct_map_to_clause
= new hash_map
<tree
, tree
>;
6845 struct_map_to_clause
->put (decl
, l
);
6848 enum gomp_map_kind mkind
6849 = code
== OMP_TARGET_EXIT_DATA
6850 ? GOMP_MAP_RELEASE
: GOMP_MAP_ALLOC
;
6851 tree c2
= build_omp_clause (OMP_CLAUSE_LOCATION (c
),
6853 OMP_CLAUSE_SET_MAP_KIND (c2
, mkind
);
6854 OMP_CLAUSE_DECL (c2
)
6855 = unshare_expr (OMP_CLAUSE_DECL (c
));
6856 OMP_CLAUSE_CHAIN (c2
) = *prev_list_p
;
6857 OMP_CLAUSE_SIZE (c2
)
6858 = TYPE_SIZE_UNIT (ptr_type_node
);
6859 OMP_CLAUSE_CHAIN (l
) = c2
;
6860 if (OMP_CLAUSE_CHAIN (*prev_list_p
) != c
)
6862 tree c4
= OMP_CLAUSE_CHAIN (*prev_list_p
);
6864 = build_omp_clause (OMP_CLAUSE_LOCATION (c
),
6866 OMP_CLAUSE_SET_MAP_KIND (c3
, mkind
);
6867 OMP_CLAUSE_DECL (c3
)
6868 = unshare_expr (OMP_CLAUSE_DECL (c4
));
6869 OMP_CLAUSE_SIZE (c3
)
6870 = TYPE_SIZE_UNIT (ptr_type_node
);
6871 OMP_CLAUSE_CHAIN (c3
) = *prev_list_p
;
6872 OMP_CLAUSE_CHAIN (c2
) = c3
;
6879 OMP_CLAUSE_CHAIN (l
) = c
;
6881 list_p
= &OMP_CLAUSE_CHAIN (l
);
6883 flags
= GOVD_MAP
| GOVD_EXPLICIT
;
6884 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c
)) || ptr
)
6890 tree
*osc
= struct_map_to_clause
->get (decl
);
6891 tree
*sc
= NULL
, *scp
= NULL
;
6892 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c
)) || ptr
)
6893 n
->value
|= GOVD_SEEN
;
6896 o1
= wi::to_offset (offset
);
6900 o1
= o1
+ bitpos
/ BITS_PER_UNIT
;
6901 for (sc
= &OMP_CLAUSE_CHAIN (*osc
);
6902 *sc
!= c
; sc
= &OMP_CLAUSE_CHAIN (*sc
))
6903 if (ptr
&& sc
== prev_list_p
)
6905 else if (TREE_CODE (OMP_CLAUSE_DECL (*sc
))
6907 && (TREE_CODE (OMP_CLAUSE_DECL (*sc
))
6909 && (TREE_CODE (OMP_CLAUSE_DECL (*sc
))
6915 HOST_WIDE_INT bitsize2
, bitpos2
;
6916 base
= OMP_CLAUSE_DECL (*sc
);
6917 if (TREE_CODE (base
) == ARRAY_REF
)
6919 while (TREE_CODE (base
) == ARRAY_REF
)
6920 base
= TREE_OPERAND (base
, 0);
6921 if (TREE_CODE (base
) != COMPONENT_REF
6922 || (TREE_CODE (TREE_TYPE (base
))
6926 else if (TREE_CODE (base
) == INDIRECT_REF
6927 && (TREE_CODE (TREE_OPERAND (base
, 0))
6929 && (TREE_CODE (TREE_TYPE
6930 (TREE_OPERAND (base
, 0)))
6932 base
= TREE_OPERAND (base
, 0);
6933 base
= get_inner_reference (base
, &bitsize2
,
6936 &reversep
, &volatilep
,
6942 gcc_assert (offset
== NULL_TREE
6943 || TREE_CODE (offset
) == INTEGER_CST
);
6944 tree d1
= OMP_CLAUSE_DECL (*sc
);
6945 tree d2
= OMP_CLAUSE_DECL (c
);
6946 while (TREE_CODE (d1
) == ARRAY_REF
)
6947 d1
= TREE_OPERAND (d1
, 0);
6948 while (TREE_CODE (d2
) == ARRAY_REF
)
6949 d2
= TREE_OPERAND (d2
, 0);
6950 if (TREE_CODE (d1
) == INDIRECT_REF
)
6951 d1
= TREE_OPERAND (d1
, 0);
6952 if (TREE_CODE (d2
) == INDIRECT_REF
)
6953 d2
= TREE_OPERAND (d2
, 0);
6954 while (TREE_CODE (d1
) == COMPONENT_REF
)
6955 if (TREE_CODE (d2
) == COMPONENT_REF
6956 && TREE_OPERAND (d1
, 1)
6957 == TREE_OPERAND (d2
, 1))
6959 d1
= TREE_OPERAND (d1
, 0);
6960 d2
= TREE_OPERAND (d2
, 0);
6966 error_at (OMP_CLAUSE_LOCATION (c
),
6967 "%qE appears more than once in map "
6968 "clauses", OMP_CLAUSE_DECL (c
));
6973 o2
= wi::to_offset (offset2
);
6977 o2
= o2
+ bitpos2
/ BITS_PER_UNIT
;
6978 if (wi::ltu_p (o1
, o2
)
6979 || (wi::eq_p (o1
, o2
) && bitpos
< bitpos2
))
6989 OMP_CLAUSE_SIZE (*osc
)
6990 = size_binop (PLUS_EXPR
, OMP_CLAUSE_SIZE (*osc
),
6994 tree c2
= build_omp_clause (OMP_CLAUSE_LOCATION (c
),
6996 tree cl
= NULL_TREE
;
6997 enum gomp_map_kind mkind
6998 = code
== OMP_TARGET_EXIT_DATA
6999 ? GOMP_MAP_RELEASE
: GOMP_MAP_ALLOC
;
7000 OMP_CLAUSE_SET_MAP_KIND (c2
, mkind
);
7001 OMP_CLAUSE_DECL (c2
)
7002 = unshare_expr (OMP_CLAUSE_DECL (c
));
7003 OMP_CLAUSE_CHAIN (c2
) = scp
? *scp
: *prev_list_p
;
7004 OMP_CLAUSE_SIZE (c2
)
7005 = TYPE_SIZE_UNIT (ptr_type_node
);
7006 cl
= scp
? *prev_list_p
: c2
;
7007 if (OMP_CLAUSE_CHAIN (*prev_list_p
) != c
)
7009 tree c4
= OMP_CLAUSE_CHAIN (*prev_list_p
);
7011 = build_omp_clause (OMP_CLAUSE_LOCATION (c
),
7013 OMP_CLAUSE_SET_MAP_KIND (c3
, mkind
);
7014 OMP_CLAUSE_DECL (c3
)
7015 = unshare_expr (OMP_CLAUSE_DECL (c4
));
7016 OMP_CLAUSE_SIZE (c3
)
7017 = TYPE_SIZE_UNIT (ptr_type_node
);
7018 OMP_CLAUSE_CHAIN (c3
) = *prev_list_p
;
7020 OMP_CLAUSE_CHAIN (c2
) = c3
;
7026 if (sc
== prev_list_p
)
7033 *prev_list_p
= OMP_CLAUSE_CHAIN (c
);
7034 list_p
= prev_list_p
;
7036 OMP_CLAUSE_CHAIN (c
) = *sc
;
7043 *list_p
= OMP_CLAUSE_CHAIN (c
);
7044 OMP_CLAUSE_CHAIN (c
) = *sc
;
7051 && OMP_CLAUSE_MAP_KIND (c
) != GOMP_MAP_ALWAYS_POINTER
7052 && OMP_CLAUSE_CHAIN (c
)
7053 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (c
)) == OMP_CLAUSE_MAP
7054 && (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c
))
7055 == GOMP_MAP_ALWAYS_POINTER
))
7056 prev_list_p
= list_p
;
7059 flags
= GOVD_MAP
| GOVD_EXPLICIT
;
7060 if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_ALWAYS_TO
7061 || OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_ALWAYS_TOFROM
)
7062 flags
|= GOVD_MAP_ALWAYS_TO
;
7065 case OMP_CLAUSE_DEPEND
:
7066 if (OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SINK
7067 || OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SOURCE
)
7069 /* Nothing to do. OMP_CLAUSE_DECL will be lowered in
7073 if (TREE_CODE (OMP_CLAUSE_DECL (c
)) == COMPOUND_EXPR
)
7075 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c
), 0), pre_p
,
7076 NULL
, is_gimple_val
, fb_rvalue
);
7077 OMP_CLAUSE_DECL (c
) = TREE_OPERAND (OMP_CLAUSE_DECL (c
), 1);
7079 if (error_operand_p (OMP_CLAUSE_DECL (c
)))
7084 OMP_CLAUSE_DECL (c
) = build_fold_addr_expr (OMP_CLAUSE_DECL (c
));
7085 if (gimplify_expr (&OMP_CLAUSE_DECL (c
), pre_p
, NULL
,
7086 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7094 case OMP_CLAUSE_FROM
:
7095 case OMP_CLAUSE__CACHE_
:
7096 decl
= OMP_CLAUSE_DECL (c
);
7097 if (error_operand_p (decl
))
7102 if (OMP_CLAUSE_SIZE (c
) == NULL_TREE
)
7103 OMP_CLAUSE_SIZE (c
) = DECL_P (decl
) ? DECL_SIZE_UNIT (decl
)
7104 : TYPE_SIZE_UNIT (TREE_TYPE (decl
));
7105 if (gimplify_expr (&OMP_CLAUSE_SIZE (c
), pre_p
,
7106 NULL
, is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7113 if (gimplify_expr (&OMP_CLAUSE_DECL (c
), pre_p
,
7114 NULL
, is_gimple_lvalue
, fb_lvalue
)
7124 case OMP_CLAUSE_USE_DEVICE
:
7125 case OMP_CLAUSE_USE_DEVICE_PTR
:
7126 flags
= GOVD_FIRSTPRIVATE
| GOVD_EXPLICIT
;
7128 case OMP_CLAUSE_IS_DEVICE_PTR
:
7129 flags
= GOVD_FIRSTPRIVATE
| GOVD_EXPLICIT
;
7133 decl
= OMP_CLAUSE_DECL (c
);
7135 if (error_operand_p (decl
))
7140 if (DECL_NAME (decl
) == NULL_TREE
&& (flags
& GOVD_SHARED
) == 0)
7142 tree t
= omp_member_access_dummy_var (decl
);
7145 tree v
= DECL_VALUE_EXPR (decl
);
7146 DECL_NAME (decl
) = DECL_NAME (TREE_OPERAND (v
, 1));
7148 omp_notice_variable (outer_ctx
, t
, true);
7151 omp_add_variable (ctx
, decl
, flags
);
7152 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_REDUCTION
7153 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c
))
7155 omp_add_variable (ctx
, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c
),
7156 GOVD_LOCAL
| GOVD_SEEN
);
7157 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c
)
7158 && walk_tree (&OMP_CLAUSE_REDUCTION_INIT (c
),
7160 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c
),
7162 omp_add_variable (ctx
,
7163 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c
),
7164 GOVD_LOCAL
| GOVD_SEEN
);
7165 gimplify_omp_ctxp
= ctx
;
7166 push_gimplify_context ();
7168 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c
) = NULL
;
7169 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c
) = NULL
;
7171 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c
),
7172 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c
));
7173 pop_gimplify_context
7174 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c
)));
7175 push_gimplify_context ();
7176 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c
),
7177 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c
));
7178 pop_gimplify_context
7179 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c
)));
7180 OMP_CLAUSE_REDUCTION_INIT (c
) = NULL_TREE
;
7181 OMP_CLAUSE_REDUCTION_MERGE (c
) = NULL_TREE
;
7183 gimplify_omp_ctxp
= outer_ctx
;
7185 else if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LASTPRIVATE
7186 && OMP_CLAUSE_LASTPRIVATE_STMT (c
))
7188 gimplify_omp_ctxp
= ctx
;
7189 push_gimplify_context ();
7190 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c
)) != BIND_EXPR
)
7192 tree bind
= build3 (BIND_EXPR
, void_type_node
, NULL
,
7194 TREE_SIDE_EFFECTS (bind
) = 1;
7195 BIND_EXPR_BODY (bind
) = OMP_CLAUSE_LASTPRIVATE_STMT (c
);
7196 OMP_CLAUSE_LASTPRIVATE_STMT (c
) = bind
;
7198 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c
),
7199 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c
));
7200 pop_gimplify_context
7201 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c
)));
7202 OMP_CLAUSE_LASTPRIVATE_STMT (c
) = NULL_TREE
;
7204 gimplify_omp_ctxp
= outer_ctx
;
7206 else if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LINEAR
7207 && OMP_CLAUSE_LINEAR_STMT (c
))
7209 gimplify_omp_ctxp
= ctx
;
7210 push_gimplify_context ();
7211 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c
)) != BIND_EXPR
)
7213 tree bind
= build3 (BIND_EXPR
, void_type_node
, NULL
,
7215 TREE_SIDE_EFFECTS (bind
) = 1;
7216 BIND_EXPR_BODY (bind
) = OMP_CLAUSE_LINEAR_STMT (c
);
7217 OMP_CLAUSE_LINEAR_STMT (c
) = bind
;
7219 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c
),
7220 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c
));
7221 pop_gimplify_context
7222 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c
)));
7223 OMP_CLAUSE_LINEAR_STMT (c
) = NULL_TREE
;
7225 gimplify_omp_ctxp
= outer_ctx
;
7231 case OMP_CLAUSE_COPYIN
:
7232 case OMP_CLAUSE_COPYPRIVATE
:
7233 decl
= OMP_CLAUSE_DECL (c
);
7234 if (error_operand_p (decl
))
7239 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_COPYPRIVATE
7241 && !omp_check_private (ctx
, decl
, true))
7244 if (is_global_var (decl
))
7246 if (DECL_THREAD_LOCAL_P (decl
))
7248 else if (DECL_HAS_VALUE_EXPR_P (decl
))
7250 tree value
= get_base_address (DECL_VALUE_EXPR (decl
));
7254 && DECL_THREAD_LOCAL_P (value
))
7259 error_at (OMP_CLAUSE_LOCATION (c
),
7260 "copyprivate variable %qE is not threadprivate"
7261 " or private in outer context", DECL_NAME (decl
));
7265 omp_notice_variable (outer_ctx
, decl
, true);
7266 if (check_non_private
7267 && region_type
== ORT_WORKSHARE
7268 && (OMP_CLAUSE_CODE (c
) != OMP_CLAUSE_REDUCTION
7269 || decl
== OMP_CLAUSE_DECL (c
)
7270 || (TREE_CODE (OMP_CLAUSE_DECL (c
)) == MEM_REF
7271 && (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c
), 0))
7273 || (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c
), 0))
7274 == POINTER_PLUS_EXPR
7275 && (TREE_CODE (TREE_OPERAND (TREE_OPERAND
7276 (OMP_CLAUSE_DECL (c
), 0), 0))
7278 && omp_check_private (ctx
, decl
, false))
7280 error ("%s variable %qE is private in outer context",
7281 check_non_private
, DECL_NAME (decl
));
7287 if (OMP_CLAUSE_IF_MODIFIER (c
) != ERROR_MARK
7288 && OMP_CLAUSE_IF_MODIFIER (c
) != code
)
7291 for (int i
= 0; i
< 2; i
++)
7292 switch (i
? OMP_CLAUSE_IF_MODIFIER (c
) : code
)
7294 case OMP_PARALLEL
: p
[i
] = "parallel"; break;
7295 case OMP_TASK
: p
[i
] = "task"; break;
7296 case OMP_TASKLOOP
: p
[i
] = "taskloop"; break;
7297 case OMP_TARGET_DATA
: p
[i
] = "target data"; break;
7298 case OMP_TARGET
: p
[i
] = "target"; break;
7299 case OMP_TARGET_UPDATE
: p
[i
] = "target update"; break;
7300 case OMP_TARGET_ENTER_DATA
:
7301 p
[i
] = "target enter data"; break;
7302 case OMP_TARGET_EXIT_DATA
: p
[i
] = "target exit data"; break;
7303 default: gcc_unreachable ();
7305 error_at (OMP_CLAUSE_LOCATION (c
),
7306 "expected %qs %<if%> clause modifier rather than %qs",
7312 case OMP_CLAUSE_FINAL
:
7313 OMP_CLAUSE_OPERAND (c
, 0)
7314 = gimple_boolify (OMP_CLAUSE_OPERAND (c
, 0));
7317 case OMP_CLAUSE_SCHEDULE
:
7318 case OMP_CLAUSE_NUM_THREADS
:
7319 case OMP_CLAUSE_NUM_TEAMS
:
7320 case OMP_CLAUSE_THREAD_LIMIT
:
7321 case OMP_CLAUSE_DIST_SCHEDULE
:
7322 case OMP_CLAUSE_DEVICE
:
7323 case OMP_CLAUSE_PRIORITY
:
7324 case OMP_CLAUSE_GRAINSIZE
:
7325 case OMP_CLAUSE_NUM_TASKS
:
7326 case OMP_CLAUSE_HINT
:
7327 case OMP_CLAUSE__CILK_FOR_COUNT_
:
7328 case OMP_CLAUSE_ASYNC
:
7329 case OMP_CLAUSE_WAIT
:
7330 case OMP_CLAUSE_NUM_GANGS
:
7331 case OMP_CLAUSE_NUM_WORKERS
:
7332 case OMP_CLAUSE_VECTOR_LENGTH
:
7333 case OMP_CLAUSE_WORKER
:
7334 case OMP_CLAUSE_VECTOR
:
7335 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c
, 0), pre_p
, NULL
,
7336 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7340 case OMP_CLAUSE_GANG
:
7341 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c
, 0), pre_p
, NULL
,
7342 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7344 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c
, 1), pre_p
, NULL
,
7345 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7349 case OMP_CLAUSE_TILE
:
7350 for (tree list
= OMP_CLAUSE_TILE_LIST (c
); !remove
&& list
;
7351 list
= TREE_CHAIN (list
))
7353 if (gimplify_expr (&TREE_VALUE (list
), pre_p
, NULL
,
7354 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7359 case OMP_CLAUSE_DEVICE_RESIDENT
:
7363 case OMP_CLAUSE_NOWAIT
:
7364 case OMP_CLAUSE_ORDERED
:
7365 case OMP_CLAUSE_UNTIED
:
7366 case OMP_CLAUSE_COLLAPSE
:
7367 case OMP_CLAUSE_AUTO
:
7368 case OMP_CLAUSE_SEQ
:
7369 case OMP_CLAUSE_INDEPENDENT
:
7370 case OMP_CLAUSE_MERGEABLE
:
7371 case OMP_CLAUSE_PROC_BIND
:
7372 case OMP_CLAUSE_SAFELEN
:
7373 case OMP_CLAUSE_SIMDLEN
:
7374 case OMP_CLAUSE_NOGROUP
:
7375 case OMP_CLAUSE_THREADS
:
7376 case OMP_CLAUSE_SIMD
:
7379 case OMP_CLAUSE_DEFAULTMAP
:
7380 ctx
->target_map_scalars_firstprivate
= false;
7383 case OMP_CLAUSE_ALIGNED
:
7384 decl
= OMP_CLAUSE_DECL (c
);
7385 if (error_operand_p (decl
))
7390 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c
), pre_p
, NULL
,
7391 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7396 if (!is_global_var (decl
)
7397 && TREE_CODE (TREE_TYPE (decl
)) == POINTER_TYPE
)
7398 omp_add_variable (ctx
, decl
, GOVD_ALIGNED
);
7401 case OMP_CLAUSE_DEFAULT
:
7402 ctx
->default_kind
= OMP_CLAUSE_DEFAULT_KIND (c
);
7410 *list_p
= OMP_CLAUSE_CHAIN (c
);
7412 list_p
= &OMP_CLAUSE_CHAIN (c
);
7415 gimplify_omp_ctxp
= ctx
;
7416 if (struct_map_to_clause
)
7417 delete struct_map_to_clause
;
7420 /* Return true if DECL is a candidate for shared to firstprivate
7421 optimization. We only consider non-addressable scalars, not
7422 too big, and not references. */
7425 omp_shared_to_firstprivate_optimizable_decl_p (tree decl
)
7427 if (TREE_ADDRESSABLE (decl
))
7429 tree type
= TREE_TYPE (decl
);
7430 if (!is_gimple_reg_type (type
)
7431 || TREE_CODE (type
) == REFERENCE_TYPE
7432 || TREE_ADDRESSABLE (type
))
7434 /* Don't optimize too large decls, as each thread/task will have
7436 HOST_WIDE_INT len
= int_size_in_bytes (type
);
7437 if (len
== -1 || len
> 4 * POINTER_SIZE
/ BITS_PER_UNIT
)
7439 if (lang_hooks
.decls
.omp_privatize_by_reference (decl
))
7444 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
7445 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
7446 GOVD_WRITTEN in outer contexts. */
7449 omp_mark_stores (struct gimplify_omp_ctx
*ctx
, tree decl
)
7451 for (; ctx
; ctx
= ctx
->outer_context
)
7453 splay_tree_node n
= splay_tree_lookup (ctx
->variables
,
7454 (splay_tree_key
) decl
);
7457 else if (n
->value
& GOVD_SHARED
)
7459 n
->value
|= GOVD_WRITTEN
;
7462 else if (n
->value
& GOVD_DATA_SHARE_CLASS
)
7467 /* Helper callback for walk_gimple_seq to discover possible stores
7468 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
7469 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
7473 omp_find_stores_op (tree
*tp
, int *walk_subtrees
, void *data
)
7475 struct walk_stmt_info
*wi
= (struct walk_stmt_info
*) data
;
7484 if (handled_component_p (op
))
7485 op
= TREE_OPERAND (op
, 0);
7486 else if ((TREE_CODE (op
) == MEM_REF
|| TREE_CODE (op
) == TARGET_MEM_REF
)
7487 && TREE_CODE (TREE_OPERAND (op
, 0)) == ADDR_EXPR
)
7488 op
= TREE_OPERAND (TREE_OPERAND (op
, 0), 0);
7493 if (!DECL_P (op
) || !omp_shared_to_firstprivate_optimizable_decl_p (op
))
7496 omp_mark_stores (gimplify_omp_ctxp
, op
);
7500 /* Helper callback for walk_gimple_seq to discover possible stores
7501 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
7502 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
7506 omp_find_stores_stmt (gimple_stmt_iterator
*gsi_p
,
7507 bool *handled_ops_p
,
7508 struct walk_stmt_info
*wi
)
7510 gimple
*stmt
= gsi_stmt (*gsi_p
);
7511 switch (gimple_code (stmt
))
7513 /* Don't recurse on OpenMP constructs for which
7514 gimplify_adjust_omp_clauses already handled the bodies,
7515 except handle gimple_omp_for_pre_body. */
7516 case GIMPLE_OMP_FOR
:
7517 *handled_ops_p
= true;
7518 if (gimple_omp_for_pre_body (stmt
))
7519 walk_gimple_seq (gimple_omp_for_pre_body (stmt
),
7520 omp_find_stores_stmt
, omp_find_stores_op
, wi
);
7522 case GIMPLE_OMP_PARALLEL
:
7523 case GIMPLE_OMP_TASK
:
7524 case GIMPLE_OMP_SECTIONS
:
7525 case GIMPLE_OMP_SINGLE
:
7526 case GIMPLE_OMP_TARGET
:
7527 case GIMPLE_OMP_TEAMS
:
7528 case GIMPLE_OMP_CRITICAL
:
7529 *handled_ops_p
= true;
7537 struct gimplify_adjust_omp_clauses_data
7543 /* For all variables that were not actually used within the context,
7544 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
7547 gimplify_adjust_omp_clauses_1 (splay_tree_node n
, void *data
)
7549 tree
*list_p
= ((struct gimplify_adjust_omp_clauses_data
*) data
)->list_p
;
7551 = ((struct gimplify_adjust_omp_clauses_data
*) data
)->pre_p
;
7552 tree decl
= (tree
) n
->key
;
7553 unsigned flags
= n
->value
;
7554 enum omp_clause_code code
;
7558 if (flags
& (GOVD_EXPLICIT
| GOVD_LOCAL
))
7560 if ((flags
& GOVD_SEEN
) == 0)
7562 if (flags
& GOVD_DEBUG_PRIVATE
)
7564 gcc_assert ((flags
& GOVD_DATA_SHARE_CLASS
) == GOVD_PRIVATE
);
7565 private_debug
= true;
7567 else if (flags
& GOVD_MAP
)
7568 private_debug
= false;
7571 = lang_hooks
.decls
.omp_private_debug_clause (decl
,
7572 !!(flags
& GOVD_SHARED
));
7574 code
= OMP_CLAUSE_PRIVATE
;
7575 else if (flags
& GOVD_MAP
)
7576 code
= OMP_CLAUSE_MAP
;
7577 else if (flags
& GOVD_SHARED
)
7579 if (is_global_var (decl
))
7581 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
->outer_context
;
7585 = splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
7586 if (on
&& (on
->value
& (GOVD_FIRSTPRIVATE
| GOVD_LASTPRIVATE
7587 | GOVD_PRIVATE
| GOVD_REDUCTION
7588 | GOVD_LINEAR
| GOVD_MAP
)) != 0)
7590 ctx
= ctx
->outer_context
;
7595 code
= OMP_CLAUSE_SHARED
;
7597 else if (flags
& GOVD_PRIVATE
)
7598 code
= OMP_CLAUSE_PRIVATE
;
7599 else if (flags
& GOVD_FIRSTPRIVATE
)
7600 code
= OMP_CLAUSE_FIRSTPRIVATE
;
7601 else if (flags
& GOVD_LASTPRIVATE
)
7602 code
= OMP_CLAUSE_LASTPRIVATE
;
7603 else if (flags
& GOVD_ALIGNED
)
7608 if (((flags
& GOVD_LASTPRIVATE
)
7609 || (code
== OMP_CLAUSE_SHARED
&& (flags
& GOVD_WRITTEN
)))
7610 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
7611 omp_mark_stores (gimplify_omp_ctxp
->outer_context
, decl
);
7613 clause
= build_omp_clause (input_location
, code
);
7614 OMP_CLAUSE_DECL (clause
) = decl
;
7615 OMP_CLAUSE_CHAIN (clause
) = *list_p
;
7617 OMP_CLAUSE_PRIVATE_DEBUG (clause
) = 1;
7618 else if (code
== OMP_CLAUSE_PRIVATE
&& (flags
& GOVD_PRIVATE_OUTER_REF
))
7619 OMP_CLAUSE_PRIVATE_OUTER_REF (clause
) = 1;
7620 else if (code
== OMP_CLAUSE_SHARED
7621 && (flags
& GOVD_WRITTEN
) == 0
7622 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
7623 OMP_CLAUSE_SHARED_READONLY (clause
) = 1;
7624 else if (code
== OMP_CLAUSE_MAP
&& (flags
& GOVD_MAP_0LEN_ARRAY
) != 0)
7626 tree nc
= build_omp_clause (input_location
, OMP_CLAUSE_MAP
);
7627 OMP_CLAUSE_DECL (nc
) = decl
;
7628 if (TREE_CODE (TREE_TYPE (decl
)) == REFERENCE_TYPE
7629 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl
))) == POINTER_TYPE
)
7630 OMP_CLAUSE_DECL (clause
)
7631 = build_simple_mem_ref_loc (input_location
, decl
);
7632 OMP_CLAUSE_DECL (clause
)
7633 = build2 (MEM_REF
, char_type_node
, OMP_CLAUSE_DECL (clause
),
7634 build_int_cst (build_pointer_type (char_type_node
), 0));
7635 OMP_CLAUSE_SIZE (clause
) = size_zero_node
;
7636 OMP_CLAUSE_SIZE (nc
) = size_zero_node
;
7637 OMP_CLAUSE_SET_MAP_KIND (clause
, GOMP_MAP_ALLOC
);
7638 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause
) = 1;
7639 OMP_CLAUSE_SET_MAP_KIND (nc
, GOMP_MAP_FIRSTPRIVATE_POINTER
);
7640 OMP_CLAUSE_CHAIN (nc
) = *list_p
;
7641 OMP_CLAUSE_CHAIN (clause
) = nc
;
7642 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
7643 gimplify_omp_ctxp
= ctx
->outer_context
;
7644 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause
), 0),
7645 pre_p
, NULL
, is_gimple_val
, fb_rvalue
);
7646 gimplify_omp_ctxp
= ctx
;
7648 else if (code
== OMP_CLAUSE_MAP
)
7650 int kind
= (flags
& GOVD_MAP_TO_ONLY
7653 if (flags
& GOVD_MAP_FORCE
)
7654 kind
|= GOMP_MAP_FLAG_FORCE
;
7655 OMP_CLAUSE_SET_MAP_KIND (clause
, kind
);
7656 if (DECL_SIZE (decl
)
7657 && TREE_CODE (DECL_SIZE (decl
)) != INTEGER_CST
)
7659 tree decl2
= DECL_VALUE_EXPR (decl
);
7660 gcc_assert (TREE_CODE (decl2
) == INDIRECT_REF
);
7661 decl2
= TREE_OPERAND (decl2
, 0);
7662 gcc_assert (DECL_P (decl2
));
7663 tree mem
= build_simple_mem_ref (decl2
);
7664 OMP_CLAUSE_DECL (clause
) = mem
;
7665 OMP_CLAUSE_SIZE (clause
) = TYPE_SIZE_UNIT (TREE_TYPE (decl
));
7666 if (gimplify_omp_ctxp
->outer_context
)
7668 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
->outer_context
;
7669 omp_notice_variable (ctx
, decl2
, true);
7670 omp_notice_variable (ctx
, OMP_CLAUSE_SIZE (clause
), true);
7672 tree nc
= build_omp_clause (OMP_CLAUSE_LOCATION (clause
),
7674 OMP_CLAUSE_DECL (nc
) = decl
;
7675 OMP_CLAUSE_SIZE (nc
) = size_zero_node
;
7676 if (gimplify_omp_ctxp
->target_firstprivatize_array_bases
)
7677 OMP_CLAUSE_SET_MAP_KIND (nc
, GOMP_MAP_FIRSTPRIVATE_POINTER
);
7679 OMP_CLAUSE_SET_MAP_KIND (nc
, GOMP_MAP_POINTER
);
7680 OMP_CLAUSE_CHAIN (nc
) = OMP_CLAUSE_CHAIN (clause
);
7681 OMP_CLAUSE_CHAIN (clause
) = nc
;
7683 else if (gimplify_omp_ctxp
->target_firstprivatize_array_bases
7684 && lang_hooks
.decls
.omp_privatize_by_reference (decl
))
7686 OMP_CLAUSE_DECL (clause
) = build_simple_mem_ref (decl
);
7687 OMP_CLAUSE_SIZE (clause
)
7688 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl
))));
7689 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
7690 gimplify_omp_ctxp
= ctx
->outer_context
;
7691 gimplify_expr (&OMP_CLAUSE_SIZE (clause
),
7692 pre_p
, NULL
, is_gimple_val
, fb_rvalue
);
7693 gimplify_omp_ctxp
= ctx
;
7694 tree nc
= build_omp_clause (OMP_CLAUSE_LOCATION (clause
),
7696 OMP_CLAUSE_DECL (nc
) = decl
;
7697 OMP_CLAUSE_SIZE (nc
) = size_zero_node
;
7698 OMP_CLAUSE_SET_MAP_KIND (nc
, GOMP_MAP_FIRSTPRIVATE_REFERENCE
);
7699 OMP_CLAUSE_CHAIN (nc
) = OMP_CLAUSE_CHAIN (clause
);
7700 OMP_CLAUSE_CHAIN (clause
) = nc
;
7703 OMP_CLAUSE_SIZE (clause
) = DECL_SIZE_UNIT (decl
);
7705 if (code
== OMP_CLAUSE_FIRSTPRIVATE
&& (flags
& GOVD_LASTPRIVATE
) != 0)
7707 tree nc
= build_omp_clause (input_location
, OMP_CLAUSE_LASTPRIVATE
);
7708 OMP_CLAUSE_DECL (nc
) = decl
;
7709 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc
) = 1;
7710 OMP_CLAUSE_CHAIN (nc
) = *list_p
;
7711 OMP_CLAUSE_CHAIN (clause
) = nc
;
7712 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
7713 gimplify_omp_ctxp
= ctx
->outer_context
;
7714 lang_hooks
.decls
.omp_finish_clause (nc
, pre_p
);
7715 gimplify_omp_ctxp
= ctx
;
7718 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
7719 gimplify_omp_ctxp
= ctx
->outer_context
;
7720 lang_hooks
.decls
.omp_finish_clause (clause
, pre_p
);
7721 gimplify_omp_ctxp
= ctx
;
7726 gimplify_adjust_omp_clauses (gimple_seq
*pre_p
, gimple_seq body
, tree
*list_p
,
7727 enum tree_code code
)
7729 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
7734 struct gimplify_omp_ctx
*octx
;
7735 for (octx
= ctx
; octx
; octx
= octx
->outer_context
)
7736 if ((octx
->region_type
& (ORT_PARALLEL
| ORT_TASK
| ORT_TEAMS
)) != 0)
7740 struct walk_stmt_info wi
;
7741 memset (&wi
, 0, sizeof (wi
));
7742 walk_gimple_seq (body
, omp_find_stores_stmt
,
7743 omp_find_stores_op
, &wi
);
7746 while ((c
= *list_p
) != NULL
)
7749 bool remove
= false;
7751 switch (OMP_CLAUSE_CODE (c
))
7753 case OMP_CLAUSE_PRIVATE
:
7754 case OMP_CLAUSE_SHARED
:
7755 case OMP_CLAUSE_FIRSTPRIVATE
:
7756 case OMP_CLAUSE_LINEAR
:
7757 decl
= OMP_CLAUSE_DECL (c
);
7758 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
7759 remove
= !(n
->value
& GOVD_SEEN
);
7762 bool shared
= OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_SHARED
;
7763 if ((n
->value
& GOVD_DEBUG_PRIVATE
)
7764 || lang_hooks
.decls
.omp_private_debug_clause (decl
, shared
))
7766 gcc_assert ((n
->value
& GOVD_DEBUG_PRIVATE
) == 0
7767 || ((n
->value
& GOVD_DATA_SHARE_CLASS
)
7769 OMP_CLAUSE_SET_CODE (c
, OMP_CLAUSE_PRIVATE
);
7770 OMP_CLAUSE_PRIVATE_DEBUG (c
) = 1;
7772 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_SHARED
7773 && (n
->value
& GOVD_WRITTEN
) == 0
7775 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
7776 OMP_CLAUSE_SHARED_READONLY (c
) = 1;
7777 else if (DECL_P (decl
)
7778 && ((OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_SHARED
7779 && (n
->value
& GOVD_WRITTEN
) != 1)
7780 || (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LINEAR
7781 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c
)))
7782 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
7783 omp_mark_stores (gimplify_omp_ctxp
->outer_context
, decl
);
7787 case OMP_CLAUSE_LASTPRIVATE
:
7788 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
7789 accurately reflect the presence of a FIRSTPRIVATE clause. */
7790 decl
= OMP_CLAUSE_DECL (c
);
7791 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
7792 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c
)
7793 = (n
->value
& GOVD_FIRSTPRIVATE
) != 0;
7794 if (omp_no_lastprivate (ctx
))
7796 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c
))
7799 OMP_CLAUSE_CODE (c
) = OMP_CLAUSE_PRIVATE
;
7801 else if (code
== OMP_DISTRIBUTE
7802 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c
))
7805 error_at (OMP_CLAUSE_LOCATION (c
),
7806 "same variable used in %<firstprivate%> and "
7807 "%<lastprivate%> clauses on %<distribute%> "
7811 && OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LASTPRIVATE
7813 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
7814 omp_mark_stores (gimplify_omp_ctxp
->outer_context
, decl
);
7817 case OMP_CLAUSE_ALIGNED
:
7818 decl
= OMP_CLAUSE_DECL (c
);
7819 if (!is_global_var (decl
))
7821 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
7822 remove
= n
== NULL
|| !(n
->value
& GOVD_SEEN
);
7823 if (!remove
&& TREE_CODE (TREE_TYPE (decl
)) == POINTER_TYPE
)
7825 struct gimplify_omp_ctx
*octx
;
7827 && (n
->value
& (GOVD_DATA_SHARE_CLASS
7828 & ~GOVD_FIRSTPRIVATE
)))
7831 for (octx
= ctx
->outer_context
; octx
;
7832 octx
= octx
->outer_context
)
7834 n
= splay_tree_lookup (octx
->variables
,
7835 (splay_tree_key
) decl
);
7838 if (n
->value
& GOVD_LOCAL
)
7840 /* We have to avoid assigning a shared variable
7841 to itself when trying to add
7842 __builtin_assume_aligned. */
7843 if (n
->value
& GOVD_SHARED
)
7851 else if (TREE_CODE (TREE_TYPE (decl
)) == ARRAY_TYPE
)
7853 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
7854 if (n
!= NULL
&& (n
->value
& GOVD_DATA_SHARE_CLASS
) != 0)
7859 case OMP_CLAUSE_MAP
:
7860 if (code
== OMP_TARGET_EXIT_DATA
7861 && OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_ALWAYS_POINTER
)
7866 decl
= OMP_CLAUSE_DECL (c
);
7869 if ((ctx
->region_type
& ORT_TARGET
) != 0
7870 && OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_FIRSTPRIVATE_POINTER
)
7872 if (TREE_CODE (decl
) == INDIRECT_REF
7873 && TREE_CODE (TREE_OPERAND (decl
, 0)) == COMPONENT_REF
7874 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl
, 0)))
7876 decl
= TREE_OPERAND (decl
, 0);
7877 if (TREE_CODE (decl
) == COMPONENT_REF
)
7879 while (TREE_CODE (decl
) == COMPONENT_REF
)
7880 decl
= TREE_OPERAND (decl
, 0);
7883 n
= splay_tree_lookup (ctx
->variables
,
7884 (splay_tree_key
) decl
);
7885 if (!(n
->value
& GOVD_SEEN
))
7892 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
7893 if ((ctx
->region_type
& ORT_TARGET
) != 0
7894 && !(n
->value
& GOVD_SEEN
)
7895 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c
)) == 0)
7898 /* For struct element mapping, if struct is never referenced
7899 in target block and none of the mapping has always modifier,
7900 remove all the struct element mappings, which immediately
7901 follow the GOMP_MAP_STRUCT map clause. */
7902 if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_STRUCT
)
7904 HOST_WIDE_INT cnt
= tree_to_shwi (OMP_CLAUSE_SIZE (c
));
7906 OMP_CLAUSE_CHAIN (c
)
7907 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c
));
7910 else if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_STRUCT
7911 && code
== OMP_TARGET_EXIT_DATA
)
7913 else if (DECL_SIZE (decl
)
7914 && TREE_CODE (DECL_SIZE (decl
)) != INTEGER_CST
7915 && OMP_CLAUSE_MAP_KIND (c
) != GOMP_MAP_POINTER
7916 && OMP_CLAUSE_MAP_KIND (c
) != GOMP_MAP_FIRSTPRIVATE_POINTER
7917 && (OMP_CLAUSE_MAP_KIND (c
)
7918 != GOMP_MAP_FIRSTPRIVATE_REFERENCE
))
7920 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
7921 for these, TREE_CODE (DECL_SIZE (decl)) will always be
7923 gcc_assert (OMP_CLAUSE_MAP_KIND (c
) != GOMP_MAP_FORCE_DEVICEPTR
);
7925 tree decl2
= DECL_VALUE_EXPR (decl
);
7926 gcc_assert (TREE_CODE (decl2
) == INDIRECT_REF
);
7927 decl2
= TREE_OPERAND (decl2
, 0);
7928 gcc_assert (DECL_P (decl2
));
7929 tree mem
= build_simple_mem_ref (decl2
);
7930 OMP_CLAUSE_DECL (c
) = mem
;
7931 OMP_CLAUSE_SIZE (c
) = TYPE_SIZE_UNIT (TREE_TYPE (decl
));
7932 if (ctx
->outer_context
)
7934 omp_notice_variable (ctx
->outer_context
, decl2
, true);
7935 omp_notice_variable (ctx
->outer_context
,
7936 OMP_CLAUSE_SIZE (c
), true);
7938 if (((ctx
->region_type
& ORT_TARGET
) != 0
7939 || !ctx
->target_firstprivatize_array_bases
)
7940 && ((n
->value
& GOVD_SEEN
) == 0
7941 || (n
->value
& (GOVD_PRIVATE
| GOVD_FIRSTPRIVATE
)) == 0))
7943 tree nc
= build_omp_clause (OMP_CLAUSE_LOCATION (c
),
7945 OMP_CLAUSE_DECL (nc
) = decl
;
7946 OMP_CLAUSE_SIZE (nc
) = size_zero_node
;
7947 if (ctx
->target_firstprivatize_array_bases
)
7948 OMP_CLAUSE_SET_MAP_KIND (nc
,
7949 GOMP_MAP_FIRSTPRIVATE_POINTER
);
7951 OMP_CLAUSE_SET_MAP_KIND (nc
, GOMP_MAP_POINTER
);
7952 OMP_CLAUSE_CHAIN (nc
) = OMP_CLAUSE_CHAIN (c
);
7953 OMP_CLAUSE_CHAIN (c
) = nc
;
7959 if (OMP_CLAUSE_SIZE (c
) == NULL_TREE
)
7960 OMP_CLAUSE_SIZE (c
) = DECL_SIZE_UNIT (decl
);
7961 gcc_assert ((n
->value
& GOVD_SEEN
) == 0
7962 || ((n
->value
& (GOVD_PRIVATE
| GOVD_FIRSTPRIVATE
))
7968 case OMP_CLAUSE_FROM
:
7969 case OMP_CLAUSE__CACHE_
:
7970 decl
= OMP_CLAUSE_DECL (c
);
7973 if (DECL_SIZE (decl
)
7974 && TREE_CODE (DECL_SIZE (decl
)) != INTEGER_CST
)
7976 tree decl2
= DECL_VALUE_EXPR (decl
);
7977 gcc_assert (TREE_CODE (decl2
) == INDIRECT_REF
);
7978 decl2
= TREE_OPERAND (decl2
, 0);
7979 gcc_assert (DECL_P (decl2
));
7980 tree mem
= build_simple_mem_ref (decl2
);
7981 OMP_CLAUSE_DECL (c
) = mem
;
7982 OMP_CLAUSE_SIZE (c
) = TYPE_SIZE_UNIT (TREE_TYPE (decl
));
7983 if (ctx
->outer_context
)
7985 omp_notice_variable (ctx
->outer_context
, decl2
, true);
7986 omp_notice_variable (ctx
->outer_context
,
7987 OMP_CLAUSE_SIZE (c
), true);
7990 else if (OMP_CLAUSE_SIZE (c
) == NULL_TREE
)
7991 OMP_CLAUSE_SIZE (c
) = DECL_SIZE_UNIT (decl
);
7994 case OMP_CLAUSE_REDUCTION
:
7995 decl
= OMP_CLAUSE_DECL (c
);
7997 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
7998 omp_mark_stores (gimplify_omp_ctxp
->outer_context
, decl
);
8000 case OMP_CLAUSE_COPYIN
:
8001 case OMP_CLAUSE_COPYPRIVATE
:
8003 case OMP_CLAUSE_NUM_THREADS
:
8004 case OMP_CLAUSE_NUM_TEAMS
:
8005 case OMP_CLAUSE_THREAD_LIMIT
:
8006 case OMP_CLAUSE_DIST_SCHEDULE
:
8007 case OMP_CLAUSE_DEVICE
:
8008 case OMP_CLAUSE_SCHEDULE
:
8009 case OMP_CLAUSE_NOWAIT
:
8010 case OMP_CLAUSE_ORDERED
:
8011 case OMP_CLAUSE_DEFAULT
:
8012 case OMP_CLAUSE_UNTIED
:
8013 case OMP_CLAUSE_COLLAPSE
:
8014 case OMP_CLAUSE_FINAL
:
8015 case OMP_CLAUSE_MERGEABLE
:
8016 case OMP_CLAUSE_PROC_BIND
:
8017 case OMP_CLAUSE_SAFELEN
:
8018 case OMP_CLAUSE_SIMDLEN
:
8019 case OMP_CLAUSE_DEPEND
:
8020 case OMP_CLAUSE_PRIORITY
:
8021 case OMP_CLAUSE_GRAINSIZE
:
8022 case OMP_CLAUSE_NUM_TASKS
:
8023 case OMP_CLAUSE_NOGROUP
:
8024 case OMP_CLAUSE_THREADS
:
8025 case OMP_CLAUSE_SIMD
:
8026 case OMP_CLAUSE_HINT
:
8027 case OMP_CLAUSE_DEFAULTMAP
:
8028 case OMP_CLAUSE_USE_DEVICE_PTR
:
8029 case OMP_CLAUSE_IS_DEVICE_PTR
:
8030 case OMP_CLAUSE__CILK_FOR_COUNT_
:
8031 case OMP_CLAUSE_ASYNC
:
8032 case OMP_CLAUSE_WAIT
:
8033 case OMP_CLAUSE_DEVICE_RESIDENT
:
8034 case OMP_CLAUSE_USE_DEVICE
:
8035 case OMP_CLAUSE_INDEPENDENT
:
8036 case OMP_CLAUSE_NUM_GANGS
:
8037 case OMP_CLAUSE_NUM_WORKERS
:
8038 case OMP_CLAUSE_VECTOR_LENGTH
:
8039 case OMP_CLAUSE_GANG
:
8040 case OMP_CLAUSE_WORKER
:
8041 case OMP_CLAUSE_VECTOR
:
8042 case OMP_CLAUSE_AUTO
:
8043 case OMP_CLAUSE_SEQ
:
8044 case OMP_CLAUSE_TILE
:
8052 *list_p
= OMP_CLAUSE_CHAIN (c
);
8054 list_p
= &OMP_CLAUSE_CHAIN (c
);
8057 /* Add in any implicit data sharing. */
8058 struct gimplify_adjust_omp_clauses_data data
;
8059 data
.list_p
= list_p
;
8061 splay_tree_foreach (ctx
->variables
, gimplify_adjust_omp_clauses_1
, &data
);
8063 gimplify_omp_ctxp
= ctx
->outer_context
;
8064 delete_omp_context (ctx
);
8067 /* Gimplify OACC_CACHE. */
8070 gimplify_oacc_cache (tree
*expr_p
, gimple_seq
*pre_p
)
8072 tree expr
= *expr_p
;
8074 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr
), pre_p
, ORT_ACC
,
8076 gimplify_adjust_omp_clauses (pre_p
, NULL
, &OACC_CACHE_CLAUSES (expr
),
8079 /* TODO: Do something sensible with this information. */
8081 *expr_p
= NULL_TREE
;
8084 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
8085 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
8086 kind. The entry kind will replace the one in CLAUSE, while the exit
8087 kind will be used in a new omp_clause and returned to the caller. */
8090 gimplify_oacc_declare_1 (tree clause
)
8092 HOST_WIDE_INT kind
, new_op
;
8096 kind
= OMP_CLAUSE_MAP_KIND (clause
);
8100 case GOMP_MAP_ALLOC
:
8101 case GOMP_MAP_FORCE_ALLOC
:
8102 case GOMP_MAP_FORCE_TO
:
8103 new_op
= GOMP_MAP_FORCE_DEALLOC
;
8107 case GOMP_MAP_FORCE_FROM
:
8108 OMP_CLAUSE_SET_MAP_KIND (clause
, GOMP_MAP_FORCE_ALLOC
);
8109 new_op
= GOMP_MAP_FORCE_FROM
;
8113 case GOMP_MAP_FORCE_TOFROM
:
8114 OMP_CLAUSE_SET_MAP_KIND (clause
, GOMP_MAP_FORCE_TO
);
8115 new_op
= GOMP_MAP_FORCE_FROM
;
8120 OMP_CLAUSE_SET_MAP_KIND (clause
, GOMP_MAP_FORCE_ALLOC
);
8121 new_op
= GOMP_MAP_FROM
;
8125 case GOMP_MAP_TOFROM
:
8126 OMP_CLAUSE_SET_MAP_KIND (clause
, GOMP_MAP_TO
);
8127 new_op
= GOMP_MAP_FROM
;
8131 case GOMP_MAP_DEVICE_RESIDENT
:
8132 case GOMP_MAP_FORCE_DEVICEPTR
:
8133 case GOMP_MAP_FORCE_PRESENT
:
8135 case GOMP_MAP_POINTER
:
8146 c
= build_omp_clause (OMP_CLAUSE_LOCATION (clause
), OMP_CLAUSE_MAP
);
8147 OMP_CLAUSE_SET_MAP_KIND (c
, new_op
);
8148 OMP_CLAUSE_DECL (c
) = OMP_CLAUSE_DECL (clause
);
8154 /* Gimplify OACC_DECLARE. */
8157 gimplify_oacc_declare (tree
*expr_p
, gimple_seq
*pre_p
)
8159 tree expr
= *expr_p
;
8163 clauses
= OACC_DECLARE_CLAUSES (expr
);
8165 gimplify_scan_omp_clauses (&clauses
, pre_p
, ORT_TARGET_DATA
, OACC_DECLARE
);
8167 for (t
= clauses
; t
; t
= OMP_CLAUSE_CHAIN (t
))
8169 tree decl
= OMP_CLAUSE_DECL (t
);
8171 if (TREE_CODE (decl
) == MEM_REF
)
8174 if (TREE_CODE (decl
) == VAR_DECL
8175 && !is_global_var (decl
)
8176 && DECL_CONTEXT (decl
) == current_function_decl
)
8178 tree c
= gimplify_oacc_declare_1 (t
);
8181 if (oacc_declare_returns
== NULL
)
8182 oacc_declare_returns
= new hash_map
<tree
, tree
>;
8184 oacc_declare_returns
->put (decl
, c
);
8188 omp_add_variable (gimplify_omp_ctxp
, decl
, GOVD_SEEN
);
8191 stmt
= gimple_build_omp_target (NULL
, GF_OMP_TARGET_KIND_OACC_DECLARE
,
8194 gimplify_seq_add_stmt (pre_p
, stmt
);
8196 *expr_p
= NULL_TREE
;
8199 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
8200 gimplification of the body, as well as scanning the body for used
8201 variables. We need to do this scan now, because variable-sized
8202 decls will be decomposed during gimplification. */
8205 gimplify_omp_parallel (tree
*expr_p
, gimple_seq
*pre_p
)
8207 tree expr
= *expr_p
;
8209 gimple_seq body
= NULL
;
8211 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr
), pre_p
,
8212 OMP_PARALLEL_COMBINED (expr
)
8213 ? ORT_COMBINED_PARALLEL
8214 : ORT_PARALLEL
, OMP_PARALLEL
);
8216 push_gimplify_context ();
8218 g
= gimplify_and_return_first (OMP_PARALLEL_BODY (expr
), &body
);
8219 if (gimple_code (g
) == GIMPLE_BIND
)
8220 pop_gimplify_context (g
);
8222 pop_gimplify_context (NULL
);
8224 gimplify_adjust_omp_clauses (pre_p
, body
, &OMP_PARALLEL_CLAUSES (expr
),
8227 g
= gimple_build_omp_parallel (body
,
8228 OMP_PARALLEL_CLAUSES (expr
),
8229 NULL_TREE
, NULL_TREE
);
8230 if (OMP_PARALLEL_COMBINED (expr
))
8231 gimple_omp_set_subcode (g
, GF_OMP_PARALLEL_COMBINED
);
8232 gimplify_seq_add_stmt (pre_p
, g
);
8233 *expr_p
= NULL_TREE
;
8236 /* Gimplify the contents of an OMP_TASK statement. This involves
8237 gimplification of the body, as well as scanning the body for used
8238 variables. We need to do this scan now, because variable-sized
8239 decls will be decomposed during gimplification. */
8242 gimplify_omp_task (tree
*expr_p
, gimple_seq
*pre_p
)
8244 tree expr
= *expr_p
;
8246 gimple_seq body
= NULL
;
8248 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr
), pre_p
,
8249 find_omp_clause (OMP_TASK_CLAUSES (expr
),
8251 ? ORT_UNTIED_TASK
: ORT_TASK
, OMP_TASK
);
8253 push_gimplify_context ();
8255 g
= gimplify_and_return_first (OMP_TASK_BODY (expr
), &body
);
8256 if (gimple_code (g
) == GIMPLE_BIND
)
8257 pop_gimplify_context (g
);
8259 pop_gimplify_context (NULL
);
8261 gimplify_adjust_omp_clauses (pre_p
, body
, &OMP_TASK_CLAUSES (expr
),
8264 g
= gimple_build_omp_task (body
,
8265 OMP_TASK_CLAUSES (expr
),
8266 NULL_TREE
, NULL_TREE
,
8267 NULL_TREE
, NULL_TREE
, NULL_TREE
);
8268 gimplify_seq_add_stmt (pre_p
, g
);
8269 *expr_p
= NULL_TREE
;
8272 /* Helper function of gimplify_omp_for, find OMP_FOR resp. OMP_SIMD
8273 with non-NULL OMP_FOR_INIT. */
8276 find_combined_omp_for (tree
*tp
, int *walk_subtrees
, void *)
8279 switch (TREE_CODE (*tp
))
8285 if (OMP_FOR_INIT (*tp
) != NULL_TREE
)
8289 case STATEMENT_LIST
:
8299 /* Gimplify the gross structure of an OMP_FOR statement. */
8301 static enum gimplify_status
8302 gimplify_omp_for (tree
*expr_p
, gimple_seq
*pre_p
)
8304 tree for_stmt
, orig_for_stmt
, inner_for_stmt
= NULL_TREE
, decl
, var
, t
;
8305 enum gimplify_status ret
= GS_ALL_DONE
;
8306 enum gimplify_status tret
;
8308 gimple_seq for_body
, for_pre_body
;
8310 bitmap has_decl_expr
= NULL
;
8311 enum omp_region_type ort
= ORT_WORKSHARE
;
8313 orig_for_stmt
= for_stmt
= *expr_p
;
8315 switch (TREE_CODE (for_stmt
))
8319 case OMP_DISTRIBUTE
:
8325 if (find_omp_clause (OMP_FOR_CLAUSES (for_stmt
), OMP_CLAUSE_UNTIED
))
8326 ort
= ORT_UNTIED_TASK
;
8338 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
8339 clause for the IV. */
8340 if (ort
== ORT_SIMD
&& TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)) == 1)
8342 t
= TREE_VEC_ELT (OMP_FOR_INIT (for_stmt
), 0);
8343 gcc_assert (TREE_CODE (t
) == MODIFY_EXPR
);
8344 decl
= TREE_OPERAND (t
, 0);
8345 for (tree c
= OMP_FOR_CLAUSES (for_stmt
); c
; c
= OMP_CLAUSE_CHAIN (c
))
8346 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LINEAR
8347 && OMP_CLAUSE_DECL (c
) == decl
)
8349 OMP_CLAUSE_LINEAR_NO_COPYIN (c
) = 1;
8354 if (OMP_FOR_INIT (for_stmt
) == NULL_TREE
)
8356 gcc_assert (TREE_CODE (for_stmt
) != OACC_LOOP
);
8357 inner_for_stmt
= walk_tree (&OMP_FOR_BODY (for_stmt
),
8358 find_combined_omp_for
, NULL
, NULL
);
8359 if (inner_for_stmt
== NULL_TREE
)
8361 gcc_assert (seen_error ());
8362 *expr_p
= NULL_TREE
;
8367 if (TREE_CODE (for_stmt
) != OMP_TASKLOOP
)
8368 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt
), pre_p
, ort
,
8369 TREE_CODE (for_stmt
));
8371 if (TREE_CODE (for_stmt
) == OMP_DISTRIBUTE
)
8372 gimplify_omp_ctxp
->distribute
= true;
8374 /* Handle OMP_FOR_INIT. */
8375 for_pre_body
= NULL
;
8376 if (ort
== ORT_SIMD
&& OMP_FOR_PRE_BODY (for_stmt
))
8378 has_decl_expr
= BITMAP_ALLOC (NULL
);
8379 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt
)) == DECL_EXPR
8380 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt
)))
8383 t
= OMP_FOR_PRE_BODY (for_stmt
);
8384 bitmap_set_bit (has_decl_expr
, DECL_UID (DECL_EXPR_DECL (t
)));
8386 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt
)) == STATEMENT_LIST
)
8388 tree_stmt_iterator si
;
8389 for (si
= tsi_start (OMP_FOR_PRE_BODY (for_stmt
)); !tsi_end_p (si
);
8393 if (TREE_CODE (t
) == DECL_EXPR
8394 && TREE_CODE (DECL_EXPR_DECL (t
)) == VAR_DECL
)
8395 bitmap_set_bit (has_decl_expr
, DECL_UID (DECL_EXPR_DECL (t
)));
8399 if (OMP_FOR_PRE_BODY (for_stmt
))
8401 if (TREE_CODE (for_stmt
) != OMP_TASKLOOP
|| gimplify_omp_ctxp
)
8402 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt
), &for_pre_body
);
8405 struct gimplify_omp_ctx ctx
;
8406 memset (&ctx
, 0, sizeof (ctx
));
8407 ctx
.region_type
= ORT_NONE
;
8408 gimplify_omp_ctxp
= &ctx
;
8409 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt
), &for_pre_body
);
8410 gimplify_omp_ctxp
= NULL
;
8413 OMP_FOR_PRE_BODY (for_stmt
) = NULL_TREE
;
8415 if (OMP_FOR_INIT (for_stmt
) == NULL_TREE
)
8416 for_stmt
= inner_for_stmt
;
8418 /* For taskloop, need to gimplify the start, end and step before the
8419 taskloop, outside of the taskloop omp context. */
8420 if (TREE_CODE (orig_for_stmt
) == OMP_TASKLOOP
)
8422 for (i
= 0; i
< TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)); i
++)
8424 t
= TREE_VEC_ELT (OMP_FOR_INIT (for_stmt
), i
);
8425 if (!is_gimple_constant (TREE_OPERAND (t
, 1)))
8428 = get_initialized_tmp_var (TREE_OPERAND (t
, 1),
8430 tree c
= build_omp_clause (input_location
,
8431 OMP_CLAUSE_FIRSTPRIVATE
);
8432 OMP_CLAUSE_DECL (c
) = TREE_OPERAND (t
, 1);
8433 OMP_CLAUSE_CHAIN (c
) = OMP_FOR_CLAUSES (orig_for_stmt
);
8434 OMP_FOR_CLAUSES (orig_for_stmt
) = c
;
8437 /* Handle OMP_FOR_COND. */
8438 t
= TREE_VEC_ELT (OMP_FOR_COND (for_stmt
), i
);
8439 if (!is_gimple_constant (TREE_OPERAND (t
, 1)))
8442 = get_initialized_tmp_var (TREE_OPERAND (t
, 1),
8443 gimple_seq_empty_p (for_pre_body
)
8444 ? pre_p
: &for_pre_body
, NULL
);
8445 tree c
= build_omp_clause (input_location
,
8446 OMP_CLAUSE_FIRSTPRIVATE
);
8447 OMP_CLAUSE_DECL (c
) = TREE_OPERAND (t
, 1);
8448 OMP_CLAUSE_CHAIN (c
) = OMP_FOR_CLAUSES (orig_for_stmt
);
8449 OMP_FOR_CLAUSES (orig_for_stmt
) = c
;
8452 /* Handle OMP_FOR_INCR. */
8453 t
= TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
);
8454 if (TREE_CODE (t
) == MODIFY_EXPR
)
8456 decl
= TREE_OPERAND (t
, 0);
8457 t
= TREE_OPERAND (t
, 1);
8458 tree
*tp
= &TREE_OPERAND (t
, 1);
8459 if (TREE_CODE (t
) == PLUS_EXPR
&& *tp
== decl
)
8460 tp
= &TREE_OPERAND (t
, 0);
8462 if (!is_gimple_constant (*tp
))
8464 gimple_seq
*seq
= gimple_seq_empty_p (for_pre_body
)
8465 ? pre_p
: &for_pre_body
;
8466 *tp
= get_initialized_tmp_var (*tp
, seq
, NULL
);
8467 tree c
= build_omp_clause (input_location
,
8468 OMP_CLAUSE_FIRSTPRIVATE
);
8469 OMP_CLAUSE_DECL (c
) = *tp
;
8470 OMP_CLAUSE_CHAIN (c
) = OMP_FOR_CLAUSES (orig_for_stmt
);
8471 OMP_FOR_CLAUSES (orig_for_stmt
) = c
;
8476 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt
), pre_p
, ort
,
8480 if (orig_for_stmt
!= for_stmt
)
8481 gimplify_omp_ctxp
->combined_loop
= true;
8484 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
))
8485 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt
)));
8486 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
))
8487 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt
)));
8489 tree c
= find_omp_clause (OMP_FOR_CLAUSES (for_stmt
), OMP_CLAUSE_ORDERED
);
8490 bool is_doacross
= false;
8491 if (c
&& OMP_CLAUSE_ORDERED_EXPR (c
))
8494 gimplify_omp_ctxp
->loop_iter_var
.create (TREE_VEC_LENGTH
8495 (OMP_FOR_INIT (for_stmt
))
8499 c
= find_omp_clause (OMP_FOR_CLAUSES (for_stmt
), OMP_CLAUSE_COLLAPSE
);
8501 collapse
= tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c
));
8502 for (i
= 0; i
< TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)); i
++)
8504 t
= TREE_VEC_ELT (OMP_FOR_INIT (for_stmt
), i
);
8505 gcc_assert (TREE_CODE (t
) == MODIFY_EXPR
);
8506 decl
= TREE_OPERAND (t
, 0);
8507 gcc_assert (DECL_P (decl
));
8508 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl
))
8509 || POINTER_TYPE_P (TREE_TYPE (decl
)));
8512 if (TREE_CODE (for_stmt
) == OMP_FOR
&& OMP_FOR_ORIG_DECLS (for_stmt
))
8513 gimplify_omp_ctxp
->loop_iter_var
.quick_push
8514 (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt
), i
));
8516 gimplify_omp_ctxp
->loop_iter_var
.quick_push (decl
);
8517 gimplify_omp_ctxp
->loop_iter_var
.quick_push (decl
);
8520 /* Make sure the iteration variable is private. */
8522 tree c2
= NULL_TREE
;
8523 if (orig_for_stmt
!= for_stmt
)
8524 /* Do this only on innermost construct for combined ones. */;
8525 else if (ort
== ORT_SIMD
)
8527 splay_tree_node n
= splay_tree_lookup (gimplify_omp_ctxp
->variables
,
8528 (splay_tree_key
) decl
);
8529 omp_is_private (gimplify_omp_ctxp
, decl
,
8530 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
))
8532 if (n
!= NULL
&& (n
->value
& GOVD_DATA_SHARE_CLASS
) != 0)
8533 omp_notice_variable (gimplify_omp_ctxp
, decl
, true);
8534 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)) == 1)
8536 c
= build_omp_clause (input_location
, OMP_CLAUSE_LINEAR
);
8537 OMP_CLAUSE_LINEAR_NO_COPYIN (c
) = 1;
8538 unsigned int flags
= GOVD_LINEAR
| GOVD_EXPLICIT
| GOVD_SEEN
;
8540 && bitmap_bit_p (has_decl_expr
, DECL_UID (decl
)))
8541 || omp_no_lastprivate (gimplify_omp_ctxp
))
8543 OMP_CLAUSE_LINEAR_NO_COPYOUT (c
) = 1;
8544 flags
|= GOVD_LINEAR_LASTPRIVATE_NO_OUTER
;
8546 struct gimplify_omp_ctx
*outer
8547 = gimplify_omp_ctxp
->outer_context
;
8548 if (outer
&& !OMP_CLAUSE_LINEAR_NO_COPYOUT (c
))
8550 if (outer
->region_type
== ORT_WORKSHARE
8551 && outer
->combined_loop
)
8553 n
= splay_tree_lookup (outer
->variables
,
8554 (splay_tree_key
)decl
);
8555 if (n
!= NULL
&& (n
->value
& GOVD_LOCAL
) != 0)
8557 OMP_CLAUSE_LINEAR_NO_COPYOUT (c
) = 1;
8558 flags
|= GOVD_LINEAR_LASTPRIVATE_NO_OUTER
;
8562 struct gimplify_omp_ctx
*octx
= outer
->outer_context
;
8564 && octx
->region_type
== ORT_COMBINED_PARALLEL
8565 && octx
->outer_context
8566 && (octx
->outer_context
->region_type
8568 && octx
->outer_context
->combined_loop
)
8570 octx
= octx
->outer_context
;
8571 n
= splay_tree_lookup (octx
->variables
,
8572 (splay_tree_key
)decl
);
8573 if (n
!= NULL
&& (n
->value
& GOVD_LOCAL
) != 0)
8575 OMP_CLAUSE_LINEAR_NO_COPYOUT (c
) = 1;
8576 flags
|= GOVD_LINEAR_LASTPRIVATE_NO_OUTER
;
8583 OMP_CLAUSE_DECL (c
) = decl
;
8584 OMP_CLAUSE_CHAIN (c
) = OMP_FOR_CLAUSES (for_stmt
);
8585 OMP_FOR_CLAUSES (for_stmt
) = c
;
8586 omp_add_variable (gimplify_omp_ctxp
, decl
, flags
);
8587 if (outer
&& !OMP_CLAUSE_LINEAR_NO_COPYOUT (c
))
8589 if (outer
->region_type
== ORT_WORKSHARE
8590 && outer
->combined_loop
)
8592 if (outer
->outer_context
8593 && (outer
->outer_context
->region_type
8594 == ORT_COMBINED_PARALLEL
))
8595 outer
= outer
->outer_context
;
8596 else if (omp_check_private (outer
, decl
, false))
8599 else if (((outer
->region_type
& ORT_TASK
) != 0)
8600 && outer
->combined_loop
8601 && !omp_check_private (gimplify_omp_ctxp
,
8604 else if (outer
->region_type
!= ORT_COMBINED_PARALLEL
)
8608 n
= splay_tree_lookup (outer
->variables
,
8609 (splay_tree_key
)decl
);
8610 if (n
== NULL
|| (n
->value
& GOVD_DATA_SHARE_CLASS
) == 0)
8612 omp_add_variable (outer
, decl
,
8613 GOVD_LASTPRIVATE
| GOVD_SEEN
);
8614 if (outer
->region_type
== ORT_COMBINED_PARALLEL
8615 && outer
->outer_context
8616 && (outer
->outer_context
->region_type
8618 && outer
->outer_context
->combined_loop
)
8620 outer
= outer
->outer_context
;
8621 n
= splay_tree_lookup (outer
->variables
,
8622 (splay_tree_key
)decl
);
8623 if (omp_check_private (outer
, decl
, false))
8626 || ((n
->value
& GOVD_DATA_SHARE_CLASS
)
8628 omp_add_variable (outer
, decl
,
8634 if (outer
&& outer
->outer_context
8635 && (outer
->outer_context
->region_type
8636 == ORT_COMBINED_TEAMS
))
8638 outer
= outer
->outer_context
;
8639 n
= splay_tree_lookup (outer
->variables
,
8640 (splay_tree_key
)decl
);
8642 || (n
->value
& GOVD_DATA_SHARE_CLASS
) == 0)
8643 omp_add_variable (outer
, decl
,
8644 GOVD_SHARED
| GOVD_SEEN
);
8648 if (outer
&& outer
->outer_context
)
8649 omp_notice_variable (outer
->outer_context
, decl
,
8659 || !bitmap_bit_p (has_decl_expr
, DECL_UID (decl
)))
8660 && !omp_no_lastprivate (gimplify_omp_ctxp
);
8661 struct gimplify_omp_ctx
*outer
8662 = gimplify_omp_ctxp
->outer_context
;
8663 if (outer
&& lastprivate
)
8665 if (outer
->region_type
== ORT_WORKSHARE
8666 && outer
->combined_loop
)
8668 n
= splay_tree_lookup (outer
->variables
,
8669 (splay_tree_key
)decl
);
8670 if (n
!= NULL
&& (n
->value
& GOVD_LOCAL
) != 0)
8672 lastprivate
= false;
8675 else if (outer
->outer_context
8676 && (outer
->outer_context
->region_type
8677 == ORT_COMBINED_PARALLEL
))
8678 outer
= outer
->outer_context
;
8679 else if (omp_check_private (outer
, decl
, false))
8682 else if (((outer
->region_type
& ORT_TASK
) != 0)
8683 && outer
->combined_loop
8684 && !omp_check_private (gimplify_omp_ctxp
,
8687 else if (outer
->region_type
!= ORT_COMBINED_PARALLEL
)
8691 n
= splay_tree_lookup (outer
->variables
,
8692 (splay_tree_key
)decl
);
8693 if (n
== NULL
|| (n
->value
& GOVD_DATA_SHARE_CLASS
) == 0)
8695 omp_add_variable (outer
, decl
,
8696 GOVD_LASTPRIVATE
| GOVD_SEEN
);
8697 if (outer
->region_type
== ORT_COMBINED_PARALLEL
8698 && outer
->outer_context
8699 && (outer
->outer_context
->region_type
8701 && outer
->outer_context
->combined_loop
)
8703 outer
= outer
->outer_context
;
8704 n
= splay_tree_lookup (outer
->variables
,
8705 (splay_tree_key
)decl
);
8706 if (omp_check_private (outer
, decl
, false))
8709 || ((n
->value
& GOVD_DATA_SHARE_CLASS
)
8711 omp_add_variable (outer
, decl
,
8717 if (outer
&& outer
->outer_context
8718 && (outer
->outer_context
->region_type
8719 == ORT_COMBINED_TEAMS
))
8721 outer
= outer
->outer_context
;
8722 n
= splay_tree_lookup (outer
->variables
,
8723 (splay_tree_key
)decl
);
8725 || (n
->value
& GOVD_DATA_SHARE_CLASS
) == 0)
8726 omp_add_variable (outer
, decl
,
8727 GOVD_SHARED
| GOVD_SEEN
);
8731 if (outer
&& outer
->outer_context
)
8732 omp_notice_variable (outer
->outer_context
, decl
,
8738 c
= build_omp_clause (input_location
,
8739 lastprivate
? OMP_CLAUSE_LASTPRIVATE
8740 : OMP_CLAUSE_PRIVATE
);
8741 OMP_CLAUSE_DECL (c
) = decl
;
8742 OMP_CLAUSE_CHAIN (c
) = OMP_FOR_CLAUSES (for_stmt
);
8743 OMP_FOR_CLAUSES (for_stmt
) = c
;
8744 omp_add_variable (gimplify_omp_ctxp
, decl
,
8745 (lastprivate
? GOVD_LASTPRIVATE
: GOVD_PRIVATE
)
8746 | GOVD_EXPLICIT
| GOVD_SEEN
);
8750 else if (omp_is_private (gimplify_omp_ctxp
, decl
, 0))
8751 omp_notice_variable (gimplify_omp_ctxp
, decl
, true);
8753 omp_add_variable (gimplify_omp_ctxp
, decl
, GOVD_PRIVATE
| GOVD_SEEN
);
8755 /* If DECL is not a gimple register, create a temporary variable to act
8756 as an iteration counter. This is valid, since DECL cannot be
8757 modified in the body of the loop. Similarly for any iteration vars
8758 in simd with collapse > 1 where the iterator vars must be
8760 if (orig_for_stmt
!= for_stmt
)
8762 else if (!is_gimple_reg (decl
)
8764 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)) > 1))
8766 var
= create_tmp_var (TREE_TYPE (decl
), get_name (decl
));
8767 TREE_OPERAND (t
, 0) = var
;
8769 gimplify_seq_add_stmt (&for_body
, gimple_build_assign (decl
, var
));
8772 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)) == 1)
8774 c2
= build_omp_clause (input_location
, OMP_CLAUSE_LINEAR
);
8775 OMP_CLAUSE_LINEAR_NO_COPYIN (c2
) = 1;
8776 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2
) = 1;
8777 OMP_CLAUSE_DECL (c2
) = var
;
8778 OMP_CLAUSE_CHAIN (c2
) = OMP_FOR_CLAUSES (for_stmt
);
8779 OMP_FOR_CLAUSES (for_stmt
) = c2
;
8780 omp_add_variable (gimplify_omp_ctxp
, var
,
8781 GOVD_LINEAR
| GOVD_EXPLICIT
| GOVD_SEEN
);
8789 omp_add_variable (gimplify_omp_ctxp
, var
,
8790 GOVD_PRIVATE
| GOVD_SEEN
);
8795 tret
= gimplify_expr (&TREE_OPERAND (t
, 1), &for_pre_body
, NULL
,
8796 is_gimple_val
, fb_rvalue
);
8797 ret
= MIN (ret
, tret
);
8798 if (ret
== GS_ERROR
)
8801 /* Handle OMP_FOR_COND. */
8802 t
= TREE_VEC_ELT (OMP_FOR_COND (for_stmt
), i
);
8803 gcc_assert (COMPARISON_CLASS_P (t
));
8804 gcc_assert (TREE_OPERAND (t
, 0) == decl
);
8806 tret
= gimplify_expr (&TREE_OPERAND (t
, 1), &for_pre_body
, NULL
,
8807 is_gimple_val
, fb_rvalue
);
8808 ret
= MIN (ret
, tret
);
8810 /* Handle OMP_FOR_INCR. */
8811 t
= TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
);
8812 switch (TREE_CODE (t
))
8814 case PREINCREMENT_EXPR
:
8815 case POSTINCREMENT_EXPR
:
8817 tree decl
= TREE_OPERAND (t
, 0);
8818 /* c_omp_for_incr_canonicalize_ptr() should have been
8819 called to massage things appropriately. */
8820 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl
)));
8822 if (orig_for_stmt
!= for_stmt
)
8824 t
= build_int_cst (TREE_TYPE (decl
), 1);
8826 OMP_CLAUSE_LINEAR_STEP (c
) = t
;
8827 t
= build2 (PLUS_EXPR
, TREE_TYPE (decl
), var
, t
);
8828 t
= build2 (MODIFY_EXPR
, TREE_TYPE (var
), var
, t
);
8829 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
) = t
;
8833 case PREDECREMENT_EXPR
:
8834 case POSTDECREMENT_EXPR
:
8835 /* c_omp_for_incr_canonicalize_ptr() should have been
8836 called to massage things appropriately. */
8837 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl
)));
8838 if (orig_for_stmt
!= for_stmt
)
8840 t
= build_int_cst (TREE_TYPE (decl
), -1);
8842 OMP_CLAUSE_LINEAR_STEP (c
) = t
;
8843 t
= build2 (PLUS_EXPR
, TREE_TYPE (decl
), var
, t
);
8844 t
= build2 (MODIFY_EXPR
, TREE_TYPE (var
), var
, t
);
8845 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
) = t
;
8849 gcc_assert (TREE_OPERAND (t
, 0) == decl
);
8850 TREE_OPERAND (t
, 0) = var
;
8852 t
= TREE_OPERAND (t
, 1);
8853 switch (TREE_CODE (t
))
8856 if (TREE_OPERAND (t
, 1) == decl
)
8858 TREE_OPERAND (t
, 1) = TREE_OPERAND (t
, 0);
8859 TREE_OPERAND (t
, 0) = var
;
8865 case POINTER_PLUS_EXPR
:
8866 gcc_assert (TREE_OPERAND (t
, 0) == decl
);
8867 TREE_OPERAND (t
, 0) = var
;
8873 tret
= gimplify_expr (&TREE_OPERAND (t
, 1), &for_pre_body
, NULL
,
8874 is_gimple_val
, fb_rvalue
);
8875 ret
= MIN (ret
, tret
);
8878 tree step
= TREE_OPERAND (t
, 1);
8879 tree stept
= TREE_TYPE (decl
);
8880 if (POINTER_TYPE_P (stept
))
8882 step
= fold_convert (stept
, step
);
8883 if (TREE_CODE (t
) == MINUS_EXPR
)
8884 step
= fold_build1 (NEGATE_EXPR
, stept
, step
);
8885 OMP_CLAUSE_LINEAR_STEP (c
) = step
;
8886 if (step
!= TREE_OPERAND (t
, 1))
8888 tret
= gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c
),
8889 &for_pre_body
, NULL
,
8890 is_gimple_val
, fb_rvalue
);
8891 ret
= MIN (ret
, tret
);
8903 OMP_CLAUSE_LINEAR_STEP (c2
) = OMP_CLAUSE_LINEAR_STEP (c
);
8906 if ((var
!= decl
|| collapse
> 1) && orig_for_stmt
== for_stmt
)
8908 for (c
= OMP_FOR_CLAUSES (for_stmt
); c
; c
= OMP_CLAUSE_CHAIN (c
))
8909 if (((OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LASTPRIVATE
8910 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c
) == NULL
)
8911 || (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LINEAR
8912 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c
)
8913 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c
) == NULL
))
8914 && OMP_CLAUSE_DECL (c
) == decl
)
8916 if (is_doacross
&& (collapse
== 1 || i
>= collapse
))
8920 t
= TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
);
8921 gcc_assert (TREE_CODE (t
) == MODIFY_EXPR
);
8922 gcc_assert (TREE_OPERAND (t
, 0) == var
);
8923 t
= TREE_OPERAND (t
, 1);
8924 gcc_assert (TREE_CODE (t
) == PLUS_EXPR
8925 || TREE_CODE (t
) == MINUS_EXPR
8926 || TREE_CODE (t
) == POINTER_PLUS_EXPR
);
8927 gcc_assert (TREE_OPERAND (t
, 0) == var
);
8928 t
= build2 (TREE_CODE (t
), TREE_TYPE (decl
),
8929 is_doacross
? var
: decl
,
8930 TREE_OPERAND (t
, 1));
8933 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LASTPRIVATE
)
8934 seq
= &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c
);
8936 seq
= &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c
);
8937 gimplify_assign (decl
, t
, seq
);
8942 BITMAP_FREE (has_decl_expr
);
8944 if (TREE_CODE (orig_for_stmt
) == OMP_TASKLOOP
)
8946 push_gimplify_context ();
8947 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt
)) != BIND_EXPR
)
8949 OMP_FOR_BODY (orig_for_stmt
)
8950 = build3 (BIND_EXPR
, void_type_node
, NULL
,
8951 OMP_FOR_BODY (orig_for_stmt
), NULL
);
8952 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt
)) = 1;
8956 gimple
*g
= gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt
),
8959 if (TREE_CODE (orig_for_stmt
) == OMP_TASKLOOP
)
8961 if (gimple_code (g
) == GIMPLE_BIND
)
8962 pop_gimplify_context (g
);
8964 pop_gimplify_context (NULL
);
8967 if (orig_for_stmt
!= for_stmt
)
8968 for (i
= 0; i
< TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)); i
++)
8970 t
= TREE_VEC_ELT (OMP_FOR_INIT (for_stmt
), i
);
8971 decl
= TREE_OPERAND (t
, 0);
8972 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
8973 if (TREE_CODE (orig_for_stmt
) == OMP_TASKLOOP
)
8974 gimplify_omp_ctxp
= ctx
->outer_context
;
8975 var
= create_tmp_var (TREE_TYPE (decl
), get_name (decl
));
8976 gimplify_omp_ctxp
= ctx
;
8977 omp_add_variable (gimplify_omp_ctxp
, var
, GOVD_PRIVATE
| GOVD_SEEN
);
8978 TREE_OPERAND (t
, 0) = var
;
8979 t
= TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
);
8980 TREE_OPERAND (t
, 1) = copy_node (TREE_OPERAND (t
, 1));
8981 TREE_OPERAND (TREE_OPERAND (t
, 1), 0) = var
;
8984 gimplify_adjust_omp_clauses (pre_p
, for_body
,
8985 &OMP_FOR_CLAUSES (orig_for_stmt
),
8986 TREE_CODE (orig_for_stmt
));
8989 switch (TREE_CODE (orig_for_stmt
))
8991 case OMP_FOR
: kind
= GF_OMP_FOR_KIND_FOR
; break;
8992 case OMP_SIMD
: kind
= GF_OMP_FOR_KIND_SIMD
; break;
8993 case CILK_SIMD
: kind
= GF_OMP_FOR_KIND_CILKSIMD
; break;
8994 case CILK_FOR
: kind
= GF_OMP_FOR_KIND_CILKFOR
; break;
8995 case OMP_DISTRIBUTE
: kind
= GF_OMP_FOR_KIND_DISTRIBUTE
; break;
8996 case OMP_TASKLOOP
: kind
= GF_OMP_FOR_KIND_TASKLOOP
; break;
8997 case OACC_LOOP
: kind
= GF_OMP_FOR_KIND_OACC_LOOP
; break;
9001 gfor
= gimple_build_omp_for (for_body
, kind
, OMP_FOR_CLAUSES (orig_for_stmt
),
9002 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)),
9004 if (orig_for_stmt
!= for_stmt
)
9005 gimple_omp_for_set_combined_p (gfor
, true);
9006 if (gimplify_omp_ctxp
9007 && (gimplify_omp_ctxp
->combined_loop
9008 || (gimplify_omp_ctxp
->region_type
== ORT_COMBINED_PARALLEL
9009 && gimplify_omp_ctxp
->outer_context
9010 && gimplify_omp_ctxp
->outer_context
->combined_loop
)))
9012 gimple_omp_for_set_combined_into_p (gfor
, true);
9013 if (gimplify_omp_ctxp
->combined_loop
)
9014 gcc_assert (TREE_CODE (orig_for_stmt
) == OMP_SIMD
);
9016 gcc_assert (TREE_CODE (orig_for_stmt
) == OMP_FOR
);
9019 for (i
= 0; i
< TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)); i
++)
9021 t
= TREE_VEC_ELT (OMP_FOR_INIT (for_stmt
), i
);
9022 gimple_omp_for_set_index (gfor
, i
, TREE_OPERAND (t
, 0));
9023 gimple_omp_for_set_initial (gfor
, i
, TREE_OPERAND (t
, 1));
9024 t
= TREE_VEC_ELT (OMP_FOR_COND (for_stmt
), i
);
9025 gimple_omp_for_set_cond (gfor
, i
, TREE_CODE (t
));
9026 gimple_omp_for_set_final (gfor
, i
, TREE_OPERAND (t
, 1));
9027 t
= TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
);
9028 gimple_omp_for_set_incr (gfor
, i
, TREE_OPERAND (t
, 1));
9031 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
9032 constructs with GIMPLE_OMP_TASK sandwiched in between them.
9033 The outer taskloop stands for computing the number of iterations,
9034 counts for collapsed loops and holding taskloop specific clauses.
9035 The task construct stands for the effect of data sharing on the
9036 explicit task it creates and the inner taskloop stands for expansion
9037 of the static loop inside of the explicit task construct. */
9038 if (TREE_CODE (orig_for_stmt
) == OMP_TASKLOOP
)
9040 tree
*gfor_clauses_ptr
= gimple_omp_for_clauses_ptr (gfor
);
9041 tree task_clauses
= NULL_TREE
;
9042 tree c
= *gfor_clauses_ptr
;
9043 tree
*gtask_clauses_ptr
= &task_clauses
;
9044 tree outer_for_clauses
= NULL_TREE
;
9045 tree
*gforo_clauses_ptr
= &outer_for_clauses
;
9046 for (; c
; c
= OMP_CLAUSE_CHAIN (c
))
9047 switch (OMP_CLAUSE_CODE (c
))
9049 /* These clauses are allowed on task, move them there. */
9050 case OMP_CLAUSE_SHARED
:
9051 case OMP_CLAUSE_FIRSTPRIVATE
:
9052 case OMP_CLAUSE_DEFAULT
:
9054 case OMP_CLAUSE_UNTIED
:
9055 case OMP_CLAUSE_FINAL
:
9056 case OMP_CLAUSE_MERGEABLE
:
9057 case OMP_CLAUSE_PRIORITY
:
9058 *gtask_clauses_ptr
= c
;
9059 gtask_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9061 case OMP_CLAUSE_PRIVATE
:
9062 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c
))
9064 /* We want private on outer for and firstprivate
9067 = build_omp_clause (OMP_CLAUSE_LOCATION (c
),
9068 OMP_CLAUSE_FIRSTPRIVATE
);
9069 OMP_CLAUSE_DECL (*gtask_clauses_ptr
) = OMP_CLAUSE_DECL (c
);
9070 lang_hooks
.decls
.omp_finish_clause (*gtask_clauses_ptr
, NULL
);
9071 gtask_clauses_ptr
= &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr
);
9072 *gforo_clauses_ptr
= c
;
9073 gforo_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9077 *gtask_clauses_ptr
= c
;
9078 gtask_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9081 /* These clauses go into outer taskloop clauses. */
9082 case OMP_CLAUSE_GRAINSIZE
:
9083 case OMP_CLAUSE_NUM_TASKS
:
9084 case OMP_CLAUSE_NOGROUP
:
9085 *gforo_clauses_ptr
= c
;
9086 gforo_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9088 /* Taskloop clause we duplicate on both taskloops. */
9089 case OMP_CLAUSE_COLLAPSE
:
9090 *gfor_clauses_ptr
= c
;
9091 gfor_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9092 *gforo_clauses_ptr
= copy_node (c
);
9093 gforo_clauses_ptr
= &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr
);
9095 /* For lastprivate, keep the clause on inner taskloop, and add
9096 a shared clause on task. If the same decl is also firstprivate,
9097 add also firstprivate clause on the inner taskloop. */
9098 case OMP_CLAUSE_LASTPRIVATE
:
9099 if (OMP_CLAUSE_LASTPRIVATE_TASKLOOP_IV (c
))
9101 /* For taskloop C++ lastprivate IVs, we want:
9102 1) private on outer taskloop
9103 2) firstprivate and shared on task
9104 3) lastprivate on inner taskloop */
9106 = build_omp_clause (OMP_CLAUSE_LOCATION (c
),
9107 OMP_CLAUSE_FIRSTPRIVATE
);
9108 OMP_CLAUSE_DECL (*gtask_clauses_ptr
) = OMP_CLAUSE_DECL (c
);
9109 lang_hooks
.decls
.omp_finish_clause (*gtask_clauses_ptr
, NULL
);
9110 gtask_clauses_ptr
= &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr
);
9111 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c
) = 1;
9112 *gforo_clauses_ptr
= build_omp_clause (OMP_CLAUSE_LOCATION (c
),
9113 OMP_CLAUSE_PRIVATE
);
9114 OMP_CLAUSE_DECL (*gforo_clauses_ptr
) = OMP_CLAUSE_DECL (c
);
9115 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr
) = 1;
9116 TREE_TYPE (*gforo_clauses_ptr
) = TREE_TYPE (c
);
9117 gforo_clauses_ptr
= &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr
);
9119 *gfor_clauses_ptr
= c
;
9120 gfor_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9122 = build_omp_clause (OMP_CLAUSE_LOCATION (c
), OMP_CLAUSE_SHARED
);
9123 OMP_CLAUSE_DECL (*gtask_clauses_ptr
) = OMP_CLAUSE_DECL (c
);
9124 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c
))
9125 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr
) = 1;
9127 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr
);
9132 *gfor_clauses_ptr
= NULL_TREE
;
9133 *gtask_clauses_ptr
= NULL_TREE
;
9134 *gforo_clauses_ptr
= NULL_TREE
;
9135 g
= gimple_build_bind (NULL_TREE
, gfor
, NULL_TREE
);
9136 g
= gimple_build_omp_task (g
, task_clauses
, NULL_TREE
, NULL_TREE
,
9137 NULL_TREE
, NULL_TREE
, NULL_TREE
);
9138 gimple_omp_task_set_taskloop_p (g
, true);
9139 g
= gimple_build_bind (NULL_TREE
, g
, NULL_TREE
);
9141 = gimple_build_omp_for (g
, GF_OMP_FOR_KIND_TASKLOOP
, outer_for_clauses
,
9142 gimple_omp_for_collapse (gfor
),
9143 gimple_omp_for_pre_body (gfor
));
9144 gimple_omp_for_set_pre_body (gfor
, NULL
);
9145 gimple_omp_for_set_combined_p (gforo
, true);
9146 gimple_omp_for_set_combined_into_p (gfor
, true);
9147 for (i
= 0; i
< (int) gimple_omp_for_collapse (gfor
); i
++)
9149 t
= unshare_expr (gimple_omp_for_index (gfor
, i
));
9150 gimple_omp_for_set_index (gforo
, i
, t
);
9151 t
= unshare_expr (gimple_omp_for_initial (gfor
, i
));
9152 gimple_omp_for_set_initial (gforo
, i
, t
);
9153 gimple_omp_for_set_cond (gforo
, i
,
9154 gimple_omp_for_cond (gfor
, i
));
9155 t
= unshare_expr (gimple_omp_for_final (gfor
, i
));
9156 gimple_omp_for_set_final (gforo
, i
, t
);
9157 t
= unshare_expr (gimple_omp_for_incr (gfor
, i
));
9158 gimple_omp_for_set_incr (gforo
, i
, t
);
9160 gimplify_seq_add_stmt (pre_p
, gforo
);
9163 gimplify_seq_add_stmt (pre_p
, gfor
);
9164 if (ret
!= GS_ALL_DONE
)
9166 *expr_p
= NULL_TREE
;
9170 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
9171 of OMP_TARGET's body. */
9174 find_omp_teams (tree
*tp
, int *walk_subtrees
, void *)
9177 switch (TREE_CODE (*tp
))
9182 case STATEMENT_LIST
:
9191 /* Helper function of optimize_target_teams, determine if the expression
9192 can be computed safely before the target construct on the host. */
9195 computable_teams_clause (tree
*tp
, int *walk_subtrees
, void *)
9204 switch (TREE_CODE (*tp
))
9210 if (error_operand_p (*tp
)
9211 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp
))
9212 || DECL_HAS_VALUE_EXPR_P (*tp
)
9213 || DECL_THREAD_LOCAL_P (*tp
)
9214 || TREE_SIDE_EFFECTS (*tp
)
9215 || TREE_THIS_VOLATILE (*tp
))
9217 if (is_global_var (*tp
)
9218 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp
))
9219 || lookup_attribute ("omp declare target link",
9220 DECL_ATTRIBUTES (*tp
))))
9222 n
= splay_tree_lookup (gimplify_omp_ctxp
->variables
,
9223 (splay_tree_key
) *tp
);
9226 if (gimplify_omp_ctxp
->target_map_scalars_firstprivate
)
9230 else if (n
->value
& GOVD_LOCAL
)
9232 else if (n
->value
& GOVD_FIRSTPRIVATE
)
9234 else if ((n
->value
& (GOVD_MAP
| GOVD_MAP_ALWAYS_TO
))
9235 == (GOVD_MAP
| GOVD_MAP_ALWAYS_TO
))
9239 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp
)))
9243 if (TARGET_EXPR_INITIAL (*tp
)
9244 || TREE_CODE (TARGET_EXPR_SLOT (*tp
)) != VAR_DECL
)
9246 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp
),
9247 walk_subtrees
, NULL
);
9248 /* Allow some reasonable subset of integral arithmetics. */
9252 case TRUNC_DIV_EXPR
:
9254 case FLOOR_DIV_EXPR
:
9255 case ROUND_DIV_EXPR
:
9256 case TRUNC_MOD_EXPR
:
9258 case FLOOR_MOD_EXPR
:
9259 case ROUND_MOD_EXPR
:
9261 case EXACT_DIV_EXPR
:
9272 case NON_LVALUE_EXPR
:
9274 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp
)))
9277 /* And disallow anything else, except for comparisons. */
9279 if (COMPARISON_CLASS_P (*tp
))
9285 /* Try to determine if the num_teams and/or thread_limit expressions
9286 can have their values determined already before entering the
9288 INTEGER_CSTs trivially are,
9289 integral decls that are firstprivate (explicitly or implicitly)
9290 or explicitly map(always, to:) or map(always, tofrom:) on the target
9291 region too, and expressions involving simple arithmetics on those
9292 too, function calls are not ok, dereferencing something neither etc.
9293 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
9294 EXPR based on what we find:
9295 0 stands for clause not specified at all, use implementation default
9296 -1 stands for value that can't be determined easily before entering
9297 the target construct.
9298 If teams construct is not present at all, use 1 for num_teams
9299 and 0 for thread_limit (only one team is involved, and the thread
9300 limit is implementation defined. */
9303 optimize_target_teams (tree target
, gimple_seq
*pre_p
)
9305 tree body
= OMP_BODY (target
);
9306 tree teams
= walk_tree (&body
, find_omp_teams
, NULL
, NULL
);
9307 tree num_teams
= integer_zero_node
;
9308 tree thread_limit
= integer_zero_node
;
9309 location_t num_teams_loc
= EXPR_LOCATION (target
);
9310 location_t thread_limit_loc
= EXPR_LOCATION (target
);
9312 struct gimplify_omp_ctx
*target_ctx
= gimplify_omp_ctxp
;
9314 if (teams
== NULL_TREE
)
9315 num_teams
= integer_one_node
;
9317 for (c
= OMP_TEAMS_CLAUSES (teams
); c
; c
= OMP_CLAUSE_CHAIN (c
))
9319 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_NUM_TEAMS
)
9322 num_teams_loc
= OMP_CLAUSE_LOCATION (c
);
9324 else if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_THREAD_LIMIT
)
9327 thread_limit_loc
= OMP_CLAUSE_LOCATION (c
);
9331 expr
= OMP_CLAUSE_OPERAND (c
, 0);
9332 if (TREE_CODE (expr
) == INTEGER_CST
)
9337 if (walk_tree (&expr
, computable_teams_clause
, NULL
, NULL
))
9339 *p
= integer_minus_one_node
;
9343 gimplify_omp_ctxp
= gimplify_omp_ctxp
->outer_context
;
9344 if (gimplify_expr (p
, pre_p
, NULL
, is_gimple_val
, fb_rvalue
)
9347 gimplify_omp_ctxp
= target_ctx
;
9348 *p
= integer_minus_one_node
;
9351 gimplify_omp_ctxp
= target_ctx
;
9352 if (!DECL_P (expr
) && TREE_CODE (expr
) != TARGET_EXPR
)
9353 OMP_CLAUSE_OPERAND (c
, 0) = *p
;
9355 c
= build_omp_clause (thread_limit_loc
, OMP_CLAUSE_THREAD_LIMIT
);
9356 OMP_CLAUSE_THREAD_LIMIT_EXPR (c
) = thread_limit
;
9357 OMP_CLAUSE_CHAIN (c
) = OMP_TARGET_CLAUSES (target
);
9358 OMP_TARGET_CLAUSES (target
) = c
;
9359 c
= build_omp_clause (num_teams_loc
, OMP_CLAUSE_NUM_TEAMS
);
9360 OMP_CLAUSE_NUM_TEAMS_EXPR (c
) = num_teams
;
9361 OMP_CLAUSE_CHAIN (c
) = OMP_TARGET_CLAUSES (target
);
9362 OMP_TARGET_CLAUSES (target
) = c
;
9365 /* Gimplify the gross structure of several OMP constructs. */
9368 gimplify_omp_workshare (tree
*expr_p
, gimple_seq
*pre_p
)
9370 tree expr
= *expr_p
;
9372 gimple_seq body
= NULL
;
9373 enum omp_region_type ort
;
9375 switch (TREE_CODE (expr
))
9379 ort
= ORT_WORKSHARE
;
9382 ort
= OMP_TARGET_COMBINED (expr
) ? ORT_COMBINED_TARGET
: ORT_TARGET
;
9385 ort
= ORT_ACC_KERNELS
;
9388 ort
= ORT_ACC_PARALLEL
;
9393 case OMP_TARGET_DATA
:
9394 ort
= ORT_TARGET_DATA
;
9397 ort
= OMP_TEAMS_COMBINED (expr
) ? ORT_COMBINED_TEAMS
: ORT_TEAMS
;
9399 case OACC_HOST_DATA
:
9400 ort
= ORT_ACC_HOST_DATA
;
9405 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr
), pre_p
, ort
,
9407 if (TREE_CODE (expr
) == OMP_TARGET
)
9408 optimize_target_teams (expr
, pre_p
);
9409 if ((ort
& (ORT_TARGET
| ORT_TARGET_DATA
)) != 0)
9411 push_gimplify_context ();
9412 gimple
*g
= gimplify_and_return_first (OMP_BODY (expr
), &body
);
9413 if (gimple_code (g
) == GIMPLE_BIND
)
9414 pop_gimplify_context (g
);
9416 pop_gimplify_context (NULL
);
9417 if ((ort
& ORT_TARGET_DATA
) != 0)
9419 enum built_in_function end_ix
;
9420 switch (TREE_CODE (expr
))
9423 case OACC_HOST_DATA
:
9424 end_ix
= BUILT_IN_GOACC_DATA_END
;
9426 case OMP_TARGET_DATA
:
9427 end_ix
= BUILT_IN_GOMP_TARGET_END_DATA
;
9432 tree fn
= builtin_decl_explicit (end_ix
);
9433 g
= gimple_build_call (fn
, 0);
9434 gimple_seq cleanup
= NULL
;
9435 gimple_seq_add_stmt (&cleanup
, g
);
9436 g
= gimple_build_try (body
, cleanup
, GIMPLE_TRY_FINALLY
);
9438 gimple_seq_add_stmt (&body
, g
);
9442 gimplify_and_add (OMP_BODY (expr
), &body
);
9443 gimplify_adjust_omp_clauses (pre_p
, body
, &OMP_CLAUSES (expr
),
9446 switch (TREE_CODE (expr
))
9449 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_OACC_DATA
,
9450 OMP_CLAUSES (expr
));
9453 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_OACC_KERNELS
,
9454 OMP_CLAUSES (expr
));
9456 case OACC_HOST_DATA
:
9457 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_OACC_HOST_DATA
,
9458 OMP_CLAUSES (expr
));
9461 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_OACC_PARALLEL
,
9462 OMP_CLAUSES (expr
));
9465 stmt
= gimple_build_omp_sections (body
, OMP_CLAUSES (expr
));
9468 stmt
= gimple_build_omp_single (body
, OMP_CLAUSES (expr
));
9471 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_REGION
,
9472 OMP_CLAUSES (expr
));
9474 case OMP_TARGET_DATA
:
9475 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_DATA
,
9476 OMP_CLAUSES (expr
));
9479 stmt
= gimple_build_omp_teams (body
, OMP_CLAUSES (expr
));
9485 gimplify_seq_add_stmt (pre_p
, stmt
);
9486 *expr_p
= NULL_TREE
;
9489 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
9490 target update constructs. */
9493 gimplify_omp_target_update (tree
*expr_p
, gimple_seq
*pre_p
)
9495 tree expr
= *expr_p
;
9498 enum omp_region_type ort
= ORT_WORKSHARE
;
9500 switch (TREE_CODE (expr
))
9502 case OACC_ENTER_DATA
:
9503 case OACC_EXIT_DATA
:
9504 kind
= GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA
;
9508 kind
= GF_OMP_TARGET_KIND_OACC_UPDATE
;
9511 case OMP_TARGET_UPDATE
:
9512 kind
= GF_OMP_TARGET_KIND_UPDATE
;
9514 case OMP_TARGET_ENTER_DATA
:
9515 kind
= GF_OMP_TARGET_KIND_ENTER_DATA
;
9517 case OMP_TARGET_EXIT_DATA
:
9518 kind
= GF_OMP_TARGET_KIND_EXIT_DATA
;
9523 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr
), pre_p
,
9524 ort
, TREE_CODE (expr
));
9525 gimplify_adjust_omp_clauses (pre_p
, NULL
, &OMP_STANDALONE_CLAUSES (expr
),
9527 stmt
= gimple_build_omp_target (NULL
, kind
, OMP_STANDALONE_CLAUSES (expr
));
9529 gimplify_seq_add_stmt (pre_p
, stmt
);
9530 *expr_p
= NULL_TREE
;
9533 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
9534 stabilized the lhs of the atomic operation as *ADDR. Return true if
9535 EXPR is this stabilized form. */
9538 goa_lhs_expr_p (tree expr
, tree addr
)
9540 /* Also include casts to other type variants. The C front end is fond
9541 of adding these for e.g. volatile variables. This is like
9542 STRIP_TYPE_NOPS but includes the main variant lookup. */
9543 STRIP_USELESS_TYPE_CONVERSION (expr
);
9545 if (TREE_CODE (expr
) == INDIRECT_REF
)
9547 expr
= TREE_OPERAND (expr
, 0);
9549 && (CONVERT_EXPR_P (expr
)
9550 || TREE_CODE (expr
) == NON_LVALUE_EXPR
)
9551 && TREE_CODE (expr
) == TREE_CODE (addr
)
9552 && types_compatible_p (TREE_TYPE (expr
), TREE_TYPE (addr
)))
9554 expr
= TREE_OPERAND (expr
, 0);
9555 addr
= TREE_OPERAND (addr
, 0);
9559 return (TREE_CODE (addr
) == ADDR_EXPR
9560 && TREE_CODE (expr
) == ADDR_EXPR
9561 && TREE_OPERAND (addr
, 0) == TREE_OPERAND (expr
, 0));
9563 if (TREE_CODE (addr
) == ADDR_EXPR
&& expr
== TREE_OPERAND (addr
, 0))
9568 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
9569 expression does not involve the lhs, evaluate it into a temporary.
9570 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
9571 or -1 if an error was encountered. */
9574 goa_stabilize_expr (tree
*expr_p
, gimple_seq
*pre_p
, tree lhs_addr
,
9577 tree expr
= *expr_p
;
9580 if (goa_lhs_expr_p (expr
, lhs_addr
))
9585 if (is_gimple_val (expr
))
9589 switch (TREE_CODE_CLASS (TREE_CODE (expr
)))
9592 case tcc_comparison
:
9593 saw_lhs
|= goa_stabilize_expr (&TREE_OPERAND (expr
, 1), pre_p
, lhs_addr
,
9596 saw_lhs
|= goa_stabilize_expr (&TREE_OPERAND (expr
, 0), pre_p
, lhs_addr
,
9599 case tcc_expression
:
9600 switch (TREE_CODE (expr
))
9602 case TRUTH_ANDIF_EXPR
:
9603 case TRUTH_ORIF_EXPR
:
9604 case TRUTH_AND_EXPR
:
9606 case TRUTH_XOR_EXPR
:
9607 saw_lhs
|= goa_stabilize_expr (&TREE_OPERAND (expr
, 1), pre_p
,
9609 case TRUTH_NOT_EXPR
:
9610 saw_lhs
|= goa_stabilize_expr (&TREE_OPERAND (expr
, 0), pre_p
,
9614 /* Break out any preevaluations from cp_build_modify_expr. */
9615 for (; TREE_CODE (expr
) == COMPOUND_EXPR
;
9616 expr
= TREE_OPERAND (expr
, 1))
9617 gimplify_stmt (&TREE_OPERAND (expr
, 0), pre_p
);
9619 return goa_stabilize_expr (expr_p
, pre_p
, lhs_addr
, lhs_var
);
9630 enum gimplify_status gs
;
9631 gs
= gimplify_expr (expr_p
, pre_p
, NULL
, is_gimple_val
, fb_rvalue
);
9632 if (gs
!= GS_ALL_DONE
)
9639 /* Gimplify an OMP_ATOMIC statement. */
9641 static enum gimplify_status
9642 gimplify_omp_atomic (tree
*expr_p
, gimple_seq
*pre_p
)
9644 tree addr
= TREE_OPERAND (*expr_p
, 0);
9645 tree rhs
= TREE_CODE (*expr_p
) == OMP_ATOMIC_READ
9646 ? NULL
: TREE_OPERAND (*expr_p
, 1);
9647 tree type
= TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr
)));
9649 gomp_atomic_load
*loadstmt
;
9650 gomp_atomic_store
*storestmt
;
9652 tmp_load
= create_tmp_reg (type
);
9653 if (rhs
&& goa_stabilize_expr (&rhs
, pre_p
, addr
, tmp_load
) < 0)
9656 if (gimplify_expr (&addr
, pre_p
, NULL
, is_gimple_val
, fb_rvalue
)
9660 loadstmt
= gimple_build_omp_atomic_load (tmp_load
, addr
);
9661 gimplify_seq_add_stmt (pre_p
, loadstmt
);
9662 if (rhs
&& gimplify_expr (&rhs
, pre_p
, NULL
, is_gimple_val
, fb_rvalue
)
9666 if (TREE_CODE (*expr_p
) == OMP_ATOMIC_READ
)
9668 storestmt
= gimple_build_omp_atomic_store (rhs
);
9669 gimplify_seq_add_stmt (pre_p
, storestmt
);
9670 if (OMP_ATOMIC_SEQ_CST (*expr_p
))
9672 gimple_omp_atomic_set_seq_cst (loadstmt
);
9673 gimple_omp_atomic_set_seq_cst (storestmt
);
9675 switch (TREE_CODE (*expr_p
))
9677 case OMP_ATOMIC_READ
:
9678 case OMP_ATOMIC_CAPTURE_OLD
:
9680 gimple_omp_atomic_set_need_value (loadstmt
);
9682 case OMP_ATOMIC_CAPTURE_NEW
:
9684 gimple_omp_atomic_set_need_value (storestmt
);
9694 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
9695 body, and adding some EH bits. */
9697 static enum gimplify_status
9698 gimplify_transaction (tree
*expr_p
, gimple_seq
*pre_p
)
9700 tree expr
= *expr_p
, temp
, tbody
= TRANSACTION_EXPR_BODY (expr
);
9702 gtransaction
*trans_stmt
;
9703 gimple_seq body
= NULL
;
9706 /* Wrap the transaction body in a BIND_EXPR so we have a context
9707 where to put decls for OMP. */
9708 if (TREE_CODE (tbody
) != BIND_EXPR
)
9710 tree bind
= build3 (BIND_EXPR
, void_type_node
, NULL
, tbody
, NULL
);
9711 TREE_SIDE_EFFECTS (bind
) = 1;
9712 SET_EXPR_LOCATION (bind
, EXPR_LOCATION (tbody
));
9713 TRANSACTION_EXPR_BODY (expr
) = bind
;
9716 push_gimplify_context ();
9717 temp
= voidify_wrapper_expr (*expr_p
, NULL
);
9719 body_stmt
= gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr
), &body
);
9720 pop_gimplify_context (body_stmt
);
9722 trans_stmt
= gimple_build_transaction (body
, NULL
);
9723 if (TRANSACTION_EXPR_OUTER (expr
))
9724 subcode
= GTMA_IS_OUTER
;
9725 else if (TRANSACTION_EXPR_RELAXED (expr
))
9726 subcode
= GTMA_IS_RELAXED
;
9727 gimple_transaction_set_subcode (trans_stmt
, subcode
);
9729 gimplify_seq_add_stmt (pre_p
, trans_stmt
);
9737 *expr_p
= NULL_TREE
;
9741 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
9742 is the OMP_BODY of the original EXPR (which has already been
9743 gimplified so it's not present in the EXPR).
9745 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
9748 gimplify_omp_ordered (tree expr
, gimple_seq body
)
9753 tree source_c
= NULL_TREE
;
9754 tree sink_c
= NULL_TREE
;
9756 if (gimplify_omp_ctxp
)
9757 for (c
= OMP_ORDERED_CLAUSES (expr
); c
; c
= OMP_CLAUSE_CHAIN (c
))
9758 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_DEPEND
9759 && gimplify_omp_ctxp
->loop_iter_var
.is_empty ()
9760 && (OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SINK
9761 || OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SOURCE
))
9763 error_at (OMP_CLAUSE_LOCATION (c
),
9764 "%<ordered%> construct with %<depend%> clause must be "
9765 "closely nested inside a loop with %<ordered%> clause "
9766 "with a parameter");
9769 else if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_DEPEND
9770 && OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SINK
)
9773 for (decls
= OMP_CLAUSE_DECL (c
), i
= 0;
9774 decls
&& TREE_CODE (decls
) == TREE_LIST
;
9775 decls
= TREE_CHAIN (decls
), ++i
)
9776 if (i
>= gimplify_omp_ctxp
->loop_iter_var
.length () / 2)
9778 else if (TREE_VALUE (decls
)
9779 != gimplify_omp_ctxp
->loop_iter_var
[2 * i
])
9781 error_at (OMP_CLAUSE_LOCATION (c
),
9782 "variable %qE is not an iteration "
9783 "of outermost loop %d, expected %qE",
9784 TREE_VALUE (decls
), i
+ 1,
9785 gimplify_omp_ctxp
->loop_iter_var
[2 * i
]);
9791 = gimplify_omp_ctxp
->loop_iter_var
[2 * i
+ 1];
9792 if (!fail
&& i
!= gimplify_omp_ctxp
->loop_iter_var
.length () / 2)
9794 error_at (OMP_CLAUSE_LOCATION (c
),
9795 "number of variables in %<depend(sink)%> "
9796 "clause does not match number of "
9797 "iteration variables");
9802 else if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_DEPEND
9803 && OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SOURCE
)
9807 error_at (OMP_CLAUSE_LOCATION (c
),
9808 "more than one %<depend(source)%> clause on an "
9809 "%<ordered%> construct");
9815 if (source_c
&& sink_c
)
9817 error_at (OMP_CLAUSE_LOCATION (source_c
),
9818 "%<depend(source)%> clause specified together with "
9819 "%<depend(sink:)%> clauses on the same construct");
9824 return gimple_build_nop ();
9825 return gimple_build_omp_ordered (body
, OMP_ORDERED_CLAUSES (expr
));
9828 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
9829 expression produces a value to be used as an operand inside a GIMPLE
9830 statement, the value will be stored back in *EXPR_P. This value will
9831 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
9832 an SSA_NAME. The corresponding sequence of GIMPLE statements is
9833 emitted in PRE_P and POST_P.
9835 Additionally, this process may overwrite parts of the input
9836 expression during gimplification. Ideally, it should be
9837 possible to do non-destructive gimplification.
9839 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
9840 the expression needs to evaluate to a value to be used as
9841 an operand in a GIMPLE statement, this value will be stored in
9842 *EXPR_P on exit. This happens when the caller specifies one
9843 of fb_lvalue or fb_rvalue fallback flags.
9845 PRE_P will contain the sequence of GIMPLE statements corresponding
9846 to the evaluation of EXPR and all the side-effects that must
9847 be executed before the main expression. On exit, the last
9848 statement of PRE_P is the core statement being gimplified. For
9849 instance, when gimplifying 'if (++a)' the last statement in
9850 PRE_P will be 'if (t.1)' where t.1 is the result of
9851 pre-incrementing 'a'.
9853 POST_P will contain the sequence of GIMPLE statements corresponding
9854 to the evaluation of all the side-effects that must be executed
9855 after the main expression. If this is NULL, the post
9856 side-effects are stored at the end of PRE_P.
9858 The reason why the output is split in two is to handle post
9859 side-effects explicitly. In some cases, an expression may have
9860 inner and outer post side-effects which need to be emitted in
9861 an order different from the one given by the recursive
9862 traversal. For instance, for the expression (*p--)++ the post
9863 side-effects of '--' must actually occur *after* the post
9864 side-effects of '++'. However, gimplification will first visit
9865 the inner expression, so if a separate POST sequence was not
9866 used, the resulting sequence would be:
9873 However, the post-decrement operation in line #2 must not be
9874 evaluated until after the store to *p at line #4, so the
9875 correct sequence should be:
9882 So, by specifying a separate post queue, it is possible
9883 to emit the post side-effects in the correct order.
9884 If POST_P is NULL, an internal queue will be used. Before
9885 returning to the caller, the sequence POST_P is appended to
9886 the main output sequence PRE_P.
9888 GIMPLE_TEST_F points to a function that takes a tree T and
9889 returns nonzero if T is in the GIMPLE form requested by the
9890 caller. The GIMPLE predicates are in gimple.c.
9892 FALLBACK tells the function what sort of a temporary we want if
9893 gimplification cannot produce an expression that complies with
9896 fb_none means that no temporary should be generated
9897 fb_rvalue means that an rvalue is OK to generate
9898 fb_lvalue means that an lvalue is OK to generate
9899 fb_either means that either is OK, but an lvalue is preferable.
9900 fb_mayfail means that gimplification may fail (in which case
9901 GS_ERROR will be returned)
9903 The return value is either GS_ERROR or GS_ALL_DONE, since this
9904 function iterates until EXPR is completely gimplified or an error
9907 enum gimplify_status
9908 gimplify_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
9909 bool (*gimple_test_f
) (tree
), fallback_t fallback
)
9912 gimple_seq internal_pre
= NULL
;
9913 gimple_seq internal_post
= NULL
;
9916 location_t saved_location
;
9917 enum gimplify_status ret
;
9918 gimple_stmt_iterator pre_last_gsi
, post_last_gsi
;
9920 save_expr
= *expr_p
;
9921 if (save_expr
== NULL_TREE
)
9924 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
9925 is_statement
= gimple_test_f
== is_gimple_stmt
;
9929 /* Consistency checks. */
9930 if (gimple_test_f
== is_gimple_reg
)
9931 gcc_assert (fallback
& (fb_rvalue
| fb_lvalue
));
9932 else if (gimple_test_f
== is_gimple_val
9933 || gimple_test_f
== is_gimple_call_addr
9934 || gimple_test_f
== is_gimple_condexpr
9935 || gimple_test_f
== is_gimple_mem_rhs
9936 || gimple_test_f
== is_gimple_mem_rhs_or_call
9937 || gimple_test_f
== is_gimple_reg_rhs
9938 || gimple_test_f
== is_gimple_reg_rhs_or_call
9939 || gimple_test_f
== is_gimple_asm_val
9940 || gimple_test_f
== is_gimple_mem_ref_addr
)
9941 gcc_assert (fallback
& fb_rvalue
);
9942 else if (gimple_test_f
== is_gimple_min_lval
9943 || gimple_test_f
== is_gimple_lvalue
)
9944 gcc_assert (fallback
& fb_lvalue
);
9945 else if (gimple_test_f
== is_gimple_addressable
)
9946 gcc_assert (fallback
& fb_either
);
9947 else if (gimple_test_f
== is_gimple_stmt
)
9948 gcc_assert (fallback
== fb_none
);
9951 /* We should have recognized the GIMPLE_TEST_F predicate to
9952 know what kind of fallback to use in case a temporary is
9953 needed to hold the value or address of *EXPR_P. */
9957 /* We used to check the predicate here and return immediately if it
9958 succeeds. This is wrong; the design is for gimplification to be
9959 idempotent, and for the predicates to only test for valid forms, not
9960 whether they are fully simplified. */
9962 pre_p
= &internal_pre
;
9965 post_p
= &internal_post
;
9967 /* Remember the last statements added to PRE_P and POST_P. Every
9968 new statement added by the gimplification helpers needs to be
9969 annotated with location information. To centralize the
9970 responsibility, we remember the last statement that had been
9971 added to both queues before gimplifying *EXPR_P. If
9972 gimplification produces new statements in PRE_P and POST_P, those
9973 statements will be annotated with the same location information
9975 pre_last_gsi
= gsi_last (*pre_p
);
9976 post_last_gsi
= gsi_last (*post_p
);
9978 saved_location
= input_location
;
9979 if (save_expr
!= error_mark_node
9980 && EXPR_HAS_LOCATION (*expr_p
))
9981 input_location
= EXPR_LOCATION (*expr_p
);
9983 /* Loop over the specific gimplifiers until the toplevel node
9984 remains the same. */
9987 /* Strip away as many useless type conversions as possible
9989 STRIP_USELESS_TYPE_CONVERSION (*expr_p
);
9991 /* Remember the expr. */
9992 save_expr
= *expr_p
;
9994 /* Die, die, die, my darling. */
9995 if (save_expr
== error_mark_node
9996 || (TREE_TYPE (save_expr
)
9997 && TREE_TYPE (save_expr
) == error_mark_node
))
10003 /* Do any language-specific gimplification. */
10004 ret
= ((enum gimplify_status
)
10005 lang_hooks
.gimplify_expr (expr_p
, pre_p
, post_p
));
10008 if (*expr_p
== NULL_TREE
)
10010 if (*expr_p
!= save_expr
)
10013 else if (ret
!= GS_UNHANDLED
)
10016 /* Make sure that all the cases set 'ret' appropriately. */
10017 ret
= GS_UNHANDLED
;
10018 switch (TREE_CODE (*expr_p
))
10020 /* First deal with the special cases. */
10022 case POSTINCREMENT_EXPR
:
10023 case POSTDECREMENT_EXPR
:
10024 case PREINCREMENT_EXPR
:
10025 case PREDECREMENT_EXPR
:
10026 ret
= gimplify_self_mod_expr (expr_p
, pre_p
, post_p
,
10027 fallback
!= fb_none
,
10028 TREE_TYPE (*expr_p
));
10031 case VIEW_CONVERT_EXPR
:
10032 if (is_gimple_reg_type (TREE_TYPE (*expr_p
))
10033 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p
, 0))))
10035 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
10036 post_p
, is_gimple_val
, fb_rvalue
);
10037 recalculate_side_effects (*expr_p
);
10043 case ARRAY_RANGE_REF
:
10044 case REALPART_EXPR
:
10045 case IMAGPART_EXPR
:
10046 case COMPONENT_REF
:
10047 ret
= gimplify_compound_lval (expr_p
, pre_p
, post_p
,
10048 fallback
? fallback
: fb_rvalue
);
10052 ret
= gimplify_cond_expr (expr_p
, pre_p
, fallback
);
10054 /* C99 code may assign to an array in a structure value of a
10055 conditional expression, and this has undefined behavior
10056 only on execution, so create a temporary if an lvalue is
10058 if (fallback
== fb_lvalue
)
10060 *expr_p
= get_initialized_tmp_var (*expr_p
, pre_p
, post_p
);
10061 mark_addressable (*expr_p
);
10067 ret
= gimplify_call_expr (expr_p
, pre_p
, fallback
!= fb_none
);
10069 /* C99 code may assign to an array in a structure returned
10070 from a function, and this has undefined behavior only on
10071 execution, so create a temporary if an lvalue is
10073 if (fallback
== fb_lvalue
)
10075 *expr_p
= get_initialized_tmp_var (*expr_p
, pre_p
, post_p
);
10076 mark_addressable (*expr_p
);
10082 gcc_unreachable ();
10084 case COMPOUND_EXPR
:
10085 ret
= gimplify_compound_expr (expr_p
, pre_p
, fallback
!= fb_none
);
10088 case COMPOUND_LITERAL_EXPR
:
10089 ret
= gimplify_compound_literal_expr (expr_p
, pre_p
,
10090 gimple_test_f
, fallback
);
10095 ret
= gimplify_modify_expr (expr_p
, pre_p
, post_p
,
10096 fallback
!= fb_none
);
10099 case TRUTH_ANDIF_EXPR
:
10100 case TRUTH_ORIF_EXPR
:
10102 /* Preserve the original type of the expression and the
10103 source location of the outer expression. */
10104 tree org_type
= TREE_TYPE (*expr_p
);
10105 *expr_p
= gimple_boolify (*expr_p
);
10106 *expr_p
= build3_loc (input_location
, COND_EXPR
,
10110 org_type
, boolean_true_node
),
10113 org_type
, boolean_false_node
));
10118 case TRUTH_NOT_EXPR
:
10120 tree type
= TREE_TYPE (*expr_p
);
10121 /* The parsers are careful to generate TRUTH_NOT_EXPR
10122 only with operands that are always zero or one.
10123 We do not fold here but handle the only interesting case
10124 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
10125 *expr_p
= gimple_boolify (*expr_p
);
10126 if (TYPE_PRECISION (TREE_TYPE (*expr_p
)) == 1)
10127 *expr_p
= build1_loc (input_location
, BIT_NOT_EXPR
,
10128 TREE_TYPE (*expr_p
),
10129 TREE_OPERAND (*expr_p
, 0));
10131 *expr_p
= build2_loc (input_location
, BIT_XOR_EXPR
,
10132 TREE_TYPE (*expr_p
),
10133 TREE_OPERAND (*expr_p
, 0),
10134 build_int_cst (TREE_TYPE (*expr_p
), 1));
10135 if (!useless_type_conversion_p (type
, TREE_TYPE (*expr_p
)))
10136 *expr_p
= fold_convert_loc (input_location
, type
, *expr_p
);
10142 ret
= gimplify_addr_expr (expr_p
, pre_p
, post_p
);
10145 case ANNOTATE_EXPR
:
10147 tree cond
= TREE_OPERAND (*expr_p
, 0);
10148 tree kind
= TREE_OPERAND (*expr_p
, 1);
10149 tree type
= TREE_TYPE (cond
);
10150 if (!INTEGRAL_TYPE_P (type
))
10156 tree tmp
= create_tmp_var (type
);
10157 gimplify_arg (&cond
, pre_p
, EXPR_LOCATION (*expr_p
));
10159 = gimple_build_call_internal (IFN_ANNOTATE
, 2, cond
, kind
);
10160 gimple_call_set_lhs (call
, tmp
);
10161 gimplify_seq_add_stmt (pre_p
, call
);
10168 ret
= gimplify_va_arg_expr (expr_p
, pre_p
, post_p
);
10172 if (IS_EMPTY_STMT (*expr_p
))
10178 if (VOID_TYPE_P (TREE_TYPE (*expr_p
))
10179 || fallback
== fb_none
)
10181 /* Just strip a conversion to void (or in void context) and
10183 *expr_p
= TREE_OPERAND (*expr_p
, 0);
10188 ret
= gimplify_conversion (expr_p
);
10189 if (ret
== GS_ERROR
)
10191 if (*expr_p
!= save_expr
)
10195 case FIX_TRUNC_EXPR
:
10196 /* unary_expr: ... | '(' cast ')' val | ... */
10197 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
10198 is_gimple_val
, fb_rvalue
);
10199 recalculate_side_effects (*expr_p
);
10204 bool volatilep
= TREE_THIS_VOLATILE (*expr_p
);
10205 bool notrap
= TREE_THIS_NOTRAP (*expr_p
);
10206 tree saved_ptr_type
= TREE_TYPE (TREE_OPERAND (*expr_p
, 0));
10208 *expr_p
= fold_indirect_ref_loc (input_location
, *expr_p
);
10209 if (*expr_p
!= save_expr
)
10215 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
10216 is_gimple_reg
, fb_rvalue
);
10217 if (ret
== GS_ERROR
)
10220 recalculate_side_effects (*expr_p
);
10221 *expr_p
= fold_build2_loc (input_location
, MEM_REF
,
10222 TREE_TYPE (*expr_p
),
10223 TREE_OPERAND (*expr_p
, 0),
10224 build_int_cst (saved_ptr_type
, 0));
10225 TREE_THIS_VOLATILE (*expr_p
) = volatilep
;
10226 TREE_THIS_NOTRAP (*expr_p
) = notrap
;
10231 /* We arrive here through the various re-gimplifcation paths. */
10233 /* First try re-folding the whole thing. */
10234 tmp
= fold_binary (MEM_REF
, TREE_TYPE (*expr_p
),
10235 TREE_OPERAND (*expr_p
, 0),
10236 TREE_OPERAND (*expr_p
, 1));
10239 REF_REVERSE_STORAGE_ORDER (tmp
)
10240 = REF_REVERSE_STORAGE_ORDER (*expr_p
);
10242 recalculate_side_effects (*expr_p
);
10246 /* Avoid re-gimplifying the address operand if it is already
10247 in suitable form. Re-gimplifying would mark the address
10248 operand addressable. Always gimplify when not in SSA form
10249 as we still may have to gimplify decls with value-exprs. */
10250 if (!gimplify_ctxp
|| !gimplify_ctxp
->into_ssa
10251 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p
, 0)))
10253 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
10254 is_gimple_mem_ref_addr
, fb_rvalue
);
10255 if (ret
== GS_ERROR
)
10258 recalculate_side_effects (*expr_p
);
10262 /* Constants need not be gimplified. */
10269 /* Drop the overflow flag on constants, we do not want
10270 that in the GIMPLE IL. */
10271 if (TREE_OVERFLOW_P (*expr_p
))
10272 *expr_p
= drop_tree_overflow (*expr_p
);
10277 /* If we require an lvalue, such as for ADDR_EXPR, retain the
10278 CONST_DECL node. Otherwise the decl is replaceable by its
10280 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
10281 if (fallback
& fb_lvalue
)
10285 *expr_p
= DECL_INITIAL (*expr_p
);
10291 ret
= gimplify_decl_expr (expr_p
, pre_p
);
10295 ret
= gimplify_bind_expr (expr_p
, pre_p
);
10299 ret
= gimplify_loop_expr (expr_p
, pre_p
);
10303 ret
= gimplify_switch_expr (expr_p
, pre_p
);
10307 ret
= gimplify_exit_expr (expr_p
);
10311 /* If the target is not LABEL, then it is a computed jump
10312 and the target needs to be gimplified. */
10313 if (TREE_CODE (GOTO_DESTINATION (*expr_p
)) != LABEL_DECL
)
10315 ret
= gimplify_expr (&GOTO_DESTINATION (*expr_p
), pre_p
,
10316 NULL
, is_gimple_val
, fb_rvalue
);
10317 if (ret
== GS_ERROR
)
10320 gimplify_seq_add_stmt (pre_p
,
10321 gimple_build_goto (GOTO_DESTINATION (*expr_p
)));
10326 gimplify_seq_add_stmt (pre_p
,
10327 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p
),
10328 PREDICT_EXPR_OUTCOME (*expr_p
)));
10334 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p
))
10335 == current_function_decl
);
10336 gimplify_seq_add_stmt (pre_p
,
10337 gimple_build_label (LABEL_EXPR_LABEL (*expr_p
)));
10340 case CASE_LABEL_EXPR
:
10341 ret
= gimplify_case_label_expr (expr_p
, pre_p
);
10345 ret
= gimplify_return_expr (*expr_p
, pre_p
);
10349 /* Don't reduce this in place; let gimplify_init_constructor work its
10350 magic. Buf if we're just elaborating this for side effects, just
10351 gimplify any element that has side-effects. */
10352 if (fallback
== fb_none
)
10354 unsigned HOST_WIDE_INT ix
;
10356 tree temp
= NULL_TREE
;
10357 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p
), ix
, val
)
10358 if (TREE_SIDE_EFFECTS (val
))
10359 append_to_statement_list (val
, &temp
);
10362 ret
= temp
? GS_OK
: GS_ALL_DONE
;
10364 /* C99 code may assign to an array in a constructed
10365 structure or union, and this has undefined behavior only
10366 on execution, so create a temporary if an lvalue is
10368 else if (fallback
== fb_lvalue
)
10370 *expr_p
= get_initialized_tmp_var (*expr_p
, pre_p
, post_p
);
10371 mark_addressable (*expr_p
);
10378 /* The following are special cases that are not handled by the
10379 original GIMPLE grammar. */
10381 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
10384 ret
= gimplify_save_expr (expr_p
, pre_p
, post_p
);
10387 case BIT_FIELD_REF
:
10388 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
10389 post_p
, is_gimple_lvalue
, fb_either
);
10390 recalculate_side_effects (*expr_p
);
10393 case TARGET_MEM_REF
:
10395 enum gimplify_status r0
= GS_ALL_DONE
, r1
= GS_ALL_DONE
;
10397 if (TMR_BASE (*expr_p
))
10398 r0
= gimplify_expr (&TMR_BASE (*expr_p
), pre_p
,
10399 post_p
, is_gimple_mem_ref_addr
, fb_either
);
10400 if (TMR_INDEX (*expr_p
))
10401 r1
= gimplify_expr (&TMR_INDEX (*expr_p
), pre_p
,
10402 post_p
, is_gimple_val
, fb_rvalue
);
10403 if (TMR_INDEX2 (*expr_p
))
10404 r1
= gimplify_expr (&TMR_INDEX2 (*expr_p
), pre_p
,
10405 post_p
, is_gimple_val
, fb_rvalue
);
10406 /* TMR_STEP and TMR_OFFSET are always integer constants. */
10407 ret
= MIN (r0
, r1
);
10411 case NON_LVALUE_EXPR
:
10412 /* This should have been stripped above. */
10413 gcc_unreachable ();
10416 ret
= gimplify_asm_expr (expr_p
, pre_p
, post_p
);
10419 case TRY_FINALLY_EXPR
:
10420 case TRY_CATCH_EXPR
:
10422 gimple_seq eval
, cleanup
;
10425 /* Calls to destructors are generated automatically in FINALLY/CATCH
10426 block. They should have location as UNKNOWN_LOCATION. However,
10427 gimplify_call_expr will reset these call stmts to input_location
10428 if it finds stmt's location is unknown. To prevent resetting for
10429 destructors, we set the input_location to unknown.
10430 Note that this only affects the destructor calls in FINALLY/CATCH
10431 block, and will automatically reset to its original value by the
10432 end of gimplify_expr. */
10433 input_location
= UNKNOWN_LOCATION
;
10434 eval
= cleanup
= NULL
;
10435 gimplify_and_add (TREE_OPERAND (*expr_p
, 0), &eval
);
10436 gimplify_and_add (TREE_OPERAND (*expr_p
, 1), &cleanup
);
10437 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
10438 if (gimple_seq_empty_p (cleanup
))
10440 gimple_seq_add_seq (pre_p
, eval
);
10444 try_
= gimple_build_try (eval
, cleanup
,
10445 TREE_CODE (*expr_p
) == TRY_FINALLY_EXPR
10446 ? GIMPLE_TRY_FINALLY
10447 : GIMPLE_TRY_CATCH
);
10448 if (EXPR_HAS_LOCATION (save_expr
))
10449 gimple_set_location (try_
, EXPR_LOCATION (save_expr
));
10450 else if (LOCATION_LOCUS (saved_location
) != UNKNOWN_LOCATION
)
10451 gimple_set_location (try_
, saved_location
);
10452 if (TREE_CODE (*expr_p
) == TRY_CATCH_EXPR
)
10453 gimple_try_set_catch_is_cleanup (try_
,
10454 TRY_CATCH_IS_CLEANUP (*expr_p
));
10455 gimplify_seq_add_stmt (pre_p
, try_
);
10460 case CLEANUP_POINT_EXPR
:
10461 ret
= gimplify_cleanup_point_expr (expr_p
, pre_p
);
10465 ret
= gimplify_target_expr (expr_p
, pre_p
, post_p
);
10471 gimple_seq handler
= NULL
;
10472 gimplify_and_add (CATCH_BODY (*expr_p
), &handler
);
10473 c
= gimple_build_catch (CATCH_TYPES (*expr_p
), handler
);
10474 gimplify_seq_add_stmt (pre_p
, c
);
10479 case EH_FILTER_EXPR
:
10482 gimple_seq failure
= NULL
;
10484 gimplify_and_add (EH_FILTER_FAILURE (*expr_p
), &failure
);
10485 ehf
= gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p
), failure
);
10486 gimple_set_no_warning (ehf
, TREE_NO_WARNING (*expr_p
));
10487 gimplify_seq_add_stmt (pre_p
, ehf
);
10494 enum gimplify_status r0
, r1
;
10495 r0
= gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p
), pre_p
,
10496 post_p
, is_gimple_val
, fb_rvalue
);
10497 r1
= gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p
), pre_p
,
10498 post_p
, is_gimple_val
, fb_rvalue
);
10499 TREE_SIDE_EFFECTS (*expr_p
) = 0;
10500 ret
= MIN (r0
, r1
);
10505 /* We get here when taking the address of a label. We mark
10506 the label as "forced"; meaning it can never be removed and
10507 it is a potential target for any computed goto. */
10508 FORCED_LABEL (*expr_p
) = 1;
10512 case STATEMENT_LIST
:
10513 ret
= gimplify_statement_list (expr_p
, pre_p
);
10516 case WITH_SIZE_EXPR
:
10518 gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
10519 post_p
== &internal_post
? NULL
: post_p
,
10520 gimple_test_f
, fallback
);
10521 gimplify_expr (&TREE_OPERAND (*expr_p
, 1), pre_p
, post_p
,
10522 is_gimple_val
, fb_rvalue
);
10529 ret
= gimplify_var_or_parm_decl (expr_p
);
10533 /* When within an OMP context, notice uses of variables. */
10534 if (gimplify_omp_ctxp
)
10535 omp_notice_variable (gimplify_omp_ctxp
, *expr_p
, true);
10540 /* Allow callbacks into the gimplifier during optimization. */
10545 gimplify_omp_parallel (expr_p
, pre_p
);
10550 gimplify_omp_task (expr_p
, pre_p
);
10558 case OMP_DISTRIBUTE
:
10561 ret
= gimplify_omp_for (expr_p
, pre_p
);
10565 gimplify_oacc_cache (expr_p
, pre_p
);
10570 gimplify_oacc_declare (expr_p
, pre_p
);
10574 case OACC_HOST_DATA
:
10577 case OACC_PARALLEL
:
10581 case OMP_TARGET_DATA
:
10583 gimplify_omp_workshare (expr_p
, pre_p
);
10587 case OACC_ENTER_DATA
:
10588 case OACC_EXIT_DATA
:
10590 case OMP_TARGET_UPDATE
:
10591 case OMP_TARGET_ENTER_DATA
:
10592 case OMP_TARGET_EXIT_DATA
:
10593 gimplify_omp_target_update (expr_p
, pre_p
);
10599 case OMP_TASKGROUP
:
10603 gimple_seq body
= NULL
;
10606 gimplify_and_add (OMP_BODY (*expr_p
), &body
);
10607 switch (TREE_CODE (*expr_p
))
10610 g
= gimple_build_omp_section (body
);
10613 g
= gimple_build_omp_master (body
);
10615 case OMP_TASKGROUP
:
10617 gimple_seq cleanup
= NULL
;
10619 = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END
);
10620 g
= gimple_build_call (fn
, 0);
10621 gimple_seq_add_stmt (&cleanup
, g
);
10622 g
= gimple_build_try (body
, cleanup
, GIMPLE_TRY_FINALLY
);
10624 gimple_seq_add_stmt (&body
, g
);
10625 g
= gimple_build_omp_taskgroup (body
);
10629 g
= gimplify_omp_ordered (*expr_p
, body
);
10632 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p
),
10633 pre_p
, ORT_WORKSHARE
, OMP_CRITICAL
);
10634 gimplify_adjust_omp_clauses (pre_p
, body
,
10635 &OMP_CRITICAL_CLAUSES (*expr_p
),
10637 g
= gimple_build_omp_critical (body
,
10638 OMP_CRITICAL_NAME (*expr_p
),
10639 OMP_CRITICAL_CLAUSES (*expr_p
));
10642 gcc_unreachable ();
10644 gimplify_seq_add_stmt (pre_p
, g
);
10650 case OMP_ATOMIC_READ
:
10651 case OMP_ATOMIC_CAPTURE_OLD
:
10652 case OMP_ATOMIC_CAPTURE_NEW
:
10653 ret
= gimplify_omp_atomic (expr_p
, pre_p
);
10656 case TRANSACTION_EXPR
:
10657 ret
= gimplify_transaction (expr_p
, pre_p
);
10660 case TRUTH_AND_EXPR
:
10661 case TRUTH_OR_EXPR
:
10662 case TRUTH_XOR_EXPR
:
10664 tree orig_type
= TREE_TYPE (*expr_p
);
10665 tree new_type
, xop0
, xop1
;
10666 *expr_p
= gimple_boolify (*expr_p
);
10667 new_type
= TREE_TYPE (*expr_p
);
10668 if (!useless_type_conversion_p (orig_type
, new_type
))
10670 *expr_p
= fold_convert_loc (input_location
, orig_type
, *expr_p
);
10675 /* Boolified binary truth expressions are semantically equivalent
10676 to bitwise binary expressions. Canonicalize them to the
10677 bitwise variant. */
10678 switch (TREE_CODE (*expr_p
))
10680 case TRUTH_AND_EXPR
:
10681 TREE_SET_CODE (*expr_p
, BIT_AND_EXPR
);
10683 case TRUTH_OR_EXPR
:
10684 TREE_SET_CODE (*expr_p
, BIT_IOR_EXPR
);
10686 case TRUTH_XOR_EXPR
:
10687 TREE_SET_CODE (*expr_p
, BIT_XOR_EXPR
);
10692 /* Now make sure that operands have compatible type to
10693 expression's new_type. */
10694 xop0
= TREE_OPERAND (*expr_p
, 0);
10695 xop1
= TREE_OPERAND (*expr_p
, 1);
10696 if (!useless_type_conversion_p (new_type
, TREE_TYPE (xop0
)))
10697 TREE_OPERAND (*expr_p
, 0) = fold_convert_loc (input_location
,
10700 if (!useless_type_conversion_p (new_type
, TREE_TYPE (xop1
)))
10701 TREE_OPERAND (*expr_p
, 1) = fold_convert_loc (input_location
,
10704 /* Continue classified as tcc_binary. */
10709 case VEC_COND_EXPR
:
10710 case VEC_PERM_EXPR
:
10711 /* Classified as tcc_expression. */
10714 case POINTER_PLUS_EXPR
:
10716 enum gimplify_status r0
, r1
;
10717 r0
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
10718 post_p
, is_gimple_val
, fb_rvalue
);
10719 r1
= gimplify_expr (&TREE_OPERAND (*expr_p
, 1), pre_p
,
10720 post_p
, is_gimple_val
, fb_rvalue
);
10721 recalculate_side_effects (*expr_p
);
10722 ret
= MIN (r0
, r1
);
10726 case CILK_SYNC_STMT
:
10728 if (!fn_contains_cilk_spawn_p (cfun
))
10730 error_at (EXPR_LOCATION (*expr_p
),
10731 "expected %<_Cilk_spawn%> before %<_Cilk_sync%>");
10736 gimplify_cilk_sync (expr_p
, pre_p
);
10743 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p
)))
10745 case tcc_comparison
:
10746 /* Handle comparison of objects of non scalar mode aggregates
10747 with a call to memcmp. It would be nice to only have to do
10748 this for variable-sized objects, but then we'd have to allow
10749 the same nest of reference nodes we allow for MODIFY_EXPR and
10750 that's too complex.
10752 Compare scalar mode aggregates as scalar mode values. Using
10753 memcmp for them would be very inefficient at best, and is
10754 plain wrong if bitfields are involved. */
10756 tree type
= TREE_TYPE (TREE_OPERAND (*expr_p
, 1));
10758 /* Vector comparisons need no boolification. */
10759 if (TREE_CODE (type
) == VECTOR_TYPE
)
10761 else if (!AGGREGATE_TYPE_P (type
))
10763 tree org_type
= TREE_TYPE (*expr_p
);
10764 *expr_p
= gimple_boolify (*expr_p
);
10765 if (!useless_type_conversion_p (org_type
,
10766 TREE_TYPE (*expr_p
)))
10768 *expr_p
= fold_convert_loc (input_location
,
10769 org_type
, *expr_p
);
10775 else if (TYPE_MODE (type
) != BLKmode
)
10776 ret
= gimplify_scalar_mode_aggregate_compare (expr_p
);
10778 ret
= gimplify_variable_sized_compare (expr_p
);
10783 /* If *EXPR_P does not need to be special-cased, handle it
10784 according to its class. */
10786 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
10787 post_p
, is_gimple_val
, fb_rvalue
);
10793 enum gimplify_status r0
, r1
;
10795 r0
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
10796 post_p
, is_gimple_val
, fb_rvalue
);
10797 r1
= gimplify_expr (&TREE_OPERAND (*expr_p
, 1), pre_p
,
10798 post_p
, is_gimple_val
, fb_rvalue
);
10800 ret
= MIN (r0
, r1
);
10806 enum gimplify_status r0
, r1
, r2
;
10808 r0
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
10809 post_p
, is_gimple_val
, fb_rvalue
);
10810 r1
= gimplify_expr (&TREE_OPERAND (*expr_p
, 1), pre_p
,
10811 post_p
, is_gimple_val
, fb_rvalue
);
10812 r2
= gimplify_expr (&TREE_OPERAND (*expr_p
, 2), pre_p
,
10813 post_p
, is_gimple_val
, fb_rvalue
);
10815 ret
= MIN (MIN (r0
, r1
), r2
);
10819 case tcc_declaration
:
10822 goto dont_recalculate
;
10825 gcc_unreachable ();
10828 recalculate_side_effects (*expr_p
);
10834 gcc_assert (*expr_p
|| ret
!= GS_OK
);
10836 while (ret
== GS_OK
);
10838 /* If we encountered an error_mark somewhere nested inside, either
10839 stub out the statement or propagate the error back out. */
10840 if (ret
== GS_ERROR
)
10847 /* This was only valid as a return value from the langhook, which
10848 we handled. Make sure it doesn't escape from any other context. */
10849 gcc_assert (ret
!= GS_UNHANDLED
);
10851 if (fallback
== fb_none
&& *expr_p
&& !is_gimple_stmt (*expr_p
))
10853 /* We aren't looking for a value, and we don't have a valid
10854 statement. If it doesn't have side-effects, throw it away. */
10855 if (!TREE_SIDE_EFFECTS (*expr_p
))
10857 else if (!TREE_THIS_VOLATILE (*expr_p
))
10859 /* This is probably a _REF that contains something nested that
10860 has side effects. Recurse through the operands to find it. */
10861 enum tree_code code
= TREE_CODE (*expr_p
);
10865 case COMPONENT_REF
:
10866 case REALPART_EXPR
:
10867 case IMAGPART_EXPR
:
10868 case VIEW_CONVERT_EXPR
:
10869 gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
10870 gimple_test_f
, fallback
);
10874 case ARRAY_RANGE_REF
:
10875 gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
10876 gimple_test_f
, fallback
);
10877 gimplify_expr (&TREE_OPERAND (*expr_p
, 1), pre_p
, post_p
,
10878 gimple_test_f
, fallback
);
10882 /* Anything else with side-effects must be converted to
10883 a valid statement before we get here. */
10884 gcc_unreachable ();
10889 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p
))
10890 && TYPE_MODE (TREE_TYPE (*expr_p
)) != BLKmode
)
10892 /* Historically, the compiler has treated a bare reference
10893 to a non-BLKmode volatile lvalue as forcing a load. */
10894 tree type
= TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p
));
10896 /* Normally, we do not want to create a temporary for a
10897 TREE_ADDRESSABLE type because such a type should not be
10898 copied by bitwise-assignment. However, we make an
10899 exception here, as all we are doing here is ensuring that
10900 we read the bytes that make up the type. We use
10901 create_tmp_var_raw because create_tmp_var will abort when
10902 given a TREE_ADDRESSABLE type. */
10903 tree tmp
= create_tmp_var_raw (type
, "vol");
10904 gimple_add_tmp_var (tmp
);
10905 gimplify_assign (tmp
, *expr_p
, pre_p
);
10909 /* We can't do anything useful with a volatile reference to
10910 an incomplete type, so just throw it away. Likewise for
10911 a BLKmode type, since any implicit inner load should
10912 already have been turned into an explicit one by the
10913 gimplification process. */
10917 /* If we are gimplifying at the statement level, we're done. Tack
10918 everything together and return. */
10919 if (fallback
== fb_none
|| is_statement
)
10921 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
10922 it out for GC to reclaim it. */
10923 *expr_p
= NULL_TREE
;
10925 if (!gimple_seq_empty_p (internal_pre
)
10926 || !gimple_seq_empty_p (internal_post
))
10928 gimplify_seq_add_seq (&internal_pre
, internal_post
);
10929 gimplify_seq_add_seq (pre_p
, internal_pre
);
10932 /* The result of gimplifying *EXPR_P is going to be the last few
10933 statements in *PRE_P and *POST_P. Add location information
10934 to all the statements that were added by the gimplification
10936 if (!gimple_seq_empty_p (*pre_p
))
10937 annotate_all_with_location_after (*pre_p
, pre_last_gsi
, input_location
);
10939 if (!gimple_seq_empty_p (*post_p
))
10940 annotate_all_with_location_after (*post_p
, post_last_gsi
,
10946 #ifdef ENABLE_GIMPLE_CHECKING
10949 enum tree_code code
= TREE_CODE (*expr_p
);
10950 /* These expressions should already be in gimple IR form. */
10951 gcc_assert (code
!= MODIFY_EXPR
10952 && code
!= ASM_EXPR
10953 && code
!= BIND_EXPR
10954 && code
!= CATCH_EXPR
10955 && (code
!= COND_EXPR
|| gimplify_ctxp
->allow_rhs_cond_expr
)
10956 && code
!= EH_FILTER_EXPR
10957 && code
!= GOTO_EXPR
10958 && code
!= LABEL_EXPR
10959 && code
!= LOOP_EXPR
10960 && code
!= SWITCH_EXPR
10961 && code
!= TRY_FINALLY_EXPR
10962 && code
!= OACC_PARALLEL
10963 && code
!= OACC_KERNELS
10964 && code
!= OACC_DATA
10965 && code
!= OACC_HOST_DATA
10966 && code
!= OACC_DECLARE
10967 && code
!= OACC_UPDATE
10968 && code
!= OACC_ENTER_DATA
10969 && code
!= OACC_EXIT_DATA
10970 && code
!= OACC_CACHE
10971 && code
!= OMP_CRITICAL
10973 && code
!= OACC_LOOP
10974 && code
!= OMP_MASTER
10975 && code
!= OMP_TASKGROUP
10976 && code
!= OMP_ORDERED
10977 && code
!= OMP_PARALLEL
10978 && code
!= OMP_SECTIONS
10979 && code
!= OMP_SECTION
10980 && code
!= OMP_SINGLE
);
10984 /* Otherwise we're gimplifying a subexpression, so the resulting
10985 value is interesting. If it's a valid operand that matches
10986 GIMPLE_TEST_F, we're done. Unless we are handling some
10987 post-effects internally; if that's the case, we need to copy into
10988 a temporary before adding the post-effects to POST_P. */
10989 if (gimple_seq_empty_p (internal_post
) && (*gimple_test_f
) (*expr_p
))
10992 /* Otherwise, we need to create a new temporary for the gimplified
10995 /* We can't return an lvalue if we have an internal postqueue. The
10996 object the lvalue refers to would (probably) be modified by the
10997 postqueue; we need to copy the value out first, which means an
10999 if ((fallback
& fb_lvalue
)
11000 && gimple_seq_empty_p (internal_post
)
11001 && is_gimple_addressable (*expr_p
))
11003 /* An lvalue will do. Take the address of the expression, store it
11004 in a temporary, and replace the expression with an INDIRECT_REF of
11006 tmp
= build_fold_addr_expr_loc (input_location
, *expr_p
);
11007 gimplify_expr (&tmp
, pre_p
, post_p
, is_gimple_reg
, fb_rvalue
);
11008 *expr_p
= build_simple_mem_ref (tmp
);
11010 else if ((fallback
& fb_rvalue
) && is_gimple_reg_rhs_or_call (*expr_p
))
11012 /* An rvalue will do. Assign the gimplified expression into a
11013 new temporary TMP and replace the original expression with
11014 TMP. First, make sure that the expression has a type so that
11015 it can be assigned into a temporary. */
11016 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p
)));
11017 *expr_p
= get_formal_tmp_var (*expr_p
, pre_p
);
11021 #ifdef ENABLE_GIMPLE_CHECKING
11022 if (!(fallback
& fb_mayfail
))
11024 fprintf (stderr
, "gimplification failed:\n");
11025 print_generic_expr (stderr
, *expr_p
, 0);
11026 debug_tree (*expr_p
);
11027 internal_error ("gimplification failed");
11030 gcc_assert (fallback
& fb_mayfail
);
11032 /* If this is an asm statement, and the user asked for the
11033 impossible, don't die. Fail and let gimplify_asm_expr
11039 /* Make sure the temporary matches our predicate. */
11040 gcc_assert ((*gimple_test_f
) (*expr_p
));
11042 if (!gimple_seq_empty_p (internal_post
))
11044 annotate_all_with_location (internal_post
, input_location
);
11045 gimplify_seq_add_seq (pre_p
, internal_post
);
11049 input_location
= saved_location
;
11053 /* Look through TYPE for variable-sized objects and gimplify each such
11054 size that we find. Add to LIST_P any statements generated. */
11057 gimplify_type_sizes (tree type
, gimple_seq
*list_p
)
11061 if (type
== NULL
|| type
== error_mark_node
)
11064 /* We first do the main variant, then copy into any other variants. */
11065 type
= TYPE_MAIN_VARIANT (type
);
11067 /* Avoid infinite recursion. */
11068 if (TYPE_SIZES_GIMPLIFIED (type
))
11071 TYPE_SIZES_GIMPLIFIED (type
) = 1;
11073 switch (TREE_CODE (type
))
11076 case ENUMERAL_TYPE
:
11079 case FIXED_POINT_TYPE
:
11080 gimplify_one_sizepos (&TYPE_MIN_VALUE (type
), list_p
);
11081 gimplify_one_sizepos (&TYPE_MAX_VALUE (type
), list_p
);
11083 for (t
= TYPE_NEXT_VARIANT (type
); t
; t
= TYPE_NEXT_VARIANT (t
))
11085 TYPE_MIN_VALUE (t
) = TYPE_MIN_VALUE (type
);
11086 TYPE_MAX_VALUE (t
) = TYPE_MAX_VALUE (type
);
11091 /* These types may not have declarations, so handle them here. */
11092 gimplify_type_sizes (TREE_TYPE (type
), list_p
);
11093 gimplify_type_sizes (TYPE_DOMAIN (type
), list_p
);
11094 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
11095 with assigned stack slots, for -O1+ -g they should be tracked
11097 if (!(TYPE_NAME (type
)
11098 && TREE_CODE (TYPE_NAME (type
)) == TYPE_DECL
11099 && DECL_IGNORED_P (TYPE_NAME (type
)))
11100 && TYPE_DOMAIN (type
)
11101 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type
)))
11103 t
= TYPE_MIN_VALUE (TYPE_DOMAIN (type
));
11104 if (t
&& TREE_CODE (t
) == VAR_DECL
&& DECL_ARTIFICIAL (t
))
11105 DECL_IGNORED_P (t
) = 0;
11106 t
= TYPE_MAX_VALUE (TYPE_DOMAIN (type
));
11107 if (t
&& TREE_CODE (t
) == VAR_DECL
&& DECL_ARTIFICIAL (t
))
11108 DECL_IGNORED_P (t
) = 0;
11114 case QUAL_UNION_TYPE
:
11115 for (field
= TYPE_FIELDS (type
); field
; field
= DECL_CHAIN (field
))
11116 if (TREE_CODE (field
) == FIELD_DECL
)
11118 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field
), list_p
);
11119 gimplify_one_sizepos (&DECL_SIZE (field
), list_p
);
11120 gimplify_one_sizepos (&DECL_SIZE_UNIT (field
), list_p
);
11121 gimplify_type_sizes (TREE_TYPE (field
), list_p
);
11126 case REFERENCE_TYPE
:
11127 /* We used to recurse on the pointed-to type here, which turned out to
11128 be incorrect because its definition might refer to variables not
11129 yet initialized at this point if a forward declaration is involved.
11131 It was actually useful for anonymous pointed-to types to ensure
11132 that the sizes evaluation dominates every possible later use of the
11133 values. Restricting to such types here would be safe since there
11134 is no possible forward declaration around, but would introduce an
11135 undesirable middle-end semantic to anonymity. We then defer to
11136 front-ends the responsibility of ensuring that the sizes are
11137 evaluated both early and late enough, e.g. by attaching artificial
11138 type declarations to the tree. */
11145 gimplify_one_sizepos (&TYPE_SIZE (type
), list_p
);
11146 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type
), list_p
);
11148 for (t
= TYPE_NEXT_VARIANT (type
); t
; t
= TYPE_NEXT_VARIANT (t
))
11150 TYPE_SIZE (t
) = TYPE_SIZE (type
);
11151 TYPE_SIZE_UNIT (t
) = TYPE_SIZE_UNIT (type
);
11152 TYPE_SIZES_GIMPLIFIED (t
) = 1;
11156 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
11157 a size or position, has had all of its SAVE_EXPRs evaluated.
11158 We add any required statements to *STMT_P. */
11161 gimplify_one_sizepos (tree
*expr_p
, gimple_seq
*stmt_p
)
11163 tree expr
= *expr_p
;
11165 /* We don't do anything if the value isn't there, is constant, or contains
11166 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
11167 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
11168 will want to replace it with a new variable, but that will cause problems
11169 if this type is from outside the function. It's OK to have that here. */
11170 if (is_gimple_sizepos (expr
))
11173 *expr_p
= unshare_expr (expr
);
11175 gimplify_expr (expr_p
, stmt_p
, NULL
, is_gimple_val
, fb_rvalue
);
11178 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
11179 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
11180 is true, also gimplify the parameters. */
11183 gimplify_body (tree fndecl
, bool do_parms
)
11185 location_t saved_location
= input_location
;
11186 gimple_seq parm_stmts
, seq
;
11187 gimple
*outer_stmt
;
11189 struct cgraph_node
*cgn
;
11191 timevar_push (TV_TREE_GIMPLIFY
);
11193 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
11195 default_rtl_profile ();
11197 gcc_assert (gimplify_ctxp
== NULL
);
11198 push_gimplify_context ();
11200 if (flag_openacc
|| flag_openmp
)
11202 gcc_assert (gimplify_omp_ctxp
== NULL
);
11203 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl
)))
11204 gimplify_omp_ctxp
= new_omp_context (ORT_TARGET
);
11207 /* Unshare most shared trees in the body and in that of any nested functions.
11208 It would seem we don't have to do this for nested functions because
11209 they are supposed to be output and then the outer function gimplified
11210 first, but the g++ front end doesn't always do it that way. */
11211 unshare_body (fndecl
);
11212 unvisit_body (fndecl
);
11214 cgn
= cgraph_node::get (fndecl
);
11215 if (cgn
&& cgn
->origin
)
11216 nonlocal_vlas
= new hash_set
<tree
>;
11218 /* Make sure input_location isn't set to something weird. */
11219 input_location
= DECL_SOURCE_LOCATION (fndecl
);
11221 /* Resolve callee-copies. This has to be done before processing
11222 the body so that DECL_VALUE_EXPR gets processed correctly. */
11223 parm_stmts
= do_parms
? gimplify_parameters () : NULL
;
11225 /* Gimplify the function's body. */
11227 gimplify_stmt (&DECL_SAVED_TREE (fndecl
), &seq
);
11228 outer_stmt
= gimple_seq_first_stmt (seq
);
11231 outer_stmt
= gimple_build_nop ();
11232 gimplify_seq_add_stmt (&seq
, outer_stmt
);
11235 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
11236 not the case, wrap everything in a GIMPLE_BIND to make it so. */
11237 if (gimple_code (outer_stmt
) == GIMPLE_BIND
11238 && gimple_seq_first (seq
) == gimple_seq_last (seq
))
11239 outer_bind
= as_a
<gbind
*> (outer_stmt
);
11241 outer_bind
= gimple_build_bind (NULL_TREE
, seq
, NULL
);
11243 DECL_SAVED_TREE (fndecl
) = NULL_TREE
;
11245 /* If we had callee-copies statements, insert them at the beginning
11246 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
11247 if (!gimple_seq_empty_p (parm_stmts
))
11251 gimplify_seq_add_seq (&parm_stmts
, gimple_bind_body (outer_bind
));
11252 gimple_bind_set_body (outer_bind
, parm_stmts
);
11254 for (parm
= DECL_ARGUMENTS (current_function_decl
);
11255 parm
; parm
= DECL_CHAIN (parm
))
11256 if (DECL_HAS_VALUE_EXPR_P (parm
))
11258 DECL_HAS_VALUE_EXPR_P (parm
) = 0;
11259 DECL_IGNORED_P (parm
) = 0;
11265 if (nonlocal_vla_vars
)
11267 /* tree-nested.c may later on call declare_vars (..., true);
11268 which relies on BLOCK_VARS chain to be the tail of the
11269 gimple_bind_vars chain. Ensure we don't violate that
11271 if (gimple_bind_block (outer_bind
)
11272 == DECL_INITIAL (current_function_decl
))
11273 declare_vars (nonlocal_vla_vars
, outer_bind
, true);
11275 BLOCK_VARS (DECL_INITIAL (current_function_decl
))
11276 = chainon (BLOCK_VARS (DECL_INITIAL (current_function_decl
)),
11277 nonlocal_vla_vars
);
11278 nonlocal_vla_vars
= NULL_TREE
;
11280 delete nonlocal_vlas
;
11281 nonlocal_vlas
= NULL
;
11284 if ((flag_openacc
|| flag_openmp
|| flag_openmp_simd
)
11285 && gimplify_omp_ctxp
)
11287 delete_omp_context (gimplify_omp_ctxp
);
11288 gimplify_omp_ctxp
= NULL
;
11291 pop_gimplify_context (outer_bind
);
11292 gcc_assert (gimplify_ctxp
== NULL
);
11294 if (flag_checking
&& !seen_error ())
11295 verify_gimple_in_seq (gimple_bind_body (outer_bind
));
11297 timevar_pop (TV_TREE_GIMPLIFY
);
11298 input_location
= saved_location
;
11303 typedef char *char_p
; /* For DEF_VEC_P. */
11305 /* Return whether we should exclude FNDECL from instrumentation. */
11308 flag_instrument_functions_exclude_p (tree fndecl
)
11312 v
= (vec
<char_p
> *) flag_instrument_functions_exclude_functions
;
11313 if (v
&& v
->length () > 0)
11319 name
= lang_hooks
.decl_printable_name (fndecl
, 0);
11320 FOR_EACH_VEC_ELT (*v
, i
, s
)
11321 if (strstr (name
, s
) != NULL
)
11325 v
= (vec
<char_p
> *) flag_instrument_functions_exclude_files
;
11326 if (v
&& v
->length () > 0)
11332 name
= DECL_SOURCE_FILE (fndecl
);
11333 FOR_EACH_VEC_ELT (*v
, i
, s
)
11334 if (strstr (name
, s
) != NULL
)
11341 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
11342 node for the function we want to gimplify.
11344 Return the sequence of GIMPLE statements corresponding to the body
11348 gimplify_function_tree (tree fndecl
)
11354 gcc_assert (!gimple_body (fndecl
));
11356 if (DECL_STRUCT_FUNCTION (fndecl
))
11357 push_cfun (DECL_STRUCT_FUNCTION (fndecl
));
11359 push_struct_function (fndecl
);
11361 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
11363 cfun
->curr_properties
|= PROP_gimple_lva
;
11365 for (parm
= DECL_ARGUMENTS (fndecl
); parm
; parm
= DECL_CHAIN (parm
))
11367 /* Preliminarily mark non-addressed complex variables as eligible
11368 for promotion to gimple registers. We'll transform their uses
11369 as we find them. */
11370 if ((TREE_CODE (TREE_TYPE (parm
)) == COMPLEX_TYPE
11371 || TREE_CODE (TREE_TYPE (parm
)) == VECTOR_TYPE
)
11372 && !TREE_THIS_VOLATILE (parm
)
11373 && !needs_to_live_in_memory (parm
))
11374 DECL_GIMPLE_REG_P (parm
) = 1;
11377 ret
= DECL_RESULT (fndecl
);
11378 if ((TREE_CODE (TREE_TYPE (ret
)) == COMPLEX_TYPE
11379 || TREE_CODE (TREE_TYPE (ret
)) == VECTOR_TYPE
)
11380 && !needs_to_live_in_memory (ret
))
11381 DECL_GIMPLE_REG_P (ret
) = 1;
11383 bind
= gimplify_body (fndecl
, true);
11385 /* The tree body of the function is no longer needed, replace it
11386 with the new GIMPLE body. */
11388 gimple_seq_add_stmt (&seq
, bind
);
11389 gimple_set_body (fndecl
, seq
);
11391 /* If we're instrumenting function entry/exit, then prepend the call to
11392 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
11393 catch the exit hook. */
11394 /* ??? Add some way to ignore exceptions for this TFE. */
11395 if (flag_instrument_function_entry_exit
11396 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl
)
11397 && !flag_instrument_functions_exclude_p (fndecl
))
11402 gimple_seq cleanup
= NULL
, body
= NULL
;
11406 x
= builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS
);
11407 call
= gimple_build_call (x
, 1, integer_zero_node
);
11408 tmp_var
= create_tmp_var (ptr_type_node
, "return_addr");
11409 gimple_call_set_lhs (call
, tmp_var
);
11410 gimplify_seq_add_stmt (&cleanup
, call
);
11411 x
= builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT
);
11412 call
= gimple_build_call (x
, 2,
11413 build_fold_addr_expr (current_function_decl
),
11415 gimplify_seq_add_stmt (&cleanup
, call
);
11416 tf
= gimple_build_try (seq
, cleanup
, GIMPLE_TRY_FINALLY
);
11418 x
= builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS
);
11419 call
= gimple_build_call (x
, 1, integer_zero_node
);
11420 tmp_var
= create_tmp_var (ptr_type_node
, "return_addr");
11421 gimple_call_set_lhs (call
, tmp_var
);
11422 gimplify_seq_add_stmt (&body
, call
);
11423 x
= builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER
);
11424 call
= gimple_build_call (x
, 2,
11425 build_fold_addr_expr (current_function_decl
),
11427 gimplify_seq_add_stmt (&body
, call
);
11428 gimplify_seq_add_stmt (&body
, tf
);
11429 new_bind
= gimple_build_bind (NULL
, body
, gimple_bind_block (bind
));
11430 /* Clear the block for BIND, since it is no longer directly inside
11431 the function, but within a try block. */
11432 gimple_bind_set_block (bind
, NULL
);
11434 /* Replace the current function body with the body
11435 wrapped in the try/finally TF. */
11437 gimple_seq_add_stmt (&seq
, new_bind
);
11438 gimple_set_body (fndecl
, seq
);
11442 if ((flag_sanitize
& SANITIZE_THREAD
) != 0
11443 && !lookup_attribute ("no_sanitize_thread", DECL_ATTRIBUTES (fndecl
)))
11445 gcall
*call
= gimple_build_call_internal (IFN_TSAN_FUNC_EXIT
, 0);
11446 gimple
*tf
= gimple_build_try (seq
, call
, GIMPLE_TRY_FINALLY
);
11447 gbind
*new_bind
= gimple_build_bind (NULL
, tf
, gimple_bind_block (bind
));
11448 /* Clear the block for BIND, since it is no longer directly inside
11449 the function, but within a try block. */
11450 gimple_bind_set_block (bind
, NULL
);
11451 /* Replace the current function body with the body
11452 wrapped in the try/finally TF. */
11454 gimple_seq_add_stmt (&seq
, new_bind
);
11455 gimple_set_body (fndecl
, seq
);
11458 DECL_SAVED_TREE (fndecl
) = NULL_TREE
;
11459 cfun
->curr_properties
|= PROP_gimple_any
;
11463 dump_function (TDI_generic
, fndecl
);
11466 /* Return a dummy expression of type TYPE in order to keep going after an
11470 dummy_object (tree type
)
11472 tree t
= build_int_cst (build_pointer_type (type
), 0);
11473 return build2 (MEM_REF
, type
, t
, t
);
11476 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
11477 builtin function, but a very special sort of operator. */
11479 enum gimplify_status
11480 gimplify_va_arg_expr (tree
*expr_p
, gimple_seq
*pre_p
,
11481 gimple_seq
*post_p ATTRIBUTE_UNUSED
)
11483 tree promoted_type
, have_va_type
;
11484 tree valist
= TREE_OPERAND (*expr_p
, 0);
11485 tree type
= TREE_TYPE (*expr_p
);
11487 location_t loc
= EXPR_LOCATION (*expr_p
);
11489 /* Verify that valist is of the proper type. */
11490 have_va_type
= TREE_TYPE (valist
);
11491 if (have_va_type
== error_mark_node
)
11493 have_va_type
= targetm
.canonical_va_list_type (have_va_type
);
11495 if (have_va_type
== NULL_TREE
)
11497 error_at (loc
, "first argument to %<va_arg%> not of type %<va_list%>");
11501 /* Generate a diagnostic for requesting data of a type that cannot
11502 be passed through `...' due to type promotion at the call site. */
11503 if ((promoted_type
= lang_hooks
.types
.type_promotes_to (type
))
11506 static bool gave_help
;
11509 /* Unfortunately, this is merely undefined, rather than a constraint
11510 violation, so we cannot make this an error. If this call is never
11511 executed, the program is still strictly conforming. */
11512 warned
= warning_at (loc
, 0,
11513 "%qT is promoted to %qT when passed through %<...%>",
11514 type
, promoted_type
);
11515 if (!gave_help
&& warned
)
11518 inform (loc
, "(so you should pass %qT not %qT to %<va_arg%>)",
11519 promoted_type
, type
);
11522 /* We can, however, treat "undefined" any way we please.
11523 Call abort to encourage the user to fix the program. */
11525 inform (loc
, "if this code is reached, the program will abort");
11526 /* Before the abort, allow the evaluation of the va_list
11527 expression to exit or longjmp. */
11528 gimplify_and_add (valist
, pre_p
);
11529 t
= build_call_expr_loc (loc
,
11530 builtin_decl_implicit (BUILT_IN_TRAP
), 0);
11531 gimplify_and_add (t
, pre_p
);
11533 /* This is dead code, but go ahead and finish so that the
11534 mode of the result comes out right. */
11535 *expr_p
= dummy_object (type
);
11536 return GS_ALL_DONE
;
11539 tag
= build_int_cst (build_pointer_type (type
), 0);
11540 *expr_p
= build_call_expr_internal_loc (loc
, IFN_VA_ARG
, type
, 2, valist
, tag
);
11542 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
11543 needs to be expanded. */
11544 cfun
->curr_properties
&= ~PROP_gimple_lva
;
11549 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
11551 DST/SRC are the destination and source respectively. You can pass
11552 ungimplified trees in DST or SRC, in which case they will be
11553 converted to a gimple operand if necessary.
11555 This function returns the newly created GIMPLE_ASSIGN tuple. */
11558 gimplify_assign (tree dst
, tree src
, gimple_seq
*seq_p
)
11560 tree t
= build2 (MODIFY_EXPR
, TREE_TYPE (dst
), dst
, src
);
11561 gimplify_and_add (t
, seq_p
);
11563 return gimple_seq_last_stmt (*seq_p
);
11567 gimplify_hasher::hash (const elt_t
*p
)
11570 return iterative_hash_expr (t
, 0);
11574 gimplify_hasher::equal (const elt_t
*p1
, const elt_t
*p2
)
11578 enum tree_code code
= TREE_CODE (t1
);
11580 if (TREE_CODE (t2
) != code
11581 || TREE_TYPE (t1
) != TREE_TYPE (t2
))
11584 if (!operand_equal_p (t1
, t2
, 0))
11587 /* Only allow them to compare equal if they also hash equal; otherwise
11588 results are nondeterminate, and we fail bootstrap comparison. */
11589 gcc_checking_assert (hash (p1
) == hash (p2
));