1 /* Tree lowering pass. This pass converts the GENERIC functions-as-trees
2 tree representation into the GIMPLE form.
3 Copyright (C) 2002-2016 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
;
158 unsigned into_ssa
: 1;
159 unsigned allow_rhs_cond_expr
: 1;
160 unsigned in_cleanup_point_expr
: 1;
161 unsigned keep_stack
: 1;
162 unsigned save_stack
: 1;
165 struct gimplify_omp_ctx
167 struct gimplify_omp_ctx
*outer_context
;
168 splay_tree variables
;
169 hash_set
<tree
> *privatized_types
;
170 /* Iteration variables in an OMP_FOR. */
171 vec
<tree
> loop_iter_var
;
173 enum omp_clause_default_kind default_kind
;
174 enum omp_region_type region_type
;
177 bool target_map_scalars_firstprivate
;
178 bool target_map_pointers_as_0len_arrays
;
179 bool target_firstprivatize_array_bases
;
182 static struct gimplify_ctx
*gimplify_ctxp
;
183 static struct gimplify_omp_ctx
*gimplify_omp_ctxp
;
185 /* Forward declaration. */
186 static enum gimplify_status
gimplify_compound_expr (tree
*, gimple_seq
*, bool);
187 static hash_map
<tree
, tree
> *oacc_declare_returns
;
188 static enum gimplify_status
gimplify_expr (tree
*, gimple_seq
*, gimple_seq
*,
189 bool (*) (tree
), fallback_t
, bool);
191 /* Shorter alias name for the above function for use in gimplify.c
195 gimplify_seq_add_stmt (gimple_seq
*seq_p
, gimple
*gs
)
197 gimple_seq_add_stmt_without_update (seq_p
, gs
);
200 /* Append sequence SRC to the end of sequence *DST_P. If *DST_P is
201 NULL, a new sequence is allocated. This function is
202 similar to gimple_seq_add_seq, but does not scan the operands.
203 During gimplification, we need to manipulate statement sequences
204 before the def/use vectors have been constructed. */
207 gimplify_seq_add_seq (gimple_seq
*dst_p
, gimple_seq src
)
209 gimple_stmt_iterator si
;
214 si
= gsi_last (*dst_p
);
215 gsi_insert_seq_after_without_update (&si
, src
, GSI_NEW_STMT
);
219 /* Pointer to a list of allocated gimplify_ctx structs to be used for pushing
220 and popping gimplify contexts. */
222 static struct gimplify_ctx
*ctx_pool
= NULL
;
224 /* Return a gimplify context struct from the pool. */
226 static inline struct gimplify_ctx
*
229 struct gimplify_ctx
* c
= ctx_pool
;
232 ctx_pool
= c
->prev_context
;
234 c
= XNEW (struct gimplify_ctx
);
236 memset (c
, '\0', sizeof (*c
));
240 /* Put gimplify context C back into the pool. */
243 ctx_free (struct gimplify_ctx
*c
)
245 c
->prev_context
= ctx_pool
;
249 /* Free allocated ctx stack memory. */
252 free_gimplify_stack (void)
254 struct gimplify_ctx
*c
;
256 while ((c
= ctx_pool
))
258 ctx_pool
= c
->prev_context
;
264 /* Set up a context for the gimplifier. */
267 push_gimplify_context (bool in_ssa
, bool rhs_cond_ok
)
269 struct gimplify_ctx
*c
= ctx_alloc ();
271 c
->prev_context
= gimplify_ctxp
;
273 gimplify_ctxp
->into_ssa
= in_ssa
;
274 gimplify_ctxp
->allow_rhs_cond_expr
= rhs_cond_ok
;
277 /* Tear down a context for the gimplifier. If BODY is non-null, then
278 put the temporaries into the outer BIND_EXPR. Otherwise, put them
281 BODY is not a sequence, but the first tuple in a sequence. */
284 pop_gimplify_context (gimple
*body
)
286 struct gimplify_ctx
*c
= gimplify_ctxp
;
289 && (!c
->bind_expr_stack
.exists ()
290 || c
->bind_expr_stack
.is_empty ()));
291 c
->bind_expr_stack
.release ();
292 gimplify_ctxp
= c
->prev_context
;
295 declare_vars (c
->temps
, body
, false);
297 record_vars (c
->temps
);
304 /* Push a GIMPLE_BIND tuple onto the stack of bindings. */
307 gimple_push_bind_expr (gbind
*bind_stmt
)
309 gimplify_ctxp
->bind_expr_stack
.reserve (8);
310 gimplify_ctxp
->bind_expr_stack
.safe_push (bind_stmt
);
313 /* Pop the first element off the stack of bindings. */
316 gimple_pop_bind_expr (void)
318 gimplify_ctxp
->bind_expr_stack
.pop ();
321 /* Return the first element of the stack of bindings. */
324 gimple_current_bind_expr (void)
326 return gimplify_ctxp
->bind_expr_stack
.last ();
329 /* Return the stack of bindings created during gimplification. */
332 gimple_bind_expr_stack (void)
334 return gimplify_ctxp
->bind_expr_stack
;
337 /* Return true iff there is a COND_EXPR between us and the innermost
338 CLEANUP_POINT_EXPR. This info is used by gimple_push_cleanup. */
341 gimple_conditional_context (void)
343 return gimplify_ctxp
->conditions
> 0;
346 /* Note that we've entered a COND_EXPR. */
349 gimple_push_condition (void)
351 #ifdef ENABLE_GIMPLE_CHECKING
352 if (gimplify_ctxp
->conditions
== 0)
353 gcc_assert (gimple_seq_empty_p (gimplify_ctxp
->conditional_cleanups
));
355 ++(gimplify_ctxp
->conditions
);
358 /* Note that we've left a COND_EXPR. If we're back at unconditional scope
359 now, add any conditional cleanups we've seen to the prequeue. */
362 gimple_pop_condition (gimple_seq
*pre_p
)
364 int conds
= --(gimplify_ctxp
->conditions
);
366 gcc_assert (conds
>= 0);
369 gimplify_seq_add_seq (pre_p
, gimplify_ctxp
->conditional_cleanups
);
370 gimplify_ctxp
->conditional_cleanups
= NULL
;
374 /* A stable comparison routine for use with splay trees and DECLs. */
377 splay_tree_compare_decl_uid (splay_tree_key xa
, splay_tree_key xb
)
382 return DECL_UID (a
) - DECL_UID (b
);
385 /* Create a new omp construct that deals with variable remapping. */
387 static struct gimplify_omp_ctx
*
388 new_omp_context (enum omp_region_type region_type
)
390 struct gimplify_omp_ctx
*c
;
392 c
= XCNEW (struct gimplify_omp_ctx
);
393 c
->outer_context
= gimplify_omp_ctxp
;
394 c
->variables
= splay_tree_new (splay_tree_compare_decl_uid
, 0, 0);
395 c
->privatized_types
= new hash_set
<tree
>;
396 c
->location
= input_location
;
397 c
->region_type
= region_type
;
398 if ((region_type
& ORT_TASK
) == 0)
399 c
->default_kind
= OMP_CLAUSE_DEFAULT_SHARED
;
401 c
->default_kind
= OMP_CLAUSE_DEFAULT_UNSPECIFIED
;
406 /* Destroy an omp construct that deals with variable remapping. */
409 delete_omp_context (struct gimplify_omp_ctx
*c
)
411 splay_tree_delete (c
->variables
);
412 delete c
->privatized_types
;
413 c
->loop_iter_var
.release ();
417 static void omp_add_variable (struct gimplify_omp_ctx
*, tree
, unsigned int);
418 static bool omp_notice_variable (struct gimplify_omp_ctx
*, tree
, bool);
420 /* Both gimplify the statement T and append it to *SEQ_P. This function
421 behaves exactly as gimplify_stmt, but you don't have to pass T as a
425 gimplify_and_add (tree t
, gimple_seq
*seq_p
)
427 gimplify_stmt (&t
, seq_p
);
430 /* Gimplify statement T into sequence *SEQ_P, and return the first
431 tuple in the sequence of generated tuples for this statement.
432 Return NULL if gimplifying T produced no tuples. */
435 gimplify_and_return_first (tree t
, gimple_seq
*seq_p
)
437 gimple_stmt_iterator last
= gsi_last (*seq_p
);
439 gimplify_and_add (t
, seq_p
);
441 if (!gsi_end_p (last
))
444 return gsi_stmt (last
);
447 return gimple_seq_first_stmt (*seq_p
);
450 /* Returns true iff T is a valid RHS for an assignment to an un-renamed
451 LHS, or for a call argument. */
454 is_gimple_mem_rhs (tree t
)
456 /* If we're dealing with a renamable type, either source or dest must be
457 a renamed variable. */
458 if (is_gimple_reg_type (TREE_TYPE (t
)))
459 return is_gimple_val (t
);
461 return is_gimple_val (t
) || is_gimple_lvalue (t
);
464 /* Return true if T is a CALL_EXPR or an expression that can be
465 assigned to a temporary. Note that this predicate should only be
466 used during gimplification. See the rationale for this in
467 gimplify_modify_expr. */
470 is_gimple_reg_rhs_or_call (tree t
)
472 return (get_gimple_rhs_class (TREE_CODE (t
)) != GIMPLE_INVALID_RHS
473 || TREE_CODE (t
) == CALL_EXPR
);
476 /* Return true if T is a valid memory RHS or a CALL_EXPR. Note that
477 this predicate should only be used during gimplification. See the
478 rationale for this in gimplify_modify_expr. */
481 is_gimple_mem_rhs_or_call (tree t
)
483 /* If we're dealing with a renamable type, either source or dest must be
484 a renamed variable. */
485 if (is_gimple_reg_type (TREE_TYPE (t
)))
486 return is_gimple_val (t
);
488 return (is_gimple_val (t
) || is_gimple_lvalue (t
)
489 || TREE_CODE (t
) == CALL_EXPR
);
492 /* Create a temporary with a name derived from VAL. Subroutine of
493 lookup_tmp_var; nobody else should call this function. */
496 create_tmp_from_val (tree val
)
498 /* Drop all qualifiers and address-space information from the value type. */
499 tree type
= TYPE_MAIN_VARIANT (TREE_TYPE (val
));
500 tree var
= create_tmp_var (type
, get_name (val
));
501 if (TREE_CODE (TREE_TYPE (var
)) == COMPLEX_TYPE
502 || TREE_CODE (TREE_TYPE (var
)) == VECTOR_TYPE
)
503 DECL_GIMPLE_REG_P (var
) = 1;
507 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
508 an existing expression temporary. */
511 lookup_tmp_var (tree val
, bool is_formal
)
515 /* If not optimizing, never really reuse a temporary. local-alloc
516 won't allocate any variable that is used in more than one basic
517 block, which means it will go into memory, causing much extra
518 work in reload and final and poorer code generation, outweighing
519 the extra memory allocation here. */
520 if (!optimize
|| !is_formal
|| TREE_SIDE_EFFECTS (val
))
521 ret
= create_tmp_from_val (val
);
528 if (!gimplify_ctxp
->temp_htab
)
529 gimplify_ctxp
->temp_htab
= new hash_table
<gimplify_hasher
> (1000);
530 slot
= gimplify_ctxp
->temp_htab
->find_slot (&elt
, INSERT
);
533 elt_p
= XNEW (elt_t
);
535 elt_p
->temp
= ret
= create_tmp_from_val (val
);
548 /* Helper for get_formal_tmp_var and get_initialized_tmp_var. */
551 internal_get_tmp_var (tree val
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
552 bool is_formal
, bool allow_ssa
)
556 /* Notice that we explicitly allow VAL to be a CALL_EXPR so that we
557 can create an INIT_EXPR and convert it into a GIMPLE_CALL below. */
558 gimplify_expr (&val
, pre_p
, post_p
, is_gimple_reg_rhs_or_call
,
562 && gimplify_ctxp
->into_ssa
563 && is_gimple_reg_type (TREE_TYPE (val
)))
565 t
= make_ssa_name (TYPE_MAIN_VARIANT (TREE_TYPE (val
)));
566 if (! gimple_in_ssa_p (cfun
))
568 const char *name
= get_name (val
);
570 SET_SSA_NAME_VAR_OR_IDENTIFIER (t
, create_tmp_var_name (name
));
574 t
= lookup_tmp_var (val
, is_formal
);
576 mod
= build2 (INIT_EXPR
, TREE_TYPE (t
), t
, unshare_expr (val
));
578 SET_EXPR_LOCATION (mod
, EXPR_LOC_OR_LOC (val
, input_location
));
580 /* gimplify_modify_expr might want to reduce this further. */
581 gimplify_and_add (mod
, pre_p
);
587 /* Return a formal temporary variable initialized with VAL. PRE_P is as
588 in gimplify_expr. Only use this function if:
590 1) The value of the unfactored expression represented by VAL will not
591 change between the initialization and use of the temporary, and
592 2) The temporary will not be otherwise modified.
594 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
595 and #2 means it is inappropriate for && temps.
597 For other cases, use get_initialized_tmp_var instead. */
600 get_formal_tmp_var (tree val
, gimple_seq
*pre_p
)
602 return internal_get_tmp_var (val
, pre_p
, NULL
, true, true);
605 /* Return a temporary variable initialized with VAL. PRE_P and POST_P
606 are as in gimplify_expr. */
609 get_initialized_tmp_var (tree val
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
612 return internal_get_tmp_var (val
, pre_p
, post_p
, false, allow_ssa
);
615 /* Declare all the variables in VARS in SCOPE. If DEBUG_INFO is true,
616 generate debug info for them; otherwise don't. */
619 declare_vars (tree vars
, gimple
*gs
, bool debug_info
)
626 gbind
*scope
= as_a
<gbind
*> (gs
);
628 temps
= nreverse (last
);
630 block
= gimple_bind_block (scope
);
631 gcc_assert (!block
|| TREE_CODE (block
) == BLOCK
);
632 if (!block
|| !debug_info
)
634 DECL_CHAIN (last
) = gimple_bind_vars (scope
);
635 gimple_bind_set_vars (scope
, temps
);
639 /* We need to attach the nodes both to the BIND_EXPR and to its
640 associated BLOCK for debugging purposes. The key point here
641 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
642 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
643 if (BLOCK_VARS (block
))
644 BLOCK_VARS (block
) = chainon (BLOCK_VARS (block
), temps
);
647 gimple_bind_set_vars (scope
,
648 chainon (gimple_bind_vars (scope
), temps
));
649 BLOCK_VARS (block
) = temps
;
655 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
656 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
657 no such upper bound can be obtained. */
660 force_constant_size (tree var
)
662 /* The only attempt we make is by querying the maximum size of objects
663 of the variable's type. */
665 HOST_WIDE_INT max_size
;
667 gcc_assert (TREE_CODE (var
) == VAR_DECL
);
669 max_size
= max_int_size_in_bytes (TREE_TYPE (var
));
671 gcc_assert (max_size
>= 0);
674 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var
)), max_size
);
676 = build_int_cst (TREE_TYPE (DECL_SIZE (var
)), max_size
* BITS_PER_UNIT
);
679 /* Push the temporary variable TMP into the current binding. */
682 gimple_add_tmp_var_fn (struct function
*fn
, tree tmp
)
684 gcc_assert (!DECL_CHAIN (tmp
) && !DECL_SEEN_IN_BIND_EXPR_P (tmp
));
686 /* Later processing assumes that the object size is constant, which might
687 not be true at this point. Force the use of a constant upper bound in
689 if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (tmp
)))
690 force_constant_size (tmp
);
692 DECL_CONTEXT (tmp
) = fn
->decl
;
693 DECL_SEEN_IN_BIND_EXPR_P (tmp
) = 1;
695 record_vars_into (tmp
, fn
->decl
);
698 /* Push the temporary variable TMP into the current binding. */
701 gimple_add_tmp_var (tree tmp
)
703 gcc_assert (!DECL_CHAIN (tmp
) && !DECL_SEEN_IN_BIND_EXPR_P (tmp
));
705 /* Later processing assumes that the object size is constant, which might
706 not be true at this point. Force the use of a constant upper bound in
708 if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (tmp
)))
709 force_constant_size (tmp
);
711 DECL_CONTEXT (tmp
) = current_function_decl
;
712 DECL_SEEN_IN_BIND_EXPR_P (tmp
) = 1;
716 DECL_CHAIN (tmp
) = gimplify_ctxp
->temps
;
717 gimplify_ctxp
->temps
= tmp
;
719 /* Mark temporaries local within the nearest enclosing parallel. */
720 if (gimplify_omp_ctxp
)
722 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
724 && (ctx
->region_type
== ORT_WORKSHARE
725 || ctx
->region_type
== ORT_SIMD
726 || ctx
->region_type
== ORT_ACC
))
727 ctx
= ctx
->outer_context
;
729 omp_add_variable (ctx
, tmp
, GOVD_LOCAL
| GOVD_SEEN
);
738 /* This case is for nested functions. We need to expose the locals
740 body_seq
= gimple_body (current_function_decl
);
741 declare_vars (tmp
, gimple_seq_first_stmt (body_seq
), false);
747 /* This page contains routines to unshare tree nodes, i.e. to duplicate tree
748 nodes that are referenced more than once in GENERIC functions. This is
749 necessary because gimplification (translation into GIMPLE) is performed
750 by modifying tree nodes in-place, so gimplication of a shared node in a
751 first context could generate an invalid GIMPLE form in a second context.
753 This is achieved with a simple mark/copy/unmark algorithm that walks the
754 GENERIC representation top-down, marks nodes with TREE_VISITED the first
755 time it encounters them, duplicates them if they already have TREE_VISITED
756 set, and finally removes the TREE_VISITED marks it has set.
758 The algorithm works only at the function level, i.e. it generates a GENERIC
759 representation of a function with no nodes shared within the function when
760 passed a GENERIC function (except for nodes that are allowed to be shared).
762 At the global level, it is also necessary to unshare tree nodes that are
763 referenced in more than one function, for the same aforementioned reason.
764 This requires some cooperation from the front-end. There are 2 strategies:
766 1. Manual unsharing. The front-end needs to call unshare_expr on every
767 expression that might end up being shared across functions.
769 2. Deep unsharing. This is an extension of regular unsharing. Instead
770 of calling unshare_expr on expressions that might be shared across
771 functions, the front-end pre-marks them with TREE_VISITED. This will
772 ensure that they are unshared on the first reference within functions
773 when the regular unsharing algorithm runs. The counterpart is that
774 this algorithm must look deeper than for manual unsharing, which is
775 specified by LANG_HOOKS_DEEP_UNSHARING.
777 If there are only few specific cases of node sharing across functions, it is
778 probably easier for a front-end to unshare the expressions manually. On the
779 contrary, if the expressions generated at the global level are as widespread
780 as expressions generated within functions, deep unsharing is very likely the
783 /* Similar to copy_tree_r but do not copy SAVE_EXPR or TARGET_EXPR nodes.
784 These nodes model computations that must be done once. If we were to
785 unshare something like SAVE_EXPR(i++), the gimplification process would
786 create wrong code. However, if DATA is non-null, it must hold a pointer
787 set that is used to unshare the subtrees of these nodes. */
790 mostly_copy_tree_r (tree
*tp
, int *walk_subtrees
, void *data
)
793 enum tree_code code
= TREE_CODE (t
);
795 /* Do not copy SAVE_EXPR, TARGET_EXPR or BIND_EXPR nodes themselves, but
796 copy their subtrees if we can make sure to do it only once. */
797 if (code
== SAVE_EXPR
|| code
== TARGET_EXPR
|| code
== BIND_EXPR
)
799 if (data
&& !((hash_set
<tree
> *)data
)->add (t
))
805 /* Stop at types, decls, constants like copy_tree_r. */
806 else if (TREE_CODE_CLASS (code
) == tcc_type
807 || TREE_CODE_CLASS (code
) == tcc_declaration
808 || TREE_CODE_CLASS (code
) == tcc_constant
809 /* We can't do anything sensible with a BLOCK used as an
810 expression, but we also can't just die when we see it
811 because of non-expression uses. So we avert our eyes
812 and cross our fingers. Silly Java. */
816 /* Cope with the statement expression extension. */
817 else if (code
== STATEMENT_LIST
)
820 /* Leave the bulk of the work to copy_tree_r itself. */
822 copy_tree_r (tp
, walk_subtrees
, NULL
);
827 /* Callback for walk_tree to unshare most of the shared trees rooted at *TP.
828 If *TP has been visited already, then *TP is deeply copied by calling
829 mostly_copy_tree_r. DATA is passed to mostly_copy_tree_r unmodified. */
832 copy_if_shared_r (tree
*tp
, int *walk_subtrees
, void *data
)
835 enum tree_code code
= TREE_CODE (t
);
837 /* Skip types, decls, and constants. But we do want to look at their
838 types and the bounds of types. Mark them as visited so we properly
839 unmark their subtrees on the unmark pass. If we've already seen them,
840 don't look down further. */
841 if (TREE_CODE_CLASS (code
) == tcc_type
842 || TREE_CODE_CLASS (code
) == tcc_declaration
843 || TREE_CODE_CLASS (code
) == tcc_constant
)
845 if (TREE_VISITED (t
))
848 TREE_VISITED (t
) = 1;
851 /* If this node has been visited already, unshare it and don't look
853 else if (TREE_VISITED (t
))
855 walk_tree (tp
, mostly_copy_tree_r
, data
, NULL
);
859 /* Otherwise, mark the node as visited and keep looking. */
861 TREE_VISITED (t
) = 1;
866 /* Unshare most of the shared trees rooted at *TP. DATA is passed to the
867 copy_if_shared_r callback unmodified. */
870 copy_if_shared (tree
*tp
, void *data
)
872 walk_tree (tp
, copy_if_shared_r
, data
, NULL
);
875 /* Unshare all the trees in the body of FNDECL, as well as in the bodies of
876 any nested functions. */
879 unshare_body (tree fndecl
)
881 struct cgraph_node
*cgn
= cgraph_node::get (fndecl
);
882 /* If the language requires deep unsharing, we need a pointer set to make
883 sure we don't repeatedly unshare subtrees of unshareable nodes. */
884 hash_set
<tree
> *visited
885 = lang_hooks
.deep_unsharing
? new hash_set
<tree
> : NULL
;
887 copy_if_shared (&DECL_SAVED_TREE (fndecl
), visited
);
888 copy_if_shared (&DECL_SIZE (DECL_RESULT (fndecl
)), visited
);
889 copy_if_shared (&DECL_SIZE_UNIT (DECL_RESULT (fndecl
)), visited
);
894 for (cgn
= cgn
->nested
; cgn
; cgn
= cgn
->next_nested
)
895 unshare_body (cgn
->decl
);
898 /* Callback for walk_tree to unmark the visited trees rooted at *TP.
899 Subtrees are walked until the first unvisited node is encountered. */
902 unmark_visited_r (tree
*tp
, int *walk_subtrees
, void *data ATTRIBUTE_UNUSED
)
906 /* If this node has been visited, unmark it and keep looking. */
907 if (TREE_VISITED (t
))
908 TREE_VISITED (t
) = 0;
910 /* Otherwise, don't look any deeper. */
917 /* Unmark the visited trees rooted at *TP. */
920 unmark_visited (tree
*tp
)
922 walk_tree (tp
, unmark_visited_r
, NULL
, NULL
);
925 /* Likewise, but mark all trees as not visited. */
928 unvisit_body (tree fndecl
)
930 struct cgraph_node
*cgn
= cgraph_node::get (fndecl
);
932 unmark_visited (&DECL_SAVED_TREE (fndecl
));
933 unmark_visited (&DECL_SIZE (DECL_RESULT (fndecl
)));
934 unmark_visited (&DECL_SIZE_UNIT (DECL_RESULT (fndecl
)));
937 for (cgn
= cgn
->nested
; cgn
; cgn
= cgn
->next_nested
)
938 unvisit_body (cgn
->decl
);
941 /* Unconditionally make an unshared copy of EXPR. This is used when using
942 stored expressions which span multiple functions, such as BINFO_VTABLE,
943 as the normal unsharing process can't tell that they're shared. */
946 unshare_expr (tree expr
)
948 walk_tree (&expr
, mostly_copy_tree_r
, NULL
, NULL
);
952 /* Worker for unshare_expr_without_location. */
955 prune_expr_location (tree
*tp
, int *walk_subtrees
, void *)
958 SET_EXPR_LOCATION (*tp
, UNKNOWN_LOCATION
);
964 /* Similar to unshare_expr but also prune all expression locations
968 unshare_expr_without_location (tree expr
)
970 walk_tree (&expr
, mostly_copy_tree_r
, NULL
, NULL
);
972 walk_tree (&expr
, prune_expr_location
, NULL
, NULL
);
976 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
977 contain statements and have a value. Assign its value to a temporary
978 and give it void_type_node. Return the temporary, or NULL_TREE if
979 WRAPPER was already void. */
982 voidify_wrapper_expr (tree wrapper
, tree temp
)
984 tree type
= TREE_TYPE (wrapper
);
985 if (type
&& !VOID_TYPE_P (type
))
989 /* Set p to point to the body of the wrapper. Loop until we find
990 something that isn't a wrapper. */
991 for (p
= &wrapper
; p
&& *p
; )
993 switch (TREE_CODE (*p
))
996 TREE_SIDE_EFFECTS (*p
) = 1;
997 TREE_TYPE (*p
) = void_type_node
;
998 /* For a BIND_EXPR, the body is operand 1. */
999 p
= &BIND_EXPR_BODY (*p
);
1002 case CLEANUP_POINT_EXPR
:
1003 case TRY_FINALLY_EXPR
:
1004 case TRY_CATCH_EXPR
:
1005 TREE_SIDE_EFFECTS (*p
) = 1;
1006 TREE_TYPE (*p
) = void_type_node
;
1007 p
= &TREE_OPERAND (*p
, 0);
1010 case STATEMENT_LIST
:
1012 tree_stmt_iterator i
= tsi_last (*p
);
1013 TREE_SIDE_EFFECTS (*p
) = 1;
1014 TREE_TYPE (*p
) = void_type_node
;
1015 p
= tsi_end_p (i
) ? NULL
: tsi_stmt_ptr (i
);
1020 /* Advance to the last statement. Set all container types to
1022 for (; TREE_CODE (*p
) == COMPOUND_EXPR
; p
= &TREE_OPERAND (*p
, 1))
1024 TREE_SIDE_EFFECTS (*p
) = 1;
1025 TREE_TYPE (*p
) = void_type_node
;
1029 case TRANSACTION_EXPR
:
1030 TREE_SIDE_EFFECTS (*p
) = 1;
1031 TREE_TYPE (*p
) = void_type_node
;
1032 p
= &TRANSACTION_EXPR_BODY (*p
);
1036 /* Assume that any tree upon which voidify_wrapper_expr is
1037 directly called is a wrapper, and that its body is op0. */
1040 TREE_SIDE_EFFECTS (*p
) = 1;
1041 TREE_TYPE (*p
) = void_type_node
;
1042 p
= &TREE_OPERAND (*p
, 0);
1050 if (p
== NULL
|| IS_EMPTY_STMT (*p
))
1054 /* The wrapper is on the RHS of an assignment that we're pushing
1056 gcc_assert (TREE_CODE (temp
) == INIT_EXPR
1057 || TREE_CODE (temp
) == MODIFY_EXPR
);
1058 TREE_OPERAND (temp
, 1) = *p
;
1063 temp
= create_tmp_var (type
, "retval");
1064 *p
= build2 (INIT_EXPR
, type
, temp
, *p
);
1073 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1074 a temporary through which they communicate. */
1077 build_stack_save_restore (gcall
**save
, gcall
**restore
)
1081 *save
= gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_SAVE
), 0);
1082 tmp_var
= create_tmp_var (ptr_type_node
, "saved_stack");
1083 gimple_call_set_lhs (*save
, tmp_var
);
1086 = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_RESTORE
),
1090 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1092 static enum gimplify_status
1093 gimplify_bind_expr (tree
*expr_p
, gimple_seq
*pre_p
)
1095 tree bind_expr
= *expr_p
;
1096 bool old_keep_stack
= gimplify_ctxp
->keep_stack
;
1097 bool old_save_stack
= gimplify_ctxp
->save_stack
;
1100 gimple_seq body
, cleanup
;
1102 location_t start_locus
= 0, end_locus
= 0;
1103 tree ret_clauses
= NULL
;
1105 tree temp
= voidify_wrapper_expr (bind_expr
, NULL
);
1107 /* Mark variables seen in this bind expr. */
1108 for (t
= BIND_EXPR_VARS (bind_expr
); t
; t
= DECL_CHAIN (t
))
1110 if (TREE_CODE (t
) == VAR_DECL
)
1112 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
1114 /* Mark variable as local. */
1115 if (ctx
&& ctx
->region_type
!= ORT_NONE
&& !DECL_EXTERNAL (t
)
1116 && (! DECL_SEEN_IN_BIND_EXPR_P (t
)
1117 || splay_tree_lookup (ctx
->variables
,
1118 (splay_tree_key
) t
) == NULL
))
1120 if (ctx
->region_type
== ORT_SIMD
1121 && TREE_ADDRESSABLE (t
)
1122 && !TREE_STATIC (t
))
1123 omp_add_variable (ctx
, t
, GOVD_PRIVATE
| GOVD_SEEN
);
1125 omp_add_variable (ctx
, t
, GOVD_LOCAL
| GOVD_SEEN
);
1128 DECL_SEEN_IN_BIND_EXPR_P (t
) = 1;
1130 if (DECL_HARD_REGISTER (t
) && !is_global_var (t
) && cfun
)
1131 cfun
->has_local_explicit_reg_vars
= true;
1134 /* Preliminarily mark non-addressed complex variables as eligible
1135 for promotion to gimple registers. We'll transform their uses
1137 if ((TREE_CODE (TREE_TYPE (t
)) == COMPLEX_TYPE
1138 || TREE_CODE (TREE_TYPE (t
)) == VECTOR_TYPE
)
1139 && !TREE_THIS_VOLATILE (t
)
1140 && (TREE_CODE (t
) == VAR_DECL
&& !DECL_HARD_REGISTER (t
))
1141 && !needs_to_live_in_memory (t
))
1142 DECL_GIMPLE_REG_P (t
) = 1;
1145 bind_stmt
= gimple_build_bind (BIND_EXPR_VARS (bind_expr
), NULL
,
1146 BIND_EXPR_BLOCK (bind_expr
));
1147 gimple_push_bind_expr (bind_stmt
);
1149 gimplify_ctxp
->keep_stack
= false;
1150 gimplify_ctxp
->save_stack
= false;
1152 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1154 gimplify_stmt (&BIND_EXPR_BODY (bind_expr
), &body
);
1155 gimple_bind_set_body (bind_stmt
, body
);
1157 /* Source location wise, the cleanup code (stack_restore and clobbers)
1158 belongs to the end of the block, so propagate what we have. The
1159 stack_save operation belongs to the beginning of block, which we can
1160 infer from the bind_expr directly if the block has no explicit
1162 if (BIND_EXPR_BLOCK (bind_expr
))
1164 end_locus
= BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr
));
1165 start_locus
= BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr
));
1167 if (start_locus
== 0)
1168 start_locus
= EXPR_LOCATION (bind_expr
);
1173 /* If the code both contains VLAs and calls alloca, then we cannot reclaim
1174 the stack space allocated to the VLAs. */
1175 if (gimplify_ctxp
->save_stack
&& !gimplify_ctxp
->keep_stack
)
1177 gcall
*stack_restore
;
1179 /* Save stack on entry and restore it on exit. Add a try_finally
1180 block to achieve this. */
1181 build_stack_save_restore (&stack_save
, &stack_restore
);
1183 gimple_set_location (stack_save
, start_locus
);
1184 gimple_set_location (stack_restore
, end_locus
);
1186 gimplify_seq_add_stmt (&cleanup
, stack_restore
);
1189 /* Add clobbers for all variables that go out of scope. */
1190 for (t
= BIND_EXPR_VARS (bind_expr
); t
; t
= DECL_CHAIN (t
))
1192 if (TREE_CODE (t
) == VAR_DECL
1193 && !is_global_var (t
)
1194 && DECL_CONTEXT (t
) == current_function_decl
1195 && !DECL_HARD_REGISTER (t
)
1196 && !TREE_THIS_VOLATILE (t
)
1197 && !DECL_HAS_VALUE_EXPR_P (t
)
1198 /* Only care for variables that have to be in memory. Others
1199 will be rewritten into SSA names, hence moved to the top-level. */
1200 && !is_gimple_reg (t
)
1201 && flag_stack_reuse
!= SR_NONE
)
1203 tree clobber
= build_constructor (TREE_TYPE (t
), NULL
);
1204 gimple
*clobber_stmt
;
1205 TREE_THIS_VOLATILE (clobber
) = 1;
1206 clobber_stmt
= gimple_build_assign (t
, clobber
);
1207 gimple_set_location (clobber_stmt
, end_locus
);
1208 gimplify_seq_add_stmt (&cleanup
, clobber_stmt
);
1210 if (flag_openacc
&& oacc_declare_returns
!= NULL
)
1212 tree
*c
= oacc_declare_returns
->get (t
);
1216 OMP_CLAUSE_CHAIN (*c
) = ret_clauses
;
1220 oacc_declare_returns
->remove (t
);
1222 if (oacc_declare_returns
->elements () == 0)
1224 delete oacc_declare_returns
;
1225 oacc_declare_returns
= NULL
;
1235 gimple_stmt_iterator si
= gsi_start (cleanup
);
1237 stmt
= gimple_build_omp_target (NULL
, GF_OMP_TARGET_KIND_OACC_DECLARE
,
1239 gsi_insert_seq_before_without_update (&si
, stmt
, GSI_NEW_STMT
);
1245 gimple_seq new_body
;
1248 gs
= gimple_build_try (gimple_bind_body (bind_stmt
), cleanup
,
1249 GIMPLE_TRY_FINALLY
);
1252 gimplify_seq_add_stmt (&new_body
, stack_save
);
1253 gimplify_seq_add_stmt (&new_body
, gs
);
1254 gimple_bind_set_body (bind_stmt
, new_body
);
1257 /* keep_stack propagates all the way up to the outermost BIND_EXPR. */
1258 if (!gimplify_ctxp
->keep_stack
)
1259 gimplify_ctxp
->keep_stack
= old_keep_stack
;
1260 gimplify_ctxp
->save_stack
= old_save_stack
;
1262 gimple_pop_bind_expr ();
1264 gimplify_seq_add_stmt (pre_p
, bind_stmt
);
1272 *expr_p
= NULL_TREE
;
1276 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1277 GIMPLE value, it is assigned to a new temporary and the statement is
1278 re-written to return the temporary.
1280 PRE_P points to the sequence where side effects that must happen before
1281 STMT should be stored. */
1283 static enum gimplify_status
1284 gimplify_return_expr (tree stmt
, gimple_seq
*pre_p
)
1287 tree ret_expr
= TREE_OPERAND (stmt
, 0);
1288 tree result_decl
, result
;
1290 if (ret_expr
== error_mark_node
)
1293 /* Implicit _Cilk_sync must be inserted right before any return statement
1294 if there is a _Cilk_spawn in the function. If the user has provided a
1295 _Cilk_sync, the optimizer should remove this duplicate one. */
1296 if (fn_contains_cilk_spawn_p (cfun
))
1298 tree impl_sync
= build0 (CILK_SYNC_STMT
, void_type_node
);
1299 gimplify_and_add (impl_sync
, pre_p
);
1303 || TREE_CODE (ret_expr
) == RESULT_DECL
1304 || ret_expr
== error_mark_node
)
1306 greturn
*ret
= gimple_build_return (ret_expr
);
1307 gimple_set_no_warning (ret
, TREE_NO_WARNING (stmt
));
1308 gimplify_seq_add_stmt (pre_p
, ret
);
1312 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl
))))
1313 result_decl
= NULL_TREE
;
1316 result_decl
= TREE_OPERAND (ret_expr
, 0);
1318 /* See through a return by reference. */
1319 if (TREE_CODE (result_decl
) == INDIRECT_REF
)
1320 result_decl
= TREE_OPERAND (result_decl
, 0);
1322 gcc_assert ((TREE_CODE (ret_expr
) == MODIFY_EXPR
1323 || TREE_CODE (ret_expr
) == INIT_EXPR
)
1324 && TREE_CODE (result_decl
) == RESULT_DECL
);
1327 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1328 Recall that aggregate_value_p is FALSE for any aggregate type that is
1329 returned in registers. If we're returning values in registers, then
1330 we don't want to extend the lifetime of the RESULT_DECL, particularly
1331 across another call. In addition, for those aggregates for which
1332 hard_function_value generates a PARALLEL, we'll die during normal
1333 expansion of structure assignments; there's special code in expand_return
1334 to handle this case that does not exist in expand_expr. */
1337 else if (aggregate_value_p (result_decl
, TREE_TYPE (current_function_decl
)))
1339 if (TREE_CODE (DECL_SIZE (result_decl
)) != INTEGER_CST
)
1341 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl
)))
1342 gimplify_type_sizes (TREE_TYPE (result_decl
), pre_p
);
1343 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1344 should be effectively allocated by the caller, i.e. all calls to
1345 this function must be subject to the Return Slot Optimization. */
1346 gimplify_one_sizepos (&DECL_SIZE (result_decl
), pre_p
);
1347 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl
), pre_p
);
1349 result
= result_decl
;
1351 else if (gimplify_ctxp
->return_temp
)
1352 result
= gimplify_ctxp
->return_temp
;
1355 result
= create_tmp_reg (TREE_TYPE (result_decl
));
1357 /* ??? With complex control flow (usually involving abnormal edges),
1358 we can wind up warning about an uninitialized value for this. Due
1359 to how this variable is constructed and initialized, this is never
1360 true. Give up and never warn. */
1361 TREE_NO_WARNING (result
) = 1;
1363 gimplify_ctxp
->return_temp
= result
;
1366 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1367 Then gimplify the whole thing. */
1368 if (result
!= result_decl
)
1369 TREE_OPERAND (ret_expr
, 0) = result
;
1371 gimplify_and_add (TREE_OPERAND (stmt
, 0), pre_p
);
1373 ret
= gimple_build_return (result
);
1374 gimple_set_no_warning (ret
, TREE_NO_WARNING (stmt
));
1375 gimplify_seq_add_stmt (pre_p
, ret
);
1380 /* Gimplify a variable-length array DECL. */
1383 gimplify_vla_decl (tree decl
, gimple_seq
*seq_p
)
1385 /* This is a variable-sized decl. Simplify its size and mark it
1386 for deferred expansion. */
1387 tree t
, addr
, ptr_type
;
1389 gimplify_one_sizepos (&DECL_SIZE (decl
), seq_p
);
1390 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl
), seq_p
);
1392 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1393 if (DECL_HAS_VALUE_EXPR_P (decl
))
1396 /* All occurrences of this decl in final gimplified code will be
1397 replaced by indirection. Setting DECL_VALUE_EXPR does two
1398 things: First, it lets the rest of the gimplifier know what
1399 replacement to use. Second, it lets the debug info know
1400 where to find the value. */
1401 ptr_type
= build_pointer_type (TREE_TYPE (decl
));
1402 addr
= create_tmp_var (ptr_type
, get_name (decl
));
1403 DECL_IGNORED_P (addr
) = 0;
1404 t
= build_fold_indirect_ref (addr
);
1405 TREE_THIS_NOTRAP (t
) = 1;
1406 SET_DECL_VALUE_EXPR (decl
, t
);
1407 DECL_HAS_VALUE_EXPR_P (decl
) = 1;
1409 t
= builtin_decl_explicit (BUILT_IN_ALLOCA_WITH_ALIGN
);
1410 t
= build_call_expr (t
, 2, DECL_SIZE_UNIT (decl
),
1411 size_int (DECL_ALIGN (decl
)));
1412 /* The call has been built for a variable-sized object. */
1413 CALL_ALLOCA_FOR_VAR_P (t
) = 1;
1414 t
= fold_convert (ptr_type
, t
);
1415 t
= build2 (MODIFY_EXPR
, TREE_TYPE (addr
), addr
, t
);
1417 gimplify_and_add (t
, seq_p
);
1420 /* A helper function to be called via walk_tree. Mark all labels under *TP
1421 as being forced. To be called for DECL_INITIAL of static variables. */
1424 force_labels_r (tree
*tp
, int *walk_subtrees
, void *data ATTRIBUTE_UNUSED
)
1428 if (TREE_CODE (*tp
) == LABEL_DECL
)
1430 FORCED_LABEL (*tp
) = 1;
1431 cfun
->has_forced_label_in_static
= 1;
1437 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
1438 and initialization explicit. */
1440 static enum gimplify_status
1441 gimplify_decl_expr (tree
*stmt_p
, gimple_seq
*seq_p
)
1443 tree stmt
= *stmt_p
;
1444 tree decl
= DECL_EXPR_DECL (stmt
);
1446 *stmt_p
= NULL_TREE
;
1448 if (TREE_TYPE (decl
) == error_mark_node
)
1451 if ((TREE_CODE (decl
) == TYPE_DECL
1452 || TREE_CODE (decl
) == VAR_DECL
)
1453 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl
)))
1455 gimplify_type_sizes (TREE_TYPE (decl
), seq_p
);
1456 if (TREE_CODE (TREE_TYPE (decl
)) == REFERENCE_TYPE
)
1457 gimplify_type_sizes (TREE_TYPE (TREE_TYPE (decl
)), seq_p
);
1460 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
1461 in case its size expressions contain problematic nodes like CALL_EXPR. */
1462 if (TREE_CODE (decl
) == TYPE_DECL
1463 && DECL_ORIGINAL_TYPE (decl
)
1464 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl
)))
1466 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl
), seq_p
);
1467 if (TREE_CODE (DECL_ORIGINAL_TYPE (decl
)) == REFERENCE_TYPE
)
1468 gimplify_type_sizes (TREE_TYPE (DECL_ORIGINAL_TYPE (decl
)), seq_p
);
1471 if (TREE_CODE (decl
) == VAR_DECL
&& !DECL_EXTERNAL (decl
))
1473 tree init
= DECL_INITIAL (decl
);
1475 if (TREE_CODE (DECL_SIZE_UNIT (decl
)) != INTEGER_CST
1476 || (!TREE_STATIC (decl
)
1477 && flag_stack_check
== GENERIC_STACK_CHECK
1478 && compare_tree_int (DECL_SIZE_UNIT (decl
),
1479 STACK_CHECK_MAX_VAR_SIZE
) > 0))
1480 gimplify_vla_decl (decl
, seq_p
);
1482 /* Some front ends do not explicitly declare all anonymous
1483 artificial variables. We compensate here by declaring the
1484 variables, though it would be better if the front ends would
1485 explicitly declare them. */
1486 if (!DECL_SEEN_IN_BIND_EXPR_P (decl
)
1487 && DECL_ARTIFICIAL (decl
) && DECL_NAME (decl
) == NULL_TREE
)
1488 gimple_add_tmp_var (decl
);
1490 if (init
&& init
!= error_mark_node
)
1492 if (!TREE_STATIC (decl
))
1494 DECL_INITIAL (decl
) = NULL_TREE
;
1495 init
= build2 (INIT_EXPR
, void_type_node
, decl
, init
);
1496 gimplify_and_add (init
, seq_p
);
1500 /* We must still examine initializers for static variables
1501 as they may contain a label address. */
1502 walk_tree (&init
, force_labels_r
, NULL
, NULL
);
1509 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1510 and replacing the LOOP_EXPR with goto, but if the loop contains an
1511 EXIT_EXPR, we need to append a label for it to jump to. */
1513 static enum gimplify_status
1514 gimplify_loop_expr (tree
*expr_p
, gimple_seq
*pre_p
)
1516 tree saved_label
= gimplify_ctxp
->exit_label
;
1517 tree start_label
= create_artificial_label (UNKNOWN_LOCATION
);
1519 gimplify_seq_add_stmt (pre_p
, gimple_build_label (start_label
));
1521 gimplify_ctxp
->exit_label
= NULL_TREE
;
1523 gimplify_and_add (LOOP_EXPR_BODY (*expr_p
), pre_p
);
1525 gimplify_seq_add_stmt (pre_p
, gimple_build_goto (start_label
));
1527 if (gimplify_ctxp
->exit_label
)
1528 gimplify_seq_add_stmt (pre_p
,
1529 gimple_build_label (gimplify_ctxp
->exit_label
));
1531 gimplify_ctxp
->exit_label
= saved_label
;
1537 /* Gimplify a statement list onto a sequence. These may be created either
1538 by an enlightened front-end, or by shortcut_cond_expr. */
1540 static enum gimplify_status
1541 gimplify_statement_list (tree
*expr_p
, gimple_seq
*pre_p
)
1543 tree temp
= voidify_wrapper_expr (*expr_p
, NULL
);
1545 tree_stmt_iterator i
= tsi_start (*expr_p
);
1547 while (!tsi_end_p (i
))
1549 gimplify_stmt (tsi_stmt_ptr (i
), pre_p
);
1562 /* Callback for walk_gimple_seq. */
1565 warn_switch_unreachable_r (gimple_stmt_iterator
*gsi_p
, bool *handled_ops_p
,
1566 struct walk_stmt_info
*wi
)
1568 gimple
*stmt
= gsi_stmt (*gsi_p
);
1570 *handled_ops_p
= true;
1571 switch (gimple_code (stmt
))
1574 /* A compiler-generated cleanup or a user-written try block.
1575 If it's empty, don't dive into it--that would result in
1576 worse location info. */
1577 if (gimple_try_eval (stmt
) == NULL
)
1580 return integer_zero_node
;
1585 case GIMPLE_EH_FILTER
:
1586 case GIMPLE_TRANSACTION
:
1587 /* Walk the sub-statements. */
1588 *handled_ops_p
= false;
1591 /* Save the first "real" statement (not a decl/lexical scope/...). */
1593 return integer_zero_node
;
1598 /* Possibly warn about unreachable statements between switch's controlling
1599 expression and the first case. SEQ is the body of a switch expression. */
1602 maybe_warn_switch_unreachable (gimple_seq seq
)
1604 if (!warn_switch_unreachable
1605 /* This warning doesn't play well with Fortran when optimizations
1607 || lang_GNU_Fortran ()
1611 struct walk_stmt_info wi
;
1612 memset (&wi
, 0, sizeof (wi
));
1613 walk_gimple_seq (seq
, warn_switch_unreachable_r
, NULL
, &wi
);
1614 gimple
*stmt
= (gimple
*) wi
.info
;
1616 if (stmt
&& gimple_code (stmt
) != GIMPLE_LABEL
)
1618 if (gimple_code (stmt
) == GIMPLE_GOTO
1619 && TREE_CODE (gimple_goto_dest (stmt
)) == LABEL_DECL
1620 && DECL_ARTIFICIAL (gimple_goto_dest (stmt
)))
1621 /* Don't warn for compiler-generated gotos. These occur
1622 in Duff's devices, for example. */;
1624 warning_at (gimple_location (stmt
), OPT_Wswitch_unreachable
,
1625 "statement will never be executed");
1630 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
1633 static enum gimplify_status
1634 gimplify_switch_expr (tree
*expr_p
, gimple_seq
*pre_p
)
1636 tree switch_expr
= *expr_p
;
1637 gimple_seq switch_body_seq
= NULL
;
1638 enum gimplify_status ret
;
1639 tree index_type
= TREE_TYPE (switch_expr
);
1640 if (index_type
== NULL_TREE
)
1641 index_type
= TREE_TYPE (SWITCH_COND (switch_expr
));
1643 ret
= gimplify_expr (&SWITCH_COND (switch_expr
), pre_p
, NULL
, is_gimple_val
,
1645 if (ret
== GS_ERROR
|| ret
== GS_UNHANDLED
)
1648 if (SWITCH_BODY (switch_expr
))
1651 vec
<tree
> saved_labels
;
1652 tree default_case
= NULL_TREE
;
1653 gswitch
*switch_stmt
;
1655 /* If someone can be bothered to fill in the labels, they can
1656 be bothered to null out the body too. */
1657 gcc_assert (!SWITCH_LABELS (switch_expr
));
1659 /* Save old labels, get new ones from body, then restore the old
1660 labels. Save all the things from the switch body to append after. */
1661 saved_labels
= gimplify_ctxp
->case_labels
;
1662 gimplify_ctxp
->case_labels
.create (8);
1664 gimplify_stmt (&SWITCH_BODY (switch_expr
), &switch_body_seq
);
1666 maybe_warn_switch_unreachable (switch_body_seq
);
1668 labels
= gimplify_ctxp
->case_labels
;
1669 gimplify_ctxp
->case_labels
= saved_labels
;
1671 preprocess_case_label_vec_for_gimple (labels
, index_type
,
1676 glabel
*new_default
;
1679 = build_case_label (NULL_TREE
, NULL_TREE
,
1680 create_artificial_label (UNKNOWN_LOCATION
));
1681 new_default
= gimple_build_label (CASE_LABEL (default_case
));
1682 gimplify_seq_add_stmt (&switch_body_seq
, new_default
);
1685 switch_stmt
= gimple_build_switch (SWITCH_COND (switch_expr
),
1686 default_case
, labels
);
1687 gimplify_seq_add_stmt (pre_p
, switch_stmt
);
1688 gimplify_seq_add_seq (pre_p
, switch_body_seq
);
1692 gcc_assert (SWITCH_LABELS (switch_expr
));
1697 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
1699 static enum gimplify_status
1700 gimplify_case_label_expr (tree
*expr_p
, gimple_seq
*pre_p
)
1702 struct gimplify_ctx
*ctxp
;
1705 /* Invalid programs can play Duff's Device type games with, for example,
1706 #pragma omp parallel. At least in the C front end, we don't
1707 detect such invalid branches until after gimplification, in the
1708 diagnose_omp_blocks pass. */
1709 for (ctxp
= gimplify_ctxp
; ; ctxp
= ctxp
->prev_context
)
1710 if (ctxp
->case_labels
.exists ())
1713 label_stmt
= gimple_build_label (CASE_LABEL (*expr_p
));
1714 ctxp
->case_labels
.safe_push (*expr_p
);
1715 gimplify_seq_add_stmt (pre_p
, label_stmt
);
1720 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
1724 build_and_jump (tree
*label_p
)
1726 if (label_p
== NULL
)
1727 /* If there's nowhere to jump, just fall through. */
1730 if (*label_p
== NULL_TREE
)
1732 tree label
= create_artificial_label (UNKNOWN_LOCATION
);
1736 return build1 (GOTO_EXPR
, void_type_node
, *label_p
);
1739 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
1740 This also involves building a label to jump to and communicating it to
1741 gimplify_loop_expr through gimplify_ctxp->exit_label. */
1743 static enum gimplify_status
1744 gimplify_exit_expr (tree
*expr_p
)
1746 tree cond
= TREE_OPERAND (*expr_p
, 0);
1749 expr
= build_and_jump (&gimplify_ctxp
->exit_label
);
1750 expr
= build3 (COND_EXPR
, void_type_node
, cond
, expr
, NULL_TREE
);
1756 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
1757 different from its canonical type, wrap the whole thing inside a
1758 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
1761 The canonical type of a COMPONENT_REF is the type of the field being
1762 referenced--unless the field is a bit-field which can be read directly
1763 in a smaller mode, in which case the canonical type is the
1764 sign-appropriate type corresponding to that mode. */
1767 canonicalize_component_ref (tree
*expr_p
)
1769 tree expr
= *expr_p
;
1772 gcc_assert (TREE_CODE (expr
) == COMPONENT_REF
);
1774 if (INTEGRAL_TYPE_P (TREE_TYPE (expr
)))
1775 type
= TREE_TYPE (get_unwidened (expr
, NULL_TREE
));
1777 type
= TREE_TYPE (TREE_OPERAND (expr
, 1));
1779 /* One could argue that all the stuff below is not necessary for
1780 the non-bitfield case and declare it a FE error if type
1781 adjustment would be needed. */
1782 if (TREE_TYPE (expr
) != type
)
1784 #ifdef ENABLE_TYPES_CHECKING
1785 tree old_type
= TREE_TYPE (expr
);
1789 /* We need to preserve qualifiers and propagate them from
1791 type_quals
= TYPE_QUALS (type
)
1792 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr
, 0)));
1793 if (TYPE_QUALS (type
) != type_quals
)
1794 type
= build_qualified_type (TYPE_MAIN_VARIANT (type
), type_quals
);
1796 /* Set the type of the COMPONENT_REF to the underlying type. */
1797 TREE_TYPE (expr
) = type
;
1799 #ifdef ENABLE_TYPES_CHECKING
1800 /* It is now a FE error, if the conversion from the canonical
1801 type to the original expression type is not useless. */
1802 gcc_assert (useless_type_conversion_p (old_type
, type
));
1807 /* If a NOP conversion is changing a pointer to array of foo to a pointer
1808 to foo, embed that change in the ADDR_EXPR by converting
1813 where L is the lower bound. For simplicity, only do this for constant
1815 The constraint is that the type of &array[L] is trivially convertible
1819 canonicalize_addr_expr (tree
*expr_p
)
1821 tree expr
= *expr_p
;
1822 tree addr_expr
= TREE_OPERAND (expr
, 0);
1823 tree datype
, ddatype
, pddatype
;
1825 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
1826 if (!POINTER_TYPE_P (TREE_TYPE (expr
))
1827 || TREE_CODE (addr_expr
) != ADDR_EXPR
)
1830 /* The addr_expr type should be a pointer to an array. */
1831 datype
= TREE_TYPE (TREE_TYPE (addr_expr
));
1832 if (TREE_CODE (datype
) != ARRAY_TYPE
)
1835 /* The pointer to element type shall be trivially convertible to
1836 the expression pointer type. */
1837 ddatype
= TREE_TYPE (datype
);
1838 pddatype
= build_pointer_type (ddatype
);
1839 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr
)),
1843 /* The lower bound and element sizes must be constant. */
1844 if (!TYPE_SIZE_UNIT (ddatype
)
1845 || TREE_CODE (TYPE_SIZE_UNIT (ddatype
)) != INTEGER_CST
1846 || !TYPE_DOMAIN (datype
) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype
))
1847 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype
))) != INTEGER_CST
)
1850 /* All checks succeeded. Build a new node to merge the cast. */
1851 *expr_p
= build4 (ARRAY_REF
, ddatype
, TREE_OPERAND (addr_expr
, 0),
1852 TYPE_MIN_VALUE (TYPE_DOMAIN (datype
)),
1853 NULL_TREE
, NULL_TREE
);
1854 *expr_p
= build1 (ADDR_EXPR
, pddatype
, *expr_p
);
1856 /* We can have stripped a required restrict qualifier above. */
1857 if (!useless_type_conversion_p (TREE_TYPE (expr
), TREE_TYPE (*expr_p
)))
1858 *expr_p
= fold_convert (TREE_TYPE (expr
), *expr_p
);
1861 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
1862 underneath as appropriate. */
1864 static enum gimplify_status
1865 gimplify_conversion (tree
*expr_p
)
1867 location_t loc
= EXPR_LOCATION (*expr_p
);
1868 gcc_assert (CONVERT_EXPR_P (*expr_p
));
1870 /* Then strip away all but the outermost conversion. */
1871 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p
, 0));
1873 /* And remove the outermost conversion if it's useless. */
1874 if (tree_ssa_useless_type_conversion (*expr_p
))
1875 *expr_p
= TREE_OPERAND (*expr_p
, 0);
1877 /* If we still have a conversion at the toplevel,
1878 then canonicalize some constructs. */
1879 if (CONVERT_EXPR_P (*expr_p
))
1881 tree sub
= TREE_OPERAND (*expr_p
, 0);
1883 /* If a NOP conversion is changing the type of a COMPONENT_REF
1884 expression, then canonicalize its type now in order to expose more
1885 redundant conversions. */
1886 if (TREE_CODE (sub
) == COMPONENT_REF
)
1887 canonicalize_component_ref (&TREE_OPERAND (*expr_p
, 0));
1889 /* If a NOP conversion is changing a pointer to array of foo
1890 to a pointer to foo, embed that change in the ADDR_EXPR. */
1891 else if (TREE_CODE (sub
) == ADDR_EXPR
)
1892 canonicalize_addr_expr (expr_p
);
1895 /* If we have a conversion to a non-register type force the
1896 use of a VIEW_CONVERT_EXPR instead. */
1897 if (CONVERT_EXPR_P (*expr_p
) && !is_gimple_reg_type (TREE_TYPE (*expr_p
)))
1898 *expr_p
= fold_build1_loc (loc
, VIEW_CONVERT_EXPR
, TREE_TYPE (*expr_p
),
1899 TREE_OPERAND (*expr_p
, 0));
1901 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
1902 if (TREE_CODE (*expr_p
) == CONVERT_EXPR
)
1903 TREE_SET_CODE (*expr_p
, NOP_EXPR
);
1908 /* Nonlocal VLAs seen in the current function. */
1909 static hash_set
<tree
> *nonlocal_vlas
;
1911 /* The VAR_DECLs created for nonlocal VLAs for debug info purposes. */
1912 static tree nonlocal_vla_vars
;
1914 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
1915 DECL_VALUE_EXPR, and it's worth re-examining things. */
1917 static enum gimplify_status
1918 gimplify_var_or_parm_decl (tree
*expr_p
)
1920 tree decl
= *expr_p
;
1922 /* ??? If this is a local variable, and it has not been seen in any
1923 outer BIND_EXPR, then it's probably the result of a duplicate
1924 declaration, for which we've already issued an error. It would
1925 be really nice if the front end wouldn't leak these at all.
1926 Currently the only known culprit is C++ destructors, as seen
1927 in g++.old-deja/g++.jason/binding.C. */
1928 if (TREE_CODE (decl
) == VAR_DECL
1929 && !DECL_SEEN_IN_BIND_EXPR_P (decl
)
1930 && !TREE_STATIC (decl
) && !DECL_EXTERNAL (decl
)
1931 && decl_function_context (decl
) == current_function_decl
)
1933 gcc_assert (seen_error ());
1937 /* When within an OMP context, notice uses of variables. */
1938 if (gimplify_omp_ctxp
&& omp_notice_variable (gimplify_omp_ctxp
, decl
, true))
1941 /* If the decl is an alias for another expression, substitute it now. */
1942 if (DECL_HAS_VALUE_EXPR_P (decl
))
1944 tree value_expr
= DECL_VALUE_EXPR (decl
);
1946 /* For referenced nonlocal VLAs add a decl for debugging purposes
1947 to the current function. */
1948 if (TREE_CODE (decl
) == VAR_DECL
1949 && TREE_CODE (DECL_SIZE_UNIT (decl
)) != INTEGER_CST
1950 && nonlocal_vlas
!= NULL
1951 && TREE_CODE (value_expr
) == INDIRECT_REF
1952 && TREE_CODE (TREE_OPERAND (value_expr
, 0)) == VAR_DECL
1953 && decl_function_context (decl
) != current_function_decl
)
1955 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
1957 && (ctx
->region_type
== ORT_WORKSHARE
1958 || ctx
->region_type
== ORT_SIMD
1959 || ctx
->region_type
== ORT_ACC
))
1960 ctx
= ctx
->outer_context
;
1961 if (!ctx
&& !nonlocal_vlas
->add (decl
))
1963 tree copy
= copy_node (decl
);
1965 lang_hooks
.dup_lang_specific_decl (copy
);
1966 SET_DECL_RTL (copy
, 0);
1967 TREE_USED (copy
) = 1;
1968 DECL_CHAIN (copy
) = nonlocal_vla_vars
;
1969 nonlocal_vla_vars
= copy
;
1970 SET_DECL_VALUE_EXPR (copy
, unshare_expr (value_expr
));
1971 DECL_HAS_VALUE_EXPR_P (copy
) = 1;
1975 *expr_p
= unshare_expr (value_expr
);
1982 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
1985 recalculate_side_effects (tree t
)
1987 enum tree_code code
= TREE_CODE (t
);
1988 int len
= TREE_OPERAND_LENGTH (t
);
1991 switch (TREE_CODE_CLASS (code
))
1993 case tcc_expression
:
1999 case PREDECREMENT_EXPR
:
2000 case PREINCREMENT_EXPR
:
2001 case POSTDECREMENT_EXPR
:
2002 case POSTINCREMENT_EXPR
:
2003 /* All of these have side-effects, no matter what their
2012 case tcc_comparison
: /* a comparison expression */
2013 case tcc_unary
: /* a unary arithmetic expression */
2014 case tcc_binary
: /* a binary arithmetic expression */
2015 case tcc_reference
: /* a reference */
2016 case tcc_vl_exp
: /* a function call */
2017 TREE_SIDE_EFFECTS (t
) = TREE_THIS_VOLATILE (t
);
2018 for (i
= 0; i
< len
; ++i
)
2020 tree op
= TREE_OPERAND (t
, i
);
2021 if (op
&& TREE_SIDE_EFFECTS (op
))
2022 TREE_SIDE_EFFECTS (t
) = 1;
2027 /* No side-effects. */
2035 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
2039 : min_lval '[' val ']'
2041 | compound_lval '[' val ']'
2042 | compound_lval '.' ID
2044 This is not part of the original SIMPLE definition, which separates
2045 array and member references, but it seems reasonable to handle them
2046 together. Also, this way we don't run into problems with union
2047 aliasing; gcc requires that for accesses through a union to alias, the
2048 union reference must be explicit, which was not always the case when we
2049 were splitting up array and member refs.
2051 PRE_P points to the sequence where side effects that must happen before
2052 *EXPR_P should be stored.
2054 POST_P points to the sequence where side effects that must happen after
2055 *EXPR_P should be stored. */
2057 static enum gimplify_status
2058 gimplify_compound_lval (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
2059 fallback_t fallback
)
2062 enum gimplify_status ret
= GS_ALL_DONE
, tret
;
2064 location_t loc
= EXPR_LOCATION (*expr_p
);
2065 tree expr
= *expr_p
;
2067 /* Create a stack of the subexpressions so later we can walk them in
2068 order from inner to outer. */
2069 auto_vec
<tree
, 10> expr_stack
;
2071 /* We can handle anything that get_inner_reference can deal with. */
2072 for (p
= expr_p
; ; p
= &TREE_OPERAND (*p
, 0))
2075 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
2076 if (TREE_CODE (*p
) == INDIRECT_REF
)
2077 *p
= fold_indirect_ref_loc (loc
, *p
);
2079 if (handled_component_p (*p
))
2081 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
2082 additional COMPONENT_REFs. */
2083 else if ((TREE_CODE (*p
) == VAR_DECL
|| TREE_CODE (*p
) == PARM_DECL
)
2084 && gimplify_var_or_parm_decl (p
) == GS_OK
)
2089 expr_stack
.safe_push (*p
);
2092 gcc_assert (expr_stack
.length ());
2094 /* Now EXPR_STACK is a stack of pointers to all the refs we've
2095 walked through and P points to the innermost expression.
2097 Java requires that we elaborated nodes in source order. That
2098 means we must gimplify the inner expression followed by each of
2099 the indices, in order. But we can't gimplify the inner
2100 expression until we deal with any variable bounds, sizes, or
2101 positions in order to deal with PLACEHOLDER_EXPRs.
2103 So we do this in three steps. First we deal with the annotations
2104 for any variables in the components, then we gimplify the base,
2105 then we gimplify any indices, from left to right. */
2106 for (i
= expr_stack
.length () - 1; i
>= 0; i
--)
2108 tree t
= expr_stack
[i
];
2110 if (TREE_CODE (t
) == ARRAY_REF
|| TREE_CODE (t
) == ARRAY_RANGE_REF
)
2112 /* Gimplify the low bound and element type size and put them into
2113 the ARRAY_REF. If these values are set, they have already been
2115 if (TREE_OPERAND (t
, 2) == NULL_TREE
)
2117 tree low
= unshare_expr (array_ref_low_bound (t
));
2118 if (!is_gimple_min_invariant (low
))
2120 TREE_OPERAND (t
, 2) = low
;
2121 tret
= gimplify_expr (&TREE_OPERAND (t
, 2), pre_p
,
2122 post_p
, is_gimple_reg
,
2124 ret
= MIN (ret
, tret
);
2129 tret
= gimplify_expr (&TREE_OPERAND (t
, 2), pre_p
, post_p
,
2130 is_gimple_reg
, fb_rvalue
);
2131 ret
= MIN (ret
, tret
);
2134 if (TREE_OPERAND (t
, 3) == NULL_TREE
)
2136 tree elmt_type
= TREE_TYPE (TREE_TYPE (TREE_OPERAND (t
, 0)));
2137 tree elmt_size
= unshare_expr (array_ref_element_size (t
));
2138 tree factor
= size_int (TYPE_ALIGN_UNIT (elmt_type
));
2140 /* Divide the element size by the alignment of the element
2143 = size_binop_loc (loc
, EXACT_DIV_EXPR
, elmt_size
, factor
);
2145 if (!is_gimple_min_invariant (elmt_size
))
2147 TREE_OPERAND (t
, 3) = elmt_size
;
2148 tret
= gimplify_expr (&TREE_OPERAND (t
, 3), pre_p
,
2149 post_p
, is_gimple_reg
,
2151 ret
= MIN (ret
, tret
);
2156 tret
= gimplify_expr (&TREE_OPERAND (t
, 3), pre_p
, post_p
,
2157 is_gimple_reg
, fb_rvalue
);
2158 ret
= MIN (ret
, tret
);
2161 else if (TREE_CODE (t
) == COMPONENT_REF
)
2163 /* Set the field offset into T and gimplify it. */
2164 if (TREE_OPERAND (t
, 2) == NULL_TREE
)
2166 tree offset
= unshare_expr (component_ref_field_offset (t
));
2167 tree field
= TREE_OPERAND (t
, 1);
2169 = size_int (DECL_OFFSET_ALIGN (field
) / BITS_PER_UNIT
);
2171 /* Divide the offset by its alignment. */
2172 offset
= size_binop_loc (loc
, EXACT_DIV_EXPR
, offset
, factor
);
2174 if (!is_gimple_min_invariant (offset
))
2176 TREE_OPERAND (t
, 2) = offset
;
2177 tret
= gimplify_expr (&TREE_OPERAND (t
, 2), pre_p
,
2178 post_p
, is_gimple_reg
,
2180 ret
= MIN (ret
, tret
);
2185 tret
= gimplify_expr (&TREE_OPERAND (t
, 2), pre_p
, post_p
,
2186 is_gimple_reg
, fb_rvalue
);
2187 ret
= MIN (ret
, tret
);
2192 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
2193 so as to match the min_lval predicate. Failure to do so may result
2194 in the creation of large aggregate temporaries. */
2195 tret
= gimplify_expr (p
, pre_p
, post_p
, is_gimple_min_lval
,
2196 fallback
| fb_lvalue
);
2197 ret
= MIN (ret
, tret
);
2199 /* And finally, the indices and operands of ARRAY_REF. During this
2200 loop we also remove any useless conversions. */
2201 for (; expr_stack
.length () > 0; )
2203 tree t
= expr_stack
.pop ();
2205 if (TREE_CODE (t
) == ARRAY_REF
|| TREE_CODE (t
) == ARRAY_RANGE_REF
)
2207 /* Gimplify the dimension. */
2208 if (!is_gimple_min_invariant (TREE_OPERAND (t
, 1)))
2210 tret
= gimplify_expr (&TREE_OPERAND (t
, 1), pre_p
, post_p
,
2211 is_gimple_val
, fb_rvalue
);
2212 ret
= MIN (ret
, tret
);
2216 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t
, 0));
2218 /* The innermost expression P may have originally had
2219 TREE_SIDE_EFFECTS set which would have caused all the outer
2220 expressions in *EXPR_P leading to P to also have had
2221 TREE_SIDE_EFFECTS set. */
2222 recalculate_side_effects (t
);
2225 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
2226 if ((fallback
& fb_rvalue
) && TREE_CODE (*expr_p
) == COMPONENT_REF
)
2228 canonicalize_component_ref (expr_p
);
2231 expr_stack
.release ();
2233 gcc_assert (*expr_p
== expr
|| ret
!= GS_ALL_DONE
);
2238 /* Gimplify the self modifying expression pointed to by EXPR_P
2241 PRE_P points to the list where side effects that must happen before
2242 *EXPR_P should be stored.
2244 POST_P points to the list where side effects that must happen after
2245 *EXPR_P should be stored.
2247 WANT_VALUE is nonzero iff we want to use the value of this expression
2248 in another expression.
2250 ARITH_TYPE is the type the computation should be performed in. */
2252 enum gimplify_status
2253 gimplify_self_mod_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
2254 bool want_value
, tree arith_type
)
2256 enum tree_code code
;
2257 tree lhs
, lvalue
, rhs
, t1
;
2258 gimple_seq post
= NULL
, *orig_post_p
= post_p
;
2260 enum tree_code arith_code
;
2261 enum gimplify_status ret
;
2262 location_t loc
= EXPR_LOCATION (*expr_p
);
2264 code
= TREE_CODE (*expr_p
);
2266 gcc_assert (code
== POSTINCREMENT_EXPR
|| code
== POSTDECREMENT_EXPR
2267 || code
== PREINCREMENT_EXPR
|| code
== PREDECREMENT_EXPR
);
2269 /* Prefix or postfix? */
2270 if (code
== POSTINCREMENT_EXPR
|| code
== POSTDECREMENT_EXPR
)
2271 /* Faster to treat as prefix if result is not used. */
2272 postfix
= want_value
;
2276 /* For postfix, make sure the inner expression's post side effects
2277 are executed after side effects from this expression. */
2281 /* Add or subtract? */
2282 if (code
== PREINCREMENT_EXPR
|| code
== POSTINCREMENT_EXPR
)
2283 arith_code
= PLUS_EXPR
;
2285 arith_code
= MINUS_EXPR
;
2287 /* Gimplify the LHS into a GIMPLE lvalue. */
2288 lvalue
= TREE_OPERAND (*expr_p
, 0);
2289 ret
= gimplify_expr (&lvalue
, pre_p
, post_p
, is_gimple_lvalue
, fb_lvalue
);
2290 if (ret
== GS_ERROR
)
2293 /* Extract the operands to the arithmetic operation. */
2295 rhs
= TREE_OPERAND (*expr_p
, 1);
2297 /* For postfix operator, we evaluate the LHS to an rvalue and then use
2298 that as the result value and in the postqueue operation. */
2301 ret
= gimplify_expr (&lhs
, pre_p
, post_p
, is_gimple_val
, fb_rvalue
);
2302 if (ret
== GS_ERROR
)
2305 lhs
= get_initialized_tmp_var (lhs
, pre_p
, NULL
);
2308 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
2309 if (POINTER_TYPE_P (TREE_TYPE (lhs
)))
2311 rhs
= convert_to_ptrofftype_loc (loc
, rhs
);
2312 if (arith_code
== MINUS_EXPR
)
2313 rhs
= fold_build1_loc (loc
, NEGATE_EXPR
, TREE_TYPE (rhs
), rhs
);
2314 t1
= fold_build2 (POINTER_PLUS_EXPR
, TREE_TYPE (*expr_p
), lhs
, rhs
);
2317 t1
= fold_convert (TREE_TYPE (*expr_p
),
2318 fold_build2 (arith_code
, arith_type
,
2319 fold_convert (arith_type
, lhs
),
2320 fold_convert (arith_type
, rhs
)));
2324 gimplify_assign (lvalue
, t1
, pre_p
);
2325 gimplify_seq_add_seq (orig_post_p
, post
);
2331 *expr_p
= build2 (MODIFY_EXPR
, TREE_TYPE (lvalue
), lvalue
, t1
);
2336 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
2339 maybe_with_size_expr (tree
*expr_p
)
2341 tree expr
= *expr_p
;
2342 tree type
= TREE_TYPE (expr
);
2345 /* If we've already wrapped this or the type is error_mark_node, we can't do
2347 if (TREE_CODE (expr
) == WITH_SIZE_EXPR
2348 || type
== error_mark_node
)
2351 /* If the size isn't known or is a constant, we have nothing to do. */
2352 size
= TYPE_SIZE_UNIT (type
);
2353 if (!size
|| TREE_CODE (size
) == INTEGER_CST
)
2356 /* Otherwise, make a WITH_SIZE_EXPR. */
2357 size
= unshare_expr (size
);
2358 size
= SUBSTITUTE_PLACEHOLDER_IN_EXPR (size
, expr
);
2359 *expr_p
= build2 (WITH_SIZE_EXPR
, type
, expr
, size
);
2362 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
2363 Store any side-effects in PRE_P. CALL_LOCATION is the location of
2364 the CALL_EXPR. If ALLOW_SSA is set the actual parameter may be
2365 gimplified to an SSA name. */
2367 enum gimplify_status
2368 gimplify_arg (tree
*arg_p
, gimple_seq
*pre_p
, location_t call_location
,
2371 bool (*test
) (tree
);
2374 /* In general, we allow lvalues for function arguments to avoid
2375 extra overhead of copying large aggregates out of even larger
2376 aggregates into temporaries only to copy the temporaries to
2377 the argument list. Make optimizers happy by pulling out to
2378 temporaries those types that fit in registers. */
2379 if (is_gimple_reg_type (TREE_TYPE (*arg_p
)))
2380 test
= is_gimple_val
, fb
= fb_rvalue
;
2383 test
= is_gimple_lvalue
, fb
= fb_either
;
2384 /* Also strip a TARGET_EXPR that would force an extra copy. */
2385 if (TREE_CODE (*arg_p
) == TARGET_EXPR
)
2387 tree init
= TARGET_EXPR_INITIAL (*arg_p
);
2389 && !VOID_TYPE_P (TREE_TYPE (init
)))
2394 /* If this is a variable sized type, we must remember the size. */
2395 maybe_with_size_expr (arg_p
);
2397 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
2398 /* Make sure arguments have the same location as the function call
2400 protected_set_expr_location (*arg_p
, call_location
);
2402 /* There is a sequence point before a function call. Side effects in
2403 the argument list must occur before the actual call. So, when
2404 gimplifying arguments, force gimplify_expr to use an internal
2405 post queue which is then appended to the end of PRE_P. */
2406 return gimplify_expr (arg_p
, pre_p
, NULL
, test
, fb
, allow_ssa
);
2409 /* Don't fold inside offloading or taskreg regions: it can break code by
2410 adding decl references that weren't in the source. We'll do it during
2411 omplower pass instead. */
2414 maybe_fold_stmt (gimple_stmt_iterator
*gsi
)
2416 struct gimplify_omp_ctx
*ctx
;
2417 for (ctx
= gimplify_omp_ctxp
; ctx
; ctx
= ctx
->outer_context
)
2418 if ((ctx
->region_type
& (ORT_TARGET
| ORT_PARALLEL
| ORT_TASK
)) != 0)
2420 return fold_stmt (gsi
);
2423 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
2424 WANT_VALUE is true if the result of the call is desired. */
2426 static enum gimplify_status
2427 gimplify_call_expr (tree
*expr_p
, gimple_seq
*pre_p
, bool want_value
)
2429 tree fndecl
, parms
, p
, fnptrtype
;
2430 enum gimplify_status ret
;
2433 bool builtin_va_start_p
= false;
2434 location_t loc
= EXPR_LOCATION (*expr_p
);
2436 gcc_assert (TREE_CODE (*expr_p
) == CALL_EXPR
);
2438 /* For reliable diagnostics during inlining, it is necessary that
2439 every call_expr be annotated with file and line. */
2440 if (! EXPR_HAS_LOCATION (*expr_p
))
2441 SET_EXPR_LOCATION (*expr_p
, input_location
);
2443 /* Gimplify internal functions created in the FEs. */
2444 if (CALL_EXPR_FN (*expr_p
) == NULL_TREE
)
2449 nargs
= call_expr_nargs (*expr_p
);
2450 enum internal_fn ifn
= CALL_EXPR_IFN (*expr_p
);
2451 auto_vec
<tree
> vargs (nargs
);
2453 for (i
= 0; i
< nargs
; i
++)
2455 gimplify_arg (&CALL_EXPR_ARG (*expr_p
, i
), pre_p
,
2456 EXPR_LOCATION (*expr_p
));
2457 vargs
.quick_push (CALL_EXPR_ARG (*expr_p
, i
));
2459 gimple
*call
= gimple_build_call_internal_vec (ifn
, vargs
);
2460 gimplify_seq_add_stmt (pre_p
, call
);
2464 /* This may be a call to a builtin function.
2466 Builtin function calls may be transformed into different
2467 (and more efficient) builtin function calls under certain
2468 circumstances. Unfortunately, gimplification can muck things
2469 up enough that the builtin expanders are not aware that certain
2470 transformations are still valid.
2472 So we attempt transformation/gimplification of the call before
2473 we gimplify the CALL_EXPR. At this time we do not manage to
2474 transform all calls in the same manner as the expanders do, but
2475 we do transform most of them. */
2476 fndecl
= get_callee_fndecl (*expr_p
);
2478 && DECL_BUILT_IN_CLASS (fndecl
) == BUILT_IN_NORMAL
)
2479 switch (DECL_FUNCTION_CODE (fndecl
))
2481 case BUILT_IN_ALLOCA
:
2482 case BUILT_IN_ALLOCA_WITH_ALIGN
:
2483 /* If the call has been built for a variable-sized object, then we
2484 want to restore the stack level when the enclosing BIND_EXPR is
2485 exited to reclaim the allocated space; otherwise, we precisely
2486 need to do the opposite and preserve the latest stack level. */
2487 if (CALL_ALLOCA_FOR_VAR_P (*expr_p
))
2488 gimplify_ctxp
->save_stack
= true;
2490 gimplify_ctxp
->keep_stack
= true;
2493 case BUILT_IN_VA_START
:
2495 builtin_va_start_p
= TRUE
;
2496 if (call_expr_nargs (*expr_p
) < 2)
2498 error ("too few arguments to function %<va_start%>");
2499 *expr_p
= build_empty_stmt (EXPR_LOCATION (*expr_p
));
2503 if (fold_builtin_next_arg (*expr_p
, true))
2505 *expr_p
= build_empty_stmt (EXPR_LOCATION (*expr_p
));
2514 if (fndecl
&& DECL_BUILT_IN (fndecl
))
2516 tree new_tree
= fold_call_expr (input_location
, *expr_p
, !want_value
);
2517 if (new_tree
&& new_tree
!= *expr_p
)
2519 /* There was a transformation of this call which computes the
2520 same value, but in a more efficient way. Return and try
2527 /* Remember the original function pointer type. */
2528 fnptrtype
= TREE_TYPE (CALL_EXPR_FN (*expr_p
));
2530 /* There is a sequence point before the call, so any side effects in
2531 the calling expression must occur before the actual call. Force
2532 gimplify_expr to use an internal post queue. */
2533 ret
= gimplify_expr (&CALL_EXPR_FN (*expr_p
), pre_p
, NULL
,
2534 is_gimple_call_addr
, fb_rvalue
);
2536 nargs
= call_expr_nargs (*expr_p
);
2538 /* Get argument types for verification. */
2539 fndecl
= get_callee_fndecl (*expr_p
);
2542 parms
= TYPE_ARG_TYPES (TREE_TYPE (fndecl
));
2544 parms
= TYPE_ARG_TYPES (TREE_TYPE (fnptrtype
));
2546 if (fndecl
&& DECL_ARGUMENTS (fndecl
))
2547 p
= DECL_ARGUMENTS (fndecl
);
2552 for (i
= 0; i
< nargs
&& p
; i
++, p
= TREE_CHAIN (p
))
2555 /* If the last argument is __builtin_va_arg_pack () and it is not
2556 passed as a named argument, decrease the number of CALL_EXPR
2557 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
2560 && TREE_CODE (CALL_EXPR_ARG (*expr_p
, nargs
- 1)) == CALL_EXPR
)
2562 tree last_arg
= CALL_EXPR_ARG (*expr_p
, nargs
- 1);
2563 tree last_arg_fndecl
= get_callee_fndecl (last_arg
);
2566 && TREE_CODE (last_arg_fndecl
) == FUNCTION_DECL
2567 && DECL_BUILT_IN_CLASS (last_arg_fndecl
) == BUILT_IN_NORMAL
2568 && DECL_FUNCTION_CODE (last_arg_fndecl
) == BUILT_IN_VA_ARG_PACK
)
2570 tree call
= *expr_p
;
2573 *expr_p
= build_call_array_loc (loc
, TREE_TYPE (call
),
2574 CALL_EXPR_FN (call
),
2575 nargs
, CALL_EXPR_ARGP (call
));
2577 /* Copy all CALL_EXPR flags, location and block, except
2578 CALL_EXPR_VA_ARG_PACK flag. */
2579 CALL_EXPR_STATIC_CHAIN (*expr_p
) = CALL_EXPR_STATIC_CHAIN (call
);
2580 CALL_EXPR_TAILCALL (*expr_p
) = CALL_EXPR_TAILCALL (call
);
2581 CALL_EXPR_RETURN_SLOT_OPT (*expr_p
)
2582 = CALL_EXPR_RETURN_SLOT_OPT (call
);
2583 CALL_FROM_THUNK_P (*expr_p
) = CALL_FROM_THUNK_P (call
);
2584 SET_EXPR_LOCATION (*expr_p
, EXPR_LOCATION (call
));
2586 /* Set CALL_EXPR_VA_ARG_PACK. */
2587 CALL_EXPR_VA_ARG_PACK (*expr_p
) = 1;
2591 /* If the call returns twice then after building the CFG the call
2592 argument computations will no longer dominate the call because
2593 we add an abnormal incoming edge to the call. So do not use SSA
2595 bool returns_twice
= call_expr_flags (*expr_p
) & ECF_RETURNS_TWICE
;
2597 /* Gimplify the function arguments. */
2600 for (i
= (PUSH_ARGS_REVERSED
? nargs
- 1 : 0);
2601 PUSH_ARGS_REVERSED
? i
>= 0 : i
< nargs
;
2602 PUSH_ARGS_REVERSED
? i
-- : i
++)
2604 enum gimplify_status t
;
2606 /* Avoid gimplifying the second argument to va_start, which needs to
2607 be the plain PARM_DECL. */
2608 if ((i
!= 1) || !builtin_va_start_p
)
2610 t
= gimplify_arg (&CALL_EXPR_ARG (*expr_p
, i
), pre_p
,
2611 EXPR_LOCATION (*expr_p
), ! returns_twice
);
2619 /* Gimplify the static chain. */
2620 if (CALL_EXPR_STATIC_CHAIN (*expr_p
))
2622 if (fndecl
&& !DECL_STATIC_CHAIN (fndecl
))
2623 CALL_EXPR_STATIC_CHAIN (*expr_p
) = NULL
;
2626 enum gimplify_status t
;
2627 t
= gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p
), pre_p
,
2628 EXPR_LOCATION (*expr_p
), ! returns_twice
);
2634 /* Verify the function result. */
2635 if (want_value
&& fndecl
2636 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype
))))
2638 error_at (loc
, "using result of function returning %<void%>");
2642 /* Try this again in case gimplification exposed something. */
2643 if (ret
!= GS_ERROR
)
2645 tree new_tree
= fold_call_expr (input_location
, *expr_p
, !want_value
);
2647 if (new_tree
&& new_tree
!= *expr_p
)
2649 /* There was a transformation of this call which computes the
2650 same value, but in a more efficient way. Return and try
2658 *expr_p
= error_mark_node
;
2662 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
2663 decl. This allows us to eliminate redundant or useless
2664 calls to "const" functions. */
2665 if (TREE_CODE (*expr_p
) == CALL_EXPR
)
2667 int flags
= call_expr_flags (*expr_p
);
2668 if (flags
& (ECF_CONST
| ECF_PURE
)
2669 /* An infinite loop is considered a side effect. */
2670 && !(flags
& (ECF_LOOPING_CONST_OR_PURE
)))
2671 TREE_SIDE_EFFECTS (*expr_p
) = 0;
2674 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
2675 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
2676 form and delegate the creation of a GIMPLE_CALL to
2677 gimplify_modify_expr. This is always possible because when
2678 WANT_VALUE is true, the caller wants the result of this call into
2679 a temporary, which means that we will emit an INIT_EXPR in
2680 internal_get_tmp_var which will then be handled by
2681 gimplify_modify_expr. */
2684 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
2685 have to do is replicate it as a GIMPLE_CALL tuple. */
2686 gimple_stmt_iterator gsi
;
2687 call
= gimple_build_call_from_tree (*expr_p
);
2688 gimple_call_set_fntype (call
, TREE_TYPE (fnptrtype
));
2689 notice_special_calls (call
);
2690 gimplify_seq_add_stmt (pre_p
, call
);
2691 gsi
= gsi_last (*pre_p
);
2692 maybe_fold_stmt (&gsi
);
2693 *expr_p
= NULL_TREE
;
2696 /* Remember the original function type. */
2697 CALL_EXPR_FN (*expr_p
) = build1 (NOP_EXPR
, fnptrtype
,
2698 CALL_EXPR_FN (*expr_p
));
2703 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
2704 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
2706 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
2707 condition is true or false, respectively. If null, we should generate
2708 our own to skip over the evaluation of this specific expression.
2710 LOCUS is the source location of the COND_EXPR.
2712 This function is the tree equivalent of do_jump.
2714 shortcut_cond_r should only be called by shortcut_cond_expr. */
2717 shortcut_cond_r (tree pred
, tree
*true_label_p
, tree
*false_label_p
,
2720 tree local_label
= NULL_TREE
;
2721 tree t
, expr
= NULL
;
2723 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
2724 retain the shortcut semantics. Just insert the gotos here;
2725 shortcut_cond_expr will append the real blocks later. */
2726 if (TREE_CODE (pred
) == TRUTH_ANDIF_EXPR
)
2728 location_t new_locus
;
2730 /* Turn if (a && b) into
2732 if (a); else goto no;
2733 if (b) goto yes; else goto no;
2736 if (false_label_p
== NULL
)
2737 false_label_p
= &local_label
;
2739 /* Keep the original source location on the first 'if'. */
2740 t
= shortcut_cond_r (TREE_OPERAND (pred
, 0), NULL
, false_label_p
, locus
);
2741 append_to_statement_list (t
, &expr
);
2743 /* Set the source location of the && on the second 'if'. */
2744 new_locus
= EXPR_HAS_LOCATION (pred
) ? EXPR_LOCATION (pred
) : locus
;
2745 t
= shortcut_cond_r (TREE_OPERAND (pred
, 1), true_label_p
, false_label_p
,
2747 append_to_statement_list (t
, &expr
);
2749 else if (TREE_CODE (pred
) == TRUTH_ORIF_EXPR
)
2751 location_t new_locus
;
2753 /* Turn if (a || b) into
2756 if (b) goto yes; else goto no;
2759 if (true_label_p
== NULL
)
2760 true_label_p
= &local_label
;
2762 /* Keep the original source location on the first 'if'. */
2763 t
= shortcut_cond_r (TREE_OPERAND (pred
, 0), true_label_p
, NULL
, locus
);
2764 append_to_statement_list (t
, &expr
);
2766 /* Set the source location of the || on the second 'if'. */
2767 new_locus
= EXPR_HAS_LOCATION (pred
) ? EXPR_LOCATION (pred
) : locus
;
2768 t
= shortcut_cond_r (TREE_OPERAND (pred
, 1), true_label_p
, false_label_p
,
2770 append_to_statement_list (t
, &expr
);
2772 else if (TREE_CODE (pred
) == COND_EXPR
2773 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred
, 1)))
2774 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred
, 2))))
2776 location_t new_locus
;
2778 /* As long as we're messing with gotos, turn if (a ? b : c) into
2780 if (b) goto yes; else goto no;
2782 if (c) goto yes; else goto no;
2784 Don't do this if one of the arms has void type, which can happen
2785 in C++ when the arm is throw. */
2787 /* Keep the original source location on the first 'if'. Set the source
2788 location of the ? on the second 'if'. */
2789 new_locus
= EXPR_HAS_LOCATION (pred
) ? EXPR_LOCATION (pred
) : locus
;
2790 expr
= build3 (COND_EXPR
, void_type_node
, TREE_OPERAND (pred
, 0),
2791 shortcut_cond_r (TREE_OPERAND (pred
, 1), true_label_p
,
2792 false_label_p
, locus
),
2793 shortcut_cond_r (TREE_OPERAND (pred
, 2), true_label_p
,
2794 false_label_p
, new_locus
));
2798 expr
= build3 (COND_EXPR
, void_type_node
, pred
,
2799 build_and_jump (true_label_p
),
2800 build_and_jump (false_label_p
));
2801 SET_EXPR_LOCATION (expr
, locus
);
2806 t
= build1 (LABEL_EXPR
, void_type_node
, local_label
);
2807 append_to_statement_list (t
, &expr
);
2813 /* Given a conditional expression EXPR with short-circuit boolean
2814 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
2815 predicate apart into the equivalent sequence of conditionals. */
2818 shortcut_cond_expr (tree expr
)
2820 tree pred
= TREE_OPERAND (expr
, 0);
2821 tree then_
= TREE_OPERAND (expr
, 1);
2822 tree else_
= TREE_OPERAND (expr
, 2);
2823 tree true_label
, false_label
, end_label
, t
;
2825 tree
*false_label_p
;
2826 bool emit_end
, emit_false
, jump_over_else
;
2827 bool then_se
= then_
&& TREE_SIDE_EFFECTS (then_
);
2828 bool else_se
= else_
&& TREE_SIDE_EFFECTS (else_
);
2830 /* First do simple transformations. */
2833 /* If there is no 'else', turn
2836 if (a) if (b) then c. */
2837 while (TREE_CODE (pred
) == TRUTH_ANDIF_EXPR
)
2839 /* Keep the original source location on the first 'if'. */
2840 location_t locus
= EXPR_LOC_OR_LOC (expr
, input_location
);
2841 TREE_OPERAND (expr
, 0) = TREE_OPERAND (pred
, 1);
2842 /* Set the source location of the && on the second 'if'. */
2843 if (EXPR_HAS_LOCATION (pred
))
2844 SET_EXPR_LOCATION (expr
, EXPR_LOCATION (pred
));
2845 then_
= shortcut_cond_expr (expr
);
2846 then_se
= then_
&& TREE_SIDE_EFFECTS (then_
);
2847 pred
= TREE_OPERAND (pred
, 0);
2848 expr
= build3 (COND_EXPR
, void_type_node
, pred
, then_
, NULL_TREE
);
2849 SET_EXPR_LOCATION (expr
, locus
);
2855 /* If there is no 'then', turn
2858 if (a); else if (b); else d. */
2859 while (TREE_CODE (pred
) == TRUTH_ORIF_EXPR
)
2861 /* Keep the original source location on the first 'if'. */
2862 location_t locus
= EXPR_LOC_OR_LOC (expr
, input_location
);
2863 TREE_OPERAND (expr
, 0) = TREE_OPERAND (pred
, 1);
2864 /* Set the source location of the || on the second 'if'. */
2865 if (EXPR_HAS_LOCATION (pred
))
2866 SET_EXPR_LOCATION (expr
, EXPR_LOCATION (pred
));
2867 else_
= shortcut_cond_expr (expr
);
2868 else_se
= else_
&& TREE_SIDE_EFFECTS (else_
);
2869 pred
= TREE_OPERAND (pred
, 0);
2870 expr
= build3 (COND_EXPR
, void_type_node
, pred
, NULL_TREE
, else_
);
2871 SET_EXPR_LOCATION (expr
, locus
);
2875 /* If we're done, great. */
2876 if (TREE_CODE (pred
) != TRUTH_ANDIF_EXPR
2877 && TREE_CODE (pred
) != TRUTH_ORIF_EXPR
)
2880 /* Otherwise we need to mess with gotos. Change
2883 if (a); else goto no;
2886 and recursively gimplify the condition. */
2888 true_label
= false_label
= end_label
= NULL_TREE
;
2890 /* If our arms just jump somewhere, hijack those labels so we don't
2891 generate jumps to jumps. */
2894 && TREE_CODE (then_
) == GOTO_EXPR
2895 && TREE_CODE (GOTO_DESTINATION (then_
)) == LABEL_DECL
)
2897 true_label
= GOTO_DESTINATION (then_
);
2903 && TREE_CODE (else_
) == GOTO_EXPR
2904 && TREE_CODE (GOTO_DESTINATION (else_
)) == LABEL_DECL
)
2906 false_label
= GOTO_DESTINATION (else_
);
2911 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
2913 true_label_p
= &true_label
;
2915 true_label_p
= NULL
;
2917 /* The 'else' branch also needs a label if it contains interesting code. */
2918 if (false_label
|| else_se
)
2919 false_label_p
= &false_label
;
2921 false_label_p
= NULL
;
2923 /* If there was nothing else in our arms, just forward the label(s). */
2924 if (!then_se
&& !else_se
)
2925 return shortcut_cond_r (pred
, true_label_p
, false_label_p
,
2926 EXPR_LOC_OR_LOC (expr
, input_location
));
2928 /* If our last subexpression already has a terminal label, reuse it. */
2930 t
= expr_last (else_
);
2932 t
= expr_last (then_
);
2935 if (t
&& TREE_CODE (t
) == LABEL_EXPR
)
2936 end_label
= LABEL_EXPR_LABEL (t
);
2938 /* If we don't care about jumping to the 'else' branch, jump to the end
2939 if the condition is false. */
2941 false_label_p
= &end_label
;
2943 /* We only want to emit these labels if we aren't hijacking them. */
2944 emit_end
= (end_label
== NULL_TREE
);
2945 emit_false
= (false_label
== NULL_TREE
);
2947 /* We only emit the jump over the else clause if we have to--if the
2948 then clause may fall through. Otherwise we can wind up with a
2949 useless jump and a useless label at the end of gimplified code,
2950 which will cause us to think that this conditional as a whole
2951 falls through even if it doesn't. If we then inline a function
2952 which ends with such a condition, that can cause us to issue an
2953 inappropriate warning about control reaching the end of a
2954 non-void function. */
2955 jump_over_else
= block_may_fallthru (then_
);
2957 pred
= shortcut_cond_r (pred
, true_label_p
, false_label_p
,
2958 EXPR_LOC_OR_LOC (expr
, input_location
));
2961 append_to_statement_list (pred
, &expr
);
2963 append_to_statement_list (then_
, &expr
);
2968 tree last
= expr_last (expr
);
2969 t
= build_and_jump (&end_label
);
2970 if (EXPR_HAS_LOCATION (last
))
2971 SET_EXPR_LOCATION (t
, EXPR_LOCATION (last
));
2972 append_to_statement_list (t
, &expr
);
2976 t
= build1 (LABEL_EXPR
, void_type_node
, false_label
);
2977 append_to_statement_list (t
, &expr
);
2979 append_to_statement_list (else_
, &expr
);
2981 if (emit_end
&& end_label
)
2983 t
= build1 (LABEL_EXPR
, void_type_node
, end_label
);
2984 append_to_statement_list (t
, &expr
);
2990 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
2993 gimple_boolify (tree expr
)
2995 tree type
= TREE_TYPE (expr
);
2996 location_t loc
= EXPR_LOCATION (expr
);
2998 if (TREE_CODE (expr
) == NE_EXPR
2999 && TREE_CODE (TREE_OPERAND (expr
, 0)) == CALL_EXPR
3000 && integer_zerop (TREE_OPERAND (expr
, 1)))
3002 tree call
= TREE_OPERAND (expr
, 0);
3003 tree fn
= get_callee_fndecl (call
);
3005 /* For __builtin_expect ((long) (x), y) recurse into x as well
3006 if x is truth_value_p. */
3008 && DECL_BUILT_IN_CLASS (fn
) == BUILT_IN_NORMAL
3009 && DECL_FUNCTION_CODE (fn
) == BUILT_IN_EXPECT
3010 && call_expr_nargs (call
) == 2)
3012 tree arg
= CALL_EXPR_ARG (call
, 0);
3015 if (TREE_CODE (arg
) == NOP_EXPR
3016 && TREE_TYPE (arg
) == TREE_TYPE (call
))
3017 arg
= TREE_OPERAND (arg
, 0);
3018 if (truth_value_p (TREE_CODE (arg
)))
3020 arg
= gimple_boolify (arg
);
3021 CALL_EXPR_ARG (call
, 0)
3022 = fold_convert_loc (loc
, TREE_TYPE (call
), arg
);
3028 switch (TREE_CODE (expr
))
3030 case TRUTH_AND_EXPR
:
3032 case TRUTH_XOR_EXPR
:
3033 case TRUTH_ANDIF_EXPR
:
3034 case TRUTH_ORIF_EXPR
:
3035 /* Also boolify the arguments of truth exprs. */
3036 TREE_OPERAND (expr
, 1) = gimple_boolify (TREE_OPERAND (expr
, 1));
3039 case TRUTH_NOT_EXPR
:
3040 TREE_OPERAND (expr
, 0) = gimple_boolify (TREE_OPERAND (expr
, 0));
3042 /* These expressions always produce boolean results. */
3043 if (TREE_CODE (type
) != BOOLEAN_TYPE
)
3044 TREE_TYPE (expr
) = boolean_type_node
;
3048 switch ((enum annot_expr_kind
) TREE_INT_CST_LOW (TREE_OPERAND (expr
, 1)))
3050 case annot_expr_ivdep_kind
:
3051 case annot_expr_no_vector_kind
:
3052 case annot_expr_vector_kind
:
3053 TREE_OPERAND (expr
, 0) = gimple_boolify (TREE_OPERAND (expr
, 0));
3054 if (TREE_CODE (type
) != BOOLEAN_TYPE
)
3055 TREE_TYPE (expr
) = boolean_type_node
;
3062 if (COMPARISON_CLASS_P (expr
))
3064 /* There expressions always prduce boolean results. */
3065 if (TREE_CODE (type
) != BOOLEAN_TYPE
)
3066 TREE_TYPE (expr
) = boolean_type_node
;
3069 /* Other expressions that get here must have boolean values, but
3070 might need to be converted to the appropriate mode. */
3071 if (TREE_CODE (type
) == BOOLEAN_TYPE
)
3073 return fold_convert_loc (loc
, boolean_type_node
, expr
);
3077 /* Given a conditional expression *EXPR_P without side effects, gimplify
3078 its operands. New statements are inserted to PRE_P. */
3080 static enum gimplify_status
3081 gimplify_pure_cond_expr (tree
*expr_p
, gimple_seq
*pre_p
)
3083 tree expr
= *expr_p
, cond
;
3084 enum gimplify_status ret
, tret
;
3085 enum tree_code code
;
3087 cond
= gimple_boolify (COND_EXPR_COND (expr
));
3089 /* We need to handle && and || specially, as their gimplification
3090 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
3091 code
= TREE_CODE (cond
);
3092 if (code
== TRUTH_ANDIF_EXPR
)
3093 TREE_SET_CODE (cond
, TRUTH_AND_EXPR
);
3094 else if (code
== TRUTH_ORIF_EXPR
)
3095 TREE_SET_CODE (cond
, TRUTH_OR_EXPR
);
3096 ret
= gimplify_expr (&cond
, pre_p
, NULL
, is_gimple_condexpr
, fb_rvalue
);
3097 COND_EXPR_COND (*expr_p
) = cond
;
3099 tret
= gimplify_expr (&COND_EXPR_THEN (expr
), pre_p
, NULL
,
3100 is_gimple_val
, fb_rvalue
);
3101 ret
= MIN (ret
, tret
);
3102 tret
= gimplify_expr (&COND_EXPR_ELSE (expr
), pre_p
, NULL
,
3103 is_gimple_val
, fb_rvalue
);
3105 return MIN (ret
, tret
);
3108 /* Return true if evaluating EXPR could trap.
3109 EXPR is GENERIC, while tree_could_trap_p can be called
3113 generic_expr_could_trap_p (tree expr
)
3117 if (!expr
|| is_gimple_val (expr
))
3120 if (!EXPR_P (expr
) || tree_could_trap_p (expr
))
3123 n
= TREE_OPERAND_LENGTH (expr
);
3124 for (i
= 0; i
< n
; i
++)
3125 if (generic_expr_could_trap_p (TREE_OPERAND (expr
, i
)))
3131 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
3140 The second form is used when *EXPR_P is of type void.
3142 PRE_P points to the list where side effects that must happen before
3143 *EXPR_P should be stored. */
3145 static enum gimplify_status
3146 gimplify_cond_expr (tree
*expr_p
, gimple_seq
*pre_p
, fallback_t fallback
)
3148 tree expr
= *expr_p
;
3149 tree type
= TREE_TYPE (expr
);
3150 location_t loc
= EXPR_LOCATION (expr
);
3151 tree tmp
, arm1
, arm2
;
3152 enum gimplify_status ret
;
3153 tree label_true
, label_false
, label_cont
;
3154 bool have_then_clause_p
, have_else_clause_p
;
3156 enum tree_code pred_code
;
3157 gimple_seq seq
= NULL
;
3159 /* If this COND_EXPR has a value, copy the values into a temporary within
3161 if (!VOID_TYPE_P (type
))
3163 tree then_
= TREE_OPERAND (expr
, 1), else_
= TREE_OPERAND (expr
, 2);
3166 /* If either an rvalue is ok or we do not require an lvalue, create the
3167 temporary. But we cannot do that if the type is addressable. */
3168 if (((fallback
& fb_rvalue
) || !(fallback
& fb_lvalue
))
3169 && !TREE_ADDRESSABLE (type
))
3171 if (gimplify_ctxp
->allow_rhs_cond_expr
3172 /* If either branch has side effects or could trap, it can't be
3173 evaluated unconditionally. */
3174 && !TREE_SIDE_EFFECTS (then_
)
3175 && !generic_expr_could_trap_p (then_
)
3176 && !TREE_SIDE_EFFECTS (else_
)
3177 && !generic_expr_could_trap_p (else_
))
3178 return gimplify_pure_cond_expr (expr_p
, pre_p
);
3180 tmp
= create_tmp_var (type
, "iftmp");
3184 /* Otherwise, only create and copy references to the values. */
3187 type
= build_pointer_type (type
);
3189 if (!VOID_TYPE_P (TREE_TYPE (then_
)))
3190 then_
= build_fold_addr_expr_loc (loc
, then_
);
3192 if (!VOID_TYPE_P (TREE_TYPE (else_
)))
3193 else_
= build_fold_addr_expr_loc (loc
, else_
);
3196 = build3 (COND_EXPR
, type
, TREE_OPERAND (expr
, 0), then_
, else_
);
3198 tmp
= create_tmp_var (type
, "iftmp");
3199 result
= build_simple_mem_ref_loc (loc
, tmp
);
3202 /* Build the new then clause, `tmp = then_;'. But don't build the
3203 assignment if the value is void; in C++ it can be if it's a throw. */
3204 if (!VOID_TYPE_P (TREE_TYPE (then_
)))
3205 TREE_OPERAND (expr
, 1) = build2 (MODIFY_EXPR
, type
, tmp
, then_
);
3207 /* Similarly, build the new else clause, `tmp = else_;'. */
3208 if (!VOID_TYPE_P (TREE_TYPE (else_
)))
3209 TREE_OPERAND (expr
, 2) = build2 (MODIFY_EXPR
, type
, tmp
, else_
);
3211 TREE_TYPE (expr
) = void_type_node
;
3212 recalculate_side_effects (expr
);
3214 /* Move the COND_EXPR to the prequeue. */
3215 gimplify_stmt (&expr
, pre_p
);
3221 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
3222 STRIP_TYPE_NOPS (TREE_OPERAND (expr
, 0));
3223 if (TREE_CODE (TREE_OPERAND (expr
, 0)) == COMPOUND_EXPR
)
3224 gimplify_compound_expr (&TREE_OPERAND (expr
, 0), pre_p
, true);
3226 /* Make sure the condition has BOOLEAN_TYPE. */
3227 TREE_OPERAND (expr
, 0) = gimple_boolify (TREE_OPERAND (expr
, 0));
3229 /* Break apart && and || conditions. */
3230 if (TREE_CODE (TREE_OPERAND (expr
, 0)) == TRUTH_ANDIF_EXPR
3231 || TREE_CODE (TREE_OPERAND (expr
, 0)) == TRUTH_ORIF_EXPR
)
3233 expr
= shortcut_cond_expr (expr
);
3235 if (expr
!= *expr_p
)
3239 /* We can't rely on gimplify_expr to re-gimplify the expanded
3240 form properly, as cleanups might cause the target labels to be
3241 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
3242 set up a conditional context. */
3243 gimple_push_condition ();
3244 gimplify_stmt (expr_p
, &seq
);
3245 gimple_pop_condition (pre_p
);
3246 gimple_seq_add_seq (pre_p
, seq
);
3252 /* Now do the normal gimplification. */
3254 /* Gimplify condition. */
3255 ret
= gimplify_expr (&TREE_OPERAND (expr
, 0), pre_p
, NULL
, is_gimple_condexpr
,
3257 if (ret
== GS_ERROR
)
3259 gcc_assert (TREE_OPERAND (expr
, 0) != NULL_TREE
);
3261 gimple_push_condition ();
3263 have_then_clause_p
= have_else_clause_p
= false;
3264 if (TREE_OPERAND (expr
, 1) != NULL
3265 && TREE_CODE (TREE_OPERAND (expr
, 1)) == GOTO_EXPR
3266 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr
, 1))) == LABEL_DECL
3267 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr
, 1)))
3268 == current_function_decl
)
3269 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
3270 have different locations, otherwise we end up with incorrect
3271 location information on the branches. */
3273 || !EXPR_HAS_LOCATION (expr
)
3274 || !EXPR_HAS_LOCATION (TREE_OPERAND (expr
, 1))
3275 || EXPR_LOCATION (expr
) == EXPR_LOCATION (TREE_OPERAND (expr
, 1))))
3277 label_true
= GOTO_DESTINATION (TREE_OPERAND (expr
, 1));
3278 have_then_clause_p
= true;
3281 label_true
= create_artificial_label (UNKNOWN_LOCATION
);
3282 if (TREE_OPERAND (expr
, 2) != NULL
3283 && TREE_CODE (TREE_OPERAND (expr
, 2)) == GOTO_EXPR
3284 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr
, 2))) == LABEL_DECL
3285 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr
, 2)))
3286 == current_function_decl
)
3287 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
3288 have different locations, otherwise we end up with incorrect
3289 location information on the branches. */
3291 || !EXPR_HAS_LOCATION (expr
)
3292 || !EXPR_HAS_LOCATION (TREE_OPERAND (expr
, 2))
3293 || EXPR_LOCATION (expr
) == EXPR_LOCATION (TREE_OPERAND (expr
, 2))))
3295 label_false
= GOTO_DESTINATION (TREE_OPERAND (expr
, 2));
3296 have_else_clause_p
= true;
3299 label_false
= create_artificial_label (UNKNOWN_LOCATION
);
3301 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr
), &pred_code
, &arm1
,
3303 cond_stmt
= gimple_build_cond (pred_code
, arm1
, arm2
, label_true
,
3305 gimple_set_no_warning (cond_stmt
, TREE_NO_WARNING (COND_EXPR_COND (expr
)));
3306 gimplify_seq_add_stmt (&seq
, cond_stmt
);
3307 gimple_stmt_iterator gsi
= gsi_last (seq
);
3308 maybe_fold_stmt (&gsi
);
3310 label_cont
= NULL_TREE
;
3311 if (!have_then_clause_p
)
3313 /* For if (...) {} else { code; } put label_true after
3315 if (TREE_OPERAND (expr
, 1) == NULL_TREE
3316 && !have_else_clause_p
3317 && TREE_OPERAND (expr
, 2) != NULL_TREE
)
3318 label_cont
= label_true
;
3321 gimplify_seq_add_stmt (&seq
, gimple_build_label (label_true
));
3322 have_then_clause_p
= gimplify_stmt (&TREE_OPERAND (expr
, 1), &seq
);
3323 /* For if (...) { code; } else {} or
3324 if (...) { code; } else goto label; or
3325 if (...) { code; return; } else { ... }
3326 label_cont isn't needed. */
3327 if (!have_else_clause_p
3328 && TREE_OPERAND (expr
, 2) != NULL_TREE
3329 && gimple_seq_may_fallthru (seq
))
3332 label_cont
= create_artificial_label (UNKNOWN_LOCATION
);
3334 g
= gimple_build_goto (label_cont
);
3336 /* GIMPLE_COND's are very low level; they have embedded
3337 gotos. This particular embedded goto should not be marked
3338 with the location of the original COND_EXPR, as it would
3339 correspond to the COND_EXPR's condition, not the ELSE or the
3340 THEN arms. To avoid marking it with the wrong location, flag
3341 it as "no location". */
3342 gimple_set_do_not_emit_location (g
);
3344 gimplify_seq_add_stmt (&seq
, g
);
3348 if (!have_else_clause_p
)
3350 gimplify_seq_add_stmt (&seq
, gimple_build_label (label_false
));
3351 have_else_clause_p
= gimplify_stmt (&TREE_OPERAND (expr
, 2), &seq
);
3354 gimplify_seq_add_stmt (&seq
, gimple_build_label (label_cont
));
3356 gimple_pop_condition (pre_p
);
3357 gimple_seq_add_seq (pre_p
, seq
);
3359 if (ret
== GS_ERROR
)
3361 else if (have_then_clause_p
|| have_else_clause_p
)
3365 /* Both arms are empty; replace the COND_EXPR with its predicate. */
3366 expr
= TREE_OPERAND (expr
, 0);
3367 gimplify_stmt (&expr
, pre_p
);
3374 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
3375 to be marked addressable.
3377 We cannot rely on such an expression being directly markable if a temporary
3378 has been created by the gimplification. In this case, we create another
3379 temporary and initialize it with a copy, which will become a store after we
3380 mark it addressable. This can happen if the front-end passed us something
3381 that it could not mark addressable yet, like a Fortran pass-by-reference
3382 parameter (int) floatvar. */
3385 prepare_gimple_addressable (tree
*expr_p
, gimple_seq
*seq_p
)
3387 while (handled_component_p (*expr_p
))
3388 expr_p
= &TREE_OPERAND (*expr_p
, 0);
3389 if (is_gimple_reg (*expr_p
))
3391 /* Do not allow an SSA name as the temporary. */
3392 tree var
= get_initialized_tmp_var (*expr_p
, seq_p
, NULL
, false);
3393 DECL_GIMPLE_REG_P (var
) = 0;
3398 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
3399 a call to __builtin_memcpy. */
3401 static enum gimplify_status
3402 gimplify_modify_expr_to_memcpy (tree
*expr_p
, tree size
, bool want_value
,
3405 tree t
, to
, to_ptr
, from
, from_ptr
;
3407 location_t loc
= EXPR_LOCATION (*expr_p
);
3409 to
= TREE_OPERAND (*expr_p
, 0);
3410 from
= TREE_OPERAND (*expr_p
, 1);
3412 /* Mark the RHS addressable. Beware that it may not be possible to do so
3413 directly if a temporary has been created by the gimplification. */
3414 prepare_gimple_addressable (&from
, seq_p
);
3416 mark_addressable (from
);
3417 from_ptr
= build_fold_addr_expr_loc (loc
, from
);
3418 gimplify_arg (&from_ptr
, seq_p
, loc
);
3420 mark_addressable (to
);
3421 to_ptr
= build_fold_addr_expr_loc (loc
, to
);
3422 gimplify_arg (&to_ptr
, seq_p
, loc
);
3424 t
= builtin_decl_implicit (BUILT_IN_MEMCPY
);
3426 gs
= gimple_build_call (t
, 3, to_ptr
, from_ptr
, size
);
3430 /* tmp = memcpy() */
3431 t
= create_tmp_var (TREE_TYPE (to_ptr
));
3432 gimple_call_set_lhs (gs
, t
);
3433 gimplify_seq_add_stmt (seq_p
, gs
);
3435 *expr_p
= build_simple_mem_ref (t
);
3439 gimplify_seq_add_stmt (seq_p
, gs
);
3444 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
3445 a call to __builtin_memset. In this case we know that the RHS is
3446 a CONSTRUCTOR with an empty element list. */
3448 static enum gimplify_status
3449 gimplify_modify_expr_to_memset (tree
*expr_p
, tree size
, bool want_value
,
3452 tree t
, from
, to
, to_ptr
;
3454 location_t loc
= EXPR_LOCATION (*expr_p
);
3456 /* Assert our assumptions, to abort instead of producing wrong code
3457 silently if they are not met. Beware that the RHS CONSTRUCTOR might
3458 not be immediately exposed. */
3459 from
= TREE_OPERAND (*expr_p
, 1);
3460 if (TREE_CODE (from
) == WITH_SIZE_EXPR
)
3461 from
= TREE_OPERAND (from
, 0);
3463 gcc_assert (TREE_CODE (from
) == CONSTRUCTOR
3464 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from
)));
3467 to
= TREE_OPERAND (*expr_p
, 0);
3469 to_ptr
= build_fold_addr_expr_loc (loc
, to
);
3470 gimplify_arg (&to_ptr
, seq_p
, loc
);
3471 t
= builtin_decl_implicit (BUILT_IN_MEMSET
);
3473 gs
= gimple_build_call (t
, 3, to_ptr
, integer_zero_node
, size
);
3477 /* tmp = memset() */
3478 t
= create_tmp_var (TREE_TYPE (to_ptr
));
3479 gimple_call_set_lhs (gs
, t
);
3480 gimplify_seq_add_stmt (seq_p
, gs
);
3482 *expr_p
= build1 (INDIRECT_REF
, TREE_TYPE (to
), t
);
3486 gimplify_seq_add_stmt (seq_p
, gs
);
3491 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
3492 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
3493 assignment. Return non-null if we detect a potential overlap. */
3495 struct gimplify_init_ctor_preeval_data
3497 /* The base decl of the lhs object. May be NULL, in which case we
3498 have to assume the lhs is indirect. */
3501 /* The alias set of the lhs object. */
3502 alias_set_type lhs_alias_set
;
3506 gimplify_init_ctor_preeval_1 (tree
*tp
, int *walk_subtrees
, void *xdata
)
3508 struct gimplify_init_ctor_preeval_data
*data
3509 = (struct gimplify_init_ctor_preeval_data
*) xdata
;
3512 /* If we find the base object, obviously we have overlap. */
3513 if (data
->lhs_base_decl
== t
)
3516 /* If the constructor component is indirect, determine if we have a
3517 potential overlap with the lhs. The only bits of information we
3518 have to go on at this point are addressability and alias sets. */
3519 if ((INDIRECT_REF_P (t
)
3520 || TREE_CODE (t
) == MEM_REF
)
3521 && (!data
->lhs_base_decl
|| TREE_ADDRESSABLE (data
->lhs_base_decl
))
3522 && alias_sets_conflict_p (data
->lhs_alias_set
, get_alias_set (t
)))
3525 /* If the constructor component is a call, determine if it can hide a
3526 potential overlap with the lhs through an INDIRECT_REF like above.
3527 ??? Ugh - this is completely broken. In fact this whole analysis
3528 doesn't look conservative. */
3529 if (TREE_CODE (t
) == CALL_EXPR
)
3531 tree type
, fntype
= TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t
)));
3533 for (type
= TYPE_ARG_TYPES (fntype
); type
; type
= TREE_CHAIN (type
))
3534 if (POINTER_TYPE_P (TREE_VALUE (type
))
3535 && (!data
->lhs_base_decl
|| TREE_ADDRESSABLE (data
->lhs_base_decl
))
3536 && alias_sets_conflict_p (data
->lhs_alias_set
,
3538 (TREE_TYPE (TREE_VALUE (type
)))))
3542 if (IS_TYPE_OR_DECL_P (t
))
3547 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
3548 force values that overlap with the lhs (as described by *DATA)
3549 into temporaries. */
3552 gimplify_init_ctor_preeval (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
3553 struct gimplify_init_ctor_preeval_data
*data
)
3555 enum gimplify_status one
;
3557 /* If the value is constant, then there's nothing to pre-evaluate. */
3558 if (TREE_CONSTANT (*expr_p
))
3560 /* Ensure it does not have side effects, it might contain a reference to
3561 the object we're initializing. */
3562 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p
));
3566 /* If the type has non-trivial constructors, we can't pre-evaluate. */
3567 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p
)))
3570 /* Recurse for nested constructors. */
3571 if (TREE_CODE (*expr_p
) == CONSTRUCTOR
)
3573 unsigned HOST_WIDE_INT ix
;
3574 constructor_elt
*ce
;
3575 vec
<constructor_elt
, va_gc
> *v
= CONSTRUCTOR_ELTS (*expr_p
);
3577 FOR_EACH_VEC_SAFE_ELT (v
, ix
, ce
)
3578 gimplify_init_ctor_preeval (&ce
->value
, pre_p
, post_p
, data
);
3583 /* If this is a variable sized type, we must remember the size. */
3584 maybe_with_size_expr (expr_p
);
3586 /* Gimplify the constructor element to something appropriate for the rhs
3587 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
3588 the gimplifier will consider this a store to memory. Doing this
3589 gimplification now means that we won't have to deal with complicated
3590 language-specific trees, nor trees like SAVE_EXPR that can induce
3591 exponential search behavior. */
3592 one
= gimplify_expr (expr_p
, pre_p
, post_p
, is_gimple_mem_rhs
, fb_rvalue
);
3593 if (one
== GS_ERROR
)
3599 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
3600 with the lhs, since "a = { .x=a }" doesn't make sense. This will
3601 always be true for all scalars, since is_gimple_mem_rhs insists on a
3602 temporary variable for them. */
3603 if (DECL_P (*expr_p
))
3606 /* If this is of variable size, we have no choice but to assume it doesn't
3607 overlap since we can't make a temporary for it. */
3608 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p
))) != INTEGER_CST
)
3611 /* Otherwise, we must search for overlap ... */
3612 if (!walk_tree (expr_p
, gimplify_init_ctor_preeval_1
, data
, NULL
))
3615 /* ... and if found, force the value into a temporary. */
3616 *expr_p
= get_formal_tmp_var (*expr_p
, pre_p
);
3619 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
3620 a RANGE_EXPR in a CONSTRUCTOR for an array.
3624 object[var] = value;
3631 We increment var _after_ the loop exit check because we might otherwise
3632 fail if upper == TYPE_MAX_VALUE (type for upper).
3634 Note that we never have to deal with SAVE_EXPRs here, because this has
3635 already been taken care of for us, in gimplify_init_ctor_preeval(). */
3637 static void gimplify_init_ctor_eval (tree
, vec
<constructor_elt
, va_gc
> *,
3638 gimple_seq
*, bool);
3641 gimplify_init_ctor_eval_range (tree object
, tree lower
, tree upper
,
3642 tree value
, tree array_elt_type
,
3643 gimple_seq
*pre_p
, bool cleared
)
3645 tree loop_entry_label
, loop_exit_label
, fall_thru_label
;
3646 tree var
, var_type
, cref
, tmp
;
3648 loop_entry_label
= create_artificial_label (UNKNOWN_LOCATION
);
3649 loop_exit_label
= create_artificial_label (UNKNOWN_LOCATION
);
3650 fall_thru_label
= create_artificial_label (UNKNOWN_LOCATION
);
3652 /* Create and initialize the index variable. */
3653 var_type
= TREE_TYPE (upper
);
3654 var
= create_tmp_var (var_type
);
3655 gimplify_seq_add_stmt (pre_p
, gimple_build_assign (var
, lower
));
3657 /* Add the loop entry label. */
3658 gimplify_seq_add_stmt (pre_p
, gimple_build_label (loop_entry_label
));
3660 /* Build the reference. */
3661 cref
= build4 (ARRAY_REF
, array_elt_type
, unshare_expr (object
),
3662 var
, NULL_TREE
, NULL_TREE
);
3664 /* If we are a constructor, just call gimplify_init_ctor_eval to do
3665 the store. Otherwise just assign value to the reference. */
3667 if (TREE_CODE (value
) == CONSTRUCTOR
)
3668 /* NB we might have to call ourself recursively through
3669 gimplify_init_ctor_eval if the value is a constructor. */
3670 gimplify_init_ctor_eval (cref
, CONSTRUCTOR_ELTS (value
),
3673 gimplify_seq_add_stmt (pre_p
, gimple_build_assign (cref
, value
));
3675 /* We exit the loop when the index var is equal to the upper bound. */
3676 gimplify_seq_add_stmt (pre_p
,
3677 gimple_build_cond (EQ_EXPR
, var
, upper
,
3678 loop_exit_label
, fall_thru_label
));
3680 gimplify_seq_add_stmt (pre_p
, gimple_build_label (fall_thru_label
));
3682 /* Otherwise, increment the index var... */
3683 tmp
= build2 (PLUS_EXPR
, var_type
, var
,
3684 fold_convert (var_type
, integer_one_node
));
3685 gimplify_seq_add_stmt (pre_p
, gimple_build_assign (var
, tmp
));
3687 /* ...and jump back to the loop entry. */
3688 gimplify_seq_add_stmt (pre_p
, gimple_build_goto (loop_entry_label
));
3690 /* Add the loop exit label. */
3691 gimplify_seq_add_stmt (pre_p
, gimple_build_label (loop_exit_label
));
3694 /* Return true if FDECL is accessing a field that is zero sized. */
3697 zero_sized_field_decl (const_tree fdecl
)
3699 if (TREE_CODE (fdecl
) == FIELD_DECL
&& DECL_SIZE (fdecl
)
3700 && integer_zerop (DECL_SIZE (fdecl
)))
3705 /* Return true if TYPE is zero sized. */
3708 zero_sized_type (const_tree type
)
3710 if (AGGREGATE_TYPE_P (type
) && TYPE_SIZE (type
)
3711 && integer_zerop (TYPE_SIZE (type
)))
3716 /* A subroutine of gimplify_init_constructor. Generate individual
3717 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
3718 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
3719 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
3723 gimplify_init_ctor_eval (tree object
, vec
<constructor_elt
, va_gc
> *elts
,
3724 gimple_seq
*pre_p
, bool cleared
)
3726 tree array_elt_type
= NULL
;
3727 unsigned HOST_WIDE_INT ix
;
3728 tree purpose
, value
;
3730 if (TREE_CODE (TREE_TYPE (object
)) == ARRAY_TYPE
)
3731 array_elt_type
= TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object
)));
3733 FOR_EACH_CONSTRUCTOR_ELT (elts
, ix
, purpose
, value
)
3737 /* NULL values are created above for gimplification errors. */
3741 if (cleared
&& initializer_zerop (value
))
3744 /* ??? Here's to hoping the front end fills in all of the indices,
3745 so we don't have to figure out what's missing ourselves. */
3746 gcc_assert (purpose
);
3748 /* Skip zero-sized fields, unless value has side-effects. This can
3749 happen with calls to functions returning a zero-sized type, which
3750 we shouldn't discard. As a number of downstream passes don't
3751 expect sets of zero-sized fields, we rely on the gimplification of
3752 the MODIFY_EXPR we make below to drop the assignment statement. */
3753 if (! TREE_SIDE_EFFECTS (value
) && zero_sized_field_decl (purpose
))
3756 /* If we have a RANGE_EXPR, we have to build a loop to assign the
3758 if (TREE_CODE (purpose
) == RANGE_EXPR
)
3760 tree lower
= TREE_OPERAND (purpose
, 0);
3761 tree upper
= TREE_OPERAND (purpose
, 1);
3763 /* If the lower bound is equal to upper, just treat it as if
3764 upper was the index. */
3765 if (simple_cst_equal (lower
, upper
))
3769 gimplify_init_ctor_eval_range (object
, lower
, upper
, value
,
3770 array_elt_type
, pre_p
, cleared
);
3777 /* Do not use bitsizetype for ARRAY_REF indices. */
3778 if (TYPE_DOMAIN (TREE_TYPE (object
)))
3780 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object
))),
3782 cref
= build4 (ARRAY_REF
, array_elt_type
, unshare_expr (object
),
3783 purpose
, NULL_TREE
, NULL_TREE
);
3787 gcc_assert (TREE_CODE (purpose
) == FIELD_DECL
);
3788 cref
= build3 (COMPONENT_REF
, TREE_TYPE (purpose
),
3789 unshare_expr (object
), purpose
, NULL_TREE
);
3792 if (TREE_CODE (value
) == CONSTRUCTOR
3793 && TREE_CODE (TREE_TYPE (value
)) != VECTOR_TYPE
)
3794 gimplify_init_ctor_eval (cref
, CONSTRUCTOR_ELTS (value
),
3798 tree init
= build2 (INIT_EXPR
, TREE_TYPE (cref
), cref
, value
);
3799 gimplify_and_add (init
, pre_p
);
3805 /* Return the appropriate RHS predicate for this LHS. */
3808 rhs_predicate_for (tree lhs
)
3810 if (is_gimple_reg (lhs
))
3811 return is_gimple_reg_rhs_or_call
;
3813 return is_gimple_mem_rhs_or_call
;
3816 /* Return the initial guess for an appropriate RHS predicate for this LHS,
3817 before the LHS has been gimplified. */
3819 static gimple_predicate
3820 initial_rhs_predicate_for (tree lhs
)
3822 if (is_gimple_reg_type (TREE_TYPE (lhs
)))
3823 return is_gimple_reg_rhs_or_call
;
3825 return is_gimple_mem_rhs_or_call
;
3828 /* Gimplify a C99 compound literal expression. This just means adding
3829 the DECL_EXPR before the current statement and using its anonymous
3832 static enum gimplify_status
3833 gimplify_compound_literal_expr (tree
*expr_p
, gimple_seq
*pre_p
,
3834 bool (*gimple_test_f
) (tree
),
3835 fallback_t fallback
)
3837 tree decl_s
= COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p
);
3838 tree decl
= DECL_EXPR_DECL (decl_s
);
3839 tree init
= DECL_INITIAL (decl
);
3840 /* Mark the decl as addressable if the compound literal
3841 expression is addressable now, otherwise it is marked too late
3842 after we gimplify the initialization expression. */
3843 if (TREE_ADDRESSABLE (*expr_p
))
3844 TREE_ADDRESSABLE (decl
) = 1;
3845 /* Otherwise, if we don't need an lvalue and have a literal directly
3846 substitute it. Check if it matches the gimple predicate, as
3847 otherwise we'd generate a new temporary, and we can as well just
3848 use the decl we already have. */
3849 else if (!TREE_ADDRESSABLE (decl
)
3851 && (fallback
& fb_lvalue
) == 0
3852 && gimple_test_f (init
))
3858 /* Preliminarily mark non-addressed complex variables as eligible
3859 for promotion to gimple registers. We'll transform their uses
3861 if ((TREE_CODE (TREE_TYPE (decl
)) == COMPLEX_TYPE
3862 || TREE_CODE (TREE_TYPE (decl
)) == VECTOR_TYPE
)
3863 && !TREE_THIS_VOLATILE (decl
)
3864 && !needs_to_live_in_memory (decl
))
3865 DECL_GIMPLE_REG_P (decl
) = 1;
3867 /* If the decl is not addressable, then it is being used in some
3868 expression or on the right hand side of a statement, and it can
3869 be put into a readonly data section. */
3870 if (!TREE_ADDRESSABLE (decl
) && (fallback
& fb_lvalue
) == 0)
3871 TREE_READONLY (decl
) = 1;
3873 /* This decl isn't mentioned in the enclosing block, so add it to the
3874 list of temps. FIXME it seems a bit of a kludge to say that
3875 anonymous artificial vars aren't pushed, but everything else is. */
3876 if (DECL_NAME (decl
) == NULL_TREE
&& !DECL_SEEN_IN_BIND_EXPR_P (decl
))
3877 gimple_add_tmp_var (decl
);
3879 gimplify_and_add (decl_s
, pre_p
);
3884 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
3885 return a new CONSTRUCTOR if something changed. */
3888 optimize_compound_literals_in_ctor (tree orig_ctor
)
3890 tree ctor
= orig_ctor
;
3891 vec
<constructor_elt
, va_gc
> *elts
= CONSTRUCTOR_ELTS (ctor
);
3892 unsigned int idx
, num
= vec_safe_length (elts
);
3894 for (idx
= 0; idx
< num
; idx
++)
3896 tree value
= (*elts
)[idx
].value
;
3897 tree newval
= value
;
3898 if (TREE_CODE (value
) == CONSTRUCTOR
)
3899 newval
= optimize_compound_literals_in_ctor (value
);
3900 else if (TREE_CODE (value
) == COMPOUND_LITERAL_EXPR
)
3902 tree decl_s
= COMPOUND_LITERAL_EXPR_DECL_EXPR (value
);
3903 tree decl
= DECL_EXPR_DECL (decl_s
);
3904 tree init
= DECL_INITIAL (decl
);
3906 if (!TREE_ADDRESSABLE (value
)
3907 && !TREE_ADDRESSABLE (decl
)
3909 && TREE_CODE (init
) == CONSTRUCTOR
)
3910 newval
= optimize_compound_literals_in_ctor (init
);
3912 if (newval
== value
)
3915 if (ctor
== orig_ctor
)
3917 ctor
= copy_node (orig_ctor
);
3918 CONSTRUCTOR_ELTS (ctor
) = vec_safe_copy (elts
);
3919 elts
= CONSTRUCTOR_ELTS (ctor
);
3921 (*elts
)[idx
].value
= newval
;
3926 /* A subroutine of gimplify_modify_expr. Break out elements of a
3927 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
3929 Note that we still need to clear any elements that don't have explicit
3930 initializers, so if not all elements are initialized we keep the
3931 original MODIFY_EXPR, we just remove all of the constructor elements.
3933 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
3934 GS_ERROR if we would have to create a temporary when gimplifying
3935 this constructor. Otherwise, return GS_OK.
3937 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
3939 static enum gimplify_status
3940 gimplify_init_constructor (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
3941 bool want_value
, bool notify_temp_creation
)
3943 tree object
, ctor
, type
;
3944 enum gimplify_status ret
;
3945 vec
<constructor_elt
, va_gc
> *elts
;
3947 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p
, 1)) == CONSTRUCTOR
);
3949 if (!notify_temp_creation
)
3951 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
3952 is_gimple_lvalue
, fb_lvalue
);
3953 if (ret
== GS_ERROR
)
3957 object
= TREE_OPERAND (*expr_p
, 0);
3958 ctor
= TREE_OPERAND (*expr_p
, 1) =
3959 optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p
, 1));
3960 type
= TREE_TYPE (ctor
);
3961 elts
= CONSTRUCTOR_ELTS (ctor
);
3964 switch (TREE_CODE (type
))
3968 case QUAL_UNION_TYPE
:
3971 struct gimplify_init_ctor_preeval_data preeval_data
;
3972 HOST_WIDE_INT num_ctor_elements
, num_nonzero_elements
;
3973 bool cleared
, complete_p
, valid_const_initializer
;
3975 /* Aggregate types must lower constructors to initialization of
3976 individual elements. The exception is that a CONSTRUCTOR node
3977 with no elements indicates zero-initialization of the whole. */
3978 if (vec_safe_is_empty (elts
))
3980 if (notify_temp_creation
)
3985 /* Fetch information about the constructor to direct later processing.
3986 We might want to make static versions of it in various cases, and
3987 can only do so if it known to be a valid constant initializer. */
3988 valid_const_initializer
3989 = categorize_ctor_elements (ctor
, &num_nonzero_elements
,
3990 &num_ctor_elements
, &complete_p
);
3992 /* If a const aggregate variable is being initialized, then it
3993 should never be a lose to promote the variable to be static. */
3994 if (valid_const_initializer
3995 && num_nonzero_elements
> 1
3996 && TREE_READONLY (object
)
3997 && TREE_CODE (object
) == VAR_DECL
3998 && (flag_merge_constants
>= 2 || !TREE_ADDRESSABLE (object
)))
4000 if (notify_temp_creation
)
4002 DECL_INITIAL (object
) = ctor
;
4003 TREE_STATIC (object
) = 1;
4004 if (!DECL_NAME (object
))
4005 DECL_NAME (object
) = create_tmp_var_name ("C");
4006 walk_tree (&DECL_INITIAL (object
), force_labels_r
, NULL
, NULL
);
4008 /* ??? C++ doesn't automatically append a .<number> to the
4009 assembler name, and even when it does, it looks at FE private
4010 data structures to figure out what that number should be,
4011 which are not set for this variable. I suppose this is
4012 important for local statics for inline functions, which aren't
4013 "local" in the object file sense. So in order to get a unique
4014 TU-local symbol, we must invoke the lhd version now. */
4015 lhd_set_decl_assembler_name (object
);
4017 *expr_p
= NULL_TREE
;
4021 /* If there are "lots" of initialized elements, even discounting
4022 those that are not address constants (and thus *must* be
4023 computed at runtime), then partition the constructor into
4024 constant and non-constant parts. Block copy the constant
4025 parts in, then generate code for the non-constant parts. */
4026 /* TODO. There's code in cp/typeck.c to do this. */
4028 if (int_size_in_bytes (TREE_TYPE (ctor
)) < 0)
4029 /* store_constructor will ignore the clearing of variable-sized
4030 objects. Initializers for such objects must explicitly set
4031 every field that needs to be set. */
4033 else if (!complete_p
&& !CONSTRUCTOR_NO_CLEARING (ctor
))
4034 /* If the constructor isn't complete, clear the whole object
4035 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
4037 ??? This ought not to be needed. For any element not present
4038 in the initializer, we should simply set them to zero. Except
4039 we'd need to *find* the elements that are not present, and that
4040 requires trickery to avoid quadratic compile-time behavior in
4041 large cases or excessive memory use in small cases. */
4043 else if (num_ctor_elements
- num_nonzero_elements
4044 > CLEAR_RATIO (optimize_function_for_speed_p (cfun
))
4045 && num_nonzero_elements
< num_ctor_elements
/ 4)
4046 /* If there are "lots" of zeros, it's more efficient to clear
4047 the memory and then set the nonzero elements. */
4052 /* If there are "lots" of initialized elements, and all of them
4053 are valid address constants, then the entire initializer can
4054 be dropped to memory, and then memcpy'd out. Don't do this
4055 for sparse arrays, though, as it's more efficient to follow
4056 the standard CONSTRUCTOR behavior of memset followed by
4057 individual element initialization. Also don't do this for small
4058 all-zero initializers (which aren't big enough to merit
4059 clearing), and don't try to make bitwise copies of
4060 TREE_ADDRESSABLE types.
4062 We cannot apply such transformation when compiling chkp static
4063 initializer because creation of initializer image in the memory
4064 will require static initialization of bounds for it. It should
4065 result in another gimplification of similar initializer and we
4066 may fall into infinite loop. */
4067 if (valid_const_initializer
4068 && !(cleared
|| num_nonzero_elements
== 0)
4069 && !TREE_ADDRESSABLE (type
)
4070 && (!current_function_decl
4071 || !lookup_attribute ("chkp ctor",
4072 DECL_ATTRIBUTES (current_function_decl
))))
4074 HOST_WIDE_INT size
= int_size_in_bytes (type
);
4077 /* ??? We can still get unbounded array types, at least
4078 from the C++ front end. This seems wrong, but attempt
4079 to work around it for now. */
4082 size
= int_size_in_bytes (TREE_TYPE (object
));
4084 TREE_TYPE (ctor
) = type
= TREE_TYPE (object
);
4087 /* Find the maximum alignment we can assume for the object. */
4088 /* ??? Make use of DECL_OFFSET_ALIGN. */
4089 if (DECL_P (object
))
4090 align
= DECL_ALIGN (object
);
4092 align
= TYPE_ALIGN (type
);
4094 /* Do a block move either if the size is so small as to make
4095 each individual move a sub-unit move on average, or if it
4096 is so large as to make individual moves inefficient. */
4098 && num_nonzero_elements
> 1
4099 && (size
< num_nonzero_elements
4100 || !can_move_by_pieces (size
, align
)))
4102 if (notify_temp_creation
)
4105 walk_tree (&ctor
, force_labels_r
, NULL
, NULL
);
4106 ctor
= tree_output_constant_def (ctor
);
4107 if (!useless_type_conversion_p (type
, TREE_TYPE (ctor
)))
4108 ctor
= build1 (VIEW_CONVERT_EXPR
, type
, ctor
);
4109 TREE_OPERAND (*expr_p
, 1) = ctor
;
4111 /* This is no longer an assignment of a CONSTRUCTOR, but
4112 we still may have processing to do on the LHS. So
4113 pretend we didn't do anything here to let that happen. */
4114 return GS_UNHANDLED
;
4118 /* If the target is volatile, we have non-zero elements and more than
4119 one field to assign, initialize the target from a temporary. */
4120 if (TREE_THIS_VOLATILE (object
)
4121 && !TREE_ADDRESSABLE (type
)
4122 && num_nonzero_elements
> 0
4123 && vec_safe_length (elts
) > 1)
4125 tree temp
= create_tmp_var (TYPE_MAIN_VARIANT (type
));
4126 TREE_OPERAND (*expr_p
, 0) = temp
;
4127 *expr_p
= build2 (COMPOUND_EXPR
, TREE_TYPE (*expr_p
),
4129 build2 (MODIFY_EXPR
, void_type_node
,
4134 if (notify_temp_creation
)
4137 /* If there are nonzero elements and if needed, pre-evaluate to capture
4138 elements overlapping with the lhs into temporaries. We must do this
4139 before clearing to fetch the values before they are zeroed-out. */
4140 if (num_nonzero_elements
> 0 && TREE_CODE (*expr_p
) != INIT_EXPR
)
4142 preeval_data
.lhs_base_decl
= get_base_address (object
);
4143 if (!DECL_P (preeval_data
.lhs_base_decl
))
4144 preeval_data
.lhs_base_decl
= NULL
;
4145 preeval_data
.lhs_alias_set
= get_alias_set (object
);
4147 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p
, 1),
4148 pre_p
, post_p
, &preeval_data
);
4151 bool ctor_has_side_effects_p
4152 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p
, 1));
4156 /* Zap the CONSTRUCTOR element list, which simplifies this case.
4157 Note that we still have to gimplify, in order to handle the
4158 case of variable sized types. Avoid shared tree structures. */
4159 CONSTRUCTOR_ELTS (ctor
) = NULL
;
4160 TREE_SIDE_EFFECTS (ctor
) = 0;
4161 object
= unshare_expr (object
);
4162 gimplify_stmt (expr_p
, pre_p
);
4165 /* If we have not block cleared the object, or if there are nonzero
4166 elements in the constructor, or if the constructor has side effects,
4167 add assignments to the individual scalar fields of the object. */
4169 || num_nonzero_elements
> 0
4170 || ctor_has_side_effects_p
)
4171 gimplify_init_ctor_eval (object
, elts
, pre_p
, cleared
);
4173 *expr_p
= NULL_TREE
;
4181 if (notify_temp_creation
)
4184 /* Extract the real and imaginary parts out of the ctor. */
4185 gcc_assert (elts
->length () == 2);
4186 r
= (*elts
)[0].value
;
4187 i
= (*elts
)[1].value
;
4188 if (r
== NULL
|| i
== NULL
)
4190 tree zero
= build_zero_cst (TREE_TYPE (type
));
4197 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
4198 represent creation of a complex value. */
4199 if (TREE_CONSTANT (r
) && TREE_CONSTANT (i
))
4201 ctor
= build_complex (type
, r
, i
);
4202 TREE_OPERAND (*expr_p
, 1) = ctor
;
4206 ctor
= build2 (COMPLEX_EXPR
, type
, r
, i
);
4207 TREE_OPERAND (*expr_p
, 1) = ctor
;
4208 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 1),
4211 rhs_predicate_for (TREE_OPERAND (*expr_p
, 0)),
4219 unsigned HOST_WIDE_INT ix
;
4220 constructor_elt
*ce
;
4222 if (notify_temp_creation
)
4225 /* Go ahead and simplify constant constructors to VECTOR_CST. */
4226 if (TREE_CONSTANT (ctor
))
4228 bool constant_p
= true;
4231 /* Even when ctor is constant, it might contain non-*_CST
4232 elements, such as addresses or trapping values like
4233 1.0/0.0 - 1.0/0.0. Such expressions don't belong
4234 in VECTOR_CST nodes. */
4235 FOR_EACH_CONSTRUCTOR_VALUE (elts
, ix
, value
)
4236 if (!CONSTANT_CLASS_P (value
))
4244 TREE_OPERAND (*expr_p
, 1) = build_vector_from_ctor (type
, elts
);
4248 TREE_CONSTANT (ctor
) = 0;
4251 /* Vector types use CONSTRUCTOR all the way through gimple
4252 compilation as a general initializer. */
4253 FOR_EACH_VEC_SAFE_ELT (elts
, ix
, ce
)
4255 enum gimplify_status tret
;
4256 tret
= gimplify_expr (&ce
->value
, pre_p
, post_p
, is_gimple_val
,
4258 if (tret
== GS_ERROR
)
4260 else if (TREE_STATIC (ctor
)
4261 && !initializer_constant_valid_p (ce
->value
,
4262 TREE_TYPE (ce
->value
)))
4263 TREE_STATIC (ctor
) = 0;
4265 if (!is_gimple_reg (TREE_OPERAND (*expr_p
, 0)))
4266 TREE_OPERAND (*expr_p
, 1) = get_formal_tmp_var (ctor
, pre_p
);
4271 /* So how did we get a CONSTRUCTOR for a scalar type? */
4275 if (ret
== GS_ERROR
)
4277 else if (want_value
)
4284 /* If we have gimplified both sides of the initializer but have
4285 not emitted an assignment, do so now. */
4288 tree lhs
= TREE_OPERAND (*expr_p
, 0);
4289 tree rhs
= TREE_OPERAND (*expr_p
, 1);
4290 gassign
*init
= gimple_build_assign (lhs
, rhs
);
4291 gimplify_seq_add_stmt (pre_p
, init
);
4299 /* Given a pointer value OP0, return a simplified version of an
4300 indirection through OP0, or NULL_TREE if no simplification is
4301 possible. This may only be applied to a rhs of an expression.
4302 Note that the resulting type may be different from the type pointed
4303 to in the sense that it is still compatible from the langhooks
4307 gimple_fold_indirect_ref_rhs (tree t
)
4309 return gimple_fold_indirect_ref (t
);
4312 /* Subroutine of gimplify_modify_expr to do simplifications of
4313 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
4314 something changes. */
4316 static enum gimplify_status
4317 gimplify_modify_expr_rhs (tree
*expr_p
, tree
*from_p
, tree
*to_p
,
4318 gimple_seq
*pre_p
, gimple_seq
*post_p
,
4321 enum gimplify_status ret
= GS_UNHANDLED
;
4327 switch (TREE_CODE (*from_p
))
4330 /* If we're assigning from a read-only variable initialized with
4331 a constructor, do the direct assignment from the constructor,
4332 but only if neither source nor target are volatile since this
4333 latter assignment might end up being done on a per-field basis. */
4334 if (DECL_INITIAL (*from_p
)
4335 && TREE_READONLY (*from_p
)
4336 && !TREE_THIS_VOLATILE (*from_p
)
4337 && !TREE_THIS_VOLATILE (*to_p
)
4338 && TREE_CODE (DECL_INITIAL (*from_p
)) == CONSTRUCTOR
)
4340 tree old_from
= *from_p
;
4341 enum gimplify_status subret
;
4343 /* Move the constructor into the RHS. */
4344 *from_p
= unshare_expr (DECL_INITIAL (*from_p
));
4346 /* Let's see if gimplify_init_constructor will need to put
4348 subret
= gimplify_init_constructor (expr_p
, NULL
, NULL
,
4350 if (subret
== GS_ERROR
)
4352 /* If so, revert the change. */
4364 /* If we have code like
4368 where the type of "x" is a (possibly cv-qualified variant
4369 of "A"), treat the entire expression as identical to "x".
4370 This kind of code arises in C++ when an object is bound
4371 to a const reference, and if "x" is a TARGET_EXPR we want
4372 to take advantage of the optimization below. */
4373 bool volatile_p
= TREE_THIS_VOLATILE (*from_p
);
4374 tree t
= gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p
, 0));
4377 if (TREE_THIS_VOLATILE (t
) != volatile_p
)
4380 t
= build_simple_mem_ref_loc (EXPR_LOCATION (*from_p
),
4381 build_fold_addr_expr (t
));
4382 if (REFERENCE_CLASS_P (t
))
4383 TREE_THIS_VOLATILE (t
) = volatile_p
;
4394 /* If we are initializing something from a TARGET_EXPR, strip the
4395 TARGET_EXPR and initialize it directly, if possible. This can't
4396 be done if the initializer is void, since that implies that the
4397 temporary is set in some non-trivial way.
4399 ??? What about code that pulls out the temp and uses it
4400 elsewhere? I think that such code never uses the TARGET_EXPR as
4401 an initializer. If I'm wrong, we'll die because the temp won't
4402 have any RTL. In that case, I guess we'll need to replace
4403 references somehow. */
4404 tree init
= TARGET_EXPR_INITIAL (*from_p
);
4407 && !VOID_TYPE_P (TREE_TYPE (init
)))
4417 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
4419 gimplify_compound_expr (from_p
, pre_p
, true);
4425 /* If we already made some changes, let the front end have a
4426 crack at this before we break it down. */
4427 if (ret
!= GS_UNHANDLED
)
4429 /* If we're initializing from a CONSTRUCTOR, break this into
4430 individual MODIFY_EXPRs. */
4431 return gimplify_init_constructor (expr_p
, pre_p
, post_p
, want_value
,
4435 /* If we're assigning to a non-register type, push the assignment
4436 down into the branches. This is mandatory for ADDRESSABLE types,
4437 since we cannot generate temporaries for such, but it saves a
4438 copy in other cases as well. */
4439 if (!is_gimple_reg_type (TREE_TYPE (*from_p
)))
4441 /* This code should mirror the code in gimplify_cond_expr. */
4442 enum tree_code code
= TREE_CODE (*expr_p
);
4443 tree cond
= *from_p
;
4444 tree result
= *to_p
;
4446 ret
= gimplify_expr (&result
, pre_p
, post_p
,
4447 is_gimple_lvalue
, fb_lvalue
);
4448 if (ret
!= GS_ERROR
)
4451 if (TREE_TYPE (TREE_OPERAND (cond
, 1)) != void_type_node
)
4452 TREE_OPERAND (cond
, 1)
4453 = build2 (code
, void_type_node
, result
,
4454 TREE_OPERAND (cond
, 1));
4455 if (TREE_TYPE (TREE_OPERAND (cond
, 2)) != void_type_node
)
4456 TREE_OPERAND (cond
, 2)
4457 = build2 (code
, void_type_node
, unshare_expr (result
),
4458 TREE_OPERAND (cond
, 2));
4460 TREE_TYPE (cond
) = void_type_node
;
4461 recalculate_side_effects (cond
);
4465 gimplify_and_add (cond
, pre_p
);
4466 *expr_p
= unshare_expr (result
);
4475 /* For calls that return in memory, give *to_p as the CALL_EXPR's
4476 return slot so that we don't generate a temporary. */
4477 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p
)
4478 && aggregate_value_p (*from_p
, *from_p
))
4482 if (!(rhs_predicate_for (*to_p
))(*from_p
))
4483 /* If we need a temporary, *to_p isn't accurate. */
4485 /* It's OK to use the return slot directly unless it's an NRV. */
4486 else if (TREE_CODE (*to_p
) == RESULT_DECL
4487 && DECL_NAME (*to_p
) == NULL_TREE
4488 && needs_to_live_in_memory (*to_p
))
4490 else if (is_gimple_reg_type (TREE_TYPE (*to_p
))
4491 || (DECL_P (*to_p
) && DECL_REGISTER (*to_p
)))
4492 /* Don't force regs into memory. */
4494 else if (TREE_CODE (*expr_p
) == INIT_EXPR
)
4495 /* It's OK to use the target directly if it's being
4498 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p
)))
4500 /* Always use the target and thus RSO for variable-sized types.
4501 GIMPLE cannot deal with a variable-sized assignment
4502 embedded in a call statement. */
4504 else if (TREE_CODE (*to_p
) != SSA_NAME
4505 && (!is_gimple_variable (*to_p
)
4506 || needs_to_live_in_memory (*to_p
)))
4507 /* Don't use the original target if it's already addressable;
4508 if its address escapes, and the called function uses the
4509 NRV optimization, a conforming program could see *to_p
4510 change before the called function returns; see c++/19317.
4511 When optimizing, the return_slot pass marks more functions
4512 as safe after we have escape info. */
4519 CALL_EXPR_RETURN_SLOT_OPT (*from_p
) = 1;
4520 mark_addressable (*to_p
);
4525 case WITH_SIZE_EXPR
:
4526 /* Likewise for calls that return an aggregate of non-constant size,
4527 since we would not be able to generate a temporary at all. */
4528 if (TREE_CODE (TREE_OPERAND (*from_p
, 0)) == CALL_EXPR
)
4530 *from_p
= TREE_OPERAND (*from_p
, 0);
4531 /* We don't change ret in this case because the
4532 WITH_SIZE_EXPR might have been added in
4533 gimplify_modify_expr, so returning GS_OK would lead to an
4539 /* If we're initializing from a container, push the initialization
4541 case CLEANUP_POINT_EXPR
:
4543 case STATEMENT_LIST
:
4545 tree wrap
= *from_p
;
4548 ret
= gimplify_expr (to_p
, pre_p
, post_p
, is_gimple_min_lval
,
4550 if (ret
!= GS_ERROR
)
4553 t
= voidify_wrapper_expr (wrap
, *expr_p
);
4554 gcc_assert (t
== *expr_p
);
4558 gimplify_and_add (wrap
, pre_p
);
4559 *expr_p
= unshare_expr (*to_p
);
4566 case COMPOUND_LITERAL_EXPR
:
4568 tree complit
= TREE_OPERAND (*expr_p
, 1);
4569 tree decl_s
= COMPOUND_LITERAL_EXPR_DECL_EXPR (complit
);
4570 tree decl
= DECL_EXPR_DECL (decl_s
);
4571 tree init
= DECL_INITIAL (decl
);
4573 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
4574 into struct T x = { 0, 1, 2 } if the address of the
4575 compound literal has never been taken. */
4576 if (!TREE_ADDRESSABLE (complit
)
4577 && !TREE_ADDRESSABLE (decl
)
4580 *expr_p
= copy_node (*expr_p
);
4581 TREE_OPERAND (*expr_p
, 1) = init
;
4596 /* Return true if T looks like a valid GIMPLE statement. */
4599 is_gimple_stmt (tree t
)
4601 const enum tree_code code
= TREE_CODE (t
);
4606 /* The only valid NOP_EXPR is the empty statement. */
4607 return IS_EMPTY_STMT (t
);
4611 /* These are only valid if they're void. */
4612 return TREE_TYPE (t
) == NULL
|| VOID_TYPE_P (TREE_TYPE (t
));
4618 case CASE_LABEL_EXPR
:
4619 case TRY_CATCH_EXPR
:
4620 case TRY_FINALLY_EXPR
:
4621 case EH_FILTER_EXPR
:
4624 case STATEMENT_LIST
:
4628 case OACC_HOST_DATA
:
4631 case OACC_ENTER_DATA
:
4632 case OACC_EXIT_DATA
:
4638 case OMP_DISTRIBUTE
:
4649 case OMP_TARGET_DATA
:
4650 case OMP_TARGET_UPDATE
:
4651 case OMP_TARGET_ENTER_DATA
:
4652 case OMP_TARGET_EXIT_DATA
:
4655 /* These are always void. */
4661 /* These are valid regardless of their type. */
4670 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
4671 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a variable with
4672 DECL_GIMPLE_REG_P set.
4674 IMPORTANT NOTE: This promotion is performed by introducing a load of the
4675 other, unmodified part of the complex object just before the total store.
4676 As a consequence, if the object is still uninitialized, an undefined value
4677 will be loaded into a register, which may result in a spurious exception
4678 if the register is floating-point and the value happens to be a signaling
4679 NaN for example. Then the fully-fledged complex operations lowering pass
4680 followed by a DCE pass are necessary in order to fix things up. */
4682 static enum gimplify_status
4683 gimplify_modify_expr_complex_part (tree
*expr_p
, gimple_seq
*pre_p
,
4686 enum tree_code code
, ocode
;
4687 tree lhs
, rhs
, new_rhs
, other
, realpart
, imagpart
;
4689 lhs
= TREE_OPERAND (*expr_p
, 0);
4690 rhs
= TREE_OPERAND (*expr_p
, 1);
4691 code
= TREE_CODE (lhs
);
4692 lhs
= TREE_OPERAND (lhs
, 0);
4694 ocode
= code
== REALPART_EXPR
? IMAGPART_EXPR
: REALPART_EXPR
;
4695 other
= build1 (ocode
, TREE_TYPE (rhs
), lhs
);
4696 TREE_NO_WARNING (other
) = 1;
4697 other
= get_formal_tmp_var (other
, pre_p
);
4699 realpart
= code
== REALPART_EXPR
? rhs
: other
;
4700 imagpart
= code
== REALPART_EXPR
? other
: rhs
;
4702 if (TREE_CONSTANT (realpart
) && TREE_CONSTANT (imagpart
))
4703 new_rhs
= build_complex (TREE_TYPE (lhs
), realpart
, imagpart
);
4705 new_rhs
= build2 (COMPLEX_EXPR
, TREE_TYPE (lhs
), realpart
, imagpart
);
4707 gimplify_seq_add_stmt (pre_p
, gimple_build_assign (lhs
, new_rhs
));
4708 *expr_p
= (want_value
) ? rhs
: NULL_TREE
;
4713 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
4719 PRE_P points to the list where side effects that must happen before
4720 *EXPR_P should be stored.
4722 POST_P points to the list where side effects that must happen after
4723 *EXPR_P should be stored.
4725 WANT_VALUE is nonzero iff we want to use the value of this expression
4726 in another expression. */
4728 static enum gimplify_status
4729 gimplify_modify_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
4732 tree
*from_p
= &TREE_OPERAND (*expr_p
, 1);
4733 tree
*to_p
= &TREE_OPERAND (*expr_p
, 0);
4734 enum gimplify_status ret
= GS_UNHANDLED
;
4736 location_t loc
= EXPR_LOCATION (*expr_p
);
4737 gimple_stmt_iterator gsi
;
4739 gcc_assert (TREE_CODE (*expr_p
) == MODIFY_EXPR
4740 || TREE_CODE (*expr_p
) == INIT_EXPR
);
4742 /* Trying to simplify a clobber using normal logic doesn't work,
4743 so handle it here. */
4744 if (TREE_CLOBBER_P (*from_p
))
4746 ret
= gimplify_expr (to_p
, pre_p
, post_p
, is_gimple_lvalue
, fb_lvalue
);
4747 if (ret
== GS_ERROR
)
4749 gcc_assert (!want_value
4750 && (TREE_CODE (*to_p
) == VAR_DECL
4751 || TREE_CODE (*to_p
) == MEM_REF
));
4752 gimplify_seq_add_stmt (pre_p
, gimple_build_assign (*to_p
, *from_p
));
4757 /* Insert pointer conversions required by the middle-end that are not
4758 required by the frontend. This fixes middle-end type checking for
4759 for example gcc.dg/redecl-6.c. */
4760 if (POINTER_TYPE_P (TREE_TYPE (*to_p
)))
4762 STRIP_USELESS_TYPE_CONVERSION (*from_p
);
4763 if (!useless_type_conversion_p (TREE_TYPE (*to_p
), TREE_TYPE (*from_p
)))
4764 *from_p
= fold_convert_loc (loc
, TREE_TYPE (*to_p
), *from_p
);
4767 /* See if any simplifications can be done based on what the RHS is. */
4768 ret
= gimplify_modify_expr_rhs (expr_p
, from_p
, to_p
, pre_p
, post_p
,
4770 if (ret
!= GS_UNHANDLED
)
4773 /* For zero sized types only gimplify the left hand side and right hand
4774 side as statements and throw away the assignment. Do this after
4775 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
4777 if (zero_sized_type (TREE_TYPE (*from_p
)) && !want_value
)
4779 gimplify_stmt (from_p
, pre_p
);
4780 gimplify_stmt (to_p
, pre_p
);
4781 *expr_p
= NULL_TREE
;
4785 /* If the value being copied is of variable width, compute the length
4786 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
4787 before gimplifying any of the operands so that we can resolve any
4788 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
4789 the size of the expression to be copied, not of the destination, so
4790 that is what we must do here. */
4791 maybe_with_size_expr (from_p
);
4793 /* As a special case, we have to temporarily allow for assignments
4794 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
4795 a toplevel statement, when gimplifying the GENERIC expression
4796 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
4797 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
4799 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
4800 prevent gimplify_expr from trying to create a new temporary for
4801 foo's LHS, we tell it that it should only gimplify until it
4802 reaches the CALL_EXPR. On return from gimplify_expr, the newly
4803 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
4804 and all we need to do here is set 'a' to be its LHS. */
4806 /* Gimplify the RHS first for C++17 and bug 71104. */
4807 gimple_predicate initial_pred
= initial_rhs_predicate_for (*to_p
);
4808 ret
= gimplify_expr (from_p
, pre_p
, post_p
, initial_pred
, fb_rvalue
);
4809 if (ret
== GS_ERROR
)
4812 /* Then gimplify the LHS. */
4813 /* If we gimplified the RHS to a CALL_EXPR and that call may return
4814 twice we have to make sure to gimplify into non-SSA as otherwise
4815 the abnormal edge added later will make those defs not dominate
4817 ??? Technically this applies only to the registers used in the
4818 resulting non-register *TO_P. */
4819 bool saved_into_ssa
= gimplify_ctxp
->into_ssa
;
4821 && TREE_CODE (*from_p
) == CALL_EXPR
4822 && call_expr_flags (*from_p
) & ECF_RETURNS_TWICE
)
4823 gimplify_ctxp
->into_ssa
= false;
4824 ret
= gimplify_expr (to_p
, pre_p
, post_p
, is_gimple_lvalue
, fb_lvalue
);
4825 gimplify_ctxp
->into_ssa
= saved_into_ssa
;
4826 if (ret
== GS_ERROR
)
4829 /* Now that the LHS is gimplified, re-gimplify the RHS if our initial
4830 guess for the predicate was wrong. */
4831 gimple_predicate final_pred
= rhs_predicate_for (*to_p
);
4832 if (final_pred
!= initial_pred
)
4834 ret
= gimplify_expr (from_p
, pre_p
, post_p
, final_pred
, fb_rvalue
);
4835 if (ret
== GS_ERROR
)
4839 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
4840 size as argument to the call. */
4841 if (TREE_CODE (*from_p
) == WITH_SIZE_EXPR
)
4843 tree call
= TREE_OPERAND (*from_p
, 0);
4844 tree vlasize
= TREE_OPERAND (*from_p
, 1);
4846 if (TREE_CODE (call
) == CALL_EXPR
4847 && CALL_EXPR_IFN (call
) == IFN_VA_ARG
)
4849 int nargs
= call_expr_nargs (call
);
4850 tree type
= TREE_TYPE (call
);
4851 tree ap
= CALL_EXPR_ARG (call
, 0);
4852 tree tag
= CALL_EXPR_ARG (call
, 1);
4853 tree aptag
= CALL_EXPR_ARG (call
, 2);
4854 tree newcall
= build_call_expr_internal_loc (EXPR_LOCATION (call
),
4858 TREE_OPERAND (*from_p
, 0) = newcall
;
4862 /* Now see if the above changed *from_p to something we handle specially. */
4863 ret
= gimplify_modify_expr_rhs (expr_p
, from_p
, to_p
, pre_p
, post_p
,
4865 if (ret
!= GS_UNHANDLED
)
4868 /* If we've got a variable sized assignment between two lvalues (i.e. does
4869 not involve a call), then we can make things a bit more straightforward
4870 by converting the assignment to memcpy or memset. */
4871 if (TREE_CODE (*from_p
) == WITH_SIZE_EXPR
)
4873 tree from
= TREE_OPERAND (*from_p
, 0);
4874 tree size
= TREE_OPERAND (*from_p
, 1);
4876 if (TREE_CODE (from
) == CONSTRUCTOR
)
4877 return gimplify_modify_expr_to_memset (expr_p
, size
, want_value
, pre_p
);
4879 if (is_gimple_addressable (from
))
4882 return gimplify_modify_expr_to_memcpy (expr_p
, size
, want_value
,
4887 /* Transform partial stores to non-addressable complex variables into
4888 total stores. This allows us to use real instead of virtual operands
4889 for these variables, which improves optimization. */
4890 if ((TREE_CODE (*to_p
) == REALPART_EXPR
4891 || TREE_CODE (*to_p
) == IMAGPART_EXPR
)
4892 && is_gimple_reg (TREE_OPERAND (*to_p
, 0)))
4893 return gimplify_modify_expr_complex_part (expr_p
, pre_p
, want_value
);
4895 /* Try to alleviate the effects of the gimplification creating artificial
4896 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
4897 make sure not to create DECL_DEBUG_EXPR links across functions. */
4898 if (!gimplify_ctxp
->into_ssa
4899 && TREE_CODE (*from_p
) == VAR_DECL
4900 && DECL_IGNORED_P (*from_p
)
4902 && !DECL_IGNORED_P (*to_p
)
4903 && decl_function_context (*to_p
) == current_function_decl
)
4905 if (!DECL_NAME (*from_p
) && DECL_NAME (*to_p
))
4907 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p
)));
4908 DECL_HAS_DEBUG_EXPR_P (*from_p
) = 1;
4909 SET_DECL_DEBUG_EXPR (*from_p
, *to_p
);
4912 if (want_value
&& TREE_THIS_VOLATILE (*to_p
))
4913 *from_p
= get_initialized_tmp_var (*from_p
, pre_p
, post_p
);
4915 if (TREE_CODE (*from_p
) == CALL_EXPR
)
4917 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
4918 instead of a GIMPLE_ASSIGN. */
4920 if (CALL_EXPR_FN (*from_p
) == NULL_TREE
)
4922 /* Gimplify internal functions created in the FEs. */
4923 int nargs
= call_expr_nargs (*from_p
), i
;
4924 enum internal_fn ifn
= CALL_EXPR_IFN (*from_p
);
4925 auto_vec
<tree
> vargs (nargs
);
4927 for (i
= 0; i
< nargs
; i
++)
4929 gimplify_arg (&CALL_EXPR_ARG (*from_p
, i
), pre_p
,
4930 EXPR_LOCATION (*from_p
));
4931 vargs
.quick_push (CALL_EXPR_ARG (*from_p
, i
));
4933 call_stmt
= gimple_build_call_internal_vec (ifn
, vargs
);
4934 gimple_set_location (call_stmt
, EXPR_LOCATION (*expr_p
));
4938 tree fnptrtype
= TREE_TYPE (CALL_EXPR_FN (*from_p
));
4939 CALL_EXPR_FN (*from_p
) = TREE_OPERAND (CALL_EXPR_FN (*from_p
), 0);
4940 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p
));
4941 tree fndecl
= get_callee_fndecl (*from_p
);
4943 && DECL_BUILT_IN_CLASS (fndecl
) == BUILT_IN_NORMAL
4944 && DECL_FUNCTION_CODE (fndecl
) == BUILT_IN_EXPECT
4945 && call_expr_nargs (*from_p
) == 3)
4946 call_stmt
= gimple_build_call_internal (IFN_BUILTIN_EXPECT
, 3,
4947 CALL_EXPR_ARG (*from_p
, 0),
4948 CALL_EXPR_ARG (*from_p
, 1),
4949 CALL_EXPR_ARG (*from_p
, 2));
4952 call_stmt
= gimple_build_call_from_tree (*from_p
);
4953 gimple_call_set_fntype (call_stmt
, TREE_TYPE (fnptrtype
));
4956 notice_special_calls (call_stmt
);
4957 if (!gimple_call_noreturn_p (call_stmt
) || !should_remove_lhs_p (*to_p
))
4958 gimple_call_set_lhs (call_stmt
, *to_p
);
4959 else if (TREE_CODE (*to_p
) == SSA_NAME
)
4960 /* The above is somewhat premature, avoid ICEing later for a
4961 SSA name w/o a definition. We may have uses in the GIMPLE IL.
4962 ??? This doesn't make it a default-def. */
4963 SSA_NAME_DEF_STMT (*to_p
) = gimple_build_nop ();
4968 assign
= gimple_build_assign (*to_p
, *from_p
);
4969 gimple_set_location (assign
, EXPR_LOCATION (*expr_p
));
4970 if (COMPARISON_CLASS_P (*from_p
))
4971 gimple_set_no_warning (assign
, TREE_NO_WARNING (*from_p
));
4974 if (gimplify_ctxp
->into_ssa
&& is_gimple_reg (*to_p
))
4976 /* We should have got an SSA name from the start. */
4977 gcc_assert (TREE_CODE (*to_p
) == SSA_NAME
4978 || ! gimple_in_ssa_p (cfun
));
4981 gimplify_seq_add_stmt (pre_p
, assign
);
4982 gsi
= gsi_last (*pre_p
);
4983 maybe_fold_stmt (&gsi
);
4987 *expr_p
= TREE_THIS_VOLATILE (*to_p
) ? *from_p
: unshare_expr (*to_p
);
4996 /* Gimplify a comparison between two variable-sized objects. Do this
4997 with a call to BUILT_IN_MEMCMP. */
4999 static enum gimplify_status
5000 gimplify_variable_sized_compare (tree
*expr_p
)
5002 location_t loc
= EXPR_LOCATION (*expr_p
);
5003 tree op0
= TREE_OPERAND (*expr_p
, 0);
5004 tree op1
= TREE_OPERAND (*expr_p
, 1);
5005 tree t
, arg
, dest
, src
, expr
;
5007 arg
= TYPE_SIZE_UNIT (TREE_TYPE (op0
));
5008 arg
= unshare_expr (arg
);
5009 arg
= SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg
, op0
);
5010 src
= build_fold_addr_expr_loc (loc
, op1
);
5011 dest
= build_fold_addr_expr_loc (loc
, op0
);
5012 t
= builtin_decl_implicit (BUILT_IN_MEMCMP
);
5013 t
= build_call_expr_loc (loc
, t
, 3, dest
, src
, arg
);
5016 = build2 (TREE_CODE (*expr_p
), TREE_TYPE (*expr_p
), t
, integer_zero_node
);
5017 SET_EXPR_LOCATION (expr
, loc
);
5023 /* Gimplify a comparison between two aggregate objects of integral scalar
5024 mode as a comparison between the bitwise equivalent scalar values. */
5026 static enum gimplify_status
5027 gimplify_scalar_mode_aggregate_compare (tree
*expr_p
)
5029 location_t loc
= EXPR_LOCATION (*expr_p
);
5030 tree op0
= TREE_OPERAND (*expr_p
, 0);
5031 tree op1
= TREE_OPERAND (*expr_p
, 1);
5033 tree type
= TREE_TYPE (op0
);
5034 tree scalar_type
= lang_hooks
.types
.type_for_mode (TYPE_MODE (type
), 1);
5036 op0
= fold_build1_loc (loc
, VIEW_CONVERT_EXPR
, scalar_type
, op0
);
5037 op1
= fold_build1_loc (loc
, VIEW_CONVERT_EXPR
, scalar_type
, op1
);
5040 = fold_build2_loc (loc
, TREE_CODE (*expr_p
), TREE_TYPE (*expr_p
), op0
, op1
);
5045 /* Gimplify an expression sequence. This function gimplifies each
5046 expression and rewrites the original expression with the last
5047 expression of the sequence in GIMPLE form.
5049 PRE_P points to the list where the side effects for all the
5050 expressions in the sequence will be emitted.
5052 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
5054 static enum gimplify_status
5055 gimplify_compound_expr (tree
*expr_p
, gimple_seq
*pre_p
, bool want_value
)
5061 tree
*sub_p
= &TREE_OPERAND (t
, 0);
5063 if (TREE_CODE (*sub_p
) == COMPOUND_EXPR
)
5064 gimplify_compound_expr (sub_p
, pre_p
, false);
5066 gimplify_stmt (sub_p
, pre_p
);
5068 t
= TREE_OPERAND (t
, 1);
5070 while (TREE_CODE (t
) == COMPOUND_EXPR
);
5077 gimplify_stmt (expr_p
, pre_p
);
5082 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
5083 gimplify. After gimplification, EXPR_P will point to a new temporary
5084 that holds the original value of the SAVE_EXPR node.
5086 PRE_P points to the list where side effects that must happen before
5087 *EXPR_P should be stored. */
5089 static enum gimplify_status
5090 gimplify_save_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
)
5092 enum gimplify_status ret
= GS_ALL_DONE
;
5095 gcc_assert (TREE_CODE (*expr_p
) == SAVE_EXPR
);
5096 val
= TREE_OPERAND (*expr_p
, 0);
5098 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
5099 if (!SAVE_EXPR_RESOLVED_P (*expr_p
))
5101 /* The operand may be a void-valued expression such as SAVE_EXPRs
5102 generated by the Java frontend for class initialization. It is
5103 being executed only for its side-effects. */
5104 if (TREE_TYPE (val
) == void_type_node
)
5106 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
5107 is_gimple_stmt
, fb_none
);
5111 /* The temporary may not be an SSA name as later abnormal and EH
5112 control flow may invalidate use/def domination. */
5113 val
= get_initialized_tmp_var (val
, pre_p
, post_p
, false);
5115 TREE_OPERAND (*expr_p
, 0) = val
;
5116 SAVE_EXPR_RESOLVED_P (*expr_p
) = 1;
5124 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
5131 PRE_P points to the list where side effects that must happen before
5132 *EXPR_P should be stored.
5134 POST_P points to the list where side effects that must happen after
5135 *EXPR_P should be stored. */
5137 static enum gimplify_status
5138 gimplify_addr_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
)
5140 tree expr
= *expr_p
;
5141 tree op0
= TREE_OPERAND (expr
, 0);
5142 enum gimplify_status ret
;
5143 location_t loc
= EXPR_LOCATION (*expr_p
);
5145 switch (TREE_CODE (op0
))
5149 /* Check if we are dealing with an expression of the form '&*ptr'.
5150 While the front end folds away '&*ptr' into 'ptr', these
5151 expressions may be generated internally by the compiler (e.g.,
5152 builtins like __builtin_va_end). */
5153 /* Caution: the silent array decomposition semantics we allow for
5154 ADDR_EXPR means we can't always discard the pair. */
5155 /* Gimplification of the ADDR_EXPR operand may drop
5156 cv-qualification conversions, so make sure we add them if
5159 tree op00
= TREE_OPERAND (op0
, 0);
5160 tree t_expr
= TREE_TYPE (expr
);
5161 tree t_op00
= TREE_TYPE (op00
);
5163 if (!useless_type_conversion_p (t_expr
, t_op00
))
5164 op00
= fold_convert_loc (loc
, TREE_TYPE (expr
), op00
);
5170 case VIEW_CONVERT_EXPR
:
5171 /* Take the address of our operand and then convert it to the type of
5174 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
5175 all clear. The impact of this transformation is even less clear. */
5177 /* If the operand is a useless conversion, look through it. Doing so
5178 guarantees that the ADDR_EXPR and its operand will remain of the
5180 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0
, 0)))
5181 op0
= TREE_OPERAND (op0
, 0);
5183 *expr_p
= fold_convert_loc (loc
, TREE_TYPE (expr
),
5184 build_fold_addr_expr_loc (loc
,
5185 TREE_OPERAND (op0
, 0)));
5190 if (integer_zerop (TREE_OPERAND (op0
, 1)))
5191 goto do_indirect_ref
;
5196 /* If we see a call to a declared builtin or see its address
5197 being taken (we can unify those cases here) then we can mark
5198 the builtin for implicit generation by GCC. */
5199 if (TREE_CODE (op0
) == FUNCTION_DECL
5200 && DECL_BUILT_IN_CLASS (op0
) == BUILT_IN_NORMAL
5201 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0
)))
5202 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0
), true);
5204 /* We use fb_either here because the C frontend sometimes takes
5205 the address of a call that returns a struct; see
5206 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
5207 the implied temporary explicit. */
5209 /* Make the operand addressable. */
5210 ret
= gimplify_expr (&TREE_OPERAND (expr
, 0), pre_p
, post_p
,
5211 is_gimple_addressable
, fb_either
);
5212 if (ret
== GS_ERROR
)
5215 /* Then mark it. Beware that it may not be possible to do so directly
5216 if a temporary has been created by the gimplification. */
5217 prepare_gimple_addressable (&TREE_OPERAND (expr
, 0), pre_p
);
5219 op0
= TREE_OPERAND (expr
, 0);
5221 /* For various reasons, the gimplification of the expression
5222 may have made a new INDIRECT_REF. */
5223 if (TREE_CODE (op0
) == INDIRECT_REF
)
5224 goto do_indirect_ref
;
5226 mark_addressable (TREE_OPERAND (expr
, 0));
5228 /* The FEs may end up building ADDR_EXPRs early on a decl with
5229 an incomplete type. Re-build ADDR_EXPRs in canonical form
5231 if (!types_compatible_p (TREE_TYPE (op0
), TREE_TYPE (TREE_TYPE (expr
))))
5232 *expr_p
= build_fold_addr_expr (op0
);
5234 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
5235 recompute_tree_invariant_for_addr_expr (*expr_p
);
5237 /* If we re-built the ADDR_EXPR add a conversion to the original type
5239 if (!useless_type_conversion_p (TREE_TYPE (expr
), TREE_TYPE (*expr_p
)))
5240 *expr_p
= fold_convert (TREE_TYPE (expr
), *expr_p
);
5248 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
5249 value; output operands should be a gimple lvalue. */
5251 static enum gimplify_status
5252 gimplify_asm_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
)
5256 const char **oconstraints
;
5259 const char *constraint
;
5260 bool allows_mem
, allows_reg
, is_inout
;
5261 enum gimplify_status ret
, tret
;
5263 vec
<tree
, va_gc
> *inputs
;
5264 vec
<tree
, va_gc
> *outputs
;
5265 vec
<tree
, va_gc
> *clobbers
;
5266 vec
<tree
, va_gc
> *labels
;
5270 noutputs
= list_length (ASM_OUTPUTS (expr
));
5271 oconstraints
= (const char **) alloca ((noutputs
) * sizeof (const char *));
5279 link_next
= NULL_TREE
;
5280 for (i
= 0, link
= ASM_OUTPUTS (expr
); link
; ++i
, link
= link_next
)
5283 size_t constraint_len
;
5285 link_next
= TREE_CHAIN (link
);
5289 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link
)));
5290 constraint_len
= strlen (constraint
);
5291 if (constraint_len
== 0)
5294 ok
= parse_output_constraint (&constraint
, i
, 0, 0,
5295 &allows_mem
, &allows_reg
, &is_inout
);
5302 if (!allows_reg
&& allows_mem
)
5303 mark_addressable (TREE_VALUE (link
));
5305 tret
= gimplify_expr (&TREE_VALUE (link
), pre_p
, post_p
,
5306 is_inout
? is_gimple_min_lval
: is_gimple_lvalue
,
5307 fb_lvalue
| fb_mayfail
);
5308 if (tret
== GS_ERROR
)
5310 error ("invalid lvalue in asm output %d", i
);
5314 /* If the constraint does not allow memory make sure we gimplify
5315 it to a register if it is not already but its base is. This
5316 happens for complex and vector components. */
5319 tree op
= TREE_VALUE (link
);
5320 if (! is_gimple_val (op
)
5321 && is_gimple_reg_type (TREE_TYPE (op
))
5322 && is_gimple_reg (get_base_address (op
)))
5324 tree tem
= create_tmp_reg (TREE_TYPE (op
));
5328 ass
= build2 (MODIFY_EXPR
, TREE_TYPE (tem
),
5329 tem
, unshare_expr (op
));
5330 gimplify_and_add (ass
, pre_p
);
5332 ass
= build2 (MODIFY_EXPR
, TREE_TYPE (tem
), op
, tem
);
5333 gimplify_and_add (ass
, post_p
);
5335 TREE_VALUE (link
) = tem
;
5340 vec_safe_push (outputs
, link
);
5341 TREE_CHAIN (link
) = NULL_TREE
;
5345 /* An input/output operand. To give the optimizers more
5346 flexibility, split it into separate input and output
5349 /* Buffer big enough to format a 32-bit UINT_MAX into. */
5352 /* Turn the in/out constraint into an output constraint. */
5353 char *p
= xstrdup (constraint
);
5355 TREE_VALUE (TREE_PURPOSE (link
)) = build_string (constraint_len
, p
);
5357 /* And add a matching input constraint. */
5360 sprintf (buf
, "%u", i
);
5362 /* If there are multiple alternatives in the constraint,
5363 handle each of them individually. Those that allow register
5364 will be replaced with operand number, the others will stay
5366 if (strchr (p
, ',') != NULL
)
5368 size_t len
= 0, buflen
= strlen (buf
);
5369 char *beg
, *end
, *str
, *dst
;
5373 end
= strchr (beg
, ',');
5375 end
= strchr (beg
, '\0');
5376 if ((size_t) (end
- beg
) < buflen
)
5379 len
+= end
- beg
+ 1;
5386 str
= (char *) alloca (len
);
5387 for (beg
= p
+ 1, dst
= str
;;)
5390 bool mem_p
, reg_p
, inout_p
;
5392 end
= strchr (beg
, ',');
5397 parse_output_constraint (&tem
, i
, 0, 0,
5398 &mem_p
, ®_p
, &inout_p
);
5403 memcpy (dst
, buf
, buflen
);
5412 memcpy (dst
, beg
, len
);
5421 input
= build_string (dst
- str
, str
);
5424 input
= build_string (strlen (buf
), buf
);
5427 input
= build_string (constraint_len
- 1, constraint
+ 1);
5431 input
= build_tree_list (build_tree_list (NULL_TREE
, input
),
5432 unshare_expr (TREE_VALUE (link
)));
5433 ASM_INPUTS (expr
) = chainon (ASM_INPUTS (expr
), input
);
5437 link_next
= NULL_TREE
;
5438 for (link
= ASM_INPUTS (expr
); link
; ++i
, link
= link_next
)
5440 link_next
= TREE_CHAIN (link
);
5441 constraint
= TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link
)));
5442 parse_input_constraint (&constraint
, 0, 0, noutputs
, 0,
5443 oconstraints
, &allows_mem
, &allows_reg
);
5445 /* If we can't make copies, we can only accept memory. */
5446 if (TREE_ADDRESSABLE (TREE_TYPE (TREE_VALUE (link
))))
5452 error ("impossible constraint in %<asm%>");
5453 error ("non-memory input %d must stay in memory", i
);
5458 /* If the operand is a memory input, it should be an lvalue. */
5459 if (!allows_reg
&& allows_mem
)
5461 tree inputv
= TREE_VALUE (link
);
5462 STRIP_NOPS (inputv
);
5463 if (TREE_CODE (inputv
) == PREDECREMENT_EXPR
5464 || TREE_CODE (inputv
) == PREINCREMENT_EXPR
5465 || TREE_CODE (inputv
) == POSTDECREMENT_EXPR
5466 || TREE_CODE (inputv
) == POSTINCREMENT_EXPR
5467 || TREE_CODE (inputv
) == MODIFY_EXPR
)
5468 TREE_VALUE (link
) = error_mark_node
;
5469 tret
= gimplify_expr (&TREE_VALUE (link
), pre_p
, post_p
,
5470 is_gimple_lvalue
, fb_lvalue
| fb_mayfail
);
5471 if (tret
!= GS_ERROR
)
5473 /* Unlike output operands, memory inputs are not guaranteed
5474 to be lvalues by the FE, and while the expressions are
5475 marked addressable there, if it is e.g. a statement
5476 expression, temporaries in it might not end up being
5477 addressable. They might be already used in the IL and thus
5478 it is too late to make them addressable now though. */
5479 tree x
= TREE_VALUE (link
);
5480 while (handled_component_p (x
))
5481 x
= TREE_OPERAND (x
, 0);
5482 if (TREE_CODE (x
) == MEM_REF
5483 && TREE_CODE (TREE_OPERAND (x
, 0)) == ADDR_EXPR
)
5484 x
= TREE_OPERAND (TREE_OPERAND (x
, 0), 0);
5485 if ((TREE_CODE (x
) == VAR_DECL
5486 || TREE_CODE (x
) == PARM_DECL
5487 || TREE_CODE (x
) == RESULT_DECL
)
5488 && !TREE_ADDRESSABLE (x
)
5489 && is_gimple_reg (x
))
5491 warning_at (EXPR_LOC_OR_LOC (TREE_VALUE (link
),
5493 "memory input %d is not directly addressable",
5495 prepare_gimple_addressable (&TREE_VALUE (link
), pre_p
);
5498 mark_addressable (TREE_VALUE (link
));
5499 if (tret
== GS_ERROR
)
5501 error_at (EXPR_LOC_OR_LOC (TREE_VALUE (link
), input_location
),
5502 "memory input %d is not directly addressable", i
);
5508 tret
= gimplify_expr (&TREE_VALUE (link
), pre_p
, post_p
,
5509 is_gimple_asm_val
, fb_rvalue
);
5510 if (tret
== GS_ERROR
)
5514 TREE_CHAIN (link
) = NULL_TREE
;
5515 vec_safe_push (inputs
, link
);
5518 link_next
= NULL_TREE
;
5519 for (link
= ASM_CLOBBERS (expr
); link
; ++i
, link
= link_next
)
5521 link_next
= TREE_CHAIN (link
);
5522 TREE_CHAIN (link
) = NULL_TREE
;
5523 vec_safe_push (clobbers
, link
);
5526 link_next
= NULL_TREE
;
5527 for (link
= ASM_LABELS (expr
); link
; ++i
, link
= link_next
)
5529 link_next
= TREE_CHAIN (link
);
5530 TREE_CHAIN (link
) = NULL_TREE
;
5531 vec_safe_push (labels
, link
);
5534 /* Do not add ASMs with errors to the gimple IL stream. */
5535 if (ret
!= GS_ERROR
)
5537 stmt
= gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr
)),
5538 inputs
, outputs
, clobbers
, labels
);
5540 gimple_asm_set_volatile (stmt
, ASM_VOLATILE_P (expr
) || noutputs
== 0);
5541 gimple_asm_set_input (stmt
, ASM_INPUT_P (expr
));
5543 gimplify_seq_add_stmt (pre_p
, stmt
);
5549 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
5550 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
5551 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
5552 return to this function.
5554 FIXME should we complexify the prequeue handling instead? Or use flags
5555 for all the cleanups and let the optimizer tighten them up? The current
5556 code seems pretty fragile; it will break on a cleanup within any
5557 non-conditional nesting. But any such nesting would be broken, anyway;
5558 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
5559 and continues out of it. We can do that at the RTL level, though, so
5560 having an optimizer to tighten up try/finally regions would be a Good
5563 static enum gimplify_status
5564 gimplify_cleanup_point_expr (tree
*expr_p
, gimple_seq
*pre_p
)
5566 gimple_stmt_iterator iter
;
5567 gimple_seq body_sequence
= NULL
;
5569 tree temp
= voidify_wrapper_expr (*expr_p
, NULL
);
5571 /* We only care about the number of conditions between the innermost
5572 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
5573 any cleanups collected outside the CLEANUP_POINT_EXPR. */
5574 int old_conds
= gimplify_ctxp
->conditions
;
5575 gimple_seq old_cleanups
= gimplify_ctxp
->conditional_cleanups
;
5576 bool old_in_cleanup_point_expr
= gimplify_ctxp
->in_cleanup_point_expr
;
5577 gimplify_ctxp
->conditions
= 0;
5578 gimplify_ctxp
->conditional_cleanups
= NULL
;
5579 gimplify_ctxp
->in_cleanup_point_expr
= true;
5581 gimplify_stmt (&TREE_OPERAND (*expr_p
, 0), &body_sequence
);
5583 gimplify_ctxp
->conditions
= old_conds
;
5584 gimplify_ctxp
->conditional_cleanups
= old_cleanups
;
5585 gimplify_ctxp
->in_cleanup_point_expr
= old_in_cleanup_point_expr
;
5587 for (iter
= gsi_start (body_sequence
); !gsi_end_p (iter
); )
5589 gimple
*wce
= gsi_stmt (iter
);
5591 if (gimple_code (wce
) == GIMPLE_WITH_CLEANUP_EXPR
)
5593 if (gsi_one_before_end_p (iter
))
5595 /* Note that gsi_insert_seq_before and gsi_remove do not
5596 scan operands, unlike some other sequence mutators. */
5597 if (!gimple_wce_cleanup_eh_only (wce
))
5598 gsi_insert_seq_before_without_update (&iter
,
5599 gimple_wce_cleanup (wce
),
5601 gsi_remove (&iter
, true);
5608 enum gimple_try_flags kind
;
5610 if (gimple_wce_cleanup_eh_only (wce
))
5611 kind
= GIMPLE_TRY_CATCH
;
5613 kind
= GIMPLE_TRY_FINALLY
;
5614 seq
= gsi_split_seq_after (iter
);
5616 gtry
= gimple_build_try (seq
, gimple_wce_cleanup (wce
), kind
);
5617 /* Do not use gsi_replace here, as it may scan operands.
5618 We want to do a simple structural modification only. */
5619 gsi_set_stmt (&iter
, gtry
);
5620 iter
= gsi_start (gtry
->eval
);
5627 gimplify_seq_add_seq (pre_p
, body_sequence
);
5640 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
5641 is the cleanup action required. EH_ONLY is true if the cleanup should
5642 only be executed if an exception is thrown, not on normal exit. */
5645 gimple_push_cleanup (tree var
, tree cleanup
, bool eh_only
, gimple_seq
*pre_p
)
5648 gimple_seq cleanup_stmts
= NULL
;
5650 /* Errors can result in improperly nested cleanups. Which results in
5651 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
5655 if (gimple_conditional_context ())
5657 /* If we're in a conditional context, this is more complex. We only
5658 want to run the cleanup if we actually ran the initialization that
5659 necessitates it, but we want to run it after the end of the
5660 conditional context. So we wrap the try/finally around the
5661 condition and use a flag to determine whether or not to actually
5662 run the destructor. Thus
5666 becomes (approximately)
5670 if (test) { A::A(temp); flag = 1; val = f(temp); }
5673 if (flag) A::~A(temp);
5677 tree flag
= create_tmp_var (boolean_type_node
, "cleanup");
5678 gassign
*ffalse
= gimple_build_assign (flag
, boolean_false_node
);
5679 gassign
*ftrue
= gimple_build_assign (flag
, boolean_true_node
);
5681 cleanup
= build3 (COND_EXPR
, void_type_node
, flag
, cleanup
, NULL
);
5682 gimplify_stmt (&cleanup
, &cleanup_stmts
);
5683 wce
= gimple_build_wce (cleanup_stmts
);
5685 gimplify_seq_add_stmt (&gimplify_ctxp
->conditional_cleanups
, ffalse
);
5686 gimplify_seq_add_stmt (&gimplify_ctxp
->conditional_cleanups
, wce
);
5687 gimplify_seq_add_stmt (pre_p
, ftrue
);
5689 /* Because of this manipulation, and the EH edges that jump
5690 threading cannot redirect, the temporary (VAR) will appear
5691 to be used uninitialized. Don't warn. */
5692 TREE_NO_WARNING (var
) = 1;
5696 gimplify_stmt (&cleanup
, &cleanup_stmts
);
5697 wce
= gimple_build_wce (cleanup_stmts
);
5698 gimple_wce_set_cleanup_eh_only (wce
, eh_only
);
5699 gimplify_seq_add_stmt (pre_p
, wce
);
5703 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
5705 static enum gimplify_status
5706 gimplify_target_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
)
5708 tree targ
= *expr_p
;
5709 tree temp
= TARGET_EXPR_SLOT (targ
);
5710 tree init
= TARGET_EXPR_INITIAL (targ
);
5711 enum gimplify_status ret
;
5715 tree cleanup
= NULL_TREE
;
5717 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
5718 to the temps list. Handle also variable length TARGET_EXPRs. */
5719 if (TREE_CODE (DECL_SIZE (temp
)) != INTEGER_CST
)
5721 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp
)))
5722 gimplify_type_sizes (TREE_TYPE (temp
), pre_p
);
5723 gimplify_vla_decl (temp
, pre_p
);
5726 gimple_add_tmp_var (temp
);
5728 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
5729 expression is supposed to initialize the slot. */
5730 if (VOID_TYPE_P (TREE_TYPE (init
)))
5731 ret
= gimplify_expr (&init
, pre_p
, post_p
, is_gimple_stmt
, fb_none
);
5734 tree init_expr
= build2 (INIT_EXPR
, void_type_node
, temp
, init
);
5736 ret
= gimplify_expr (&init
, pre_p
, post_p
, is_gimple_stmt
, fb_none
);
5738 ggc_free (init_expr
);
5740 if (ret
== GS_ERROR
)
5742 /* PR c++/28266 Make sure this is expanded only once. */
5743 TARGET_EXPR_INITIAL (targ
) = NULL_TREE
;
5747 gimplify_and_add (init
, pre_p
);
5749 /* If needed, push the cleanup for the temp. */
5750 if (TARGET_EXPR_CLEANUP (targ
))
5752 if (CLEANUP_EH_ONLY (targ
))
5753 gimple_push_cleanup (temp
, TARGET_EXPR_CLEANUP (targ
),
5754 CLEANUP_EH_ONLY (targ
), pre_p
);
5756 cleanup
= TARGET_EXPR_CLEANUP (targ
);
5759 /* Add a clobber for the temporary going out of scope, like
5760 gimplify_bind_expr. */
5761 if (gimplify_ctxp
->in_cleanup_point_expr
5762 && needs_to_live_in_memory (temp
)
5763 && flag_stack_reuse
== SR_ALL
)
5765 tree clobber
= build_constructor (TREE_TYPE (temp
),
5767 TREE_THIS_VOLATILE (clobber
) = true;
5768 clobber
= build2 (MODIFY_EXPR
, TREE_TYPE (temp
), temp
, clobber
);
5770 cleanup
= build2 (COMPOUND_EXPR
, void_type_node
, cleanup
,
5777 gimple_push_cleanup (temp
, cleanup
, false, pre_p
);
5779 /* Only expand this once. */
5780 TREE_OPERAND (targ
, 3) = init
;
5781 TARGET_EXPR_INITIAL (targ
) = NULL_TREE
;
5784 /* We should have expanded this before. */
5785 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp
));
5791 /* Gimplification of expression trees. */
5793 /* Gimplify an expression which appears at statement context. The
5794 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
5795 NULL, a new sequence is allocated.
5797 Return true if we actually added a statement to the queue. */
5800 gimplify_stmt (tree
*stmt_p
, gimple_seq
*seq_p
)
5802 gimple_seq_node last
;
5804 last
= gimple_seq_last (*seq_p
);
5805 gimplify_expr (stmt_p
, seq_p
, NULL
, is_gimple_stmt
, fb_none
);
5806 return last
!= gimple_seq_last (*seq_p
);
5809 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
5810 to CTX. If entries already exist, force them to be some flavor of private.
5811 If there is no enclosing parallel, do nothing. */
5814 omp_firstprivatize_variable (struct gimplify_omp_ctx
*ctx
, tree decl
)
5818 if (decl
== NULL
|| !DECL_P (decl
) || ctx
->region_type
== ORT_NONE
)
5823 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
5826 if (n
->value
& GOVD_SHARED
)
5827 n
->value
= GOVD_FIRSTPRIVATE
| (n
->value
& GOVD_SEEN
);
5828 else if (n
->value
& GOVD_MAP
)
5829 n
->value
|= GOVD_MAP_TO_ONLY
;
5833 else if ((ctx
->region_type
& ORT_TARGET
) != 0)
5835 if (ctx
->target_map_scalars_firstprivate
)
5836 omp_add_variable (ctx
, decl
, GOVD_FIRSTPRIVATE
);
5838 omp_add_variable (ctx
, decl
, GOVD_MAP
| GOVD_MAP_TO_ONLY
);
5840 else if (ctx
->region_type
!= ORT_WORKSHARE
5841 && ctx
->region_type
!= ORT_SIMD
5842 && ctx
->region_type
!= ORT_ACC
5843 && !(ctx
->region_type
& ORT_TARGET_DATA
))
5844 omp_add_variable (ctx
, decl
, GOVD_FIRSTPRIVATE
);
5846 ctx
= ctx
->outer_context
;
5851 /* Similarly for each of the type sizes of TYPE. */
5854 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx
*ctx
, tree type
)
5856 if (type
== NULL
|| type
== error_mark_node
)
5858 type
= TYPE_MAIN_VARIANT (type
);
5860 if (ctx
->privatized_types
->add (type
))
5863 switch (TREE_CODE (type
))
5869 case FIXED_POINT_TYPE
:
5870 omp_firstprivatize_variable (ctx
, TYPE_MIN_VALUE (type
));
5871 omp_firstprivatize_variable (ctx
, TYPE_MAX_VALUE (type
));
5875 omp_firstprivatize_type_sizes (ctx
, TREE_TYPE (type
));
5876 omp_firstprivatize_type_sizes (ctx
, TYPE_DOMAIN (type
));
5881 case QUAL_UNION_TYPE
:
5884 for (field
= TYPE_FIELDS (type
); field
; field
= DECL_CHAIN (field
))
5885 if (TREE_CODE (field
) == FIELD_DECL
)
5887 omp_firstprivatize_variable (ctx
, DECL_FIELD_OFFSET (field
));
5888 omp_firstprivatize_type_sizes (ctx
, TREE_TYPE (field
));
5894 case REFERENCE_TYPE
:
5895 omp_firstprivatize_type_sizes (ctx
, TREE_TYPE (type
));
5902 omp_firstprivatize_variable (ctx
, TYPE_SIZE (type
));
5903 omp_firstprivatize_variable (ctx
, TYPE_SIZE_UNIT (type
));
5904 lang_hooks
.types
.omp_firstprivatize_type_sizes (ctx
, type
);
5907 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
5910 omp_add_variable (struct gimplify_omp_ctx
*ctx
, tree decl
, unsigned int flags
)
5913 unsigned int nflags
;
5916 if (error_operand_p (decl
) || ctx
->region_type
== ORT_NONE
)
5919 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
5920 there are constructors involved somewhere. */
5921 if (TREE_ADDRESSABLE (TREE_TYPE (decl
))
5922 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl
)))
5925 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
5926 if (n
!= NULL
&& (n
->value
& GOVD_DATA_SHARE_CLASS
) != 0)
5928 /* We shouldn't be re-adding the decl with the same data
5930 gcc_assert ((n
->value
& GOVD_DATA_SHARE_CLASS
& flags
) == 0);
5931 nflags
= n
->value
| flags
;
5932 /* The only combination of data sharing classes we should see is
5933 FIRSTPRIVATE and LASTPRIVATE. However, OpenACC permits
5934 reduction variables to be used in data sharing clauses. */
5935 gcc_assert ((ctx
->region_type
& ORT_ACC
) != 0
5936 || ((nflags
& GOVD_DATA_SHARE_CLASS
)
5937 == (GOVD_FIRSTPRIVATE
| GOVD_LASTPRIVATE
))
5938 || (flags
& GOVD_DATA_SHARE_CLASS
) == 0);
5943 /* When adding a variable-sized variable, we have to handle all sorts
5944 of additional bits of data: the pointer replacement variable, and
5945 the parameters of the type. */
5946 if (DECL_SIZE (decl
) && TREE_CODE (DECL_SIZE (decl
)) != INTEGER_CST
)
5948 /* Add the pointer replacement variable as PRIVATE if the variable
5949 replacement is private, else FIRSTPRIVATE since we'll need the
5950 address of the original variable either for SHARED, or for the
5951 copy into or out of the context. */
5952 if (!(flags
& GOVD_LOCAL
))
5954 if (flags
& GOVD_MAP
)
5955 nflags
= GOVD_MAP
| GOVD_MAP_TO_ONLY
| GOVD_EXPLICIT
;
5956 else if (flags
& GOVD_PRIVATE
)
5957 nflags
= GOVD_PRIVATE
;
5958 else if ((ctx
->region_type
& (ORT_TARGET
| ORT_TARGET_DATA
)) != 0
5959 && (flags
& GOVD_FIRSTPRIVATE
))
5960 nflags
= GOVD_PRIVATE
| GOVD_EXPLICIT
;
5962 nflags
= GOVD_FIRSTPRIVATE
;
5963 nflags
|= flags
& GOVD_SEEN
;
5964 t
= DECL_VALUE_EXPR (decl
);
5965 gcc_assert (TREE_CODE (t
) == INDIRECT_REF
);
5966 t
= TREE_OPERAND (t
, 0);
5967 gcc_assert (DECL_P (t
));
5968 omp_add_variable (ctx
, t
, nflags
);
5971 /* Add all of the variable and type parameters (which should have
5972 been gimplified to a formal temporary) as FIRSTPRIVATE. */
5973 omp_firstprivatize_variable (ctx
, DECL_SIZE_UNIT (decl
));
5974 omp_firstprivatize_variable (ctx
, DECL_SIZE (decl
));
5975 omp_firstprivatize_type_sizes (ctx
, TREE_TYPE (decl
));
5977 /* The variable-sized variable itself is never SHARED, only some form
5978 of PRIVATE. The sharing would take place via the pointer variable
5979 which we remapped above. */
5980 if (flags
& GOVD_SHARED
)
5981 flags
= GOVD_PRIVATE
| GOVD_DEBUG_PRIVATE
5982 | (flags
& (GOVD_SEEN
| GOVD_EXPLICIT
));
5984 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
5985 alloca statement we generate for the variable, so make sure it
5986 is available. This isn't automatically needed for the SHARED
5987 case, since we won't be allocating local storage then.
5988 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
5989 in this case omp_notice_variable will be called later
5990 on when it is gimplified. */
5991 else if (! (flags
& (GOVD_LOCAL
| GOVD_MAP
))
5992 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl
))))
5993 omp_notice_variable (ctx
, TYPE_SIZE_UNIT (TREE_TYPE (decl
)), true);
5995 else if ((flags
& (GOVD_MAP
| GOVD_LOCAL
)) == 0
5996 && lang_hooks
.decls
.omp_privatize_by_reference (decl
))
5998 omp_firstprivatize_type_sizes (ctx
, TREE_TYPE (decl
));
6000 /* Similar to the direct variable sized case above, we'll need the
6001 size of references being privatized. */
6002 if ((flags
& GOVD_SHARED
) == 0)
6004 t
= TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl
)));
6006 omp_notice_variable (ctx
, t
, true);
6013 splay_tree_insert (ctx
->variables
, (splay_tree_key
)decl
, flags
);
6015 /* For reductions clauses in OpenACC loop directives, by default create a
6016 copy clause on the enclosing parallel construct for carrying back the
6018 if (ctx
->region_type
== ORT_ACC
&& (flags
& GOVD_REDUCTION
))
6020 struct gimplify_omp_ctx
*outer_ctx
= ctx
->outer_context
;
6023 n
= splay_tree_lookup (outer_ctx
->variables
, (splay_tree_key
)decl
);
6026 /* Ignore local variables and explicitly declared clauses. */
6027 if (n
->value
& (GOVD_LOCAL
| GOVD_EXPLICIT
))
6029 else if (outer_ctx
->region_type
== ORT_ACC_KERNELS
)
6031 /* According to the OpenACC spec, such a reduction variable
6032 should already have a copy map on a kernels construct,
6033 verify that here. */
6034 gcc_assert (!(n
->value
& GOVD_FIRSTPRIVATE
)
6035 && (n
->value
& GOVD_MAP
));
6037 else if (outer_ctx
->region_type
== ORT_ACC_PARALLEL
)
6039 /* Remove firstprivate and make it a copy map. */
6040 n
->value
&= ~GOVD_FIRSTPRIVATE
;
6041 n
->value
|= GOVD_MAP
;
6044 else if (outer_ctx
->region_type
== ORT_ACC_PARALLEL
)
6046 splay_tree_insert (outer_ctx
->variables
, (splay_tree_key
)decl
,
6047 GOVD_MAP
| GOVD_SEEN
);
6050 outer_ctx
= outer_ctx
->outer_context
;
6055 /* Notice a threadprivate variable DECL used in OMP context CTX.
6056 This just prints out diagnostics about threadprivate variable uses
6057 in untied tasks. If DECL2 is non-NULL, prevent this warning
6058 on that variable. */
6061 omp_notice_threadprivate_variable (struct gimplify_omp_ctx
*ctx
, tree decl
,
6065 struct gimplify_omp_ctx
*octx
;
6067 for (octx
= ctx
; octx
; octx
= octx
->outer_context
)
6068 if ((octx
->region_type
& ORT_TARGET
) != 0)
6070 n
= splay_tree_lookup (octx
->variables
, (splay_tree_key
)decl
);
6073 error ("threadprivate variable %qE used in target region",
6075 error_at (octx
->location
, "enclosing target region");
6076 splay_tree_insert (octx
->variables
, (splay_tree_key
)decl
, 0);
6079 splay_tree_insert (octx
->variables
, (splay_tree_key
)decl2
, 0);
6082 if (ctx
->region_type
!= ORT_UNTIED_TASK
)
6084 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
6087 error ("threadprivate variable %qE used in untied task",
6089 error_at (ctx
->location
, "enclosing task");
6090 splay_tree_insert (ctx
->variables
, (splay_tree_key
)decl
, 0);
6093 splay_tree_insert (ctx
->variables
, (splay_tree_key
)decl2
, 0);
6097 /* Return true if global var DECL is device resident. */
6100 device_resident_p (tree decl
)
6102 tree attr
= lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (decl
));
6107 for (tree t
= TREE_VALUE (attr
); t
; t
= TREE_PURPOSE (t
))
6109 tree c
= TREE_VALUE (t
);
6110 if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_DEVICE_RESIDENT
)
6117 /* Determine outer default flags for DECL mentioned in an OMP region
6118 but not declared in an enclosing clause.
6120 ??? Some compiler-generated variables (like SAVE_EXPRs) could be
6121 remapped firstprivate instead of shared. To some extent this is
6122 addressed in omp_firstprivatize_type_sizes, but not
6126 omp_default_clause (struct gimplify_omp_ctx
*ctx
, tree decl
,
6127 bool in_code
, unsigned flags
)
6129 enum omp_clause_default_kind default_kind
= ctx
->default_kind
;
6130 enum omp_clause_default_kind kind
;
6132 kind
= lang_hooks
.decls
.omp_predetermined_sharing (decl
);
6133 if (kind
!= OMP_CLAUSE_DEFAULT_UNSPECIFIED
)
6134 default_kind
= kind
;
6136 switch (default_kind
)
6138 case OMP_CLAUSE_DEFAULT_NONE
:
6142 if (ctx
->region_type
& ORT_PARALLEL
)
6144 else if (ctx
->region_type
& ORT_TASK
)
6146 else if (ctx
->region_type
& ORT_TEAMS
)
6151 error ("%qE not specified in enclosing %s",
6152 DECL_NAME (lang_hooks
.decls
.omp_report_decl (decl
)), rtype
);
6153 error_at (ctx
->location
, "enclosing %s", rtype
);
6156 case OMP_CLAUSE_DEFAULT_SHARED
:
6157 flags
|= GOVD_SHARED
;
6159 case OMP_CLAUSE_DEFAULT_PRIVATE
:
6160 flags
|= GOVD_PRIVATE
;
6162 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE
:
6163 flags
|= GOVD_FIRSTPRIVATE
;
6165 case OMP_CLAUSE_DEFAULT_UNSPECIFIED
:
6166 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
6167 gcc_assert ((ctx
->region_type
& ORT_TASK
) != 0);
6168 if (struct gimplify_omp_ctx
*octx
= ctx
->outer_context
)
6170 omp_notice_variable (octx
, decl
, in_code
);
6171 for (; octx
; octx
= octx
->outer_context
)
6175 n2
= splay_tree_lookup (octx
->variables
, (splay_tree_key
) decl
);
6176 if ((octx
->region_type
& (ORT_TARGET_DATA
| ORT_TARGET
)) != 0
6177 && (n2
== NULL
|| (n2
->value
& GOVD_DATA_SHARE_CLASS
) == 0))
6179 if (n2
&& (n2
->value
& GOVD_DATA_SHARE_CLASS
) != GOVD_SHARED
)
6181 flags
|= GOVD_FIRSTPRIVATE
;
6184 if ((octx
->region_type
& (ORT_PARALLEL
| ORT_TEAMS
)) != 0)
6186 flags
|= GOVD_SHARED
;
6192 if (TREE_CODE (decl
) == PARM_DECL
6193 || (!is_global_var (decl
)
6194 && DECL_CONTEXT (decl
) == current_function_decl
))
6195 flags
|= GOVD_FIRSTPRIVATE
;
6197 flags
|= GOVD_SHARED
;
6209 /* Determine outer default flags for DECL mentioned in an OACC region
6210 but not declared in an enclosing clause. */
6213 oacc_default_clause (struct gimplify_omp_ctx
*ctx
, tree decl
, unsigned flags
)
6216 bool on_device
= false;
6217 tree type
= TREE_TYPE (decl
);
6219 if (lang_hooks
.decls
.omp_privatize_by_reference (decl
))
6220 type
= TREE_TYPE (type
);
6222 if ((ctx
->region_type
& (ORT_ACC_PARALLEL
| ORT_ACC_KERNELS
)) != 0
6223 && is_global_var (decl
)
6224 && device_resident_p (decl
))
6227 flags
|= GOVD_MAP_TO_ONLY
;
6230 switch (ctx
->region_type
)
6235 case ORT_ACC_KERNELS
:
6236 /* Scalars are default 'copy' under kernels, non-scalars are default
6237 'present_or_copy'. */
6239 if (!AGGREGATE_TYPE_P (type
))
6240 flags
|= GOVD_MAP_FORCE
;
6245 case ORT_ACC_PARALLEL
:
6247 if (on_device
|| AGGREGATE_TYPE_P (type
))
6248 /* Aggregates default to 'present_or_copy'. */
6251 /* Scalars default to 'firstprivate'. */
6252 flags
|= GOVD_FIRSTPRIVATE
;
6258 if (DECL_ARTIFICIAL (decl
))
6259 ; /* We can get compiler-generated decls, and should not complain
6261 else if (ctx
->default_kind
== OMP_CLAUSE_DEFAULT_NONE
)
6263 error ("%qE not specified in enclosing OpenACC %qs construct",
6264 DECL_NAME (lang_hooks
.decls
.omp_report_decl (decl
)), rkind
);
6265 inform (ctx
->location
, "enclosing OpenACC %qs construct", rkind
);
6268 gcc_checking_assert (ctx
->default_kind
== OMP_CLAUSE_DEFAULT_SHARED
);
6273 /* Record the fact that DECL was used within the OMP context CTX.
6274 IN_CODE is true when real code uses DECL, and false when we should
6275 merely emit default(none) errors. Return true if DECL is going to
6276 be remapped and thus DECL shouldn't be gimplified into its
6277 DECL_VALUE_EXPR (if any). */
6280 omp_notice_variable (struct gimplify_omp_ctx
*ctx
, tree decl
, bool in_code
)
6283 unsigned flags
= in_code
? GOVD_SEEN
: 0;
6284 bool ret
= false, shared
;
6286 if (error_operand_p (decl
))
6289 if (ctx
->region_type
== ORT_NONE
)
6290 return lang_hooks
.decls
.omp_disregard_value_expr (decl
, false);
6292 if (is_global_var (decl
))
6294 /* Threadprivate variables are predetermined. */
6295 if (DECL_THREAD_LOCAL_P (decl
))
6296 return omp_notice_threadprivate_variable (ctx
, decl
, NULL_TREE
);
6298 if (DECL_HAS_VALUE_EXPR_P (decl
))
6300 tree value
= get_base_address (DECL_VALUE_EXPR (decl
));
6302 if (value
&& DECL_P (value
) && DECL_THREAD_LOCAL_P (value
))
6303 return omp_notice_threadprivate_variable (ctx
, decl
, value
);
6306 if (gimplify_omp_ctxp
->outer_context
== NULL
6308 && get_oacc_fn_attrib (current_function_decl
))
6310 location_t loc
= DECL_SOURCE_LOCATION (decl
);
6312 if (lookup_attribute ("omp declare target link",
6313 DECL_ATTRIBUTES (decl
)))
6316 "%qE with %<link%> clause used in %<routine%> function",
6320 else if (!lookup_attribute ("omp declare target",
6321 DECL_ATTRIBUTES (decl
)))
6324 "%qE requires a %<declare%> directive for use "
6325 "in a %<routine%> function", DECL_NAME (decl
));
6331 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
6332 if ((ctx
->region_type
& ORT_TARGET
) != 0)
6334 ret
= lang_hooks
.decls
.omp_disregard_value_expr (decl
, true);
6337 unsigned nflags
= flags
;
6338 if (ctx
->target_map_pointers_as_0len_arrays
6339 || ctx
->target_map_scalars_firstprivate
)
6341 bool is_declare_target
= false;
6342 bool is_scalar
= false;
6343 if (is_global_var (decl
)
6344 && varpool_node::get_create (decl
)->offloadable
)
6346 struct gimplify_omp_ctx
*octx
;
6347 for (octx
= ctx
->outer_context
;
6348 octx
; octx
= octx
->outer_context
)
6350 n
= splay_tree_lookup (octx
->variables
,
6351 (splay_tree_key
)decl
);
6353 && (n
->value
& GOVD_DATA_SHARE_CLASS
) != GOVD_SHARED
6354 && (n
->value
& GOVD_DATA_SHARE_CLASS
) != 0)
6357 is_declare_target
= octx
== NULL
;
6359 if (!is_declare_target
&& ctx
->target_map_scalars_firstprivate
)
6361 tree type
= TREE_TYPE (decl
);
6362 if (TREE_CODE (type
) == REFERENCE_TYPE
)
6363 type
= TREE_TYPE (type
);
6364 if (TREE_CODE (type
) == COMPLEX_TYPE
)
6365 type
= TREE_TYPE (type
);
6366 if (INTEGRAL_TYPE_P (type
)
6367 || SCALAR_FLOAT_TYPE_P (type
)
6368 || TREE_CODE (type
) == POINTER_TYPE
)
6371 if (is_declare_target
)
6373 else if (ctx
->target_map_pointers_as_0len_arrays
6374 && (TREE_CODE (TREE_TYPE (decl
)) == POINTER_TYPE
6375 || (TREE_CODE (TREE_TYPE (decl
)) == REFERENCE_TYPE
6376 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl
)))
6378 nflags
|= GOVD_MAP
| GOVD_MAP_0LEN_ARRAY
;
6380 nflags
|= GOVD_FIRSTPRIVATE
;
6383 struct gimplify_omp_ctx
*octx
= ctx
->outer_context
;
6384 if ((ctx
->region_type
& ORT_ACC
) && octx
)
6386 /* Look in outer OpenACC contexts, to see if there's a
6387 data attribute for this variable. */
6388 omp_notice_variable (octx
, decl
, in_code
);
6390 for (; octx
; octx
= octx
->outer_context
)
6392 if (!(octx
->region_type
& (ORT_TARGET_DATA
| ORT_TARGET
)))
6395 = splay_tree_lookup (octx
->variables
,
6396 (splay_tree_key
) decl
);
6399 if (octx
->region_type
== ORT_ACC_HOST_DATA
)
6400 error ("variable %qE declared in enclosing "
6401 "%<host_data%> region", DECL_NAME (decl
));
6403 if (octx
->region_type
== ORT_ACC_DATA
6404 && (n2
->value
& GOVD_MAP_0LEN_ARRAY
))
6405 nflags
|= GOVD_MAP_0LEN_ARRAY
;
6412 tree type
= TREE_TYPE (decl
);
6415 && gimplify_omp_ctxp
->target_firstprivatize_array_bases
6416 && lang_hooks
.decls
.omp_privatize_by_reference (decl
))
6417 type
= TREE_TYPE (type
);
6419 && !lang_hooks
.types
.omp_mappable_type (type
))
6421 error ("%qD referenced in target region does not have "
6422 "a mappable type", decl
);
6423 nflags
|= GOVD_MAP
| GOVD_EXPLICIT
;
6425 else if (nflags
== flags
)
6427 if ((ctx
->region_type
& ORT_ACC
) != 0)
6428 nflags
= oacc_default_clause (ctx
, decl
, flags
);
6434 omp_add_variable (ctx
, decl
, nflags
);
6438 /* If nothing changed, there's nothing left to do. */
6439 if ((n
->value
& flags
) == flags
)
6449 if (ctx
->region_type
== ORT_WORKSHARE
6450 || ctx
->region_type
== ORT_SIMD
6451 || ctx
->region_type
== ORT_ACC
6452 || (ctx
->region_type
& ORT_TARGET_DATA
) != 0)
6455 flags
= omp_default_clause (ctx
, decl
, in_code
, flags
);
6457 if ((flags
& GOVD_PRIVATE
)
6458 && lang_hooks
.decls
.omp_private_outer_ref (decl
))
6459 flags
|= GOVD_PRIVATE_OUTER_REF
;
6461 omp_add_variable (ctx
, decl
, flags
);
6463 shared
= (flags
& GOVD_SHARED
) != 0;
6464 ret
= lang_hooks
.decls
.omp_disregard_value_expr (decl
, shared
);
6468 if ((n
->value
& (GOVD_SEEN
| GOVD_LOCAL
)) == 0
6469 && (flags
& (GOVD_SEEN
| GOVD_LOCAL
)) == GOVD_SEEN
6470 && DECL_SIZE (decl
))
6472 if (TREE_CODE (DECL_SIZE (decl
)) != INTEGER_CST
)
6475 tree t
= DECL_VALUE_EXPR (decl
);
6476 gcc_assert (TREE_CODE (t
) == INDIRECT_REF
);
6477 t
= TREE_OPERAND (t
, 0);
6478 gcc_assert (DECL_P (t
));
6479 n2
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) t
);
6480 n2
->value
|= GOVD_SEEN
;
6482 else if (lang_hooks
.decls
.omp_privatize_by_reference (decl
)
6483 && TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl
)))
6484 && (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl
))))
6488 tree t
= TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl
)));
6489 gcc_assert (DECL_P (t
));
6490 n2
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) t
);
6492 n2
->value
|= GOVD_SEEN
;
6496 shared
= ((flags
| n
->value
) & GOVD_SHARED
) != 0;
6497 ret
= lang_hooks
.decls
.omp_disregard_value_expr (decl
, shared
);
6499 /* If nothing changed, there's nothing left to do. */
6500 if ((n
->value
& flags
) == flags
)
6506 /* If the variable is private in the current context, then we don't
6507 need to propagate anything to an outer context. */
6508 if ((flags
& GOVD_PRIVATE
) && !(flags
& GOVD_PRIVATE_OUTER_REF
))
6510 if ((flags
& (GOVD_LINEAR
| GOVD_LINEAR_LASTPRIVATE_NO_OUTER
))
6511 == (GOVD_LINEAR
| GOVD_LINEAR_LASTPRIVATE_NO_OUTER
))
6513 if ((flags
& (GOVD_FIRSTPRIVATE
| GOVD_LASTPRIVATE
6514 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER
))
6515 == (GOVD_LASTPRIVATE
| GOVD_LINEAR_LASTPRIVATE_NO_OUTER
))
6517 if (ctx
->outer_context
6518 && omp_notice_variable (ctx
->outer_context
, decl
, in_code
))
6523 /* Verify that DECL is private within CTX. If there's specific information
6524 to the contrary in the innermost scope, generate an error. */
6527 omp_is_private (struct gimplify_omp_ctx
*ctx
, tree decl
, int simd
)
6531 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
6534 if (n
->value
& GOVD_SHARED
)
6536 if (ctx
== gimplify_omp_ctxp
)
6539 error ("iteration variable %qE is predetermined linear",
6542 error ("iteration variable %qE should be private",
6544 n
->value
= GOVD_PRIVATE
;
6550 else if ((n
->value
& GOVD_EXPLICIT
) != 0
6551 && (ctx
== gimplify_omp_ctxp
6552 || (ctx
->region_type
== ORT_COMBINED_PARALLEL
6553 && gimplify_omp_ctxp
->outer_context
== ctx
)))
6555 if ((n
->value
& GOVD_FIRSTPRIVATE
) != 0)
6556 error ("iteration variable %qE should not be firstprivate",
6558 else if ((n
->value
& GOVD_REDUCTION
) != 0)
6559 error ("iteration variable %qE should not be reduction",
6561 else if (simd
== 0 && (n
->value
& GOVD_LINEAR
) != 0)
6562 error ("iteration variable %qE should not be linear",
6564 else if (simd
== 1 && (n
->value
& GOVD_LASTPRIVATE
) != 0)
6565 error ("iteration variable %qE should not be lastprivate",
6567 else if (simd
&& (n
->value
& GOVD_PRIVATE
) != 0)
6568 error ("iteration variable %qE should not be private",
6570 else if (simd
== 2 && (n
->value
& GOVD_LINEAR
) != 0)
6571 error ("iteration variable %qE is predetermined linear",
6574 return (ctx
== gimplify_omp_ctxp
6575 || (ctx
->region_type
== ORT_COMBINED_PARALLEL
6576 && gimplify_omp_ctxp
->outer_context
== ctx
));
6579 if (ctx
->region_type
!= ORT_WORKSHARE
6580 && ctx
->region_type
!= ORT_SIMD
6581 && ctx
->region_type
!= ORT_ACC
)
6583 else if (ctx
->outer_context
)
6584 return omp_is_private (ctx
->outer_context
, decl
, simd
);
6588 /* Return true if DECL is private within a parallel region
6589 that binds to the current construct's context or in parallel
6590 region's REDUCTION clause. */
6593 omp_check_private (struct gimplify_omp_ctx
*ctx
, tree decl
, bool copyprivate
)
6599 ctx
= ctx
->outer_context
;
6602 if (is_global_var (decl
))
6605 /* References might be private, but might be shared too,
6606 when checking for copyprivate, assume they might be
6607 private, otherwise assume they might be shared. */
6611 if (lang_hooks
.decls
.omp_privatize_by_reference (decl
))
6614 /* Treat C++ privatized non-static data members outside
6615 of the privatization the same. */
6616 if (omp_member_access_dummy_var (decl
))
6622 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
6624 if ((ctx
->region_type
& (ORT_TARGET
| ORT_TARGET_DATA
)) != 0
6625 && (n
== NULL
|| (n
->value
& GOVD_DATA_SHARE_CLASS
) == 0))
6630 if ((n
->value
& GOVD_LOCAL
) != 0
6631 && omp_member_access_dummy_var (decl
))
6633 return (n
->value
& GOVD_SHARED
) == 0;
6636 while (ctx
->region_type
== ORT_WORKSHARE
6637 || ctx
->region_type
== ORT_SIMD
6638 || ctx
->region_type
== ORT_ACC
);
6642 /* Return true if the CTX is combined with distribute and thus
6643 lastprivate can't be supported. */
6646 omp_no_lastprivate (struct gimplify_omp_ctx
*ctx
)
6650 if (ctx
->outer_context
== NULL
)
6652 ctx
= ctx
->outer_context
;
6653 switch (ctx
->region_type
)
6656 if (!ctx
->combined_loop
)
6658 if (ctx
->distribute
)
6659 return lang_GNU_Fortran ();
6661 case ORT_COMBINED_PARALLEL
:
6663 case ORT_COMBINED_TEAMS
:
6664 return lang_GNU_Fortran ();
6672 /* Callback for walk_tree to find a DECL_EXPR for the given DECL. */
6675 find_decl_expr (tree
*tp
, int *walk_subtrees
, void *data
)
6679 /* If this node has been visited, unmark it and keep looking. */
6680 if (TREE_CODE (t
) == DECL_EXPR
&& DECL_EXPR_DECL (t
) == (tree
) data
)
6683 if (IS_TYPE_OR_DECL_P (t
))
6688 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
6689 and previous omp contexts. */
6692 gimplify_scan_omp_clauses (tree
*list_p
, gimple_seq
*pre_p
,
6693 enum omp_region_type region_type
,
6694 enum tree_code code
)
6696 struct gimplify_omp_ctx
*ctx
, *outer_ctx
;
6698 hash_map
<tree
, tree
> *struct_map_to_clause
= NULL
;
6699 tree
*prev_list_p
= NULL
;
6701 ctx
= new_omp_context (region_type
);
6702 outer_ctx
= ctx
->outer_context
;
6703 if (code
== OMP_TARGET
&& !lang_GNU_Fortran ())
6705 ctx
->target_map_pointers_as_0len_arrays
= true;
6706 /* FIXME: For Fortran we want to set this too, when
6707 the Fortran FE is updated to OpenMP 4.5. */
6708 ctx
->target_map_scalars_firstprivate
= true;
6710 if (!lang_GNU_Fortran ())
6714 case OMP_TARGET_DATA
:
6715 case OMP_TARGET_ENTER_DATA
:
6716 case OMP_TARGET_EXIT_DATA
:
6717 case OACC_HOST_DATA
:
6718 ctx
->target_firstprivatize_array_bases
= true;
6723 while ((c
= *list_p
) != NULL
)
6725 bool remove
= false;
6726 bool notice_outer
= true;
6727 const char *check_non_private
= NULL
;
6731 switch (OMP_CLAUSE_CODE (c
))
6733 case OMP_CLAUSE_PRIVATE
:
6734 flags
= GOVD_PRIVATE
| GOVD_EXPLICIT
;
6735 if (lang_hooks
.decls
.omp_private_outer_ref (OMP_CLAUSE_DECL (c
)))
6737 flags
|= GOVD_PRIVATE_OUTER_REF
;
6738 OMP_CLAUSE_PRIVATE_OUTER_REF (c
) = 1;
6741 notice_outer
= false;
6743 case OMP_CLAUSE_SHARED
:
6744 flags
= GOVD_SHARED
| GOVD_EXPLICIT
;
6746 case OMP_CLAUSE_FIRSTPRIVATE
:
6747 flags
= GOVD_FIRSTPRIVATE
| GOVD_EXPLICIT
;
6748 check_non_private
= "firstprivate";
6750 case OMP_CLAUSE_LASTPRIVATE
:
6751 flags
= GOVD_LASTPRIVATE
| GOVD_SEEN
| GOVD_EXPLICIT
;
6752 check_non_private
= "lastprivate";
6753 decl
= OMP_CLAUSE_DECL (c
);
6754 if (omp_no_lastprivate (ctx
))
6756 notice_outer
= false;
6757 flags
|= GOVD_LINEAR_LASTPRIVATE_NO_OUTER
;
6759 else if (error_operand_p (decl
))
6762 && (outer_ctx
->region_type
== ORT_COMBINED_PARALLEL
6763 || outer_ctx
->region_type
== ORT_COMBINED_TEAMS
)
6764 && splay_tree_lookup (outer_ctx
->variables
,
6765 (splay_tree_key
) decl
) == NULL
)
6767 omp_add_variable (outer_ctx
, decl
, GOVD_SHARED
| GOVD_SEEN
);
6768 if (outer_ctx
->outer_context
)
6769 omp_notice_variable (outer_ctx
->outer_context
, decl
, true);
6772 && (outer_ctx
->region_type
& ORT_TASK
) != 0
6773 && outer_ctx
->combined_loop
6774 && splay_tree_lookup (outer_ctx
->variables
,
6775 (splay_tree_key
) decl
) == NULL
)
6777 omp_add_variable (outer_ctx
, decl
, GOVD_LASTPRIVATE
| GOVD_SEEN
);
6778 if (outer_ctx
->outer_context
)
6779 omp_notice_variable (outer_ctx
->outer_context
, decl
, true);
6782 && (outer_ctx
->region_type
== ORT_WORKSHARE
6783 || outer_ctx
->region_type
== ORT_ACC
)
6784 && outer_ctx
->combined_loop
6785 && splay_tree_lookup (outer_ctx
->variables
,
6786 (splay_tree_key
) decl
) == NULL
6787 && !omp_check_private (outer_ctx
, decl
, false))
6789 omp_add_variable (outer_ctx
, decl
, GOVD_LASTPRIVATE
| GOVD_SEEN
);
6790 if (outer_ctx
->outer_context
6791 && (outer_ctx
->outer_context
->region_type
6792 == ORT_COMBINED_PARALLEL
)
6793 && splay_tree_lookup (outer_ctx
->outer_context
->variables
,
6794 (splay_tree_key
) decl
) == NULL
)
6796 struct gimplify_omp_ctx
*octx
= outer_ctx
->outer_context
;
6797 omp_add_variable (octx
, decl
, GOVD_SHARED
| GOVD_SEEN
);
6798 if (octx
->outer_context
)
6799 omp_notice_variable (octx
->outer_context
, decl
, true);
6801 else if (outer_ctx
->outer_context
)
6802 omp_notice_variable (outer_ctx
->outer_context
, decl
, true);
6805 case OMP_CLAUSE_REDUCTION
:
6806 flags
= GOVD_REDUCTION
| GOVD_SEEN
| GOVD_EXPLICIT
;
6807 /* OpenACC permits reductions on private variables. */
6808 if (!(region_type
& ORT_ACC
))
6809 check_non_private
= "reduction";
6810 decl
= OMP_CLAUSE_DECL (c
);
6811 if (TREE_CODE (decl
) == MEM_REF
)
6813 tree type
= TREE_TYPE (decl
);
6814 if (gimplify_expr (&TYPE_MAX_VALUE (TYPE_DOMAIN (type
)), pre_p
,
6815 NULL
, is_gimple_val
, fb_rvalue
, false)
6821 tree v
= TYPE_MAX_VALUE (TYPE_DOMAIN (type
));
6824 omp_firstprivatize_variable (ctx
, v
);
6825 omp_notice_variable (ctx
, v
, true);
6827 decl
= TREE_OPERAND (decl
, 0);
6828 if (TREE_CODE (decl
) == POINTER_PLUS_EXPR
)
6830 if (gimplify_expr (&TREE_OPERAND (decl
, 1), pre_p
,
6831 NULL
, is_gimple_val
, fb_rvalue
, false)
6837 v
= TREE_OPERAND (decl
, 1);
6840 omp_firstprivatize_variable (ctx
, v
);
6841 omp_notice_variable (ctx
, v
, true);
6843 decl
= TREE_OPERAND (decl
, 0);
6845 if (TREE_CODE (decl
) == ADDR_EXPR
6846 || TREE_CODE (decl
) == INDIRECT_REF
)
6847 decl
= TREE_OPERAND (decl
, 0);
6850 case OMP_CLAUSE_LINEAR
:
6851 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c
), pre_p
, NULL
,
6852 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
6859 if (code
== OMP_SIMD
6860 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c
))
6862 struct gimplify_omp_ctx
*octx
= outer_ctx
;
6864 && octx
->region_type
== ORT_WORKSHARE
6865 && octx
->combined_loop
6866 && !octx
->distribute
)
6868 if (octx
->outer_context
6869 && (octx
->outer_context
->region_type
6870 == ORT_COMBINED_PARALLEL
))
6871 octx
= octx
->outer_context
->outer_context
;
6873 octx
= octx
->outer_context
;
6876 && octx
->region_type
== ORT_WORKSHARE
6877 && octx
->combined_loop
6879 && !lang_GNU_Fortran ())
6881 error_at (OMP_CLAUSE_LOCATION (c
),
6882 "%<linear%> clause for variable other than "
6883 "loop iterator specified on construct "
6884 "combined with %<distribute%>");
6889 /* For combined #pragma omp parallel for simd, need to put
6890 lastprivate and perhaps firstprivate too on the
6891 parallel. Similarly for #pragma omp for simd. */
6892 struct gimplify_omp_ctx
*octx
= outer_ctx
;
6894 if (omp_no_lastprivate (ctx
))
6895 OMP_CLAUSE_LINEAR_NO_COPYOUT (c
) = 1;
6898 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c
)
6899 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c
))
6901 decl
= OMP_CLAUSE_DECL (c
);
6902 if (error_operand_p (decl
))
6908 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c
))
6909 flags
|= GOVD_FIRSTPRIVATE
;
6910 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c
))
6911 flags
|= GOVD_LASTPRIVATE
;
6913 && octx
->region_type
== ORT_WORKSHARE
6914 && octx
->combined_loop
)
6916 if (octx
->outer_context
6917 && (octx
->outer_context
->region_type
6918 == ORT_COMBINED_PARALLEL
))
6919 octx
= octx
->outer_context
;
6920 else if (omp_check_private (octx
, decl
, false))
6924 && (octx
->region_type
& ORT_TASK
) != 0
6925 && octx
->combined_loop
)
6928 && octx
->region_type
== ORT_COMBINED_PARALLEL
6929 && ctx
->region_type
== ORT_WORKSHARE
6930 && octx
== outer_ctx
)
6931 flags
= GOVD_SEEN
| GOVD_SHARED
;
6933 && octx
->region_type
== ORT_COMBINED_TEAMS
)
6934 flags
= GOVD_SEEN
| GOVD_SHARED
;
6936 && octx
->region_type
== ORT_COMBINED_TARGET
)
6938 flags
&= ~GOVD_LASTPRIVATE
;
6939 if (flags
== GOVD_SEEN
)
6945 = splay_tree_lookup (octx
->variables
,
6946 (splay_tree_key
) decl
);
6947 if (on
&& (on
->value
& GOVD_DATA_SHARE_CLASS
) != 0)
6952 omp_add_variable (octx
, decl
, flags
);
6953 if (octx
->outer_context
== NULL
)
6955 octx
= octx
->outer_context
;
6960 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c
)
6961 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c
)))
6962 omp_notice_variable (octx
, decl
, true);
6964 flags
= GOVD_LINEAR
| GOVD_EXPLICIT
;
6965 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c
)
6966 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c
))
6968 notice_outer
= false;
6969 flags
|= GOVD_LINEAR_LASTPRIVATE_NO_OUTER
;
6973 case OMP_CLAUSE_MAP
:
6974 decl
= OMP_CLAUSE_DECL (c
);
6975 if (error_operand_p (decl
))
6982 if (TREE_CODE (TREE_TYPE (decl
)) != ARRAY_TYPE
)
6985 case OMP_TARGET_DATA
:
6986 case OMP_TARGET_ENTER_DATA
:
6987 case OMP_TARGET_EXIT_DATA
:
6988 case OACC_ENTER_DATA
:
6989 case OACC_EXIT_DATA
:
6990 case OACC_HOST_DATA
:
6991 if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_FIRSTPRIVATE_POINTER
6992 || (OMP_CLAUSE_MAP_KIND (c
)
6993 == GOMP_MAP_FIRSTPRIVATE_REFERENCE
))
6994 /* For target {,enter ,exit }data only the array slice is
6995 mapped, but not the pointer to it. */
7003 if (DECL_P (decl
) && outer_ctx
&& (region_type
& ORT_ACC
))
7005 struct gimplify_omp_ctx
*octx
;
7006 for (octx
= outer_ctx
; octx
; octx
= octx
->outer_context
)
7008 if (octx
->region_type
!= ORT_ACC_HOST_DATA
)
7011 = splay_tree_lookup (octx
->variables
,
7012 (splay_tree_key
) decl
);
7014 error_at (OMP_CLAUSE_LOCATION (c
), "variable %qE "
7015 "declared in enclosing %<host_data%> region",
7019 if (OMP_CLAUSE_SIZE (c
) == NULL_TREE
)
7020 OMP_CLAUSE_SIZE (c
) = DECL_P (decl
) ? DECL_SIZE_UNIT (decl
)
7021 : TYPE_SIZE_UNIT (TREE_TYPE (decl
));
7022 if (gimplify_expr (&OMP_CLAUSE_SIZE (c
), pre_p
,
7023 NULL
, is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7028 else if ((OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_FIRSTPRIVATE_POINTER
7029 || (OMP_CLAUSE_MAP_KIND (c
)
7030 == GOMP_MAP_FIRSTPRIVATE_REFERENCE
))
7031 && TREE_CODE (OMP_CLAUSE_SIZE (c
)) != INTEGER_CST
)
7034 = get_initialized_tmp_var (OMP_CLAUSE_SIZE (c
), pre_p
, NULL
,
7036 omp_add_variable (ctx
, OMP_CLAUSE_SIZE (c
),
7037 GOVD_FIRSTPRIVATE
| GOVD_SEEN
);
7042 if (TREE_CODE (d
) == ARRAY_REF
)
7044 while (TREE_CODE (d
) == ARRAY_REF
)
7045 d
= TREE_OPERAND (d
, 0);
7046 if (TREE_CODE (d
) == COMPONENT_REF
7047 && TREE_CODE (TREE_TYPE (d
)) == ARRAY_TYPE
)
7050 pd
= &OMP_CLAUSE_DECL (c
);
7052 && TREE_CODE (decl
) == INDIRECT_REF
7053 && TREE_CODE (TREE_OPERAND (decl
, 0)) == COMPONENT_REF
7054 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl
, 0)))
7057 pd
= &TREE_OPERAND (decl
, 0);
7058 decl
= TREE_OPERAND (decl
, 0);
7060 if (TREE_CODE (decl
) == COMPONENT_REF
)
7062 while (TREE_CODE (decl
) == COMPONENT_REF
)
7063 decl
= TREE_OPERAND (decl
, 0);
7064 if (TREE_CODE (decl
) == INDIRECT_REF
7065 && DECL_P (TREE_OPERAND (decl
, 0))
7066 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl
, 0)))
7068 decl
= TREE_OPERAND (decl
, 0);
7070 if (gimplify_expr (pd
, pre_p
, NULL
, is_gimple_lvalue
, fb_lvalue
)
7078 if (error_operand_p (decl
))
7084 tree stype
= TREE_TYPE (decl
);
7085 if (TREE_CODE (stype
) == REFERENCE_TYPE
)
7086 stype
= TREE_TYPE (stype
);
7087 if (TYPE_SIZE_UNIT (stype
) == NULL
7088 || TREE_CODE (TYPE_SIZE_UNIT (stype
)) != INTEGER_CST
)
7090 error_at (OMP_CLAUSE_LOCATION (c
),
7091 "mapping field %qE of variable length "
7092 "structure", OMP_CLAUSE_DECL (c
));
7097 if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_ALWAYS_POINTER
)
7099 /* Error recovery. */
7100 if (prev_list_p
== NULL
)
7105 if (OMP_CLAUSE_CHAIN (*prev_list_p
) != c
)
7107 tree ch
= OMP_CLAUSE_CHAIN (*prev_list_p
);
7108 if (ch
== NULL_TREE
|| OMP_CLAUSE_CHAIN (ch
) != c
)
7117 HOST_WIDE_INT bitsize
, bitpos
;
7119 int unsignedp
, reversep
, volatilep
= 0;
7120 tree base
= OMP_CLAUSE_DECL (c
);
7121 while (TREE_CODE (base
) == ARRAY_REF
)
7122 base
= TREE_OPERAND (base
, 0);
7123 if (TREE_CODE (base
) == INDIRECT_REF
)
7124 base
= TREE_OPERAND (base
, 0);
7125 base
= get_inner_reference (base
, &bitsize
, &bitpos
, &offset
,
7126 &mode
, &unsignedp
, &reversep
,
7128 tree orig_base
= base
;
7129 if ((TREE_CODE (base
) == INDIRECT_REF
7130 || (TREE_CODE (base
) == MEM_REF
7131 && integer_zerop (TREE_OPERAND (base
, 1))))
7132 && DECL_P (TREE_OPERAND (base
, 0))
7133 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (base
, 0)))
7135 base
= TREE_OPERAND (base
, 0);
7136 gcc_assert (base
== decl
7137 && (offset
== NULL_TREE
7138 || TREE_CODE (offset
) == INTEGER_CST
));
7141 = splay_tree_lookup (ctx
->variables
, (splay_tree_key
)decl
);
7142 bool ptr
= (OMP_CLAUSE_MAP_KIND (c
)
7143 == GOMP_MAP_ALWAYS_POINTER
);
7144 if (n
== NULL
|| (n
->value
& GOVD_MAP
) == 0)
7146 tree l
= build_omp_clause (OMP_CLAUSE_LOCATION (c
),
7148 OMP_CLAUSE_SET_MAP_KIND (l
, GOMP_MAP_STRUCT
);
7149 if (orig_base
!= base
)
7150 OMP_CLAUSE_DECL (l
) = unshare_expr (orig_base
);
7152 OMP_CLAUSE_DECL (l
) = decl
;
7153 OMP_CLAUSE_SIZE (l
) = size_int (1);
7154 if (struct_map_to_clause
== NULL
)
7155 struct_map_to_clause
= new hash_map
<tree
, tree
>;
7156 struct_map_to_clause
->put (decl
, l
);
7159 enum gomp_map_kind mkind
7160 = code
== OMP_TARGET_EXIT_DATA
7161 ? GOMP_MAP_RELEASE
: GOMP_MAP_ALLOC
;
7162 tree c2
= build_omp_clause (OMP_CLAUSE_LOCATION (c
),
7164 OMP_CLAUSE_SET_MAP_KIND (c2
, mkind
);
7165 OMP_CLAUSE_DECL (c2
)
7166 = unshare_expr (OMP_CLAUSE_DECL (c
));
7167 OMP_CLAUSE_CHAIN (c2
) = *prev_list_p
;
7168 OMP_CLAUSE_SIZE (c2
)
7169 = TYPE_SIZE_UNIT (ptr_type_node
);
7170 OMP_CLAUSE_CHAIN (l
) = c2
;
7171 if (OMP_CLAUSE_CHAIN (*prev_list_p
) != c
)
7173 tree c4
= OMP_CLAUSE_CHAIN (*prev_list_p
);
7175 = build_omp_clause (OMP_CLAUSE_LOCATION (c
),
7177 OMP_CLAUSE_SET_MAP_KIND (c3
, mkind
);
7178 OMP_CLAUSE_DECL (c3
)
7179 = unshare_expr (OMP_CLAUSE_DECL (c4
));
7180 OMP_CLAUSE_SIZE (c3
)
7181 = TYPE_SIZE_UNIT (ptr_type_node
);
7182 OMP_CLAUSE_CHAIN (c3
) = *prev_list_p
;
7183 OMP_CLAUSE_CHAIN (c2
) = c3
;
7190 OMP_CLAUSE_CHAIN (l
) = c
;
7192 list_p
= &OMP_CLAUSE_CHAIN (l
);
7194 if (orig_base
!= base
&& code
== OMP_TARGET
)
7196 tree c2
= build_omp_clause (OMP_CLAUSE_LOCATION (c
),
7198 enum gomp_map_kind mkind
7199 = GOMP_MAP_FIRSTPRIVATE_REFERENCE
;
7200 OMP_CLAUSE_SET_MAP_KIND (c2
, mkind
);
7201 OMP_CLAUSE_DECL (c2
) = decl
;
7202 OMP_CLAUSE_SIZE (c2
) = size_zero_node
;
7203 OMP_CLAUSE_CHAIN (c2
) = OMP_CLAUSE_CHAIN (l
);
7204 OMP_CLAUSE_CHAIN (l
) = c2
;
7206 flags
= GOVD_MAP
| GOVD_EXPLICIT
;
7207 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c
)) || ptr
)
7213 tree
*osc
= struct_map_to_clause
->get (decl
);
7214 tree
*sc
= NULL
, *scp
= NULL
;
7215 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c
)) || ptr
)
7216 n
->value
|= GOVD_SEEN
;
7219 o1
= wi::to_offset (offset
);
7223 o1
= o1
+ bitpos
/ BITS_PER_UNIT
;
7224 sc
= &OMP_CLAUSE_CHAIN (*osc
);
7226 && (OMP_CLAUSE_MAP_KIND (*sc
)
7227 == GOMP_MAP_FIRSTPRIVATE_REFERENCE
))
7228 sc
= &OMP_CLAUSE_CHAIN (*sc
);
7229 for (; *sc
!= c
; sc
= &OMP_CLAUSE_CHAIN (*sc
))
7230 if (ptr
&& sc
== prev_list_p
)
7232 else if (TREE_CODE (OMP_CLAUSE_DECL (*sc
))
7234 && (TREE_CODE (OMP_CLAUSE_DECL (*sc
))
7236 && (TREE_CODE (OMP_CLAUSE_DECL (*sc
))
7242 HOST_WIDE_INT bitsize2
, bitpos2
;
7243 base
= OMP_CLAUSE_DECL (*sc
);
7244 if (TREE_CODE (base
) == ARRAY_REF
)
7246 while (TREE_CODE (base
) == ARRAY_REF
)
7247 base
= TREE_OPERAND (base
, 0);
7248 if (TREE_CODE (base
) != COMPONENT_REF
7249 || (TREE_CODE (TREE_TYPE (base
))
7253 else if (TREE_CODE (base
) == INDIRECT_REF
7254 && (TREE_CODE (TREE_OPERAND (base
, 0))
7256 && (TREE_CODE (TREE_TYPE
7257 (TREE_OPERAND (base
, 0)))
7259 base
= TREE_OPERAND (base
, 0);
7260 base
= get_inner_reference (base
, &bitsize2
,
7263 &reversep
, &volatilep
);
7264 if ((TREE_CODE (base
) == INDIRECT_REF
7265 || (TREE_CODE (base
) == MEM_REF
7266 && integer_zerop (TREE_OPERAND (base
,
7268 && DECL_P (TREE_OPERAND (base
, 0))
7269 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (base
,
7272 base
= TREE_OPERAND (base
, 0);
7277 gcc_assert (offset
== NULL_TREE
7278 || TREE_CODE (offset
) == INTEGER_CST
);
7279 tree d1
= OMP_CLAUSE_DECL (*sc
);
7280 tree d2
= OMP_CLAUSE_DECL (c
);
7281 while (TREE_CODE (d1
) == ARRAY_REF
)
7282 d1
= TREE_OPERAND (d1
, 0);
7283 while (TREE_CODE (d2
) == ARRAY_REF
)
7284 d2
= TREE_OPERAND (d2
, 0);
7285 if (TREE_CODE (d1
) == INDIRECT_REF
)
7286 d1
= TREE_OPERAND (d1
, 0);
7287 if (TREE_CODE (d2
) == INDIRECT_REF
)
7288 d2
= TREE_OPERAND (d2
, 0);
7289 while (TREE_CODE (d1
) == COMPONENT_REF
)
7290 if (TREE_CODE (d2
) == COMPONENT_REF
7291 && TREE_OPERAND (d1
, 1)
7292 == TREE_OPERAND (d2
, 1))
7294 d1
= TREE_OPERAND (d1
, 0);
7295 d2
= TREE_OPERAND (d2
, 0);
7301 error_at (OMP_CLAUSE_LOCATION (c
),
7302 "%qE appears more than once in map "
7303 "clauses", OMP_CLAUSE_DECL (c
));
7308 o2
= wi::to_offset (offset2
);
7312 o2
= o2
+ bitpos2
/ BITS_PER_UNIT
;
7313 if (wi::ltu_p (o1
, o2
)
7314 || (wi::eq_p (o1
, o2
) && bitpos
< bitpos2
))
7324 OMP_CLAUSE_SIZE (*osc
)
7325 = size_binop (PLUS_EXPR
, OMP_CLAUSE_SIZE (*osc
),
7329 tree c2
= build_omp_clause (OMP_CLAUSE_LOCATION (c
),
7331 tree cl
= NULL_TREE
;
7332 enum gomp_map_kind mkind
7333 = code
== OMP_TARGET_EXIT_DATA
7334 ? GOMP_MAP_RELEASE
: GOMP_MAP_ALLOC
;
7335 OMP_CLAUSE_SET_MAP_KIND (c2
, mkind
);
7336 OMP_CLAUSE_DECL (c2
)
7337 = unshare_expr (OMP_CLAUSE_DECL (c
));
7338 OMP_CLAUSE_CHAIN (c2
) = scp
? *scp
: *prev_list_p
;
7339 OMP_CLAUSE_SIZE (c2
)
7340 = TYPE_SIZE_UNIT (ptr_type_node
);
7341 cl
= scp
? *prev_list_p
: c2
;
7342 if (OMP_CLAUSE_CHAIN (*prev_list_p
) != c
)
7344 tree c4
= OMP_CLAUSE_CHAIN (*prev_list_p
);
7346 = build_omp_clause (OMP_CLAUSE_LOCATION (c
),
7348 OMP_CLAUSE_SET_MAP_KIND (c3
, mkind
);
7349 OMP_CLAUSE_DECL (c3
)
7350 = unshare_expr (OMP_CLAUSE_DECL (c4
));
7351 OMP_CLAUSE_SIZE (c3
)
7352 = TYPE_SIZE_UNIT (ptr_type_node
);
7353 OMP_CLAUSE_CHAIN (c3
) = *prev_list_p
;
7355 OMP_CLAUSE_CHAIN (c2
) = c3
;
7361 if (sc
== prev_list_p
)
7368 *prev_list_p
= OMP_CLAUSE_CHAIN (c
);
7369 list_p
= prev_list_p
;
7371 OMP_CLAUSE_CHAIN (c
) = *sc
;
7378 *list_p
= OMP_CLAUSE_CHAIN (c
);
7379 OMP_CLAUSE_CHAIN (c
) = *sc
;
7386 && OMP_CLAUSE_MAP_KIND (c
) != GOMP_MAP_ALWAYS_POINTER
7387 && OMP_CLAUSE_CHAIN (c
)
7388 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (c
)) == OMP_CLAUSE_MAP
7389 && (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c
))
7390 == GOMP_MAP_ALWAYS_POINTER
))
7391 prev_list_p
= list_p
;
7394 flags
= GOVD_MAP
| GOVD_EXPLICIT
;
7395 if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_ALWAYS_TO
7396 || OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_ALWAYS_TOFROM
)
7397 flags
|= GOVD_MAP_ALWAYS_TO
;
7400 case OMP_CLAUSE_DEPEND
:
7401 if (OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SINK
7402 || OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SOURCE
)
7404 /* Nothing to do. OMP_CLAUSE_DECL will be lowered in
7408 if (TREE_CODE (OMP_CLAUSE_DECL (c
)) == COMPOUND_EXPR
)
7410 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c
), 0), pre_p
,
7411 NULL
, is_gimple_val
, fb_rvalue
);
7412 OMP_CLAUSE_DECL (c
) = TREE_OPERAND (OMP_CLAUSE_DECL (c
), 1);
7414 if (error_operand_p (OMP_CLAUSE_DECL (c
)))
7419 OMP_CLAUSE_DECL (c
) = build_fold_addr_expr (OMP_CLAUSE_DECL (c
));
7420 if (gimplify_expr (&OMP_CLAUSE_DECL (c
), pre_p
, NULL
,
7421 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7429 case OMP_CLAUSE_FROM
:
7430 case OMP_CLAUSE__CACHE_
:
7431 decl
= OMP_CLAUSE_DECL (c
);
7432 if (error_operand_p (decl
))
7437 if (OMP_CLAUSE_SIZE (c
) == NULL_TREE
)
7438 OMP_CLAUSE_SIZE (c
) = DECL_P (decl
) ? DECL_SIZE_UNIT (decl
)
7439 : TYPE_SIZE_UNIT (TREE_TYPE (decl
));
7440 if (gimplify_expr (&OMP_CLAUSE_SIZE (c
), pre_p
,
7441 NULL
, is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7448 if (gimplify_expr (&OMP_CLAUSE_DECL (c
), pre_p
,
7449 NULL
, is_gimple_lvalue
, fb_lvalue
)
7459 case OMP_CLAUSE_USE_DEVICE_PTR
:
7460 flags
= GOVD_FIRSTPRIVATE
| GOVD_EXPLICIT
;
7462 case OMP_CLAUSE_IS_DEVICE_PTR
:
7463 flags
= GOVD_FIRSTPRIVATE
| GOVD_EXPLICIT
;
7467 decl
= OMP_CLAUSE_DECL (c
);
7469 if (error_operand_p (decl
))
7474 if (DECL_NAME (decl
) == NULL_TREE
&& (flags
& GOVD_SHARED
) == 0)
7476 tree t
= omp_member_access_dummy_var (decl
);
7479 tree v
= DECL_VALUE_EXPR (decl
);
7480 DECL_NAME (decl
) = DECL_NAME (TREE_OPERAND (v
, 1));
7482 omp_notice_variable (outer_ctx
, t
, true);
7485 if (code
== OACC_DATA
7486 && OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_MAP
7487 && OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_FIRSTPRIVATE_POINTER
)
7488 flags
|= GOVD_MAP_0LEN_ARRAY
;
7489 omp_add_variable (ctx
, decl
, flags
);
7490 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_REDUCTION
7491 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c
))
7493 omp_add_variable (ctx
, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c
),
7494 GOVD_LOCAL
| GOVD_SEEN
);
7495 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c
)
7496 && walk_tree (&OMP_CLAUSE_REDUCTION_INIT (c
),
7498 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c
),
7500 omp_add_variable (ctx
,
7501 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c
),
7502 GOVD_LOCAL
| GOVD_SEEN
);
7503 gimplify_omp_ctxp
= ctx
;
7504 push_gimplify_context ();
7506 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c
) = NULL
;
7507 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c
) = NULL
;
7509 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c
),
7510 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c
));
7511 pop_gimplify_context
7512 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c
)));
7513 push_gimplify_context ();
7514 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c
),
7515 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c
));
7516 pop_gimplify_context
7517 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c
)));
7518 OMP_CLAUSE_REDUCTION_INIT (c
) = NULL_TREE
;
7519 OMP_CLAUSE_REDUCTION_MERGE (c
) = NULL_TREE
;
7521 gimplify_omp_ctxp
= outer_ctx
;
7523 else if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LASTPRIVATE
7524 && OMP_CLAUSE_LASTPRIVATE_STMT (c
))
7526 gimplify_omp_ctxp
= ctx
;
7527 push_gimplify_context ();
7528 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c
)) != BIND_EXPR
)
7530 tree bind
= build3 (BIND_EXPR
, void_type_node
, NULL
,
7532 TREE_SIDE_EFFECTS (bind
) = 1;
7533 BIND_EXPR_BODY (bind
) = OMP_CLAUSE_LASTPRIVATE_STMT (c
);
7534 OMP_CLAUSE_LASTPRIVATE_STMT (c
) = bind
;
7536 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c
),
7537 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c
));
7538 pop_gimplify_context
7539 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c
)));
7540 OMP_CLAUSE_LASTPRIVATE_STMT (c
) = NULL_TREE
;
7542 gimplify_omp_ctxp
= outer_ctx
;
7544 else if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LINEAR
7545 && OMP_CLAUSE_LINEAR_STMT (c
))
7547 gimplify_omp_ctxp
= ctx
;
7548 push_gimplify_context ();
7549 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c
)) != BIND_EXPR
)
7551 tree bind
= build3 (BIND_EXPR
, void_type_node
, NULL
,
7553 TREE_SIDE_EFFECTS (bind
) = 1;
7554 BIND_EXPR_BODY (bind
) = OMP_CLAUSE_LINEAR_STMT (c
);
7555 OMP_CLAUSE_LINEAR_STMT (c
) = bind
;
7557 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c
),
7558 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c
));
7559 pop_gimplify_context
7560 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c
)));
7561 OMP_CLAUSE_LINEAR_STMT (c
) = NULL_TREE
;
7563 gimplify_omp_ctxp
= outer_ctx
;
7569 case OMP_CLAUSE_COPYIN
:
7570 case OMP_CLAUSE_COPYPRIVATE
:
7571 decl
= OMP_CLAUSE_DECL (c
);
7572 if (error_operand_p (decl
))
7577 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_COPYPRIVATE
7579 && !omp_check_private (ctx
, decl
, true))
7582 if (is_global_var (decl
))
7584 if (DECL_THREAD_LOCAL_P (decl
))
7586 else if (DECL_HAS_VALUE_EXPR_P (decl
))
7588 tree value
= get_base_address (DECL_VALUE_EXPR (decl
));
7592 && DECL_THREAD_LOCAL_P (value
))
7597 error_at (OMP_CLAUSE_LOCATION (c
),
7598 "copyprivate variable %qE is not threadprivate"
7599 " or private in outer context", DECL_NAME (decl
));
7603 omp_notice_variable (outer_ctx
, decl
, true);
7604 if (check_non_private
7605 && region_type
== ORT_WORKSHARE
7606 && (OMP_CLAUSE_CODE (c
) != OMP_CLAUSE_REDUCTION
7607 || decl
== OMP_CLAUSE_DECL (c
)
7608 || (TREE_CODE (OMP_CLAUSE_DECL (c
)) == MEM_REF
7609 && (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c
), 0))
7611 || (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c
), 0))
7612 == POINTER_PLUS_EXPR
7613 && (TREE_CODE (TREE_OPERAND (TREE_OPERAND
7614 (OMP_CLAUSE_DECL (c
), 0), 0))
7616 && omp_check_private (ctx
, decl
, false))
7618 error ("%s variable %qE is private in outer context",
7619 check_non_private
, DECL_NAME (decl
));
7625 if (OMP_CLAUSE_IF_MODIFIER (c
) != ERROR_MARK
7626 && OMP_CLAUSE_IF_MODIFIER (c
) != code
)
7629 for (int i
= 0; i
< 2; i
++)
7630 switch (i
? OMP_CLAUSE_IF_MODIFIER (c
) : code
)
7632 case OMP_PARALLEL
: p
[i
] = "parallel"; break;
7633 case OMP_TASK
: p
[i
] = "task"; break;
7634 case OMP_TASKLOOP
: p
[i
] = "taskloop"; break;
7635 case OMP_TARGET_DATA
: p
[i
] = "target data"; break;
7636 case OMP_TARGET
: p
[i
] = "target"; break;
7637 case OMP_TARGET_UPDATE
: p
[i
] = "target update"; break;
7638 case OMP_TARGET_ENTER_DATA
:
7639 p
[i
] = "target enter data"; break;
7640 case OMP_TARGET_EXIT_DATA
: p
[i
] = "target exit data"; break;
7641 default: gcc_unreachable ();
7643 error_at (OMP_CLAUSE_LOCATION (c
),
7644 "expected %qs %<if%> clause modifier rather than %qs",
7650 case OMP_CLAUSE_FINAL
:
7651 OMP_CLAUSE_OPERAND (c
, 0)
7652 = gimple_boolify (OMP_CLAUSE_OPERAND (c
, 0));
7655 case OMP_CLAUSE_SCHEDULE
:
7656 case OMP_CLAUSE_NUM_THREADS
:
7657 case OMP_CLAUSE_NUM_TEAMS
:
7658 case OMP_CLAUSE_THREAD_LIMIT
:
7659 case OMP_CLAUSE_DIST_SCHEDULE
:
7660 case OMP_CLAUSE_DEVICE
:
7661 case OMP_CLAUSE_PRIORITY
:
7662 case OMP_CLAUSE_GRAINSIZE
:
7663 case OMP_CLAUSE_NUM_TASKS
:
7664 case OMP_CLAUSE_HINT
:
7665 case OMP_CLAUSE__CILK_FOR_COUNT_
:
7666 case OMP_CLAUSE_ASYNC
:
7667 case OMP_CLAUSE_WAIT
:
7668 case OMP_CLAUSE_NUM_GANGS
:
7669 case OMP_CLAUSE_NUM_WORKERS
:
7670 case OMP_CLAUSE_VECTOR_LENGTH
:
7671 case OMP_CLAUSE_WORKER
:
7672 case OMP_CLAUSE_VECTOR
:
7673 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c
, 0), pre_p
, NULL
,
7674 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7678 case OMP_CLAUSE_GANG
:
7679 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c
, 0), pre_p
, NULL
,
7680 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7682 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c
, 1), pre_p
, NULL
,
7683 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7687 case OMP_CLAUSE_TILE
:
7688 for (tree list
= OMP_CLAUSE_TILE_LIST (c
); !remove
&& list
;
7689 list
= TREE_CHAIN (list
))
7691 if (gimplify_expr (&TREE_VALUE (list
), pre_p
, NULL
,
7692 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7697 case OMP_CLAUSE_NOWAIT
:
7698 case OMP_CLAUSE_ORDERED
:
7699 case OMP_CLAUSE_UNTIED
:
7700 case OMP_CLAUSE_COLLAPSE
:
7701 case OMP_CLAUSE_AUTO
:
7702 case OMP_CLAUSE_SEQ
:
7703 case OMP_CLAUSE_INDEPENDENT
:
7704 case OMP_CLAUSE_MERGEABLE
:
7705 case OMP_CLAUSE_PROC_BIND
:
7706 case OMP_CLAUSE_SAFELEN
:
7707 case OMP_CLAUSE_SIMDLEN
:
7708 case OMP_CLAUSE_NOGROUP
:
7709 case OMP_CLAUSE_THREADS
:
7710 case OMP_CLAUSE_SIMD
:
7713 case OMP_CLAUSE_DEFAULTMAP
:
7714 ctx
->target_map_scalars_firstprivate
= false;
7717 case OMP_CLAUSE_ALIGNED
:
7718 decl
= OMP_CLAUSE_DECL (c
);
7719 if (error_operand_p (decl
))
7724 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c
), pre_p
, NULL
,
7725 is_gimple_val
, fb_rvalue
) == GS_ERROR
)
7730 if (!is_global_var (decl
)
7731 && TREE_CODE (TREE_TYPE (decl
)) == POINTER_TYPE
)
7732 omp_add_variable (ctx
, decl
, GOVD_ALIGNED
);
7735 case OMP_CLAUSE_DEFAULT
:
7736 ctx
->default_kind
= OMP_CLAUSE_DEFAULT_KIND (c
);
7743 if (code
== OACC_DATA
7744 && OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_MAP
7745 && OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_FIRSTPRIVATE_POINTER
)
7748 *list_p
= OMP_CLAUSE_CHAIN (c
);
7750 list_p
= &OMP_CLAUSE_CHAIN (c
);
7753 gimplify_omp_ctxp
= ctx
;
7754 if (struct_map_to_clause
)
7755 delete struct_map_to_clause
;
7758 /* Return true if DECL is a candidate for shared to firstprivate
7759 optimization. We only consider non-addressable scalars, not
7760 too big, and not references. */
7763 omp_shared_to_firstprivate_optimizable_decl_p (tree decl
)
7765 if (TREE_ADDRESSABLE (decl
))
7767 tree type
= TREE_TYPE (decl
);
7768 if (!is_gimple_reg_type (type
)
7769 || TREE_CODE (type
) == REFERENCE_TYPE
7770 || TREE_ADDRESSABLE (type
))
7772 /* Don't optimize too large decls, as each thread/task will have
7774 HOST_WIDE_INT len
= int_size_in_bytes (type
);
7775 if (len
== -1 || len
> 4 * POINTER_SIZE
/ BITS_PER_UNIT
)
7777 if (lang_hooks
.decls
.omp_privatize_by_reference (decl
))
7782 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
7783 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
7784 GOVD_WRITTEN in outer contexts. */
7787 omp_mark_stores (struct gimplify_omp_ctx
*ctx
, tree decl
)
7789 for (; ctx
; ctx
= ctx
->outer_context
)
7791 splay_tree_node n
= splay_tree_lookup (ctx
->variables
,
7792 (splay_tree_key
) decl
);
7795 else if (n
->value
& GOVD_SHARED
)
7797 n
->value
|= GOVD_WRITTEN
;
7800 else if (n
->value
& GOVD_DATA_SHARE_CLASS
)
7805 /* Helper callback for walk_gimple_seq to discover possible stores
7806 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
7807 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
7811 omp_find_stores_op (tree
*tp
, int *walk_subtrees
, void *data
)
7813 struct walk_stmt_info
*wi
= (struct walk_stmt_info
*) data
;
7822 if (handled_component_p (op
))
7823 op
= TREE_OPERAND (op
, 0);
7824 else if ((TREE_CODE (op
) == MEM_REF
|| TREE_CODE (op
) == TARGET_MEM_REF
)
7825 && TREE_CODE (TREE_OPERAND (op
, 0)) == ADDR_EXPR
)
7826 op
= TREE_OPERAND (TREE_OPERAND (op
, 0), 0);
7831 if (!DECL_P (op
) || !omp_shared_to_firstprivate_optimizable_decl_p (op
))
7834 omp_mark_stores (gimplify_omp_ctxp
, op
);
7838 /* Helper callback for walk_gimple_seq to discover possible stores
7839 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
7840 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
7844 omp_find_stores_stmt (gimple_stmt_iterator
*gsi_p
,
7845 bool *handled_ops_p
,
7846 struct walk_stmt_info
*wi
)
7848 gimple
*stmt
= gsi_stmt (*gsi_p
);
7849 switch (gimple_code (stmt
))
7851 /* Don't recurse on OpenMP constructs for which
7852 gimplify_adjust_omp_clauses already handled the bodies,
7853 except handle gimple_omp_for_pre_body. */
7854 case GIMPLE_OMP_FOR
:
7855 *handled_ops_p
= true;
7856 if (gimple_omp_for_pre_body (stmt
))
7857 walk_gimple_seq (gimple_omp_for_pre_body (stmt
),
7858 omp_find_stores_stmt
, omp_find_stores_op
, wi
);
7860 case GIMPLE_OMP_PARALLEL
:
7861 case GIMPLE_OMP_TASK
:
7862 case GIMPLE_OMP_SECTIONS
:
7863 case GIMPLE_OMP_SINGLE
:
7864 case GIMPLE_OMP_TARGET
:
7865 case GIMPLE_OMP_TEAMS
:
7866 case GIMPLE_OMP_CRITICAL
:
7867 *handled_ops_p
= true;
7875 struct gimplify_adjust_omp_clauses_data
7881 /* For all variables that were not actually used within the context,
7882 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
7885 gimplify_adjust_omp_clauses_1 (splay_tree_node n
, void *data
)
7887 tree
*list_p
= ((struct gimplify_adjust_omp_clauses_data
*) data
)->list_p
;
7889 = ((struct gimplify_adjust_omp_clauses_data
*) data
)->pre_p
;
7890 tree decl
= (tree
) n
->key
;
7891 unsigned flags
= n
->value
;
7892 enum omp_clause_code code
;
7896 if (flags
& (GOVD_EXPLICIT
| GOVD_LOCAL
))
7898 if ((flags
& GOVD_SEEN
) == 0)
7900 if (flags
& GOVD_DEBUG_PRIVATE
)
7902 gcc_assert ((flags
& GOVD_DATA_SHARE_CLASS
) == GOVD_PRIVATE
);
7903 private_debug
= true;
7905 else if (flags
& GOVD_MAP
)
7906 private_debug
= false;
7909 = lang_hooks
.decls
.omp_private_debug_clause (decl
,
7910 !!(flags
& GOVD_SHARED
));
7912 code
= OMP_CLAUSE_PRIVATE
;
7913 else if (flags
& GOVD_MAP
)
7915 code
= OMP_CLAUSE_MAP
;
7916 if ((gimplify_omp_ctxp
->region_type
& ORT_ACC
) == 0
7917 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl
))))
7919 error ("%<_Atomic%> %qD in implicit %<map%> clause", decl
);
7923 else if (flags
& GOVD_SHARED
)
7925 if (is_global_var (decl
))
7927 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
->outer_context
;
7931 = splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
7932 if (on
&& (on
->value
& (GOVD_FIRSTPRIVATE
| GOVD_LASTPRIVATE
7933 | GOVD_PRIVATE
| GOVD_REDUCTION
7934 | GOVD_LINEAR
| GOVD_MAP
)) != 0)
7936 ctx
= ctx
->outer_context
;
7941 code
= OMP_CLAUSE_SHARED
;
7943 else if (flags
& GOVD_PRIVATE
)
7944 code
= OMP_CLAUSE_PRIVATE
;
7945 else if (flags
& GOVD_FIRSTPRIVATE
)
7947 code
= OMP_CLAUSE_FIRSTPRIVATE
;
7948 if ((gimplify_omp_ctxp
->region_type
& ORT_TARGET
)
7949 && (gimplify_omp_ctxp
->region_type
& ORT_ACC
) == 0
7950 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl
))))
7952 error ("%<_Atomic%> %qD in implicit %<firstprivate%> clause on "
7953 "%<target%> construct", decl
);
7957 else if (flags
& GOVD_LASTPRIVATE
)
7958 code
= OMP_CLAUSE_LASTPRIVATE
;
7959 else if (flags
& GOVD_ALIGNED
)
7964 if (((flags
& GOVD_LASTPRIVATE
)
7965 || (code
== OMP_CLAUSE_SHARED
&& (flags
& GOVD_WRITTEN
)))
7966 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
7967 omp_mark_stores (gimplify_omp_ctxp
->outer_context
, decl
);
7969 clause
= build_omp_clause (input_location
, code
);
7970 OMP_CLAUSE_DECL (clause
) = decl
;
7971 OMP_CLAUSE_CHAIN (clause
) = *list_p
;
7973 OMP_CLAUSE_PRIVATE_DEBUG (clause
) = 1;
7974 else if (code
== OMP_CLAUSE_PRIVATE
&& (flags
& GOVD_PRIVATE_OUTER_REF
))
7975 OMP_CLAUSE_PRIVATE_OUTER_REF (clause
) = 1;
7976 else if (code
== OMP_CLAUSE_SHARED
7977 && (flags
& GOVD_WRITTEN
) == 0
7978 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
7979 OMP_CLAUSE_SHARED_READONLY (clause
) = 1;
7980 else if (code
== OMP_CLAUSE_FIRSTPRIVATE
&& (flags
& GOVD_EXPLICIT
) == 0)
7981 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (clause
) = 1;
7982 else if (code
== OMP_CLAUSE_MAP
&& (flags
& GOVD_MAP_0LEN_ARRAY
) != 0)
7984 tree nc
= build_omp_clause (input_location
, OMP_CLAUSE_MAP
);
7985 OMP_CLAUSE_DECL (nc
) = decl
;
7986 if (TREE_CODE (TREE_TYPE (decl
)) == REFERENCE_TYPE
7987 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl
))) == POINTER_TYPE
)
7988 OMP_CLAUSE_DECL (clause
)
7989 = build_simple_mem_ref_loc (input_location
, decl
);
7990 OMP_CLAUSE_DECL (clause
)
7991 = build2 (MEM_REF
, char_type_node
, OMP_CLAUSE_DECL (clause
),
7992 build_int_cst (build_pointer_type (char_type_node
), 0));
7993 OMP_CLAUSE_SIZE (clause
) = size_zero_node
;
7994 OMP_CLAUSE_SIZE (nc
) = size_zero_node
;
7995 OMP_CLAUSE_SET_MAP_KIND (clause
, GOMP_MAP_ALLOC
);
7996 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause
) = 1;
7997 OMP_CLAUSE_SET_MAP_KIND (nc
, GOMP_MAP_FIRSTPRIVATE_POINTER
);
7998 OMP_CLAUSE_CHAIN (nc
) = *list_p
;
7999 OMP_CLAUSE_CHAIN (clause
) = nc
;
8000 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
8001 gimplify_omp_ctxp
= ctx
->outer_context
;
8002 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause
), 0),
8003 pre_p
, NULL
, is_gimple_val
, fb_rvalue
);
8004 gimplify_omp_ctxp
= ctx
;
8006 else if (code
== OMP_CLAUSE_MAP
)
8008 int kind
= (flags
& GOVD_MAP_TO_ONLY
8011 if (flags
& GOVD_MAP_FORCE
)
8012 kind
|= GOMP_MAP_FLAG_FORCE
;
8013 OMP_CLAUSE_SET_MAP_KIND (clause
, kind
);
8014 if (DECL_SIZE (decl
)
8015 && TREE_CODE (DECL_SIZE (decl
)) != INTEGER_CST
)
8017 tree decl2
= DECL_VALUE_EXPR (decl
);
8018 gcc_assert (TREE_CODE (decl2
) == INDIRECT_REF
);
8019 decl2
= TREE_OPERAND (decl2
, 0);
8020 gcc_assert (DECL_P (decl2
));
8021 tree mem
= build_simple_mem_ref (decl2
);
8022 OMP_CLAUSE_DECL (clause
) = mem
;
8023 OMP_CLAUSE_SIZE (clause
) = TYPE_SIZE_UNIT (TREE_TYPE (decl
));
8024 if (gimplify_omp_ctxp
->outer_context
)
8026 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
->outer_context
;
8027 omp_notice_variable (ctx
, decl2
, true);
8028 omp_notice_variable (ctx
, OMP_CLAUSE_SIZE (clause
), true);
8030 tree nc
= build_omp_clause (OMP_CLAUSE_LOCATION (clause
),
8032 OMP_CLAUSE_DECL (nc
) = decl
;
8033 OMP_CLAUSE_SIZE (nc
) = size_zero_node
;
8034 if (gimplify_omp_ctxp
->target_firstprivatize_array_bases
)
8035 OMP_CLAUSE_SET_MAP_KIND (nc
, GOMP_MAP_FIRSTPRIVATE_POINTER
);
8037 OMP_CLAUSE_SET_MAP_KIND (nc
, GOMP_MAP_POINTER
);
8038 OMP_CLAUSE_CHAIN (nc
) = OMP_CLAUSE_CHAIN (clause
);
8039 OMP_CLAUSE_CHAIN (clause
) = nc
;
8041 else if (gimplify_omp_ctxp
->target_firstprivatize_array_bases
8042 && lang_hooks
.decls
.omp_privatize_by_reference (decl
))
8044 OMP_CLAUSE_DECL (clause
) = build_simple_mem_ref (decl
);
8045 OMP_CLAUSE_SIZE (clause
)
8046 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl
))));
8047 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
8048 gimplify_omp_ctxp
= ctx
->outer_context
;
8049 gimplify_expr (&OMP_CLAUSE_SIZE (clause
),
8050 pre_p
, NULL
, is_gimple_val
, fb_rvalue
);
8051 gimplify_omp_ctxp
= ctx
;
8052 tree nc
= build_omp_clause (OMP_CLAUSE_LOCATION (clause
),
8054 OMP_CLAUSE_DECL (nc
) = decl
;
8055 OMP_CLAUSE_SIZE (nc
) = size_zero_node
;
8056 OMP_CLAUSE_SET_MAP_KIND (nc
, GOMP_MAP_FIRSTPRIVATE_REFERENCE
);
8057 OMP_CLAUSE_CHAIN (nc
) = OMP_CLAUSE_CHAIN (clause
);
8058 OMP_CLAUSE_CHAIN (clause
) = nc
;
8061 OMP_CLAUSE_SIZE (clause
) = DECL_SIZE_UNIT (decl
);
8063 if (code
== OMP_CLAUSE_FIRSTPRIVATE
&& (flags
& GOVD_LASTPRIVATE
) != 0)
8065 tree nc
= build_omp_clause (input_location
, OMP_CLAUSE_LASTPRIVATE
);
8066 OMP_CLAUSE_DECL (nc
) = decl
;
8067 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc
) = 1;
8068 OMP_CLAUSE_CHAIN (nc
) = *list_p
;
8069 OMP_CLAUSE_CHAIN (clause
) = nc
;
8070 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
8071 gimplify_omp_ctxp
= ctx
->outer_context
;
8072 lang_hooks
.decls
.omp_finish_clause (nc
, pre_p
);
8073 gimplify_omp_ctxp
= ctx
;
8076 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
8077 gimplify_omp_ctxp
= ctx
->outer_context
;
8078 lang_hooks
.decls
.omp_finish_clause (clause
, pre_p
);
8079 gimplify_omp_ctxp
= ctx
;
8084 gimplify_adjust_omp_clauses (gimple_seq
*pre_p
, gimple_seq body
, tree
*list_p
,
8085 enum tree_code code
)
8087 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
8092 struct gimplify_omp_ctx
*octx
;
8093 for (octx
= ctx
; octx
; octx
= octx
->outer_context
)
8094 if ((octx
->region_type
& (ORT_PARALLEL
| ORT_TASK
| ORT_TEAMS
)) != 0)
8098 struct walk_stmt_info wi
;
8099 memset (&wi
, 0, sizeof (wi
));
8100 walk_gimple_seq (body
, omp_find_stores_stmt
,
8101 omp_find_stores_op
, &wi
);
8104 while ((c
= *list_p
) != NULL
)
8107 bool remove
= false;
8109 switch (OMP_CLAUSE_CODE (c
))
8111 case OMP_CLAUSE_FIRSTPRIVATE
:
8112 if ((ctx
->region_type
& ORT_TARGET
)
8113 && (ctx
->region_type
& ORT_ACC
) == 0
8114 && TYPE_ATOMIC (strip_array_types
8115 (TREE_TYPE (OMP_CLAUSE_DECL (c
)))))
8117 error_at (OMP_CLAUSE_LOCATION (c
),
8118 "%<_Atomic%> %qD in %<firstprivate%> clause on "
8119 "%<target%> construct", OMP_CLAUSE_DECL (c
));
8124 case OMP_CLAUSE_PRIVATE
:
8125 case OMP_CLAUSE_SHARED
:
8126 case OMP_CLAUSE_LINEAR
:
8127 decl
= OMP_CLAUSE_DECL (c
);
8128 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
8129 remove
= !(n
->value
& GOVD_SEEN
);
8132 bool shared
= OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_SHARED
;
8133 if ((n
->value
& GOVD_DEBUG_PRIVATE
)
8134 || lang_hooks
.decls
.omp_private_debug_clause (decl
, shared
))
8136 gcc_assert ((n
->value
& GOVD_DEBUG_PRIVATE
) == 0
8137 || ((n
->value
& GOVD_DATA_SHARE_CLASS
)
8139 OMP_CLAUSE_SET_CODE (c
, OMP_CLAUSE_PRIVATE
);
8140 OMP_CLAUSE_PRIVATE_DEBUG (c
) = 1;
8142 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_SHARED
8143 && (n
->value
& GOVD_WRITTEN
) == 0
8145 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
8146 OMP_CLAUSE_SHARED_READONLY (c
) = 1;
8147 else if (DECL_P (decl
)
8148 && ((OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_SHARED
8149 && (n
->value
& GOVD_WRITTEN
) != 1)
8150 || (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LINEAR
8151 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c
)))
8152 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
8153 omp_mark_stores (gimplify_omp_ctxp
->outer_context
, decl
);
8157 case OMP_CLAUSE_LASTPRIVATE
:
8158 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
8159 accurately reflect the presence of a FIRSTPRIVATE clause. */
8160 decl
= OMP_CLAUSE_DECL (c
);
8161 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
8162 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c
)
8163 = (n
->value
& GOVD_FIRSTPRIVATE
) != 0;
8164 if (omp_no_lastprivate (ctx
))
8166 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c
))
8169 OMP_CLAUSE_CODE (c
) = OMP_CLAUSE_PRIVATE
;
8171 else if (code
== OMP_DISTRIBUTE
8172 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c
))
8175 error_at (OMP_CLAUSE_LOCATION (c
),
8176 "same variable used in %<firstprivate%> and "
8177 "%<lastprivate%> clauses on %<distribute%> "
8181 && OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LASTPRIVATE
8183 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
8184 omp_mark_stores (gimplify_omp_ctxp
->outer_context
, decl
);
8187 case OMP_CLAUSE_ALIGNED
:
8188 decl
= OMP_CLAUSE_DECL (c
);
8189 if (!is_global_var (decl
))
8191 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
8192 remove
= n
== NULL
|| !(n
->value
& GOVD_SEEN
);
8193 if (!remove
&& TREE_CODE (TREE_TYPE (decl
)) == POINTER_TYPE
)
8195 struct gimplify_omp_ctx
*octx
;
8197 && (n
->value
& (GOVD_DATA_SHARE_CLASS
8198 & ~GOVD_FIRSTPRIVATE
)))
8201 for (octx
= ctx
->outer_context
; octx
;
8202 octx
= octx
->outer_context
)
8204 n
= splay_tree_lookup (octx
->variables
,
8205 (splay_tree_key
) decl
);
8208 if (n
->value
& GOVD_LOCAL
)
8210 /* We have to avoid assigning a shared variable
8211 to itself when trying to add
8212 __builtin_assume_aligned. */
8213 if (n
->value
& GOVD_SHARED
)
8221 else if (TREE_CODE (TREE_TYPE (decl
)) == ARRAY_TYPE
)
8223 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
8224 if (n
!= NULL
&& (n
->value
& GOVD_DATA_SHARE_CLASS
) != 0)
8229 case OMP_CLAUSE_MAP
:
8230 if (code
== OMP_TARGET_EXIT_DATA
8231 && OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_ALWAYS_POINTER
)
8236 decl
= OMP_CLAUSE_DECL (c
);
8237 /* Data clauses associated with acc parallel reductions must be
8238 compatible with present_or_copy. Warn and adjust the clause
8239 if that is not the case. */
8240 if (ctx
->region_type
== ORT_ACC_PARALLEL
)
8242 tree t
= DECL_P (decl
) ? decl
: TREE_OPERAND (decl
, 0);
8246 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) t
);
8248 if (n
&& (n
->value
& GOVD_REDUCTION
))
8250 enum gomp_map_kind kind
= OMP_CLAUSE_MAP_KIND (c
);
8252 OMP_CLAUSE_MAP_IN_REDUCTION (c
) = 1;
8253 if ((kind
& GOMP_MAP_TOFROM
) != GOMP_MAP_TOFROM
8254 && kind
!= GOMP_MAP_FORCE_PRESENT
8255 && kind
!= GOMP_MAP_POINTER
)
8257 warning_at (OMP_CLAUSE_LOCATION (c
), 0,
8258 "incompatible data clause with reduction "
8259 "on %qE; promoting to present_or_copy",
8261 OMP_CLAUSE_SET_MAP_KIND (c
, GOMP_MAP_TOFROM
);
8267 if ((ctx
->region_type
& ORT_TARGET
) != 0
8268 && OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_FIRSTPRIVATE_POINTER
)
8270 if (TREE_CODE (decl
) == INDIRECT_REF
8271 && TREE_CODE (TREE_OPERAND (decl
, 0)) == COMPONENT_REF
8272 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl
, 0)))
8274 decl
= TREE_OPERAND (decl
, 0);
8275 if (TREE_CODE (decl
) == COMPONENT_REF
)
8277 while (TREE_CODE (decl
) == COMPONENT_REF
)
8278 decl
= TREE_OPERAND (decl
, 0);
8281 n
= splay_tree_lookup (ctx
->variables
,
8282 (splay_tree_key
) decl
);
8283 if (!(n
->value
& GOVD_SEEN
))
8290 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
8291 if ((ctx
->region_type
& ORT_TARGET
) != 0
8292 && !(n
->value
& GOVD_SEEN
)
8293 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c
)) == 0
8294 && !lookup_attribute ("omp declare target link",
8295 DECL_ATTRIBUTES (decl
)))
8298 /* For struct element mapping, if struct is never referenced
8299 in target block and none of the mapping has always modifier,
8300 remove all the struct element mappings, which immediately
8301 follow the GOMP_MAP_STRUCT map clause. */
8302 if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_STRUCT
)
8304 HOST_WIDE_INT cnt
= tree_to_shwi (OMP_CLAUSE_SIZE (c
));
8306 OMP_CLAUSE_CHAIN (c
)
8307 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c
));
8310 else if (OMP_CLAUSE_MAP_KIND (c
) == GOMP_MAP_STRUCT
8311 && code
== OMP_TARGET_EXIT_DATA
)
8313 else if (DECL_SIZE (decl
)
8314 && TREE_CODE (DECL_SIZE (decl
)) != INTEGER_CST
8315 && OMP_CLAUSE_MAP_KIND (c
) != GOMP_MAP_POINTER
8316 && OMP_CLAUSE_MAP_KIND (c
) != GOMP_MAP_FIRSTPRIVATE_POINTER
8317 && (OMP_CLAUSE_MAP_KIND (c
)
8318 != GOMP_MAP_FIRSTPRIVATE_REFERENCE
))
8320 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
8321 for these, TREE_CODE (DECL_SIZE (decl)) will always be
8323 gcc_assert (OMP_CLAUSE_MAP_KIND (c
) != GOMP_MAP_FORCE_DEVICEPTR
);
8325 tree decl2
= DECL_VALUE_EXPR (decl
);
8326 gcc_assert (TREE_CODE (decl2
) == INDIRECT_REF
);
8327 decl2
= TREE_OPERAND (decl2
, 0);
8328 gcc_assert (DECL_P (decl2
));
8329 tree mem
= build_simple_mem_ref (decl2
);
8330 OMP_CLAUSE_DECL (c
) = mem
;
8331 OMP_CLAUSE_SIZE (c
) = TYPE_SIZE_UNIT (TREE_TYPE (decl
));
8332 if (ctx
->outer_context
)
8334 omp_notice_variable (ctx
->outer_context
, decl2
, true);
8335 omp_notice_variable (ctx
->outer_context
,
8336 OMP_CLAUSE_SIZE (c
), true);
8338 if (((ctx
->region_type
& ORT_TARGET
) != 0
8339 || !ctx
->target_firstprivatize_array_bases
)
8340 && ((n
->value
& GOVD_SEEN
) == 0
8341 || (n
->value
& (GOVD_PRIVATE
| GOVD_FIRSTPRIVATE
)) == 0))
8343 tree nc
= build_omp_clause (OMP_CLAUSE_LOCATION (c
),
8345 OMP_CLAUSE_DECL (nc
) = decl
;
8346 OMP_CLAUSE_SIZE (nc
) = size_zero_node
;
8347 if (ctx
->target_firstprivatize_array_bases
)
8348 OMP_CLAUSE_SET_MAP_KIND (nc
,
8349 GOMP_MAP_FIRSTPRIVATE_POINTER
);
8351 OMP_CLAUSE_SET_MAP_KIND (nc
, GOMP_MAP_POINTER
);
8352 OMP_CLAUSE_CHAIN (nc
) = OMP_CLAUSE_CHAIN (c
);
8353 OMP_CLAUSE_CHAIN (c
) = nc
;
8359 if (OMP_CLAUSE_SIZE (c
) == NULL_TREE
)
8360 OMP_CLAUSE_SIZE (c
) = DECL_SIZE_UNIT (decl
);
8361 gcc_assert ((n
->value
& GOVD_SEEN
) == 0
8362 || ((n
->value
& (GOVD_PRIVATE
| GOVD_FIRSTPRIVATE
))
8368 case OMP_CLAUSE_FROM
:
8369 case OMP_CLAUSE__CACHE_
:
8370 decl
= OMP_CLAUSE_DECL (c
);
8373 if (DECL_SIZE (decl
)
8374 && TREE_CODE (DECL_SIZE (decl
)) != INTEGER_CST
)
8376 tree decl2
= DECL_VALUE_EXPR (decl
);
8377 gcc_assert (TREE_CODE (decl2
) == INDIRECT_REF
);
8378 decl2
= TREE_OPERAND (decl2
, 0);
8379 gcc_assert (DECL_P (decl2
));
8380 tree mem
= build_simple_mem_ref (decl2
);
8381 OMP_CLAUSE_DECL (c
) = mem
;
8382 OMP_CLAUSE_SIZE (c
) = TYPE_SIZE_UNIT (TREE_TYPE (decl
));
8383 if (ctx
->outer_context
)
8385 omp_notice_variable (ctx
->outer_context
, decl2
, true);
8386 omp_notice_variable (ctx
->outer_context
,
8387 OMP_CLAUSE_SIZE (c
), true);
8390 else if (OMP_CLAUSE_SIZE (c
) == NULL_TREE
)
8391 OMP_CLAUSE_SIZE (c
) = DECL_SIZE_UNIT (decl
);
8394 case OMP_CLAUSE_REDUCTION
:
8395 decl
= OMP_CLAUSE_DECL (c
);
8396 /* OpenACC reductions need a present_or_copy data clause.
8397 Add one if necessary. Error is the reduction is private. */
8398 if (ctx
->region_type
== ORT_ACC_PARALLEL
)
8400 n
= splay_tree_lookup (ctx
->variables
, (splay_tree_key
) decl
);
8401 if (n
->value
& (GOVD_PRIVATE
| GOVD_FIRSTPRIVATE
))
8402 error_at (OMP_CLAUSE_LOCATION (c
), "invalid private "
8403 "reduction on %qE", DECL_NAME (decl
));
8404 else if ((n
->value
& GOVD_MAP
) == 0)
8406 tree next
= OMP_CLAUSE_CHAIN (c
);
8407 tree nc
= build_omp_clause (UNKNOWN_LOCATION
, OMP_CLAUSE_MAP
);
8408 OMP_CLAUSE_SET_MAP_KIND (nc
, GOMP_MAP_TOFROM
);
8409 OMP_CLAUSE_DECL (nc
) = decl
;
8410 OMP_CLAUSE_CHAIN (c
) = nc
;
8411 lang_hooks
.decls
.omp_finish_clause (nc
, pre_p
);
8414 OMP_CLAUSE_MAP_IN_REDUCTION (nc
) = 1;
8415 if (OMP_CLAUSE_CHAIN (nc
) == NULL
)
8417 nc
= OMP_CLAUSE_CHAIN (nc
);
8419 OMP_CLAUSE_CHAIN (nc
) = next
;
8420 n
->value
|= GOVD_MAP
;
8424 && omp_shared_to_firstprivate_optimizable_decl_p (decl
))
8425 omp_mark_stores (gimplify_omp_ctxp
->outer_context
, decl
);
8427 case OMP_CLAUSE_COPYIN
:
8428 case OMP_CLAUSE_COPYPRIVATE
:
8430 case OMP_CLAUSE_NUM_THREADS
:
8431 case OMP_CLAUSE_NUM_TEAMS
:
8432 case OMP_CLAUSE_THREAD_LIMIT
:
8433 case OMP_CLAUSE_DIST_SCHEDULE
:
8434 case OMP_CLAUSE_DEVICE
:
8435 case OMP_CLAUSE_SCHEDULE
:
8436 case OMP_CLAUSE_NOWAIT
:
8437 case OMP_CLAUSE_ORDERED
:
8438 case OMP_CLAUSE_DEFAULT
:
8439 case OMP_CLAUSE_UNTIED
:
8440 case OMP_CLAUSE_COLLAPSE
:
8441 case OMP_CLAUSE_FINAL
:
8442 case OMP_CLAUSE_MERGEABLE
:
8443 case OMP_CLAUSE_PROC_BIND
:
8444 case OMP_CLAUSE_SAFELEN
:
8445 case OMP_CLAUSE_SIMDLEN
:
8446 case OMP_CLAUSE_DEPEND
:
8447 case OMP_CLAUSE_PRIORITY
:
8448 case OMP_CLAUSE_GRAINSIZE
:
8449 case OMP_CLAUSE_NUM_TASKS
:
8450 case OMP_CLAUSE_NOGROUP
:
8451 case OMP_CLAUSE_THREADS
:
8452 case OMP_CLAUSE_SIMD
:
8453 case OMP_CLAUSE_HINT
:
8454 case OMP_CLAUSE_DEFAULTMAP
:
8455 case OMP_CLAUSE_USE_DEVICE_PTR
:
8456 case OMP_CLAUSE_IS_DEVICE_PTR
:
8457 case OMP_CLAUSE__CILK_FOR_COUNT_
:
8458 case OMP_CLAUSE_ASYNC
:
8459 case OMP_CLAUSE_WAIT
:
8460 case OMP_CLAUSE_INDEPENDENT
:
8461 case OMP_CLAUSE_NUM_GANGS
:
8462 case OMP_CLAUSE_NUM_WORKERS
:
8463 case OMP_CLAUSE_VECTOR_LENGTH
:
8464 case OMP_CLAUSE_GANG
:
8465 case OMP_CLAUSE_WORKER
:
8466 case OMP_CLAUSE_VECTOR
:
8467 case OMP_CLAUSE_AUTO
:
8468 case OMP_CLAUSE_SEQ
:
8471 case OMP_CLAUSE_TILE
:
8472 /* We're not yet making use of the information provided by OpenACC
8473 tile clauses. Discard these here, to simplify later middle end
8483 *list_p
= OMP_CLAUSE_CHAIN (c
);
8485 list_p
= &OMP_CLAUSE_CHAIN (c
);
8488 /* Add in any implicit data sharing. */
8489 struct gimplify_adjust_omp_clauses_data data
;
8490 data
.list_p
= list_p
;
8492 splay_tree_foreach (ctx
->variables
, gimplify_adjust_omp_clauses_1
, &data
);
8494 gimplify_omp_ctxp
= ctx
->outer_context
;
8495 delete_omp_context (ctx
);
8498 /* Gimplify OACC_CACHE. */
8501 gimplify_oacc_cache (tree
*expr_p
, gimple_seq
*pre_p
)
8503 tree expr
= *expr_p
;
8505 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr
), pre_p
, ORT_ACC
,
8507 gimplify_adjust_omp_clauses (pre_p
, NULL
, &OACC_CACHE_CLAUSES (expr
),
8510 /* TODO: Do something sensible with this information. */
8512 *expr_p
= NULL_TREE
;
8515 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
8516 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
8517 kind. The entry kind will replace the one in CLAUSE, while the exit
8518 kind will be used in a new omp_clause and returned to the caller. */
8521 gimplify_oacc_declare_1 (tree clause
)
8523 HOST_WIDE_INT kind
, new_op
;
8527 kind
= OMP_CLAUSE_MAP_KIND (clause
);
8531 case GOMP_MAP_ALLOC
:
8532 case GOMP_MAP_FORCE_ALLOC
:
8533 case GOMP_MAP_FORCE_TO
:
8534 new_op
= GOMP_MAP_DELETE
;
8538 case GOMP_MAP_FORCE_FROM
:
8539 OMP_CLAUSE_SET_MAP_KIND (clause
, GOMP_MAP_FORCE_ALLOC
);
8540 new_op
= GOMP_MAP_FORCE_FROM
;
8544 case GOMP_MAP_FORCE_TOFROM
:
8545 OMP_CLAUSE_SET_MAP_KIND (clause
, GOMP_MAP_FORCE_TO
);
8546 new_op
= GOMP_MAP_FORCE_FROM
;
8551 OMP_CLAUSE_SET_MAP_KIND (clause
, GOMP_MAP_FORCE_ALLOC
);
8552 new_op
= GOMP_MAP_FROM
;
8556 case GOMP_MAP_TOFROM
:
8557 OMP_CLAUSE_SET_MAP_KIND (clause
, GOMP_MAP_TO
);
8558 new_op
= GOMP_MAP_FROM
;
8562 case GOMP_MAP_DEVICE_RESIDENT
:
8563 case GOMP_MAP_FORCE_DEVICEPTR
:
8564 case GOMP_MAP_FORCE_PRESENT
:
8566 case GOMP_MAP_POINTER
:
8577 c
= build_omp_clause (OMP_CLAUSE_LOCATION (clause
), OMP_CLAUSE_MAP
);
8578 OMP_CLAUSE_SET_MAP_KIND (c
, new_op
);
8579 OMP_CLAUSE_DECL (c
) = OMP_CLAUSE_DECL (clause
);
8585 /* Gimplify OACC_DECLARE. */
8588 gimplify_oacc_declare (tree
*expr_p
, gimple_seq
*pre_p
)
8590 tree expr
= *expr_p
;
8594 clauses
= OACC_DECLARE_CLAUSES (expr
);
8596 gimplify_scan_omp_clauses (&clauses
, pre_p
, ORT_TARGET_DATA
, OACC_DECLARE
);
8598 for (t
= clauses
; t
; t
= OMP_CLAUSE_CHAIN (t
))
8600 tree decl
= OMP_CLAUSE_DECL (t
);
8602 if (TREE_CODE (decl
) == MEM_REF
)
8605 if (TREE_CODE (decl
) == VAR_DECL
8606 && !is_global_var (decl
)
8607 && DECL_CONTEXT (decl
) == current_function_decl
)
8609 tree c
= gimplify_oacc_declare_1 (t
);
8612 if (oacc_declare_returns
== NULL
)
8613 oacc_declare_returns
= new hash_map
<tree
, tree
>;
8615 oacc_declare_returns
->put (decl
, c
);
8619 omp_add_variable (gimplify_omp_ctxp
, decl
, GOVD_SEEN
);
8622 stmt
= gimple_build_omp_target (NULL
, GF_OMP_TARGET_KIND_OACC_DECLARE
,
8625 gimplify_seq_add_stmt (pre_p
, stmt
);
8627 *expr_p
= NULL_TREE
;
8630 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
8631 gimplification of the body, as well as scanning the body for used
8632 variables. We need to do this scan now, because variable-sized
8633 decls will be decomposed during gimplification. */
8636 gimplify_omp_parallel (tree
*expr_p
, gimple_seq
*pre_p
)
8638 tree expr
= *expr_p
;
8640 gimple_seq body
= NULL
;
8642 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr
), pre_p
,
8643 OMP_PARALLEL_COMBINED (expr
)
8644 ? ORT_COMBINED_PARALLEL
8645 : ORT_PARALLEL
, OMP_PARALLEL
);
8647 push_gimplify_context ();
8649 g
= gimplify_and_return_first (OMP_PARALLEL_BODY (expr
), &body
);
8650 if (gimple_code (g
) == GIMPLE_BIND
)
8651 pop_gimplify_context (g
);
8653 pop_gimplify_context (NULL
);
8655 gimplify_adjust_omp_clauses (pre_p
, body
, &OMP_PARALLEL_CLAUSES (expr
),
8658 g
= gimple_build_omp_parallel (body
,
8659 OMP_PARALLEL_CLAUSES (expr
),
8660 NULL_TREE
, NULL_TREE
);
8661 if (OMP_PARALLEL_COMBINED (expr
))
8662 gimple_omp_set_subcode (g
, GF_OMP_PARALLEL_COMBINED
);
8663 gimplify_seq_add_stmt (pre_p
, g
);
8664 *expr_p
= NULL_TREE
;
8667 /* Gimplify the contents of an OMP_TASK statement. This involves
8668 gimplification of the body, as well as scanning the body for used
8669 variables. We need to do this scan now, because variable-sized
8670 decls will be decomposed during gimplification. */
8673 gimplify_omp_task (tree
*expr_p
, gimple_seq
*pre_p
)
8675 tree expr
= *expr_p
;
8677 gimple_seq body
= NULL
;
8679 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr
), pre_p
,
8680 find_omp_clause (OMP_TASK_CLAUSES (expr
),
8682 ? ORT_UNTIED_TASK
: ORT_TASK
, OMP_TASK
);
8684 push_gimplify_context ();
8686 g
= gimplify_and_return_first (OMP_TASK_BODY (expr
), &body
);
8687 if (gimple_code (g
) == GIMPLE_BIND
)
8688 pop_gimplify_context (g
);
8690 pop_gimplify_context (NULL
);
8692 gimplify_adjust_omp_clauses (pre_p
, body
, &OMP_TASK_CLAUSES (expr
),
8695 g
= gimple_build_omp_task (body
,
8696 OMP_TASK_CLAUSES (expr
),
8697 NULL_TREE
, NULL_TREE
,
8698 NULL_TREE
, NULL_TREE
, NULL_TREE
);
8699 gimplify_seq_add_stmt (pre_p
, g
);
8700 *expr_p
= NULL_TREE
;
8703 /* Helper function of gimplify_omp_for, find OMP_FOR resp. OMP_SIMD
8704 with non-NULL OMP_FOR_INIT. */
8707 find_combined_omp_for (tree
*tp
, int *walk_subtrees
, void *)
8710 switch (TREE_CODE (*tp
))
8716 if (OMP_FOR_INIT (*tp
) != NULL_TREE
)
8720 case STATEMENT_LIST
:
8730 /* Gimplify the gross structure of an OMP_FOR statement. */
8732 static enum gimplify_status
8733 gimplify_omp_for (tree
*expr_p
, gimple_seq
*pre_p
)
8735 tree for_stmt
, orig_for_stmt
, inner_for_stmt
= NULL_TREE
, decl
, var
, t
;
8736 enum gimplify_status ret
= GS_ALL_DONE
;
8737 enum gimplify_status tret
;
8739 gimple_seq for_body
, for_pre_body
;
8741 bitmap has_decl_expr
= NULL
;
8742 enum omp_region_type ort
= ORT_WORKSHARE
;
8744 orig_for_stmt
= for_stmt
= *expr_p
;
8746 switch (TREE_CODE (for_stmt
))
8750 case OMP_DISTRIBUTE
:
8756 if (find_omp_clause (OMP_FOR_CLAUSES (for_stmt
), OMP_CLAUSE_UNTIED
))
8757 ort
= ORT_UNTIED_TASK
;
8769 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
8770 clause for the IV. */
8771 if (ort
== ORT_SIMD
&& TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)) == 1)
8773 t
= TREE_VEC_ELT (OMP_FOR_INIT (for_stmt
), 0);
8774 gcc_assert (TREE_CODE (t
) == MODIFY_EXPR
);
8775 decl
= TREE_OPERAND (t
, 0);
8776 for (tree c
= OMP_FOR_CLAUSES (for_stmt
); c
; c
= OMP_CLAUSE_CHAIN (c
))
8777 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LINEAR
8778 && OMP_CLAUSE_DECL (c
) == decl
)
8780 OMP_CLAUSE_LINEAR_NO_COPYIN (c
) = 1;
8785 if (OMP_FOR_INIT (for_stmt
) == NULL_TREE
)
8787 gcc_assert (TREE_CODE (for_stmt
) != OACC_LOOP
);
8788 inner_for_stmt
= walk_tree (&OMP_FOR_BODY (for_stmt
),
8789 find_combined_omp_for
, NULL
, NULL
);
8790 if (inner_for_stmt
== NULL_TREE
)
8792 gcc_assert (seen_error ());
8793 *expr_p
= NULL_TREE
;
8798 if (TREE_CODE (for_stmt
) != OMP_TASKLOOP
)
8799 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt
), pre_p
, ort
,
8800 TREE_CODE (for_stmt
));
8802 if (TREE_CODE (for_stmt
) == OMP_DISTRIBUTE
)
8803 gimplify_omp_ctxp
->distribute
= true;
8805 /* Handle OMP_FOR_INIT. */
8806 for_pre_body
= NULL
;
8807 if (ort
== ORT_SIMD
&& OMP_FOR_PRE_BODY (for_stmt
))
8809 has_decl_expr
= BITMAP_ALLOC (NULL
);
8810 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt
)) == DECL_EXPR
8811 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt
)))
8814 t
= OMP_FOR_PRE_BODY (for_stmt
);
8815 bitmap_set_bit (has_decl_expr
, DECL_UID (DECL_EXPR_DECL (t
)));
8817 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt
)) == STATEMENT_LIST
)
8819 tree_stmt_iterator si
;
8820 for (si
= tsi_start (OMP_FOR_PRE_BODY (for_stmt
)); !tsi_end_p (si
);
8824 if (TREE_CODE (t
) == DECL_EXPR
8825 && TREE_CODE (DECL_EXPR_DECL (t
)) == VAR_DECL
)
8826 bitmap_set_bit (has_decl_expr
, DECL_UID (DECL_EXPR_DECL (t
)));
8830 if (OMP_FOR_PRE_BODY (for_stmt
))
8832 if (TREE_CODE (for_stmt
) != OMP_TASKLOOP
|| gimplify_omp_ctxp
)
8833 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt
), &for_pre_body
);
8836 struct gimplify_omp_ctx ctx
;
8837 memset (&ctx
, 0, sizeof (ctx
));
8838 ctx
.region_type
= ORT_NONE
;
8839 gimplify_omp_ctxp
= &ctx
;
8840 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt
), &for_pre_body
);
8841 gimplify_omp_ctxp
= NULL
;
8844 OMP_FOR_PRE_BODY (for_stmt
) = NULL_TREE
;
8846 if (OMP_FOR_INIT (for_stmt
) == NULL_TREE
)
8847 for_stmt
= inner_for_stmt
;
8849 /* For taskloop, need to gimplify the start, end and step before the
8850 taskloop, outside of the taskloop omp context. */
8851 if (TREE_CODE (orig_for_stmt
) == OMP_TASKLOOP
)
8853 for (i
= 0; i
< TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)); i
++)
8855 t
= TREE_VEC_ELT (OMP_FOR_INIT (for_stmt
), i
);
8856 if (!is_gimple_constant (TREE_OPERAND (t
, 1)))
8859 = get_initialized_tmp_var (TREE_OPERAND (t
, 1),
8860 pre_p
, NULL
, false);
8861 tree c
= build_omp_clause (input_location
,
8862 OMP_CLAUSE_FIRSTPRIVATE
);
8863 OMP_CLAUSE_DECL (c
) = TREE_OPERAND (t
, 1);
8864 OMP_CLAUSE_CHAIN (c
) = OMP_FOR_CLAUSES (orig_for_stmt
);
8865 OMP_FOR_CLAUSES (orig_for_stmt
) = c
;
8868 /* Handle OMP_FOR_COND. */
8869 t
= TREE_VEC_ELT (OMP_FOR_COND (for_stmt
), i
);
8870 if (!is_gimple_constant (TREE_OPERAND (t
, 1)))
8873 = get_initialized_tmp_var (TREE_OPERAND (t
, 1),
8874 gimple_seq_empty_p (for_pre_body
)
8875 ? pre_p
: &for_pre_body
, NULL
,
8877 tree c
= build_omp_clause (input_location
,
8878 OMP_CLAUSE_FIRSTPRIVATE
);
8879 OMP_CLAUSE_DECL (c
) = TREE_OPERAND (t
, 1);
8880 OMP_CLAUSE_CHAIN (c
) = OMP_FOR_CLAUSES (orig_for_stmt
);
8881 OMP_FOR_CLAUSES (orig_for_stmt
) = c
;
8884 /* Handle OMP_FOR_INCR. */
8885 t
= TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
);
8886 if (TREE_CODE (t
) == MODIFY_EXPR
)
8888 decl
= TREE_OPERAND (t
, 0);
8889 t
= TREE_OPERAND (t
, 1);
8890 tree
*tp
= &TREE_OPERAND (t
, 1);
8891 if (TREE_CODE (t
) == PLUS_EXPR
&& *tp
== decl
)
8892 tp
= &TREE_OPERAND (t
, 0);
8894 if (!is_gimple_constant (*tp
))
8896 gimple_seq
*seq
= gimple_seq_empty_p (for_pre_body
)
8897 ? pre_p
: &for_pre_body
;
8898 *tp
= get_initialized_tmp_var (*tp
, seq
, NULL
, false);
8899 tree c
= build_omp_clause (input_location
,
8900 OMP_CLAUSE_FIRSTPRIVATE
);
8901 OMP_CLAUSE_DECL (c
) = *tp
;
8902 OMP_CLAUSE_CHAIN (c
) = OMP_FOR_CLAUSES (orig_for_stmt
);
8903 OMP_FOR_CLAUSES (orig_for_stmt
) = c
;
8908 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt
), pre_p
, ort
,
8912 if (orig_for_stmt
!= for_stmt
)
8913 gimplify_omp_ctxp
->combined_loop
= true;
8916 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
))
8917 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt
)));
8918 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
))
8919 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt
)));
8921 tree c
= find_omp_clause (OMP_FOR_CLAUSES (for_stmt
), OMP_CLAUSE_ORDERED
);
8922 bool is_doacross
= false;
8923 if (c
&& OMP_CLAUSE_ORDERED_EXPR (c
))
8926 gimplify_omp_ctxp
->loop_iter_var
.create (TREE_VEC_LENGTH
8927 (OMP_FOR_INIT (for_stmt
))
8931 c
= find_omp_clause (OMP_FOR_CLAUSES (for_stmt
), OMP_CLAUSE_COLLAPSE
);
8933 collapse
= tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c
));
8934 for (i
= 0; i
< TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)); i
++)
8936 t
= TREE_VEC_ELT (OMP_FOR_INIT (for_stmt
), i
);
8937 gcc_assert (TREE_CODE (t
) == MODIFY_EXPR
);
8938 decl
= TREE_OPERAND (t
, 0);
8939 gcc_assert (DECL_P (decl
));
8940 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl
))
8941 || POINTER_TYPE_P (TREE_TYPE (decl
)));
8944 if (TREE_CODE (for_stmt
) == OMP_FOR
&& OMP_FOR_ORIG_DECLS (for_stmt
))
8945 gimplify_omp_ctxp
->loop_iter_var
.quick_push
8946 (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt
), i
));
8948 gimplify_omp_ctxp
->loop_iter_var
.quick_push (decl
);
8949 gimplify_omp_ctxp
->loop_iter_var
.quick_push (decl
);
8952 /* Make sure the iteration variable is private. */
8954 tree c2
= NULL_TREE
;
8955 if (orig_for_stmt
!= for_stmt
)
8956 /* Do this only on innermost construct for combined ones. */;
8957 else if (ort
== ORT_SIMD
)
8959 splay_tree_node n
= splay_tree_lookup (gimplify_omp_ctxp
->variables
,
8960 (splay_tree_key
) decl
);
8961 omp_is_private (gimplify_omp_ctxp
, decl
,
8962 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
))
8964 if (n
!= NULL
&& (n
->value
& GOVD_DATA_SHARE_CLASS
) != 0)
8965 omp_notice_variable (gimplify_omp_ctxp
, decl
, true);
8966 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)) == 1)
8968 c
= build_omp_clause (input_location
, OMP_CLAUSE_LINEAR
);
8969 OMP_CLAUSE_LINEAR_NO_COPYIN (c
) = 1;
8970 unsigned int flags
= GOVD_LINEAR
| GOVD_EXPLICIT
| GOVD_SEEN
;
8972 && bitmap_bit_p (has_decl_expr
, DECL_UID (decl
)))
8973 || omp_no_lastprivate (gimplify_omp_ctxp
))
8975 OMP_CLAUSE_LINEAR_NO_COPYOUT (c
) = 1;
8976 flags
|= GOVD_LINEAR_LASTPRIVATE_NO_OUTER
;
8978 struct gimplify_omp_ctx
*outer
8979 = gimplify_omp_ctxp
->outer_context
;
8980 if (outer
&& !OMP_CLAUSE_LINEAR_NO_COPYOUT (c
))
8982 if (outer
->region_type
== ORT_WORKSHARE
8983 && outer
->combined_loop
)
8985 n
= splay_tree_lookup (outer
->variables
,
8986 (splay_tree_key
)decl
);
8987 if (n
!= NULL
&& (n
->value
& GOVD_LOCAL
) != 0)
8989 OMP_CLAUSE_LINEAR_NO_COPYOUT (c
) = 1;
8990 flags
|= GOVD_LINEAR_LASTPRIVATE_NO_OUTER
;
8994 struct gimplify_omp_ctx
*octx
= outer
->outer_context
;
8996 && octx
->region_type
== ORT_COMBINED_PARALLEL
8997 && octx
->outer_context
8998 && (octx
->outer_context
->region_type
9000 && octx
->outer_context
->combined_loop
)
9002 octx
= octx
->outer_context
;
9003 n
= splay_tree_lookup (octx
->variables
,
9004 (splay_tree_key
)decl
);
9005 if (n
!= NULL
&& (n
->value
& GOVD_LOCAL
) != 0)
9007 OMP_CLAUSE_LINEAR_NO_COPYOUT (c
) = 1;
9008 flags
|= GOVD_LINEAR_LASTPRIVATE_NO_OUTER
;
9015 OMP_CLAUSE_DECL (c
) = decl
;
9016 OMP_CLAUSE_CHAIN (c
) = OMP_FOR_CLAUSES (for_stmt
);
9017 OMP_FOR_CLAUSES (for_stmt
) = c
;
9018 omp_add_variable (gimplify_omp_ctxp
, decl
, flags
);
9019 if (outer
&& !OMP_CLAUSE_LINEAR_NO_COPYOUT (c
))
9021 if (outer
->region_type
== ORT_WORKSHARE
9022 && outer
->combined_loop
)
9024 if (outer
->outer_context
9025 && (outer
->outer_context
->region_type
9026 == ORT_COMBINED_PARALLEL
))
9027 outer
= outer
->outer_context
;
9028 else if (omp_check_private (outer
, decl
, false))
9031 else if (((outer
->region_type
& ORT_TASK
) != 0)
9032 && outer
->combined_loop
9033 && !omp_check_private (gimplify_omp_ctxp
,
9036 else if (outer
->region_type
!= ORT_COMBINED_PARALLEL
)
9038 omp_notice_variable (outer
, decl
, true);
9043 n
= splay_tree_lookup (outer
->variables
,
9044 (splay_tree_key
)decl
);
9045 if (n
== NULL
|| (n
->value
& GOVD_DATA_SHARE_CLASS
) == 0)
9047 omp_add_variable (outer
, decl
,
9048 GOVD_LASTPRIVATE
| GOVD_SEEN
);
9049 if (outer
->region_type
== ORT_COMBINED_PARALLEL
9050 && outer
->outer_context
9051 && (outer
->outer_context
->region_type
9053 && outer
->outer_context
->combined_loop
)
9055 outer
= outer
->outer_context
;
9056 n
= splay_tree_lookup (outer
->variables
,
9057 (splay_tree_key
)decl
);
9058 if (omp_check_private (outer
, decl
, false))
9061 || ((n
->value
& GOVD_DATA_SHARE_CLASS
)
9063 omp_add_variable (outer
, decl
,
9069 if (outer
&& outer
->outer_context
9070 && (outer
->outer_context
->region_type
9071 == ORT_COMBINED_TEAMS
))
9073 outer
= outer
->outer_context
;
9074 n
= splay_tree_lookup (outer
->variables
,
9075 (splay_tree_key
)decl
);
9077 || (n
->value
& GOVD_DATA_SHARE_CLASS
) == 0)
9078 omp_add_variable (outer
, decl
,
9079 GOVD_SHARED
| GOVD_SEEN
);
9083 if (outer
&& outer
->outer_context
)
9084 omp_notice_variable (outer
->outer_context
, decl
,
9094 || !bitmap_bit_p (has_decl_expr
, DECL_UID (decl
)))
9095 && !omp_no_lastprivate (gimplify_omp_ctxp
);
9096 struct gimplify_omp_ctx
*outer
9097 = gimplify_omp_ctxp
->outer_context
;
9098 if (outer
&& lastprivate
)
9100 if (outer
->region_type
== ORT_WORKSHARE
9101 && outer
->combined_loop
)
9103 n
= splay_tree_lookup (outer
->variables
,
9104 (splay_tree_key
)decl
);
9105 if (n
!= NULL
&& (n
->value
& GOVD_LOCAL
) != 0)
9107 lastprivate
= false;
9110 else if (outer
->outer_context
9111 && (outer
->outer_context
->region_type
9112 == ORT_COMBINED_PARALLEL
))
9113 outer
= outer
->outer_context
;
9114 else if (omp_check_private (outer
, decl
, false))
9117 else if (((outer
->region_type
& ORT_TASK
) != 0)
9118 && outer
->combined_loop
9119 && !omp_check_private (gimplify_omp_ctxp
,
9122 else if (outer
->region_type
!= ORT_COMBINED_PARALLEL
)
9124 omp_notice_variable (outer
, decl
, true);
9129 n
= splay_tree_lookup (outer
->variables
,
9130 (splay_tree_key
)decl
);
9131 if (n
== NULL
|| (n
->value
& GOVD_DATA_SHARE_CLASS
) == 0)
9133 omp_add_variable (outer
, decl
,
9134 GOVD_LASTPRIVATE
| GOVD_SEEN
);
9135 if (outer
->region_type
== ORT_COMBINED_PARALLEL
9136 && outer
->outer_context
9137 && (outer
->outer_context
->region_type
9139 && outer
->outer_context
->combined_loop
)
9141 outer
= outer
->outer_context
;
9142 n
= splay_tree_lookup (outer
->variables
,
9143 (splay_tree_key
)decl
);
9144 if (omp_check_private (outer
, decl
, false))
9147 || ((n
->value
& GOVD_DATA_SHARE_CLASS
)
9149 omp_add_variable (outer
, decl
,
9155 if (outer
&& outer
->outer_context
9156 && (outer
->outer_context
->region_type
9157 == ORT_COMBINED_TEAMS
))
9159 outer
= outer
->outer_context
;
9160 n
= splay_tree_lookup (outer
->variables
,
9161 (splay_tree_key
)decl
);
9163 || (n
->value
& GOVD_DATA_SHARE_CLASS
) == 0)
9164 omp_add_variable (outer
, decl
,
9165 GOVD_SHARED
| GOVD_SEEN
);
9169 if (outer
&& outer
->outer_context
)
9170 omp_notice_variable (outer
->outer_context
, decl
,
9176 c
= build_omp_clause (input_location
,
9177 lastprivate
? OMP_CLAUSE_LASTPRIVATE
9178 : OMP_CLAUSE_PRIVATE
);
9179 OMP_CLAUSE_DECL (c
) = decl
;
9180 OMP_CLAUSE_CHAIN (c
) = OMP_FOR_CLAUSES (for_stmt
);
9181 OMP_FOR_CLAUSES (for_stmt
) = c
;
9182 omp_add_variable (gimplify_omp_ctxp
, decl
,
9183 (lastprivate
? GOVD_LASTPRIVATE
: GOVD_PRIVATE
)
9184 | GOVD_EXPLICIT
| GOVD_SEEN
);
9188 else if (omp_is_private (gimplify_omp_ctxp
, decl
, 0))
9189 omp_notice_variable (gimplify_omp_ctxp
, decl
, true);
9191 omp_add_variable (gimplify_omp_ctxp
, decl
, GOVD_PRIVATE
| GOVD_SEEN
);
9193 /* If DECL is not a gimple register, create a temporary variable to act
9194 as an iteration counter. This is valid, since DECL cannot be
9195 modified in the body of the loop. Similarly for any iteration vars
9196 in simd with collapse > 1 where the iterator vars must be
9198 if (orig_for_stmt
!= for_stmt
)
9200 else if (!is_gimple_reg (decl
)
9202 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)) > 1))
9204 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
9205 /* Make sure omp_add_variable is not called on it prematurely.
9206 We call it ourselves a few lines later. */
9207 gimplify_omp_ctxp
= NULL
;
9208 var
= create_tmp_var (TREE_TYPE (decl
), get_name (decl
));
9209 gimplify_omp_ctxp
= ctx
;
9210 TREE_OPERAND (t
, 0) = var
;
9212 gimplify_seq_add_stmt (&for_body
, gimple_build_assign (decl
, var
));
9215 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)) == 1)
9217 c2
= build_omp_clause (input_location
, OMP_CLAUSE_LINEAR
);
9218 OMP_CLAUSE_LINEAR_NO_COPYIN (c2
) = 1;
9219 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2
) = 1;
9220 OMP_CLAUSE_DECL (c2
) = var
;
9221 OMP_CLAUSE_CHAIN (c2
) = OMP_FOR_CLAUSES (for_stmt
);
9222 OMP_FOR_CLAUSES (for_stmt
) = c2
;
9223 omp_add_variable (gimplify_omp_ctxp
, var
,
9224 GOVD_LINEAR
| GOVD_EXPLICIT
| GOVD_SEEN
);
9232 omp_add_variable (gimplify_omp_ctxp
, var
,
9233 GOVD_PRIVATE
| GOVD_SEEN
);
9238 tret
= gimplify_expr (&TREE_OPERAND (t
, 1), &for_pre_body
, NULL
,
9239 is_gimple_val
, fb_rvalue
, false);
9240 ret
= MIN (ret
, tret
);
9241 if (ret
== GS_ERROR
)
9244 /* Handle OMP_FOR_COND. */
9245 t
= TREE_VEC_ELT (OMP_FOR_COND (for_stmt
), i
);
9246 gcc_assert (COMPARISON_CLASS_P (t
));
9247 gcc_assert (TREE_OPERAND (t
, 0) == decl
);
9249 tret
= gimplify_expr (&TREE_OPERAND (t
, 1), &for_pre_body
, NULL
,
9250 is_gimple_val
, fb_rvalue
, false);
9251 ret
= MIN (ret
, tret
);
9253 /* Handle OMP_FOR_INCR. */
9254 t
= TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
);
9255 switch (TREE_CODE (t
))
9257 case PREINCREMENT_EXPR
:
9258 case POSTINCREMENT_EXPR
:
9260 tree decl
= TREE_OPERAND (t
, 0);
9261 /* c_omp_for_incr_canonicalize_ptr() should have been
9262 called to massage things appropriately. */
9263 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl
)));
9265 if (orig_for_stmt
!= for_stmt
)
9267 t
= build_int_cst (TREE_TYPE (decl
), 1);
9269 OMP_CLAUSE_LINEAR_STEP (c
) = t
;
9270 t
= build2 (PLUS_EXPR
, TREE_TYPE (decl
), var
, t
);
9271 t
= build2 (MODIFY_EXPR
, TREE_TYPE (var
), var
, t
);
9272 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
) = t
;
9276 case PREDECREMENT_EXPR
:
9277 case POSTDECREMENT_EXPR
:
9278 /* c_omp_for_incr_canonicalize_ptr() should have been
9279 called to massage things appropriately. */
9280 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl
)));
9281 if (orig_for_stmt
!= for_stmt
)
9283 t
= build_int_cst (TREE_TYPE (decl
), -1);
9285 OMP_CLAUSE_LINEAR_STEP (c
) = t
;
9286 t
= build2 (PLUS_EXPR
, TREE_TYPE (decl
), var
, t
);
9287 t
= build2 (MODIFY_EXPR
, TREE_TYPE (var
), var
, t
);
9288 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
) = t
;
9292 gcc_assert (TREE_OPERAND (t
, 0) == decl
);
9293 TREE_OPERAND (t
, 0) = var
;
9295 t
= TREE_OPERAND (t
, 1);
9296 switch (TREE_CODE (t
))
9299 if (TREE_OPERAND (t
, 1) == decl
)
9301 TREE_OPERAND (t
, 1) = TREE_OPERAND (t
, 0);
9302 TREE_OPERAND (t
, 0) = var
;
9308 case POINTER_PLUS_EXPR
:
9309 gcc_assert (TREE_OPERAND (t
, 0) == decl
);
9310 TREE_OPERAND (t
, 0) = var
;
9316 tret
= gimplify_expr (&TREE_OPERAND (t
, 1), &for_pre_body
, NULL
,
9317 is_gimple_val
, fb_rvalue
, false);
9318 ret
= MIN (ret
, tret
);
9321 tree step
= TREE_OPERAND (t
, 1);
9322 tree stept
= TREE_TYPE (decl
);
9323 if (POINTER_TYPE_P (stept
))
9325 step
= fold_convert (stept
, step
);
9326 if (TREE_CODE (t
) == MINUS_EXPR
)
9327 step
= fold_build1 (NEGATE_EXPR
, stept
, step
);
9328 OMP_CLAUSE_LINEAR_STEP (c
) = step
;
9329 if (step
!= TREE_OPERAND (t
, 1))
9331 tret
= gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c
),
9332 &for_pre_body
, NULL
,
9333 is_gimple_val
, fb_rvalue
, false);
9334 ret
= MIN (ret
, tret
);
9346 OMP_CLAUSE_LINEAR_STEP (c2
) = OMP_CLAUSE_LINEAR_STEP (c
);
9349 if ((var
!= decl
|| collapse
> 1) && orig_for_stmt
== for_stmt
)
9351 for (c
= OMP_FOR_CLAUSES (for_stmt
); c
; c
= OMP_CLAUSE_CHAIN (c
))
9352 if (((OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LASTPRIVATE
9353 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c
) == NULL
)
9354 || (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LINEAR
9355 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c
)
9356 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c
) == NULL
))
9357 && OMP_CLAUSE_DECL (c
) == decl
)
9359 if (is_doacross
&& (collapse
== 1 || i
>= collapse
))
9363 t
= TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
);
9364 gcc_assert (TREE_CODE (t
) == MODIFY_EXPR
);
9365 gcc_assert (TREE_OPERAND (t
, 0) == var
);
9366 t
= TREE_OPERAND (t
, 1);
9367 gcc_assert (TREE_CODE (t
) == PLUS_EXPR
9368 || TREE_CODE (t
) == MINUS_EXPR
9369 || TREE_CODE (t
) == POINTER_PLUS_EXPR
);
9370 gcc_assert (TREE_OPERAND (t
, 0) == var
);
9371 t
= build2 (TREE_CODE (t
), TREE_TYPE (decl
),
9372 is_doacross
? var
: decl
,
9373 TREE_OPERAND (t
, 1));
9376 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_LASTPRIVATE
)
9377 seq
= &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c
);
9379 seq
= &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c
);
9380 gimplify_assign (decl
, t
, seq
);
9385 BITMAP_FREE (has_decl_expr
);
9387 if (TREE_CODE (orig_for_stmt
) == OMP_TASKLOOP
)
9389 push_gimplify_context ();
9390 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt
)) != BIND_EXPR
)
9392 OMP_FOR_BODY (orig_for_stmt
)
9393 = build3 (BIND_EXPR
, void_type_node
, NULL
,
9394 OMP_FOR_BODY (orig_for_stmt
), NULL
);
9395 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt
)) = 1;
9399 gimple
*g
= gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt
),
9402 if (TREE_CODE (orig_for_stmt
) == OMP_TASKLOOP
)
9404 if (gimple_code (g
) == GIMPLE_BIND
)
9405 pop_gimplify_context (g
);
9407 pop_gimplify_context (NULL
);
9410 if (orig_for_stmt
!= for_stmt
)
9411 for (i
= 0; i
< TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)); i
++)
9413 t
= TREE_VEC_ELT (OMP_FOR_INIT (for_stmt
), i
);
9414 decl
= TREE_OPERAND (t
, 0);
9415 struct gimplify_omp_ctx
*ctx
= gimplify_omp_ctxp
;
9416 if (TREE_CODE (orig_for_stmt
) == OMP_TASKLOOP
)
9417 gimplify_omp_ctxp
= ctx
->outer_context
;
9418 var
= create_tmp_var (TREE_TYPE (decl
), get_name (decl
));
9419 gimplify_omp_ctxp
= ctx
;
9420 omp_add_variable (gimplify_omp_ctxp
, var
, GOVD_PRIVATE
| GOVD_SEEN
);
9421 TREE_OPERAND (t
, 0) = var
;
9422 t
= TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
);
9423 TREE_OPERAND (t
, 1) = copy_node (TREE_OPERAND (t
, 1));
9424 TREE_OPERAND (TREE_OPERAND (t
, 1), 0) = var
;
9427 gimplify_adjust_omp_clauses (pre_p
, for_body
,
9428 &OMP_FOR_CLAUSES (orig_for_stmt
),
9429 TREE_CODE (orig_for_stmt
));
9432 switch (TREE_CODE (orig_for_stmt
))
9434 case OMP_FOR
: kind
= GF_OMP_FOR_KIND_FOR
; break;
9435 case OMP_SIMD
: kind
= GF_OMP_FOR_KIND_SIMD
; break;
9436 case CILK_SIMD
: kind
= GF_OMP_FOR_KIND_CILKSIMD
; break;
9437 case CILK_FOR
: kind
= GF_OMP_FOR_KIND_CILKFOR
; break;
9438 case OMP_DISTRIBUTE
: kind
= GF_OMP_FOR_KIND_DISTRIBUTE
; break;
9439 case OMP_TASKLOOP
: kind
= GF_OMP_FOR_KIND_TASKLOOP
; break;
9440 case OACC_LOOP
: kind
= GF_OMP_FOR_KIND_OACC_LOOP
; break;
9444 gfor
= gimple_build_omp_for (for_body
, kind
, OMP_FOR_CLAUSES (orig_for_stmt
),
9445 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)),
9447 if (orig_for_stmt
!= for_stmt
)
9448 gimple_omp_for_set_combined_p (gfor
, true);
9449 if (gimplify_omp_ctxp
9450 && (gimplify_omp_ctxp
->combined_loop
9451 || (gimplify_omp_ctxp
->region_type
== ORT_COMBINED_PARALLEL
9452 && gimplify_omp_ctxp
->outer_context
9453 && gimplify_omp_ctxp
->outer_context
->combined_loop
)))
9455 gimple_omp_for_set_combined_into_p (gfor
, true);
9456 if (gimplify_omp_ctxp
->combined_loop
)
9457 gcc_assert (TREE_CODE (orig_for_stmt
) == OMP_SIMD
);
9459 gcc_assert (TREE_CODE (orig_for_stmt
) == OMP_FOR
);
9462 for (i
= 0; i
< TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt
)); i
++)
9464 t
= TREE_VEC_ELT (OMP_FOR_INIT (for_stmt
), i
);
9465 gimple_omp_for_set_index (gfor
, i
, TREE_OPERAND (t
, 0));
9466 gimple_omp_for_set_initial (gfor
, i
, TREE_OPERAND (t
, 1));
9467 t
= TREE_VEC_ELT (OMP_FOR_COND (for_stmt
), i
);
9468 gimple_omp_for_set_cond (gfor
, i
, TREE_CODE (t
));
9469 gimple_omp_for_set_final (gfor
, i
, TREE_OPERAND (t
, 1));
9470 t
= TREE_VEC_ELT (OMP_FOR_INCR (for_stmt
), i
);
9471 gimple_omp_for_set_incr (gfor
, i
, TREE_OPERAND (t
, 1));
9474 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
9475 constructs with GIMPLE_OMP_TASK sandwiched in between them.
9476 The outer taskloop stands for computing the number of iterations,
9477 counts for collapsed loops and holding taskloop specific clauses.
9478 The task construct stands for the effect of data sharing on the
9479 explicit task it creates and the inner taskloop stands for expansion
9480 of the static loop inside of the explicit task construct. */
9481 if (TREE_CODE (orig_for_stmt
) == OMP_TASKLOOP
)
9483 tree
*gfor_clauses_ptr
= gimple_omp_for_clauses_ptr (gfor
);
9484 tree task_clauses
= NULL_TREE
;
9485 tree c
= *gfor_clauses_ptr
;
9486 tree
*gtask_clauses_ptr
= &task_clauses
;
9487 tree outer_for_clauses
= NULL_TREE
;
9488 tree
*gforo_clauses_ptr
= &outer_for_clauses
;
9489 for (; c
; c
= OMP_CLAUSE_CHAIN (c
))
9490 switch (OMP_CLAUSE_CODE (c
))
9492 /* These clauses are allowed on task, move them there. */
9493 case OMP_CLAUSE_SHARED
:
9494 case OMP_CLAUSE_FIRSTPRIVATE
:
9495 case OMP_CLAUSE_DEFAULT
:
9497 case OMP_CLAUSE_UNTIED
:
9498 case OMP_CLAUSE_FINAL
:
9499 case OMP_CLAUSE_MERGEABLE
:
9500 case OMP_CLAUSE_PRIORITY
:
9501 *gtask_clauses_ptr
= c
;
9502 gtask_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9504 case OMP_CLAUSE_PRIVATE
:
9505 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c
))
9507 /* We want private on outer for and firstprivate
9510 = build_omp_clause (OMP_CLAUSE_LOCATION (c
),
9511 OMP_CLAUSE_FIRSTPRIVATE
);
9512 OMP_CLAUSE_DECL (*gtask_clauses_ptr
) = OMP_CLAUSE_DECL (c
);
9513 lang_hooks
.decls
.omp_finish_clause (*gtask_clauses_ptr
, NULL
);
9514 gtask_clauses_ptr
= &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr
);
9515 *gforo_clauses_ptr
= c
;
9516 gforo_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9520 *gtask_clauses_ptr
= c
;
9521 gtask_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9524 /* These clauses go into outer taskloop clauses. */
9525 case OMP_CLAUSE_GRAINSIZE
:
9526 case OMP_CLAUSE_NUM_TASKS
:
9527 case OMP_CLAUSE_NOGROUP
:
9528 *gforo_clauses_ptr
= c
;
9529 gforo_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9531 /* Taskloop clause we duplicate on both taskloops. */
9532 case OMP_CLAUSE_COLLAPSE
:
9533 *gfor_clauses_ptr
= c
;
9534 gfor_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9535 *gforo_clauses_ptr
= copy_node (c
);
9536 gforo_clauses_ptr
= &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr
);
9538 /* For lastprivate, keep the clause on inner taskloop, and add
9539 a shared clause on task. If the same decl is also firstprivate,
9540 add also firstprivate clause on the inner taskloop. */
9541 case OMP_CLAUSE_LASTPRIVATE
:
9542 if (OMP_CLAUSE_LASTPRIVATE_TASKLOOP_IV (c
))
9544 /* For taskloop C++ lastprivate IVs, we want:
9545 1) private on outer taskloop
9546 2) firstprivate and shared on task
9547 3) lastprivate on inner taskloop */
9549 = build_omp_clause (OMP_CLAUSE_LOCATION (c
),
9550 OMP_CLAUSE_FIRSTPRIVATE
);
9551 OMP_CLAUSE_DECL (*gtask_clauses_ptr
) = OMP_CLAUSE_DECL (c
);
9552 lang_hooks
.decls
.omp_finish_clause (*gtask_clauses_ptr
, NULL
);
9553 gtask_clauses_ptr
= &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr
);
9554 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c
) = 1;
9555 *gforo_clauses_ptr
= build_omp_clause (OMP_CLAUSE_LOCATION (c
),
9556 OMP_CLAUSE_PRIVATE
);
9557 OMP_CLAUSE_DECL (*gforo_clauses_ptr
) = OMP_CLAUSE_DECL (c
);
9558 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr
) = 1;
9559 TREE_TYPE (*gforo_clauses_ptr
) = TREE_TYPE (c
);
9560 gforo_clauses_ptr
= &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr
);
9562 *gfor_clauses_ptr
= c
;
9563 gfor_clauses_ptr
= &OMP_CLAUSE_CHAIN (c
);
9565 = build_omp_clause (OMP_CLAUSE_LOCATION (c
), OMP_CLAUSE_SHARED
);
9566 OMP_CLAUSE_DECL (*gtask_clauses_ptr
) = OMP_CLAUSE_DECL (c
);
9567 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c
))
9568 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr
) = 1;
9570 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr
);
9575 *gfor_clauses_ptr
= NULL_TREE
;
9576 *gtask_clauses_ptr
= NULL_TREE
;
9577 *gforo_clauses_ptr
= NULL_TREE
;
9578 g
= gimple_build_bind (NULL_TREE
, gfor
, NULL_TREE
);
9579 g
= gimple_build_omp_task (g
, task_clauses
, NULL_TREE
, NULL_TREE
,
9580 NULL_TREE
, NULL_TREE
, NULL_TREE
);
9581 gimple_omp_task_set_taskloop_p (g
, true);
9582 g
= gimple_build_bind (NULL_TREE
, g
, NULL_TREE
);
9584 = gimple_build_omp_for (g
, GF_OMP_FOR_KIND_TASKLOOP
, outer_for_clauses
,
9585 gimple_omp_for_collapse (gfor
),
9586 gimple_omp_for_pre_body (gfor
));
9587 gimple_omp_for_set_pre_body (gfor
, NULL
);
9588 gimple_omp_for_set_combined_p (gforo
, true);
9589 gimple_omp_for_set_combined_into_p (gfor
, true);
9590 for (i
= 0; i
< (int) gimple_omp_for_collapse (gfor
); i
++)
9592 t
= unshare_expr (gimple_omp_for_index (gfor
, i
));
9593 gimple_omp_for_set_index (gforo
, i
, t
);
9594 t
= unshare_expr (gimple_omp_for_initial (gfor
, i
));
9595 gimple_omp_for_set_initial (gforo
, i
, t
);
9596 gimple_omp_for_set_cond (gforo
, i
,
9597 gimple_omp_for_cond (gfor
, i
));
9598 t
= unshare_expr (gimple_omp_for_final (gfor
, i
));
9599 gimple_omp_for_set_final (gforo
, i
, t
);
9600 t
= unshare_expr (gimple_omp_for_incr (gfor
, i
));
9601 gimple_omp_for_set_incr (gforo
, i
, t
);
9603 gimplify_seq_add_stmt (pre_p
, gforo
);
9606 gimplify_seq_add_stmt (pre_p
, gfor
);
9607 if (ret
!= GS_ALL_DONE
)
9609 *expr_p
= NULL_TREE
;
9613 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
9614 of OMP_TARGET's body. */
9617 find_omp_teams (tree
*tp
, int *walk_subtrees
, void *)
9620 switch (TREE_CODE (*tp
))
9625 case STATEMENT_LIST
:
9634 /* Helper function of optimize_target_teams, determine if the expression
9635 can be computed safely before the target construct on the host. */
9638 computable_teams_clause (tree
*tp
, int *walk_subtrees
, void *)
9647 switch (TREE_CODE (*tp
))
9653 if (error_operand_p (*tp
)
9654 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp
))
9655 || DECL_HAS_VALUE_EXPR_P (*tp
)
9656 || DECL_THREAD_LOCAL_P (*tp
)
9657 || TREE_SIDE_EFFECTS (*tp
)
9658 || TREE_THIS_VOLATILE (*tp
))
9660 if (is_global_var (*tp
)
9661 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp
))
9662 || lookup_attribute ("omp declare target link",
9663 DECL_ATTRIBUTES (*tp
))))
9665 n
= splay_tree_lookup (gimplify_omp_ctxp
->variables
,
9666 (splay_tree_key
) *tp
);
9669 if (gimplify_omp_ctxp
->target_map_scalars_firstprivate
)
9673 else if (n
->value
& GOVD_LOCAL
)
9675 else if (n
->value
& GOVD_FIRSTPRIVATE
)
9677 else if ((n
->value
& (GOVD_MAP
| GOVD_MAP_ALWAYS_TO
))
9678 == (GOVD_MAP
| GOVD_MAP_ALWAYS_TO
))
9682 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp
)))
9686 if (TARGET_EXPR_INITIAL (*tp
)
9687 || TREE_CODE (TARGET_EXPR_SLOT (*tp
)) != VAR_DECL
)
9689 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp
),
9690 walk_subtrees
, NULL
);
9691 /* Allow some reasonable subset of integral arithmetics. */
9695 case TRUNC_DIV_EXPR
:
9697 case FLOOR_DIV_EXPR
:
9698 case ROUND_DIV_EXPR
:
9699 case TRUNC_MOD_EXPR
:
9701 case FLOOR_MOD_EXPR
:
9702 case ROUND_MOD_EXPR
:
9704 case EXACT_DIV_EXPR
:
9715 case NON_LVALUE_EXPR
:
9717 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp
)))
9720 /* And disallow anything else, except for comparisons. */
9722 if (COMPARISON_CLASS_P (*tp
))
9728 /* Try to determine if the num_teams and/or thread_limit expressions
9729 can have their values determined already before entering the
9731 INTEGER_CSTs trivially are,
9732 integral decls that are firstprivate (explicitly or implicitly)
9733 or explicitly map(always, to:) or map(always, tofrom:) on the target
9734 region too, and expressions involving simple arithmetics on those
9735 too, function calls are not ok, dereferencing something neither etc.
9736 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
9737 EXPR based on what we find:
9738 0 stands for clause not specified at all, use implementation default
9739 -1 stands for value that can't be determined easily before entering
9740 the target construct.
9741 If teams construct is not present at all, use 1 for num_teams
9742 and 0 for thread_limit (only one team is involved, and the thread
9743 limit is implementation defined. */
9746 optimize_target_teams (tree target
, gimple_seq
*pre_p
)
9748 tree body
= OMP_BODY (target
);
9749 tree teams
= walk_tree (&body
, find_omp_teams
, NULL
, NULL
);
9750 tree num_teams
= integer_zero_node
;
9751 tree thread_limit
= integer_zero_node
;
9752 location_t num_teams_loc
= EXPR_LOCATION (target
);
9753 location_t thread_limit_loc
= EXPR_LOCATION (target
);
9755 struct gimplify_omp_ctx
*target_ctx
= gimplify_omp_ctxp
;
9757 if (teams
== NULL_TREE
)
9758 num_teams
= integer_one_node
;
9760 for (c
= OMP_TEAMS_CLAUSES (teams
); c
; c
= OMP_CLAUSE_CHAIN (c
))
9762 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_NUM_TEAMS
)
9765 num_teams_loc
= OMP_CLAUSE_LOCATION (c
);
9767 else if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_THREAD_LIMIT
)
9770 thread_limit_loc
= OMP_CLAUSE_LOCATION (c
);
9774 expr
= OMP_CLAUSE_OPERAND (c
, 0);
9775 if (TREE_CODE (expr
) == INTEGER_CST
)
9780 if (walk_tree (&expr
, computable_teams_clause
, NULL
, NULL
))
9782 *p
= integer_minus_one_node
;
9786 gimplify_omp_ctxp
= gimplify_omp_ctxp
->outer_context
;
9787 if (gimplify_expr (p
, pre_p
, NULL
, is_gimple_val
, fb_rvalue
, false)
9790 gimplify_omp_ctxp
= target_ctx
;
9791 *p
= integer_minus_one_node
;
9794 gimplify_omp_ctxp
= target_ctx
;
9795 if (!DECL_P (expr
) && TREE_CODE (expr
) != TARGET_EXPR
)
9796 OMP_CLAUSE_OPERAND (c
, 0) = *p
;
9798 c
= build_omp_clause (thread_limit_loc
, OMP_CLAUSE_THREAD_LIMIT
);
9799 OMP_CLAUSE_THREAD_LIMIT_EXPR (c
) = thread_limit
;
9800 OMP_CLAUSE_CHAIN (c
) = OMP_TARGET_CLAUSES (target
);
9801 OMP_TARGET_CLAUSES (target
) = c
;
9802 c
= build_omp_clause (num_teams_loc
, OMP_CLAUSE_NUM_TEAMS
);
9803 OMP_CLAUSE_NUM_TEAMS_EXPR (c
) = num_teams
;
9804 OMP_CLAUSE_CHAIN (c
) = OMP_TARGET_CLAUSES (target
);
9805 OMP_TARGET_CLAUSES (target
) = c
;
9808 /* Gimplify the gross structure of several OMP constructs. */
9811 gimplify_omp_workshare (tree
*expr_p
, gimple_seq
*pre_p
)
9813 tree expr
= *expr_p
;
9815 gimple_seq body
= NULL
;
9816 enum omp_region_type ort
;
9818 switch (TREE_CODE (expr
))
9822 ort
= ORT_WORKSHARE
;
9825 ort
= OMP_TARGET_COMBINED (expr
) ? ORT_COMBINED_TARGET
: ORT_TARGET
;
9828 ort
= ORT_ACC_KERNELS
;
9831 ort
= ORT_ACC_PARALLEL
;
9836 case OMP_TARGET_DATA
:
9837 ort
= ORT_TARGET_DATA
;
9840 ort
= OMP_TEAMS_COMBINED (expr
) ? ORT_COMBINED_TEAMS
: ORT_TEAMS
;
9842 case OACC_HOST_DATA
:
9843 ort
= ORT_ACC_HOST_DATA
;
9848 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr
), pre_p
, ort
,
9850 if (TREE_CODE (expr
) == OMP_TARGET
)
9851 optimize_target_teams (expr
, pre_p
);
9852 if ((ort
& (ORT_TARGET
| ORT_TARGET_DATA
)) != 0)
9854 push_gimplify_context ();
9855 gimple
*g
= gimplify_and_return_first (OMP_BODY (expr
), &body
);
9856 if (gimple_code (g
) == GIMPLE_BIND
)
9857 pop_gimplify_context (g
);
9859 pop_gimplify_context (NULL
);
9860 if ((ort
& ORT_TARGET_DATA
) != 0)
9862 enum built_in_function end_ix
;
9863 switch (TREE_CODE (expr
))
9866 case OACC_HOST_DATA
:
9867 end_ix
= BUILT_IN_GOACC_DATA_END
;
9869 case OMP_TARGET_DATA
:
9870 end_ix
= BUILT_IN_GOMP_TARGET_END_DATA
;
9875 tree fn
= builtin_decl_explicit (end_ix
);
9876 g
= gimple_build_call (fn
, 0);
9877 gimple_seq cleanup
= NULL
;
9878 gimple_seq_add_stmt (&cleanup
, g
);
9879 g
= gimple_build_try (body
, cleanup
, GIMPLE_TRY_FINALLY
);
9881 gimple_seq_add_stmt (&body
, g
);
9885 gimplify_and_add (OMP_BODY (expr
), &body
);
9886 gimplify_adjust_omp_clauses (pre_p
, body
, &OMP_CLAUSES (expr
),
9889 switch (TREE_CODE (expr
))
9892 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_OACC_DATA
,
9893 OMP_CLAUSES (expr
));
9896 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_OACC_KERNELS
,
9897 OMP_CLAUSES (expr
));
9899 case OACC_HOST_DATA
:
9900 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_OACC_HOST_DATA
,
9901 OMP_CLAUSES (expr
));
9904 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_OACC_PARALLEL
,
9905 OMP_CLAUSES (expr
));
9908 stmt
= gimple_build_omp_sections (body
, OMP_CLAUSES (expr
));
9911 stmt
= gimple_build_omp_single (body
, OMP_CLAUSES (expr
));
9914 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_REGION
,
9915 OMP_CLAUSES (expr
));
9917 case OMP_TARGET_DATA
:
9918 stmt
= gimple_build_omp_target (body
, GF_OMP_TARGET_KIND_DATA
,
9919 OMP_CLAUSES (expr
));
9922 stmt
= gimple_build_omp_teams (body
, OMP_CLAUSES (expr
));
9928 gimplify_seq_add_stmt (pre_p
, stmt
);
9929 *expr_p
= NULL_TREE
;
9932 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
9933 target update constructs. */
9936 gimplify_omp_target_update (tree
*expr_p
, gimple_seq
*pre_p
)
9938 tree expr
= *expr_p
;
9941 enum omp_region_type ort
= ORT_WORKSHARE
;
9943 switch (TREE_CODE (expr
))
9945 case OACC_ENTER_DATA
:
9946 case OACC_EXIT_DATA
:
9947 kind
= GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA
;
9951 kind
= GF_OMP_TARGET_KIND_OACC_UPDATE
;
9954 case OMP_TARGET_UPDATE
:
9955 kind
= GF_OMP_TARGET_KIND_UPDATE
;
9957 case OMP_TARGET_ENTER_DATA
:
9958 kind
= GF_OMP_TARGET_KIND_ENTER_DATA
;
9960 case OMP_TARGET_EXIT_DATA
:
9961 kind
= GF_OMP_TARGET_KIND_EXIT_DATA
;
9966 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr
), pre_p
,
9967 ort
, TREE_CODE (expr
));
9968 gimplify_adjust_omp_clauses (pre_p
, NULL
, &OMP_STANDALONE_CLAUSES (expr
),
9970 stmt
= gimple_build_omp_target (NULL
, kind
, OMP_STANDALONE_CLAUSES (expr
));
9972 gimplify_seq_add_stmt (pre_p
, stmt
);
9973 *expr_p
= NULL_TREE
;
9976 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
9977 stabilized the lhs of the atomic operation as *ADDR. Return true if
9978 EXPR is this stabilized form. */
9981 goa_lhs_expr_p (tree expr
, tree addr
)
9983 /* Also include casts to other type variants. The C front end is fond
9984 of adding these for e.g. volatile variables. This is like
9985 STRIP_TYPE_NOPS but includes the main variant lookup. */
9986 STRIP_USELESS_TYPE_CONVERSION (expr
);
9988 if (TREE_CODE (expr
) == INDIRECT_REF
)
9990 expr
= TREE_OPERAND (expr
, 0);
9992 && (CONVERT_EXPR_P (expr
)
9993 || TREE_CODE (expr
) == NON_LVALUE_EXPR
)
9994 && TREE_CODE (expr
) == TREE_CODE (addr
)
9995 && types_compatible_p (TREE_TYPE (expr
), TREE_TYPE (addr
)))
9997 expr
= TREE_OPERAND (expr
, 0);
9998 addr
= TREE_OPERAND (addr
, 0);
10002 return (TREE_CODE (addr
) == ADDR_EXPR
10003 && TREE_CODE (expr
) == ADDR_EXPR
10004 && TREE_OPERAND (addr
, 0) == TREE_OPERAND (expr
, 0));
10006 if (TREE_CODE (addr
) == ADDR_EXPR
&& expr
== TREE_OPERAND (addr
, 0))
10011 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
10012 expression does not involve the lhs, evaluate it into a temporary.
10013 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
10014 or -1 if an error was encountered. */
10017 goa_stabilize_expr (tree
*expr_p
, gimple_seq
*pre_p
, tree lhs_addr
,
10020 tree expr
= *expr_p
;
10023 if (goa_lhs_expr_p (expr
, lhs_addr
))
10028 if (is_gimple_val (expr
))
10032 switch (TREE_CODE_CLASS (TREE_CODE (expr
)))
10035 case tcc_comparison
:
10036 saw_lhs
|= goa_stabilize_expr (&TREE_OPERAND (expr
, 1), pre_p
, lhs_addr
,
10040 saw_lhs
|= goa_stabilize_expr (&TREE_OPERAND (expr
, 0), pre_p
, lhs_addr
,
10043 case tcc_expression
:
10044 switch (TREE_CODE (expr
))
10046 case TRUTH_ANDIF_EXPR
:
10047 case TRUTH_ORIF_EXPR
:
10048 case TRUTH_AND_EXPR
:
10049 case TRUTH_OR_EXPR
:
10050 case TRUTH_XOR_EXPR
:
10051 saw_lhs
|= goa_stabilize_expr (&TREE_OPERAND (expr
, 1), pre_p
,
10052 lhs_addr
, lhs_var
);
10054 case TRUTH_NOT_EXPR
:
10055 saw_lhs
|= goa_stabilize_expr (&TREE_OPERAND (expr
, 0), pre_p
,
10056 lhs_addr
, lhs_var
);
10058 case COMPOUND_EXPR
:
10059 /* Break out any preevaluations from cp_build_modify_expr. */
10060 for (; TREE_CODE (expr
) == COMPOUND_EXPR
;
10061 expr
= TREE_OPERAND (expr
, 1))
10062 gimplify_stmt (&TREE_OPERAND (expr
, 0), pre_p
);
10064 return goa_stabilize_expr (expr_p
, pre_p
, lhs_addr
, lhs_var
);
10075 enum gimplify_status gs
;
10076 gs
= gimplify_expr (expr_p
, pre_p
, NULL
, is_gimple_val
, fb_rvalue
);
10077 if (gs
!= GS_ALL_DONE
)
10084 /* Gimplify an OMP_ATOMIC statement. */
10086 static enum gimplify_status
10087 gimplify_omp_atomic (tree
*expr_p
, gimple_seq
*pre_p
)
10089 tree addr
= TREE_OPERAND (*expr_p
, 0);
10090 tree rhs
= TREE_CODE (*expr_p
) == OMP_ATOMIC_READ
10091 ? NULL
: TREE_OPERAND (*expr_p
, 1);
10092 tree type
= TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr
)));
10094 gomp_atomic_load
*loadstmt
;
10095 gomp_atomic_store
*storestmt
;
10097 tmp_load
= create_tmp_reg (type
);
10098 if (rhs
&& goa_stabilize_expr (&rhs
, pre_p
, addr
, tmp_load
) < 0)
10101 if (gimplify_expr (&addr
, pre_p
, NULL
, is_gimple_val
, fb_rvalue
)
10105 loadstmt
= gimple_build_omp_atomic_load (tmp_load
, addr
);
10106 gimplify_seq_add_stmt (pre_p
, loadstmt
);
10107 if (rhs
&& gimplify_expr (&rhs
, pre_p
, NULL
, is_gimple_val
, fb_rvalue
)
10111 if (TREE_CODE (*expr_p
) == OMP_ATOMIC_READ
)
10113 storestmt
= gimple_build_omp_atomic_store (rhs
);
10114 gimplify_seq_add_stmt (pre_p
, storestmt
);
10115 if (OMP_ATOMIC_SEQ_CST (*expr_p
))
10117 gimple_omp_atomic_set_seq_cst (loadstmt
);
10118 gimple_omp_atomic_set_seq_cst (storestmt
);
10120 switch (TREE_CODE (*expr_p
))
10122 case OMP_ATOMIC_READ
:
10123 case OMP_ATOMIC_CAPTURE_OLD
:
10124 *expr_p
= tmp_load
;
10125 gimple_omp_atomic_set_need_value (loadstmt
);
10127 case OMP_ATOMIC_CAPTURE_NEW
:
10129 gimple_omp_atomic_set_need_value (storestmt
);
10136 return GS_ALL_DONE
;
10139 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
10140 body, and adding some EH bits. */
10142 static enum gimplify_status
10143 gimplify_transaction (tree
*expr_p
, gimple_seq
*pre_p
)
10145 tree expr
= *expr_p
, temp
, tbody
= TRANSACTION_EXPR_BODY (expr
);
10147 gtransaction
*trans_stmt
;
10148 gimple_seq body
= NULL
;
10151 /* Wrap the transaction body in a BIND_EXPR so we have a context
10152 where to put decls for OMP. */
10153 if (TREE_CODE (tbody
) != BIND_EXPR
)
10155 tree bind
= build3 (BIND_EXPR
, void_type_node
, NULL
, tbody
, NULL
);
10156 TREE_SIDE_EFFECTS (bind
) = 1;
10157 SET_EXPR_LOCATION (bind
, EXPR_LOCATION (tbody
));
10158 TRANSACTION_EXPR_BODY (expr
) = bind
;
10161 push_gimplify_context ();
10162 temp
= voidify_wrapper_expr (*expr_p
, NULL
);
10164 body_stmt
= gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr
), &body
);
10165 pop_gimplify_context (body_stmt
);
10167 trans_stmt
= gimple_build_transaction (body
);
10168 if (TRANSACTION_EXPR_OUTER (expr
))
10169 subcode
= GTMA_IS_OUTER
;
10170 else if (TRANSACTION_EXPR_RELAXED (expr
))
10171 subcode
= GTMA_IS_RELAXED
;
10172 gimple_transaction_set_subcode (trans_stmt
, subcode
);
10174 gimplify_seq_add_stmt (pre_p
, trans_stmt
);
10182 *expr_p
= NULL_TREE
;
10183 return GS_ALL_DONE
;
10186 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
10187 is the OMP_BODY of the original EXPR (which has already been
10188 gimplified so it's not present in the EXPR).
10190 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
10193 gimplify_omp_ordered (tree expr
, gimple_seq body
)
10198 tree source_c
= NULL_TREE
;
10199 tree sink_c
= NULL_TREE
;
10201 if (gimplify_omp_ctxp
)
10203 for (c
= OMP_ORDERED_CLAUSES (expr
); c
; c
= OMP_CLAUSE_CHAIN (c
))
10204 if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_DEPEND
10205 && gimplify_omp_ctxp
->loop_iter_var
.is_empty ()
10206 && (OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SINK
10207 || OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SOURCE
))
10209 error_at (OMP_CLAUSE_LOCATION (c
),
10210 "%<ordered%> construct with %<depend%> clause must be "
10211 "closely nested inside a loop with %<ordered%> clause "
10212 "with a parameter");
10215 else if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_DEPEND
10216 && OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SINK
)
10219 for (decls
= OMP_CLAUSE_DECL (c
), i
= 0;
10220 decls
&& TREE_CODE (decls
) == TREE_LIST
;
10221 decls
= TREE_CHAIN (decls
), ++i
)
10222 if (i
>= gimplify_omp_ctxp
->loop_iter_var
.length () / 2)
10224 else if (TREE_VALUE (decls
)
10225 != gimplify_omp_ctxp
->loop_iter_var
[2 * i
])
10227 error_at (OMP_CLAUSE_LOCATION (c
),
10228 "variable %qE is not an iteration "
10229 "of outermost loop %d, expected %qE",
10230 TREE_VALUE (decls
), i
+ 1,
10231 gimplify_omp_ctxp
->loop_iter_var
[2 * i
]);
10237 = gimplify_omp_ctxp
->loop_iter_var
[2 * i
+ 1];
10238 if (!fail
&& i
!= gimplify_omp_ctxp
->loop_iter_var
.length () / 2)
10240 error_at (OMP_CLAUSE_LOCATION (c
),
10241 "number of variables in %<depend(sink)%> "
10242 "clause does not match number of "
10243 "iteration variables");
10248 else if (OMP_CLAUSE_CODE (c
) == OMP_CLAUSE_DEPEND
10249 && OMP_CLAUSE_DEPEND_KIND (c
) == OMP_CLAUSE_DEPEND_SOURCE
)
10253 error_at (OMP_CLAUSE_LOCATION (c
),
10254 "more than one %<depend(source)%> clause on an "
10255 "%<ordered%> construct");
10262 if (source_c
&& sink_c
)
10264 error_at (OMP_CLAUSE_LOCATION (source_c
),
10265 "%<depend(source)%> clause specified together with "
10266 "%<depend(sink:)%> clauses on the same construct");
10271 return gimple_build_nop ();
10272 return gimple_build_omp_ordered (body
, OMP_ORDERED_CLAUSES (expr
));
10275 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
10276 expression produces a value to be used as an operand inside a GIMPLE
10277 statement, the value will be stored back in *EXPR_P. This value will
10278 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
10279 an SSA_NAME. The corresponding sequence of GIMPLE statements is
10280 emitted in PRE_P and POST_P.
10282 Additionally, this process may overwrite parts of the input
10283 expression during gimplification. Ideally, it should be
10284 possible to do non-destructive gimplification.
10286 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
10287 the expression needs to evaluate to a value to be used as
10288 an operand in a GIMPLE statement, this value will be stored in
10289 *EXPR_P on exit. This happens when the caller specifies one
10290 of fb_lvalue or fb_rvalue fallback flags.
10292 PRE_P will contain the sequence of GIMPLE statements corresponding
10293 to the evaluation of EXPR and all the side-effects that must
10294 be executed before the main expression. On exit, the last
10295 statement of PRE_P is the core statement being gimplified. For
10296 instance, when gimplifying 'if (++a)' the last statement in
10297 PRE_P will be 'if (t.1)' where t.1 is the result of
10298 pre-incrementing 'a'.
10300 POST_P will contain the sequence of GIMPLE statements corresponding
10301 to the evaluation of all the side-effects that must be executed
10302 after the main expression. If this is NULL, the post
10303 side-effects are stored at the end of PRE_P.
10305 The reason why the output is split in two is to handle post
10306 side-effects explicitly. In some cases, an expression may have
10307 inner and outer post side-effects which need to be emitted in
10308 an order different from the one given by the recursive
10309 traversal. For instance, for the expression (*p--)++ the post
10310 side-effects of '--' must actually occur *after* the post
10311 side-effects of '++'. However, gimplification will first visit
10312 the inner expression, so if a separate POST sequence was not
10313 used, the resulting sequence would be:
10320 However, the post-decrement operation in line #2 must not be
10321 evaluated until after the store to *p at line #4, so the
10322 correct sequence should be:
10329 So, by specifying a separate post queue, it is possible
10330 to emit the post side-effects in the correct order.
10331 If POST_P is NULL, an internal queue will be used. Before
10332 returning to the caller, the sequence POST_P is appended to
10333 the main output sequence PRE_P.
10335 GIMPLE_TEST_F points to a function that takes a tree T and
10336 returns nonzero if T is in the GIMPLE form requested by the
10337 caller. The GIMPLE predicates are in gimple.c.
10339 FALLBACK tells the function what sort of a temporary we want if
10340 gimplification cannot produce an expression that complies with
10343 fb_none means that no temporary should be generated
10344 fb_rvalue means that an rvalue is OK to generate
10345 fb_lvalue means that an lvalue is OK to generate
10346 fb_either means that either is OK, but an lvalue is preferable.
10347 fb_mayfail means that gimplification may fail (in which case
10348 GS_ERROR will be returned)
10350 The return value is either GS_ERROR or GS_ALL_DONE, since this
10351 function iterates until EXPR is completely gimplified or an error
10354 enum gimplify_status
10355 gimplify_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
10356 bool (*gimple_test_f
) (tree
), fallback_t fallback
)
10359 gimple_seq internal_pre
= NULL
;
10360 gimple_seq internal_post
= NULL
;
10363 location_t saved_location
;
10364 enum gimplify_status ret
;
10365 gimple_stmt_iterator pre_last_gsi
, post_last_gsi
;
10367 save_expr
= *expr_p
;
10368 if (save_expr
== NULL_TREE
)
10369 return GS_ALL_DONE
;
10371 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
10372 is_statement
= gimple_test_f
== is_gimple_stmt
;
10374 gcc_assert (pre_p
);
10376 /* Consistency checks. */
10377 if (gimple_test_f
== is_gimple_reg
)
10378 gcc_assert (fallback
& (fb_rvalue
| fb_lvalue
));
10379 else if (gimple_test_f
== is_gimple_val
10380 || gimple_test_f
== is_gimple_call_addr
10381 || gimple_test_f
== is_gimple_condexpr
10382 || gimple_test_f
== is_gimple_mem_rhs
10383 || gimple_test_f
== is_gimple_mem_rhs_or_call
10384 || gimple_test_f
== is_gimple_reg_rhs
10385 || gimple_test_f
== is_gimple_reg_rhs_or_call
10386 || gimple_test_f
== is_gimple_asm_val
10387 || gimple_test_f
== is_gimple_mem_ref_addr
)
10388 gcc_assert (fallback
& fb_rvalue
);
10389 else if (gimple_test_f
== is_gimple_min_lval
10390 || gimple_test_f
== is_gimple_lvalue
)
10391 gcc_assert (fallback
& fb_lvalue
);
10392 else if (gimple_test_f
== is_gimple_addressable
)
10393 gcc_assert (fallback
& fb_either
);
10394 else if (gimple_test_f
== is_gimple_stmt
)
10395 gcc_assert (fallback
== fb_none
);
10398 /* We should have recognized the GIMPLE_TEST_F predicate to
10399 know what kind of fallback to use in case a temporary is
10400 needed to hold the value or address of *EXPR_P. */
10401 gcc_unreachable ();
10404 /* We used to check the predicate here and return immediately if it
10405 succeeds. This is wrong; the design is for gimplification to be
10406 idempotent, and for the predicates to only test for valid forms, not
10407 whether they are fully simplified. */
10409 pre_p
= &internal_pre
;
10411 if (post_p
== NULL
)
10412 post_p
= &internal_post
;
10414 /* Remember the last statements added to PRE_P and POST_P. Every
10415 new statement added by the gimplification helpers needs to be
10416 annotated with location information. To centralize the
10417 responsibility, we remember the last statement that had been
10418 added to both queues before gimplifying *EXPR_P. If
10419 gimplification produces new statements in PRE_P and POST_P, those
10420 statements will be annotated with the same location information
10422 pre_last_gsi
= gsi_last (*pre_p
);
10423 post_last_gsi
= gsi_last (*post_p
);
10425 saved_location
= input_location
;
10426 if (save_expr
!= error_mark_node
10427 && EXPR_HAS_LOCATION (*expr_p
))
10428 input_location
= EXPR_LOCATION (*expr_p
);
10430 /* Loop over the specific gimplifiers until the toplevel node
10431 remains the same. */
10434 /* Strip away as many useless type conversions as possible
10435 at the toplevel. */
10436 STRIP_USELESS_TYPE_CONVERSION (*expr_p
);
10438 /* Remember the expr. */
10439 save_expr
= *expr_p
;
10441 /* Die, die, die, my darling. */
10442 if (save_expr
== error_mark_node
10443 || (TREE_TYPE (save_expr
)
10444 && TREE_TYPE (save_expr
) == error_mark_node
))
10450 /* Do any language-specific gimplification. */
10451 ret
= ((enum gimplify_status
)
10452 lang_hooks
.gimplify_expr (expr_p
, pre_p
, post_p
));
10455 if (*expr_p
== NULL_TREE
)
10457 if (*expr_p
!= save_expr
)
10460 else if (ret
!= GS_UNHANDLED
)
10463 /* Make sure that all the cases set 'ret' appropriately. */
10464 ret
= GS_UNHANDLED
;
10465 switch (TREE_CODE (*expr_p
))
10467 /* First deal with the special cases. */
10469 case POSTINCREMENT_EXPR
:
10470 case POSTDECREMENT_EXPR
:
10471 case PREINCREMENT_EXPR
:
10472 case PREDECREMENT_EXPR
:
10473 ret
= gimplify_self_mod_expr (expr_p
, pre_p
, post_p
,
10474 fallback
!= fb_none
,
10475 TREE_TYPE (*expr_p
));
10478 case VIEW_CONVERT_EXPR
:
10479 if (is_gimple_reg_type (TREE_TYPE (*expr_p
))
10480 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p
, 0))))
10482 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
10483 post_p
, is_gimple_val
, fb_rvalue
);
10484 recalculate_side_effects (*expr_p
);
10490 case ARRAY_RANGE_REF
:
10491 case REALPART_EXPR
:
10492 case IMAGPART_EXPR
:
10493 case COMPONENT_REF
:
10494 ret
= gimplify_compound_lval (expr_p
, pre_p
, post_p
,
10495 fallback
? fallback
: fb_rvalue
);
10499 ret
= gimplify_cond_expr (expr_p
, pre_p
, fallback
);
10501 /* C99 code may assign to an array in a structure value of a
10502 conditional expression, and this has undefined behavior
10503 only on execution, so create a temporary if an lvalue is
10505 if (fallback
== fb_lvalue
)
10507 *expr_p
= get_initialized_tmp_var (*expr_p
, pre_p
, post_p
, false);
10508 mark_addressable (*expr_p
);
10514 ret
= gimplify_call_expr (expr_p
, pre_p
, fallback
!= fb_none
);
10516 /* C99 code may assign to an array in a structure returned
10517 from a function, and this has undefined behavior only on
10518 execution, so create a temporary if an lvalue is
10520 if (fallback
== fb_lvalue
)
10522 *expr_p
= get_initialized_tmp_var (*expr_p
, pre_p
, post_p
, false);
10523 mark_addressable (*expr_p
);
10529 gcc_unreachable ();
10531 case COMPOUND_EXPR
:
10532 ret
= gimplify_compound_expr (expr_p
, pre_p
, fallback
!= fb_none
);
10535 case COMPOUND_LITERAL_EXPR
:
10536 ret
= gimplify_compound_literal_expr (expr_p
, pre_p
,
10537 gimple_test_f
, fallback
);
10542 ret
= gimplify_modify_expr (expr_p
, pre_p
, post_p
,
10543 fallback
!= fb_none
);
10546 case TRUTH_ANDIF_EXPR
:
10547 case TRUTH_ORIF_EXPR
:
10549 /* Preserve the original type of the expression and the
10550 source location of the outer expression. */
10551 tree org_type
= TREE_TYPE (*expr_p
);
10552 *expr_p
= gimple_boolify (*expr_p
);
10553 *expr_p
= build3_loc (input_location
, COND_EXPR
,
10557 org_type
, boolean_true_node
),
10560 org_type
, boolean_false_node
));
10565 case TRUTH_NOT_EXPR
:
10567 tree type
= TREE_TYPE (*expr_p
);
10568 /* The parsers are careful to generate TRUTH_NOT_EXPR
10569 only with operands that are always zero or one.
10570 We do not fold here but handle the only interesting case
10571 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
10572 *expr_p
= gimple_boolify (*expr_p
);
10573 if (TYPE_PRECISION (TREE_TYPE (*expr_p
)) == 1)
10574 *expr_p
= build1_loc (input_location
, BIT_NOT_EXPR
,
10575 TREE_TYPE (*expr_p
),
10576 TREE_OPERAND (*expr_p
, 0));
10578 *expr_p
= build2_loc (input_location
, BIT_XOR_EXPR
,
10579 TREE_TYPE (*expr_p
),
10580 TREE_OPERAND (*expr_p
, 0),
10581 build_int_cst (TREE_TYPE (*expr_p
), 1));
10582 if (!useless_type_conversion_p (type
, TREE_TYPE (*expr_p
)))
10583 *expr_p
= fold_convert_loc (input_location
, type
, *expr_p
);
10589 ret
= gimplify_addr_expr (expr_p
, pre_p
, post_p
);
10592 case ANNOTATE_EXPR
:
10594 tree cond
= TREE_OPERAND (*expr_p
, 0);
10595 tree kind
= TREE_OPERAND (*expr_p
, 1);
10596 tree type
= TREE_TYPE (cond
);
10597 if (!INTEGRAL_TYPE_P (type
))
10603 tree tmp
= create_tmp_var (type
);
10604 gimplify_arg (&cond
, pre_p
, EXPR_LOCATION (*expr_p
));
10606 = gimple_build_call_internal (IFN_ANNOTATE
, 2, cond
, kind
);
10607 gimple_call_set_lhs (call
, tmp
);
10608 gimplify_seq_add_stmt (pre_p
, call
);
10615 ret
= gimplify_va_arg_expr (expr_p
, pre_p
, post_p
);
10619 if (IS_EMPTY_STMT (*expr_p
))
10625 if (VOID_TYPE_P (TREE_TYPE (*expr_p
))
10626 || fallback
== fb_none
)
10628 /* Just strip a conversion to void (or in void context) and
10630 *expr_p
= TREE_OPERAND (*expr_p
, 0);
10635 ret
= gimplify_conversion (expr_p
);
10636 if (ret
== GS_ERROR
)
10638 if (*expr_p
!= save_expr
)
10642 case FIX_TRUNC_EXPR
:
10643 /* unary_expr: ... | '(' cast ')' val | ... */
10644 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
10645 is_gimple_val
, fb_rvalue
);
10646 recalculate_side_effects (*expr_p
);
10651 bool volatilep
= TREE_THIS_VOLATILE (*expr_p
);
10652 bool notrap
= TREE_THIS_NOTRAP (*expr_p
);
10653 tree saved_ptr_type
= TREE_TYPE (TREE_OPERAND (*expr_p
, 0));
10655 *expr_p
= fold_indirect_ref_loc (input_location
, *expr_p
);
10656 if (*expr_p
!= save_expr
)
10662 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
10663 is_gimple_reg
, fb_rvalue
);
10664 if (ret
== GS_ERROR
)
10667 recalculate_side_effects (*expr_p
);
10668 *expr_p
= fold_build2_loc (input_location
, MEM_REF
,
10669 TREE_TYPE (*expr_p
),
10670 TREE_OPERAND (*expr_p
, 0),
10671 build_int_cst (saved_ptr_type
, 0));
10672 TREE_THIS_VOLATILE (*expr_p
) = volatilep
;
10673 TREE_THIS_NOTRAP (*expr_p
) = notrap
;
10678 /* We arrive here through the various re-gimplifcation paths. */
10680 /* First try re-folding the whole thing. */
10681 tmp
= fold_binary (MEM_REF
, TREE_TYPE (*expr_p
),
10682 TREE_OPERAND (*expr_p
, 0),
10683 TREE_OPERAND (*expr_p
, 1));
10686 REF_REVERSE_STORAGE_ORDER (tmp
)
10687 = REF_REVERSE_STORAGE_ORDER (*expr_p
);
10689 recalculate_side_effects (*expr_p
);
10693 /* Avoid re-gimplifying the address operand if it is already
10694 in suitable form. Re-gimplifying would mark the address
10695 operand addressable. Always gimplify when not in SSA form
10696 as we still may have to gimplify decls with value-exprs. */
10697 if (!gimplify_ctxp
|| !gimple_in_ssa_p (cfun
)
10698 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p
, 0)))
10700 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
10701 is_gimple_mem_ref_addr
, fb_rvalue
);
10702 if (ret
== GS_ERROR
)
10705 recalculate_side_effects (*expr_p
);
10709 /* Constants need not be gimplified. */
10716 /* Drop the overflow flag on constants, we do not want
10717 that in the GIMPLE IL. */
10718 if (TREE_OVERFLOW_P (*expr_p
))
10719 *expr_p
= drop_tree_overflow (*expr_p
);
10724 /* If we require an lvalue, such as for ADDR_EXPR, retain the
10725 CONST_DECL node. Otherwise the decl is replaceable by its
10727 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
10728 if (fallback
& fb_lvalue
)
10732 *expr_p
= DECL_INITIAL (*expr_p
);
10738 ret
= gimplify_decl_expr (expr_p
, pre_p
);
10742 ret
= gimplify_bind_expr (expr_p
, pre_p
);
10746 ret
= gimplify_loop_expr (expr_p
, pre_p
);
10750 ret
= gimplify_switch_expr (expr_p
, pre_p
);
10754 ret
= gimplify_exit_expr (expr_p
);
10758 /* If the target is not LABEL, then it is a computed jump
10759 and the target needs to be gimplified. */
10760 if (TREE_CODE (GOTO_DESTINATION (*expr_p
)) != LABEL_DECL
)
10762 ret
= gimplify_expr (&GOTO_DESTINATION (*expr_p
), pre_p
,
10763 NULL
, is_gimple_val
, fb_rvalue
);
10764 if (ret
== GS_ERROR
)
10767 gimplify_seq_add_stmt (pre_p
,
10768 gimple_build_goto (GOTO_DESTINATION (*expr_p
)));
10773 gimplify_seq_add_stmt (pre_p
,
10774 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p
),
10775 PREDICT_EXPR_OUTCOME (*expr_p
)));
10781 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p
))
10782 == current_function_decl
);
10783 gimplify_seq_add_stmt (pre_p
,
10784 gimple_build_label (LABEL_EXPR_LABEL (*expr_p
)));
10787 case CASE_LABEL_EXPR
:
10788 ret
= gimplify_case_label_expr (expr_p
, pre_p
);
10792 ret
= gimplify_return_expr (*expr_p
, pre_p
);
10796 /* Don't reduce this in place; let gimplify_init_constructor work its
10797 magic. Buf if we're just elaborating this for side effects, just
10798 gimplify any element that has side-effects. */
10799 if (fallback
== fb_none
)
10801 unsigned HOST_WIDE_INT ix
;
10803 tree temp
= NULL_TREE
;
10804 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p
), ix
, val
)
10805 if (TREE_SIDE_EFFECTS (val
))
10806 append_to_statement_list (val
, &temp
);
10809 ret
= temp
? GS_OK
: GS_ALL_DONE
;
10811 /* C99 code may assign to an array in a constructed
10812 structure or union, and this has undefined behavior only
10813 on execution, so create a temporary if an lvalue is
10815 else if (fallback
== fb_lvalue
)
10817 *expr_p
= get_initialized_tmp_var (*expr_p
, pre_p
, post_p
, false);
10818 mark_addressable (*expr_p
);
10825 /* The following are special cases that are not handled by the
10826 original GIMPLE grammar. */
10828 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
10831 ret
= gimplify_save_expr (expr_p
, pre_p
, post_p
);
10834 case BIT_FIELD_REF
:
10835 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
10836 post_p
, is_gimple_lvalue
, fb_either
);
10837 recalculate_side_effects (*expr_p
);
10840 case TARGET_MEM_REF
:
10842 enum gimplify_status r0
= GS_ALL_DONE
, r1
= GS_ALL_DONE
;
10844 if (TMR_BASE (*expr_p
))
10845 r0
= gimplify_expr (&TMR_BASE (*expr_p
), pre_p
,
10846 post_p
, is_gimple_mem_ref_addr
, fb_either
);
10847 if (TMR_INDEX (*expr_p
))
10848 r1
= gimplify_expr (&TMR_INDEX (*expr_p
), pre_p
,
10849 post_p
, is_gimple_val
, fb_rvalue
);
10850 if (TMR_INDEX2 (*expr_p
))
10851 r1
= gimplify_expr (&TMR_INDEX2 (*expr_p
), pre_p
,
10852 post_p
, is_gimple_val
, fb_rvalue
);
10853 /* TMR_STEP and TMR_OFFSET are always integer constants. */
10854 ret
= MIN (r0
, r1
);
10858 case NON_LVALUE_EXPR
:
10859 /* This should have been stripped above. */
10860 gcc_unreachable ();
10863 ret
= gimplify_asm_expr (expr_p
, pre_p
, post_p
);
10866 case TRY_FINALLY_EXPR
:
10867 case TRY_CATCH_EXPR
:
10869 gimple_seq eval
, cleanup
;
10872 /* Calls to destructors are generated automatically in FINALLY/CATCH
10873 block. They should have location as UNKNOWN_LOCATION. However,
10874 gimplify_call_expr will reset these call stmts to input_location
10875 if it finds stmt's location is unknown. To prevent resetting for
10876 destructors, we set the input_location to unknown.
10877 Note that this only affects the destructor calls in FINALLY/CATCH
10878 block, and will automatically reset to its original value by the
10879 end of gimplify_expr. */
10880 input_location
= UNKNOWN_LOCATION
;
10881 eval
= cleanup
= NULL
;
10882 gimplify_and_add (TREE_OPERAND (*expr_p
, 0), &eval
);
10883 gimplify_and_add (TREE_OPERAND (*expr_p
, 1), &cleanup
);
10884 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
10885 if (gimple_seq_empty_p (cleanup
))
10887 gimple_seq_add_seq (pre_p
, eval
);
10891 try_
= gimple_build_try (eval
, cleanup
,
10892 TREE_CODE (*expr_p
) == TRY_FINALLY_EXPR
10893 ? GIMPLE_TRY_FINALLY
10894 : GIMPLE_TRY_CATCH
);
10895 if (EXPR_HAS_LOCATION (save_expr
))
10896 gimple_set_location (try_
, EXPR_LOCATION (save_expr
));
10897 else if (LOCATION_LOCUS (saved_location
) != UNKNOWN_LOCATION
)
10898 gimple_set_location (try_
, saved_location
);
10899 if (TREE_CODE (*expr_p
) == TRY_CATCH_EXPR
)
10900 gimple_try_set_catch_is_cleanup (try_
,
10901 TRY_CATCH_IS_CLEANUP (*expr_p
));
10902 gimplify_seq_add_stmt (pre_p
, try_
);
10907 case CLEANUP_POINT_EXPR
:
10908 ret
= gimplify_cleanup_point_expr (expr_p
, pre_p
);
10912 ret
= gimplify_target_expr (expr_p
, pre_p
, post_p
);
10918 gimple_seq handler
= NULL
;
10919 gimplify_and_add (CATCH_BODY (*expr_p
), &handler
);
10920 c
= gimple_build_catch (CATCH_TYPES (*expr_p
), handler
);
10921 gimplify_seq_add_stmt (pre_p
, c
);
10926 case EH_FILTER_EXPR
:
10929 gimple_seq failure
= NULL
;
10931 gimplify_and_add (EH_FILTER_FAILURE (*expr_p
), &failure
);
10932 ehf
= gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p
), failure
);
10933 gimple_set_no_warning (ehf
, TREE_NO_WARNING (*expr_p
));
10934 gimplify_seq_add_stmt (pre_p
, ehf
);
10941 enum gimplify_status r0
, r1
;
10942 r0
= gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p
), pre_p
,
10943 post_p
, is_gimple_val
, fb_rvalue
);
10944 r1
= gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p
), pre_p
,
10945 post_p
, is_gimple_val
, fb_rvalue
);
10946 TREE_SIDE_EFFECTS (*expr_p
) = 0;
10947 ret
= MIN (r0
, r1
);
10952 /* We get here when taking the address of a label. We mark
10953 the label as "forced"; meaning it can never be removed and
10954 it is a potential target for any computed goto. */
10955 FORCED_LABEL (*expr_p
) = 1;
10959 case STATEMENT_LIST
:
10960 ret
= gimplify_statement_list (expr_p
, pre_p
);
10963 case WITH_SIZE_EXPR
:
10965 gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
10966 post_p
== &internal_post
? NULL
: post_p
,
10967 gimple_test_f
, fallback
);
10968 gimplify_expr (&TREE_OPERAND (*expr_p
, 1), pre_p
, post_p
,
10969 is_gimple_val
, fb_rvalue
);
10976 ret
= gimplify_var_or_parm_decl (expr_p
);
10980 /* When within an OMP context, notice uses of variables. */
10981 if (gimplify_omp_ctxp
)
10982 omp_notice_variable (gimplify_omp_ctxp
, *expr_p
, true);
10987 /* Allow callbacks into the gimplifier during optimization. */
10992 gimplify_omp_parallel (expr_p
, pre_p
);
10997 gimplify_omp_task (expr_p
, pre_p
);
11005 case OMP_DISTRIBUTE
:
11008 ret
= gimplify_omp_for (expr_p
, pre_p
);
11012 gimplify_oacc_cache (expr_p
, pre_p
);
11017 gimplify_oacc_declare (expr_p
, pre_p
);
11021 case OACC_HOST_DATA
:
11024 case OACC_PARALLEL
:
11028 case OMP_TARGET_DATA
:
11030 gimplify_omp_workshare (expr_p
, pre_p
);
11034 case OACC_ENTER_DATA
:
11035 case OACC_EXIT_DATA
:
11037 case OMP_TARGET_UPDATE
:
11038 case OMP_TARGET_ENTER_DATA
:
11039 case OMP_TARGET_EXIT_DATA
:
11040 gimplify_omp_target_update (expr_p
, pre_p
);
11046 case OMP_TASKGROUP
:
11050 gimple_seq body
= NULL
;
11053 gimplify_and_add (OMP_BODY (*expr_p
), &body
);
11054 switch (TREE_CODE (*expr_p
))
11057 g
= gimple_build_omp_section (body
);
11060 g
= gimple_build_omp_master (body
);
11062 case OMP_TASKGROUP
:
11064 gimple_seq cleanup
= NULL
;
11066 = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END
);
11067 g
= gimple_build_call (fn
, 0);
11068 gimple_seq_add_stmt (&cleanup
, g
);
11069 g
= gimple_build_try (body
, cleanup
, GIMPLE_TRY_FINALLY
);
11071 gimple_seq_add_stmt (&body
, g
);
11072 g
= gimple_build_omp_taskgroup (body
);
11076 g
= gimplify_omp_ordered (*expr_p
, body
);
11079 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p
),
11080 pre_p
, ORT_WORKSHARE
, OMP_CRITICAL
);
11081 gimplify_adjust_omp_clauses (pre_p
, body
,
11082 &OMP_CRITICAL_CLAUSES (*expr_p
),
11084 g
= gimple_build_omp_critical (body
,
11085 OMP_CRITICAL_NAME (*expr_p
),
11086 OMP_CRITICAL_CLAUSES (*expr_p
));
11089 gcc_unreachable ();
11091 gimplify_seq_add_stmt (pre_p
, g
);
11097 case OMP_ATOMIC_READ
:
11098 case OMP_ATOMIC_CAPTURE_OLD
:
11099 case OMP_ATOMIC_CAPTURE_NEW
:
11100 ret
= gimplify_omp_atomic (expr_p
, pre_p
);
11103 case TRANSACTION_EXPR
:
11104 ret
= gimplify_transaction (expr_p
, pre_p
);
11107 case TRUTH_AND_EXPR
:
11108 case TRUTH_OR_EXPR
:
11109 case TRUTH_XOR_EXPR
:
11111 tree orig_type
= TREE_TYPE (*expr_p
);
11112 tree new_type
, xop0
, xop1
;
11113 *expr_p
= gimple_boolify (*expr_p
);
11114 new_type
= TREE_TYPE (*expr_p
);
11115 if (!useless_type_conversion_p (orig_type
, new_type
))
11117 *expr_p
= fold_convert_loc (input_location
, orig_type
, *expr_p
);
11122 /* Boolified binary truth expressions are semantically equivalent
11123 to bitwise binary expressions. Canonicalize them to the
11124 bitwise variant. */
11125 switch (TREE_CODE (*expr_p
))
11127 case TRUTH_AND_EXPR
:
11128 TREE_SET_CODE (*expr_p
, BIT_AND_EXPR
);
11130 case TRUTH_OR_EXPR
:
11131 TREE_SET_CODE (*expr_p
, BIT_IOR_EXPR
);
11133 case TRUTH_XOR_EXPR
:
11134 TREE_SET_CODE (*expr_p
, BIT_XOR_EXPR
);
11139 /* Now make sure that operands have compatible type to
11140 expression's new_type. */
11141 xop0
= TREE_OPERAND (*expr_p
, 0);
11142 xop1
= TREE_OPERAND (*expr_p
, 1);
11143 if (!useless_type_conversion_p (new_type
, TREE_TYPE (xop0
)))
11144 TREE_OPERAND (*expr_p
, 0) = fold_convert_loc (input_location
,
11147 if (!useless_type_conversion_p (new_type
, TREE_TYPE (xop1
)))
11148 TREE_OPERAND (*expr_p
, 1) = fold_convert_loc (input_location
,
11151 /* Continue classified as tcc_binary. */
11155 case VEC_COND_EXPR
:
11157 enum gimplify_status r0
, r1
, r2
;
11159 r0
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
11160 post_p
, is_gimple_condexpr
, fb_rvalue
);
11161 r1
= gimplify_expr (&TREE_OPERAND (*expr_p
, 1), pre_p
,
11162 post_p
, is_gimple_val
, fb_rvalue
);
11163 r2
= gimplify_expr (&TREE_OPERAND (*expr_p
, 2), pre_p
,
11164 post_p
, is_gimple_val
, fb_rvalue
);
11166 ret
= MIN (MIN (r0
, r1
), r2
);
11167 recalculate_side_effects (*expr_p
);
11172 case VEC_PERM_EXPR
:
11173 /* Classified as tcc_expression. */
11176 case BIT_INSERT_EXPR
:
11177 /* Argument 3 is a constant. */
11180 case POINTER_PLUS_EXPR
:
11182 enum gimplify_status r0
, r1
;
11183 r0
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
11184 post_p
, is_gimple_val
, fb_rvalue
);
11185 r1
= gimplify_expr (&TREE_OPERAND (*expr_p
, 1), pre_p
,
11186 post_p
, is_gimple_val
, fb_rvalue
);
11187 recalculate_side_effects (*expr_p
);
11188 ret
= MIN (r0
, r1
);
11192 case CILK_SYNC_STMT
:
11194 if (!fn_contains_cilk_spawn_p (cfun
))
11196 error_at (EXPR_LOCATION (*expr_p
),
11197 "expected %<_Cilk_spawn%> before %<_Cilk_sync%>");
11202 gimplify_cilk_sync (expr_p
, pre_p
);
11209 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p
)))
11211 case tcc_comparison
:
11212 /* Handle comparison of objects of non scalar mode aggregates
11213 with a call to memcmp. It would be nice to only have to do
11214 this for variable-sized objects, but then we'd have to allow
11215 the same nest of reference nodes we allow for MODIFY_EXPR and
11216 that's too complex.
11218 Compare scalar mode aggregates as scalar mode values. Using
11219 memcmp for them would be very inefficient at best, and is
11220 plain wrong if bitfields are involved. */
11222 tree type
= TREE_TYPE (TREE_OPERAND (*expr_p
, 1));
11224 /* Vector comparisons need no boolification. */
11225 if (TREE_CODE (type
) == VECTOR_TYPE
)
11227 else if (!AGGREGATE_TYPE_P (type
))
11229 tree org_type
= TREE_TYPE (*expr_p
);
11230 *expr_p
= gimple_boolify (*expr_p
);
11231 if (!useless_type_conversion_p (org_type
,
11232 TREE_TYPE (*expr_p
)))
11234 *expr_p
= fold_convert_loc (input_location
,
11235 org_type
, *expr_p
);
11241 else if (TYPE_MODE (type
) != BLKmode
)
11242 ret
= gimplify_scalar_mode_aggregate_compare (expr_p
);
11244 ret
= gimplify_variable_sized_compare (expr_p
);
11249 /* If *EXPR_P does not need to be special-cased, handle it
11250 according to its class. */
11252 ret
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
11253 post_p
, is_gimple_val
, fb_rvalue
);
11259 enum gimplify_status r0
, r1
;
11261 r0
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
11262 post_p
, is_gimple_val
, fb_rvalue
);
11263 r1
= gimplify_expr (&TREE_OPERAND (*expr_p
, 1), pre_p
,
11264 post_p
, is_gimple_val
, fb_rvalue
);
11266 ret
= MIN (r0
, r1
);
11272 enum gimplify_status r0
, r1
, r2
;
11274 r0
= gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
,
11275 post_p
, is_gimple_val
, fb_rvalue
);
11276 r1
= gimplify_expr (&TREE_OPERAND (*expr_p
, 1), pre_p
,
11277 post_p
, is_gimple_val
, fb_rvalue
);
11278 r2
= gimplify_expr (&TREE_OPERAND (*expr_p
, 2), pre_p
,
11279 post_p
, is_gimple_val
, fb_rvalue
);
11281 ret
= MIN (MIN (r0
, r1
), r2
);
11285 case tcc_declaration
:
11288 goto dont_recalculate
;
11291 gcc_unreachable ();
11294 recalculate_side_effects (*expr_p
);
11300 gcc_assert (*expr_p
|| ret
!= GS_OK
);
11302 while (ret
== GS_OK
);
11304 /* If we encountered an error_mark somewhere nested inside, either
11305 stub out the statement or propagate the error back out. */
11306 if (ret
== GS_ERROR
)
11313 /* This was only valid as a return value from the langhook, which
11314 we handled. Make sure it doesn't escape from any other context. */
11315 gcc_assert (ret
!= GS_UNHANDLED
);
11317 if (fallback
== fb_none
&& *expr_p
&& !is_gimple_stmt (*expr_p
))
11319 /* We aren't looking for a value, and we don't have a valid
11320 statement. If it doesn't have side-effects, throw it away. */
11321 if (!TREE_SIDE_EFFECTS (*expr_p
))
11323 else if (!TREE_THIS_VOLATILE (*expr_p
))
11325 /* This is probably a _REF that contains something nested that
11326 has side effects. Recurse through the operands to find it. */
11327 enum tree_code code
= TREE_CODE (*expr_p
);
11331 case COMPONENT_REF
:
11332 case REALPART_EXPR
:
11333 case IMAGPART_EXPR
:
11334 case VIEW_CONVERT_EXPR
:
11335 gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
11336 gimple_test_f
, fallback
);
11340 case ARRAY_RANGE_REF
:
11341 gimplify_expr (&TREE_OPERAND (*expr_p
, 0), pre_p
, post_p
,
11342 gimple_test_f
, fallback
);
11343 gimplify_expr (&TREE_OPERAND (*expr_p
, 1), pre_p
, post_p
,
11344 gimple_test_f
, fallback
);
11348 /* Anything else with side-effects must be converted to
11349 a valid statement before we get here. */
11350 gcc_unreachable ();
11355 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p
))
11356 && TYPE_MODE (TREE_TYPE (*expr_p
)) != BLKmode
)
11358 /* Historically, the compiler has treated a bare reference
11359 to a non-BLKmode volatile lvalue as forcing a load. */
11360 tree type
= TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p
));
11362 /* Normally, we do not want to create a temporary for a
11363 TREE_ADDRESSABLE type because such a type should not be
11364 copied by bitwise-assignment. However, we make an
11365 exception here, as all we are doing here is ensuring that
11366 we read the bytes that make up the type. We use
11367 create_tmp_var_raw because create_tmp_var will abort when
11368 given a TREE_ADDRESSABLE type. */
11369 tree tmp
= create_tmp_var_raw (type
, "vol");
11370 gimple_add_tmp_var (tmp
);
11371 gimplify_assign (tmp
, *expr_p
, pre_p
);
11375 /* We can't do anything useful with a volatile reference to
11376 an incomplete type, so just throw it away. Likewise for
11377 a BLKmode type, since any implicit inner load should
11378 already have been turned into an explicit one by the
11379 gimplification process. */
11383 /* If we are gimplifying at the statement level, we're done. Tack
11384 everything together and return. */
11385 if (fallback
== fb_none
|| is_statement
)
11387 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
11388 it out for GC to reclaim it. */
11389 *expr_p
= NULL_TREE
;
11391 if (!gimple_seq_empty_p (internal_pre
)
11392 || !gimple_seq_empty_p (internal_post
))
11394 gimplify_seq_add_seq (&internal_pre
, internal_post
);
11395 gimplify_seq_add_seq (pre_p
, internal_pre
);
11398 /* The result of gimplifying *EXPR_P is going to be the last few
11399 statements in *PRE_P and *POST_P. Add location information
11400 to all the statements that were added by the gimplification
11402 if (!gimple_seq_empty_p (*pre_p
))
11403 annotate_all_with_location_after (*pre_p
, pre_last_gsi
, input_location
);
11405 if (!gimple_seq_empty_p (*post_p
))
11406 annotate_all_with_location_after (*post_p
, post_last_gsi
,
11412 #ifdef ENABLE_GIMPLE_CHECKING
11415 enum tree_code code
= TREE_CODE (*expr_p
);
11416 /* These expressions should already be in gimple IR form. */
11417 gcc_assert (code
!= MODIFY_EXPR
11418 && code
!= ASM_EXPR
11419 && code
!= BIND_EXPR
11420 && code
!= CATCH_EXPR
11421 && (code
!= COND_EXPR
|| gimplify_ctxp
->allow_rhs_cond_expr
)
11422 && code
!= EH_FILTER_EXPR
11423 && code
!= GOTO_EXPR
11424 && code
!= LABEL_EXPR
11425 && code
!= LOOP_EXPR
11426 && code
!= SWITCH_EXPR
11427 && code
!= TRY_FINALLY_EXPR
11428 && code
!= OACC_PARALLEL
11429 && code
!= OACC_KERNELS
11430 && code
!= OACC_DATA
11431 && code
!= OACC_HOST_DATA
11432 && code
!= OACC_DECLARE
11433 && code
!= OACC_UPDATE
11434 && code
!= OACC_ENTER_DATA
11435 && code
!= OACC_EXIT_DATA
11436 && code
!= OACC_CACHE
11437 && code
!= OMP_CRITICAL
11439 && code
!= OACC_LOOP
11440 && code
!= OMP_MASTER
11441 && code
!= OMP_TASKGROUP
11442 && code
!= OMP_ORDERED
11443 && code
!= OMP_PARALLEL
11444 && code
!= OMP_SECTIONS
11445 && code
!= OMP_SECTION
11446 && code
!= OMP_SINGLE
);
11450 /* Otherwise we're gimplifying a subexpression, so the resulting
11451 value is interesting. If it's a valid operand that matches
11452 GIMPLE_TEST_F, we're done. Unless we are handling some
11453 post-effects internally; if that's the case, we need to copy into
11454 a temporary before adding the post-effects to POST_P. */
11455 if (gimple_seq_empty_p (internal_post
) && (*gimple_test_f
) (*expr_p
))
11458 /* Otherwise, we need to create a new temporary for the gimplified
11461 /* We can't return an lvalue if we have an internal postqueue. The
11462 object the lvalue refers to would (probably) be modified by the
11463 postqueue; we need to copy the value out first, which means an
11465 if ((fallback
& fb_lvalue
)
11466 && gimple_seq_empty_p (internal_post
)
11467 && is_gimple_addressable (*expr_p
))
11469 /* An lvalue will do. Take the address of the expression, store it
11470 in a temporary, and replace the expression with an INDIRECT_REF of
11472 tmp
= build_fold_addr_expr_loc (input_location
, *expr_p
);
11473 gimplify_expr (&tmp
, pre_p
, post_p
, is_gimple_reg
, fb_rvalue
);
11474 *expr_p
= build_simple_mem_ref (tmp
);
11476 else if ((fallback
& fb_rvalue
) && is_gimple_reg_rhs_or_call (*expr_p
))
11478 /* An rvalue will do. Assign the gimplified expression into a
11479 new temporary TMP and replace the original expression with
11480 TMP. First, make sure that the expression has a type so that
11481 it can be assigned into a temporary. */
11482 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p
)));
11483 *expr_p
= get_formal_tmp_var (*expr_p
, pre_p
);
11487 #ifdef ENABLE_GIMPLE_CHECKING
11488 if (!(fallback
& fb_mayfail
))
11490 fprintf (stderr
, "gimplification failed:\n");
11491 print_generic_expr (stderr
, *expr_p
, 0);
11492 debug_tree (*expr_p
);
11493 internal_error ("gimplification failed");
11496 gcc_assert (fallback
& fb_mayfail
);
11498 /* If this is an asm statement, and the user asked for the
11499 impossible, don't die. Fail and let gimplify_asm_expr
11505 /* Make sure the temporary matches our predicate. */
11506 gcc_assert ((*gimple_test_f
) (*expr_p
));
11508 if (!gimple_seq_empty_p (internal_post
))
11510 annotate_all_with_location (internal_post
, input_location
);
11511 gimplify_seq_add_seq (pre_p
, internal_post
);
11515 input_location
= saved_location
;
11519 /* Like gimplify_expr but make sure the gimplified result is not itself
11520 a SSA name (but a decl if it were). Temporaries required by
11521 evaluating *EXPR_P may be still SSA names. */
11523 static enum gimplify_status
11524 gimplify_expr (tree
*expr_p
, gimple_seq
*pre_p
, gimple_seq
*post_p
,
11525 bool (*gimple_test_f
) (tree
), fallback_t fallback
,
11528 bool was_ssa_name_p
= TREE_CODE (*expr_p
) == SSA_NAME
;
11529 enum gimplify_status ret
= gimplify_expr (expr_p
, pre_p
, post_p
,
11530 gimple_test_f
, fallback
);
11532 && TREE_CODE (*expr_p
) == SSA_NAME
)
11534 tree name
= *expr_p
;
11535 if (was_ssa_name_p
)
11536 *expr_p
= get_initialized_tmp_var (*expr_p
, pre_p
, NULL
, false);
11539 /* Avoid the extra copy if possible. */
11540 *expr_p
= create_tmp_reg (TREE_TYPE (name
));
11541 gimple_set_lhs (SSA_NAME_DEF_STMT (name
), *expr_p
);
11542 release_ssa_name (name
);
11548 /* Look through TYPE for variable-sized objects and gimplify each such
11549 size that we find. Add to LIST_P any statements generated. */
11552 gimplify_type_sizes (tree type
, gimple_seq
*list_p
)
11556 if (type
== NULL
|| type
== error_mark_node
)
11559 /* We first do the main variant, then copy into any other variants. */
11560 type
= TYPE_MAIN_VARIANT (type
);
11562 /* Avoid infinite recursion. */
11563 if (TYPE_SIZES_GIMPLIFIED (type
))
11566 TYPE_SIZES_GIMPLIFIED (type
) = 1;
11568 switch (TREE_CODE (type
))
11571 case ENUMERAL_TYPE
:
11574 case FIXED_POINT_TYPE
:
11575 gimplify_one_sizepos (&TYPE_MIN_VALUE (type
), list_p
);
11576 gimplify_one_sizepos (&TYPE_MAX_VALUE (type
), list_p
);
11578 for (t
= TYPE_NEXT_VARIANT (type
); t
; t
= TYPE_NEXT_VARIANT (t
))
11580 TYPE_MIN_VALUE (t
) = TYPE_MIN_VALUE (type
);
11581 TYPE_MAX_VALUE (t
) = TYPE_MAX_VALUE (type
);
11586 /* These types may not have declarations, so handle them here. */
11587 gimplify_type_sizes (TREE_TYPE (type
), list_p
);
11588 gimplify_type_sizes (TYPE_DOMAIN (type
), list_p
);
11589 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
11590 with assigned stack slots, for -O1+ -g they should be tracked
11592 if (!(TYPE_NAME (type
)
11593 && TREE_CODE (TYPE_NAME (type
)) == TYPE_DECL
11594 && DECL_IGNORED_P (TYPE_NAME (type
)))
11595 && TYPE_DOMAIN (type
)
11596 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type
)))
11598 t
= TYPE_MIN_VALUE (TYPE_DOMAIN (type
));
11599 if (t
&& TREE_CODE (t
) == VAR_DECL
&& DECL_ARTIFICIAL (t
))
11600 DECL_IGNORED_P (t
) = 0;
11601 t
= TYPE_MAX_VALUE (TYPE_DOMAIN (type
));
11602 if (t
&& TREE_CODE (t
) == VAR_DECL
&& DECL_ARTIFICIAL (t
))
11603 DECL_IGNORED_P (t
) = 0;
11609 case QUAL_UNION_TYPE
:
11610 for (field
= TYPE_FIELDS (type
); field
; field
= DECL_CHAIN (field
))
11611 if (TREE_CODE (field
) == FIELD_DECL
)
11613 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field
), list_p
);
11614 gimplify_one_sizepos (&DECL_SIZE (field
), list_p
);
11615 gimplify_one_sizepos (&DECL_SIZE_UNIT (field
), list_p
);
11616 gimplify_type_sizes (TREE_TYPE (field
), list_p
);
11621 case REFERENCE_TYPE
:
11622 /* We used to recurse on the pointed-to type here, which turned out to
11623 be incorrect because its definition might refer to variables not
11624 yet initialized at this point if a forward declaration is involved.
11626 It was actually useful for anonymous pointed-to types to ensure
11627 that the sizes evaluation dominates every possible later use of the
11628 values. Restricting to such types here would be safe since there
11629 is no possible forward declaration around, but would introduce an
11630 undesirable middle-end semantic to anonymity. We then defer to
11631 front-ends the responsibility of ensuring that the sizes are
11632 evaluated both early and late enough, e.g. by attaching artificial
11633 type declarations to the tree. */
11640 gimplify_one_sizepos (&TYPE_SIZE (type
), list_p
);
11641 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type
), list_p
);
11643 for (t
= TYPE_NEXT_VARIANT (type
); t
; t
= TYPE_NEXT_VARIANT (t
))
11645 TYPE_SIZE (t
) = TYPE_SIZE (type
);
11646 TYPE_SIZE_UNIT (t
) = TYPE_SIZE_UNIT (type
);
11647 TYPE_SIZES_GIMPLIFIED (t
) = 1;
11651 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
11652 a size or position, has had all of its SAVE_EXPRs evaluated.
11653 We add any required statements to *STMT_P. */
11656 gimplify_one_sizepos (tree
*expr_p
, gimple_seq
*stmt_p
)
11658 tree expr
= *expr_p
;
11660 /* We don't do anything if the value isn't there, is constant, or contains
11661 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
11662 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
11663 will want to replace it with a new variable, but that will cause problems
11664 if this type is from outside the function. It's OK to have that here. */
11665 if (is_gimple_sizepos (expr
))
11668 *expr_p
= unshare_expr (expr
);
11670 /* SSA names in decl/type fields are a bad idea - they'll get reclaimed
11671 if the def vanishes. */
11672 gimplify_expr (expr_p
, stmt_p
, NULL
, is_gimple_val
, fb_rvalue
, false);
11675 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
11676 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
11677 is true, also gimplify the parameters. */
11680 gimplify_body (tree fndecl
, bool do_parms
)
11682 location_t saved_location
= input_location
;
11683 gimple_seq parm_stmts
, seq
;
11684 gimple
*outer_stmt
;
11686 struct cgraph_node
*cgn
;
11688 timevar_push (TV_TREE_GIMPLIFY
);
11690 init_tree_ssa (cfun
);
11692 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
11694 default_rtl_profile ();
11696 gcc_assert (gimplify_ctxp
== NULL
);
11697 push_gimplify_context (true);
11699 if (flag_openacc
|| flag_openmp
)
11701 gcc_assert (gimplify_omp_ctxp
== NULL
);
11702 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl
)))
11703 gimplify_omp_ctxp
= new_omp_context (ORT_TARGET
);
11706 /* Unshare most shared trees in the body and in that of any nested functions.
11707 It would seem we don't have to do this for nested functions because
11708 they are supposed to be output and then the outer function gimplified
11709 first, but the g++ front end doesn't always do it that way. */
11710 unshare_body (fndecl
);
11711 unvisit_body (fndecl
);
11713 cgn
= cgraph_node::get (fndecl
);
11714 if (cgn
&& cgn
->origin
)
11715 nonlocal_vlas
= new hash_set
<tree
>;
11717 /* Make sure input_location isn't set to something weird. */
11718 input_location
= DECL_SOURCE_LOCATION (fndecl
);
11720 /* Resolve callee-copies. This has to be done before processing
11721 the body so that DECL_VALUE_EXPR gets processed correctly. */
11722 parm_stmts
= do_parms
? gimplify_parameters () : NULL
;
11724 /* Gimplify the function's body. */
11726 gimplify_stmt (&DECL_SAVED_TREE (fndecl
), &seq
);
11727 outer_stmt
= gimple_seq_first_stmt (seq
);
11730 outer_stmt
= gimple_build_nop ();
11731 gimplify_seq_add_stmt (&seq
, outer_stmt
);
11734 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
11735 not the case, wrap everything in a GIMPLE_BIND to make it so. */
11736 if (gimple_code (outer_stmt
) == GIMPLE_BIND
11737 && gimple_seq_first (seq
) == gimple_seq_last (seq
))
11738 outer_bind
= as_a
<gbind
*> (outer_stmt
);
11740 outer_bind
= gimple_build_bind (NULL_TREE
, seq
, NULL
);
11742 DECL_SAVED_TREE (fndecl
) = NULL_TREE
;
11744 /* If we had callee-copies statements, insert them at the beginning
11745 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
11746 if (!gimple_seq_empty_p (parm_stmts
))
11750 gimplify_seq_add_seq (&parm_stmts
, gimple_bind_body (outer_bind
));
11751 gimple_bind_set_body (outer_bind
, parm_stmts
);
11753 for (parm
= DECL_ARGUMENTS (current_function_decl
);
11754 parm
; parm
= DECL_CHAIN (parm
))
11755 if (DECL_HAS_VALUE_EXPR_P (parm
))
11757 DECL_HAS_VALUE_EXPR_P (parm
) = 0;
11758 DECL_IGNORED_P (parm
) = 0;
11764 if (nonlocal_vla_vars
)
11766 /* tree-nested.c may later on call declare_vars (..., true);
11767 which relies on BLOCK_VARS chain to be the tail of the
11768 gimple_bind_vars chain. Ensure we don't violate that
11770 if (gimple_bind_block (outer_bind
)
11771 == DECL_INITIAL (current_function_decl
))
11772 declare_vars (nonlocal_vla_vars
, outer_bind
, true);
11774 BLOCK_VARS (DECL_INITIAL (current_function_decl
))
11775 = chainon (BLOCK_VARS (DECL_INITIAL (current_function_decl
)),
11776 nonlocal_vla_vars
);
11777 nonlocal_vla_vars
= NULL_TREE
;
11779 delete nonlocal_vlas
;
11780 nonlocal_vlas
= NULL
;
11783 if ((flag_openacc
|| flag_openmp
|| flag_openmp_simd
)
11784 && gimplify_omp_ctxp
)
11786 delete_omp_context (gimplify_omp_ctxp
);
11787 gimplify_omp_ctxp
= NULL
;
11790 pop_gimplify_context (outer_bind
);
11791 gcc_assert (gimplify_ctxp
== NULL
);
11793 if (flag_checking
&& !seen_error ())
11794 verify_gimple_in_seq (gimple_bind_body (outer_bind
));
11796 timevar_pop (TV_TREE_GIMPLIFY
);
11797 input_location
= saved_location
;
11802 typedef char *char_p
; /* For DEF_VEC_P. */
11804 /* Return whether we should exclude FNDECL from instrumentation. */
11807 flag_instrument_functions_exclude_p (tree fndecl
)
11811 v
= (vec
<char_p
> *) flag_instrument_functions_exclude_functions
;
11812 if (v
&& v
->length () > 0)
11818 name
= lang_hooks
.decl_printable_name (fndecl
, 0);
11819 FOR_EACH_VEC_ELT (*v
, i
, s
)
11820 if (strstr (name
, s
) != NULL
)
11824 v
= (vec
<char_p
> *) flag_instrument_functions_exclude_files
;
11825 if (v
&& v
->length () > 0)
11831 name
= DECL_SOURCE_FILE (fndecl
);
11832 FOR_EACH_VEC_ELT (*v
, i
, s
)
11833 if (strstr (name
, s
) != NULL
)
11840 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
11841 node for the function we want to gimplify.
11843 Return the sequence of GIMPLE statements corresponding to the body
11847 gimplify_function_tree (tree fndecl
)
11853 gcc_assert (!gimple_body (fndecl
));
11855 if (DECL_STRUCT_FUNCTION (fndecl
))
11856 push_cfun (DECL_STRUCT_FUNCTION (fndecl
));
11858 push_struct_function (fndecl
);
11860 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
11862 cfun
->curr_properties
|= PROP_gimple_lva
;
11864 for (parm
= DECL_ARGUMENTS (fndecl
); parm
; parm
= DECL_CHAIN (parm
))
11866 /* Preliminarily mark non-addressed complex variables as eligible
11867 for promotion to gimple registers. We'll transform their uses
11868 as we find them. */
11869 if ((TREE_CODE (TREE_TYPE (parm
)) == COMPLEX_TYPE
11870 || TREE_CODE (TREE_TYPE (parm
)) == VECTOR_TYPE
)
11871 && !TREE_THIS_VOLATILE (parm
)
11872 && !needs_to_live_in_memory (parm
))
11873 DECL_GIMPLE_REG_P (parm
) = 1;
11876 ret
= DECL_RESULT (fndecl
);
11877 if ((TREE_CODE (TREE_TYPE (ret
)) == COMPLEX_TYPE
11878 || TREE_CODE (TREE_TYPE (ret
)) == VECTOR_TYPE
)
11879 && !needs_to_live_in_memory (ret
))
11880 DECL_GIMPLE_REG_P (ret
) = 1;
11882 bind
= gimplify_body (fndecl
, true);
11884 /* The tree body of the function is no longer needed, replace it
11885 with the new GIMPLE body. */
11887 gimple_seq_add_stmt (&seq
, bind
);
11888 gimple_set_body (fndecl
, seq
);
11890 /* If we're instrumenting function entry/exit, then prepend the call to
11891 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
11892 catch the exit hook. */
11893 /* ??? Add some way to ignore exceptions for this TFE. */
11894 if (flag_instrument_function_entry_exit
11895 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl
)
11896 && !flag_instrument_functions_exclude_p (fndecl
))
11901 gimple_seq cleanup
= NULL
, body
= NULL
;
11905 x
= builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS
);
11906 call
= gimple_build_call (x
, 1, integer_zero_node
);
11907 tmp_var
= create_tmp_var (ptr_type_node
, "return_addr");
11908 gimple_call_set_lhs (call
, tmp_var
);
11909 gimplify_seq_add_stmt (&cleanup
, call
);
11910 x
= builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT
);
11911 call
= gimple_build_call (x
, 2,
11912 build_fold_addr_expr (current_function_decl
),
11914 gimplify_seq_add_stmt (&cleanup
, call
);
11915 tf
= gimple_build_try (seq
, cleanup
, GIMPLE_TRY_FINALLY
);
11917 x
= builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS
);
11918 call
= gimple_build_call (x
, 1, integer_zero_node
);
11919 tmp_var
= create_tmp_var (ptr_type_node
, "return_addr");
11920 gimple_call_set_lhs (call
, tmp_var
);
11921 gimplify_seq_add_stmt (&body
, call
);
11922 x
= builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER
);
11923 call
= gimple_build_call (x
, 2,
11924 build_fold_addr_expr (current_function_decl
),
11926 gimplify_seq_add_stmt (&body
, call
);
11927 gimplify_seq_add_stmt (&body
, tf
);
11928 new_bind
= gimple_build_bind (NULL
, body
, gimple_bind_block (bind
));
11929 /* Clear the block for BIND, since it is no longer directly inside
11930 the function, but within a try block. */
11931 gimple_bind_set_block (bind
, NULL
);
11933 /* Replace the current function body with the body
11934 wrapped in the try/finally TF. */
11936 gimple_seq_add_stmt (&seq
, new_bind
);
11937 gimple_set_body (fndecl
, seq
);
11941 if ((flag_sanitize
& SANITIZE_THREAD
) != 0
11942 && !lookup_attribute ("no_sanitize_thread", DECL_ATTRIBUTES (fndecl
)))
11944 gcall
*call
= gimple_build_call_internal (IFN_TSAN_FUNC_EXIT
, 0);
11945 gimple
*tf
= gimple_build_try (seq
, call
, GIMPLE_TRY_FINALLY
);
11946 gbind
*new_bind
= gimple_build_bind (NULL
, tf
, gimple_bind_block (bind
));
11947 /* Clear the block for BIND, since it is no longer directly inside
11948 the function, but within a try block. */
11949 gimple_bind_set_block (bind
, NULL
);
11950 /* Replace the current function body with the body
11951 wrapped in the try/finally TF. */
11953 gimple_seq_add_stmt (&seq
, new_bind
);
11954 gimple_set_body (fndecl
, seq
);
11957 DECL_SAVED_TREE (fndecl
) = NULL_TREE
;
11958 cfun
->curr_properties
|= PROP_gimple_any
;
11962 dump_function (TDI_generic
, fndecl
);
11965 /* Return a dummy expression of type TYPE in order to keep going after an
11969 dummy_object (tree type
)
11971 tree t
= build_int_cst (build_pointer_type (type
), 0);
11972 return build2 (MEM_REF
, type
, t
, t
);
11975 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
11976 builtin function, but a very special sort of operator. */
11978 enum gimplify_status
11979 gimplify_va_arg_expr (tree
*expr_p
, gimple_seq
*pre_p
,
11980 gimple_seq
*post_p ATTRIBUTE_UNUSED
)
11982 tree promoted_type
, have_va_type
;
11983 tree valist
= TREE_OPERAND (*expr_p
, 0);
11984 tree type
= TREE_TYPE (*expr_p
);
11985 tree t
, tag
, aptag
;
11986 location_t loc
= EXPR_LOCATION (*expr_p
);
11988 /* Verify that valist is of the proper type. */
11989 have_va_type
= TREE_TYPE (valist
);
11990 if (have_va_type
== error_mark_node
)
11992 have_va_type
= targetm
.canonical_va_list_type (have_va_type
);
11993 if (have_va_type
== NULL_TREE
11994 && TREE_CODE (valist
) == ADDR_EXPR
)
11995 /* Handle 'Case 1: Not an array type' from c-common.c/build_va_arg. */
11997 = targetm
.canonical_va_list_type (TREE_TYPE (TREE_TYPE (valist
)));
11998 gcc_assert (have_va_type
!= NULL_TREE
);
12000 /* Generate a diagnostic for requesting data of a type that cannot
12001 be passed through `...' due to type promotion at the call site. */
12002 if ((promoted_type
= lang_hooks
.types
.type_promotes_to (type
))
12005 static bool gave_help
;
12007 /* Use the expansion point to handle cases such as passing bool (defined
12008 in a system header) through `...'. */
12009 source_location xloc
12010 = expansion_point_location_if_in_system_header (loc
);
12012 /* Unfortunately, this is merely undefined, rather than a constraint
12013 violation, so we cannot make this an error. If this call is never
12014 executed, the program is still strictly conforming. */
12015 warned
= warning_at (xloc
, 0,
12016 "%qT is promoted to %qT when passed through %<...%>",
12017 type
, promoted_type
);
12018 if (!gave_help
&& warned
)
12021 inform (xloc
, "(so you should pass %qT not %qT to %<va_arg%>)",
12022 promoted_type
, type
);
12025 /* We can, however, treat "undefined" any way we please.
12026 Call abort to encourage the user to fix the program. */
12028 inform (xloc
, "if this code is reached, the program will abort");
12029 /* Before the abort, allow the evaluation of the va_list
12030 expression to exit or longjmp. */
12031 gimplify_and_add (valist
, pre_p
);
12032 t
= build_call_expr_loc (loc
,
12033 builtin_decl_implicit (BUILT_IN_TRAP
), 0);
12034 gimplify_and_add (t
, pre_p
);
12036 /* This is dead code, but go ahead and finish so that the
12037 mode of the result comes out right. */
12038 *expr_p
= dummy_object (type
);
12039 return GS_ALL_DONE
;
12042 tag
= build_int_cst (build_pointer_type (type
), 0);
12043 aptag
= build_int_cst (TREE_TYPE (valist
), 0);
12045 *expr_p
= build_call_expr_internal_loc (loc
, IFN_VA_ARG
, type
, 3,
12046 valist
, tag
, aptag
);
12048 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
12049 needs to be expanded. */
12050 cfun
->curr_properties
&= ~PROP_gimple_lva
;
12055 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
12057 DST/SRC are the destination and source respectively. You can pass
12058 ungimplified trees in DST or SRC, in which case they will be
12059 converted to a gimple operand if necessary.
12061 This function returns the newly created GIMPLE_ASSIGN tuple. */
12064 gimplify_assign (tree dst
, tree src
, gimple_seq
*seq_p
)
12066 tree t
= build2 (MODIFY_EXPR
, TREE_TYPE (dst
), dst
, src
);
12067 gimplify_and_add (t
, seq_p
);
12069 return gimple_seq_last_stmt (*seq_p
);
12073 gimplify_hasher::hash (const elt_t
*p
)
12076 return iterative_hash_expr (t
, 0);
12080 gimplify_hasher::equal (const elt_t
*p1
, const elt_t
*p2
)
12084 enum tree_code code
= TREE_CODE (t1
);
12086 if (TREE_CODE (t2
) != code
12087 || TREE_TYPE (t1
) != TREE_TYPE (t2
))
12090 if (!operand_equal_p (t1
, t2
, 0))
12093 /* Only allow them to compare equal if they also hash equal; otherwise
12094 results are nondeterminate, and we fail bootstrap comparison. */
12095 gcc_checking_assert (hash (p1
) == hash (p2
));