diff mbox series

[C,v3] Fix ICEs related to VM types in C 2/2

Message ID d4357b98b6e61dc227db9b21e21e5878af6a7ceb.camel@tugraz.at
State New
Headers show
Series [C,v3] Fix ICEs related to VM types in C 2/2 | expand

Commit Message

Martin Uecker May 22, 2023, 5:23 p.m. UTC
This version contains the middle-end changes for PR109450
and test cases as before.  The main middle-end change is that
we use gimplify_type_sizes also for parameters and remove
the special code that also walked into pointers (which is
incorrect).  

In addition, in the C FE this patch now also adds DECL_EXPR
for vm-types which are pointed-to by parameters declared
as arrays.  The new function created contains the exact
code previously used only for regular pointers, and is
now also called for parameters declared as arrays.


Martin







    Fix ICEs related to VM types in C 2/2 [PR109450]
    
    Size expressions were sometimes lost and not gimplified correctly,
    leading to ICEs and incorrect evaluation order.  Fix this by 1) not
    recursing pointers when gimplifying parameters in the middle-end
    (the code is merged with gimplify_type_sizes), which is incorrect
    because it might access variables declared later for incomplete
    structs, and 2) adding a decl expr for variably-modified arrays
    that are pointed to by parameters declared as arrays.
    
            PR c/109450
    
            gcc/
            * c/c-decl.cc (add_decl_expr): New function.
            (grokdeclarator): Add decl expr for size expression in
            types pointed to by parameters declared as arrays.
            * function.cc (gimplify_parm_type): Remove function.
            (gimplify_parameters): Call gimplify_parm_sizes.
            * gimplify.cc (gimplify_type_sizes): Make function static.
            (gimplify_parm_sizes): New function.
    
            gcc/testsuite/
            * gcc.dg/pr109450-1.c: New test.
            * gcc.dg/pr109450-2.c: New test.
            * gcc.dg/vla-26.c: New test.

Comments

Joseph Myers May 22, 2023, 8:22 p.m. UTC | #1
On Mon, 22 May 2023, Martin Uecker via Gcc-patches wrote:

> +static void
> +add_decl_expr(location_t loc, enum decl_context decl_context, tree type, tree *expr)

Missing space before '(', and the line should be wrapped to be no more 
than 80 columns.

The C front-end changes are OK with those fixes.  The testsuite changes 
are also OK.
Richard Biener May 23, 2023, 6:13 a.m. UTC | #2
On Mon, May 22, 2023 at 7:24 PM Martin Uecker via Gcc-patches
<gcc-patches@gcc.gnu.org> wrote:
>
>
>
> This version contains the middle-end changes for PR109450
> and test cases as before.  The main middle-end change is that
> we use gimplify_type_sizes also for parameters and remove
> the special code that also walked into pointers (which is
> incorrect).
>
> In addition, in the C FE this patch now also adds DECL_EXPR
> for vm-types which are pointed-to by parameters declared
> as arrays.  The new function created contains the exact
> code previously used only for regular pointers, and is
> now also called for parameters declared as arrays.
>
>
> Martin
>
>
>
>
>
>
>
>     Fix ICEs related to VM types in C 2/2 [PR109450]
>
>     Size expressions were sometimes lost and not gimplified correctly,
>     leading to ICEs and incorrect evaluation order.  Fix this by 1) not
>     recursing pointers when gimplifying parameters in the middle-end
>     (the code is merged with gimplify_type_sizes), which is incorrect
>     because it might access variables declared later for incomplete
>     structs, and 2) adding a decl expr for variably-modified arrays
>     that are pointed to by parameters declared as arrays.
>
>             PR c/109450
>
>             gcc/
>             * c/c-decl.cc (add_decl_expr): New function.
>             (grokdeclarator): Add decl expr for size expression in
>             types pointed to by parameters declared as arrays.
>             * function.cc (gimplify_parm_type): Remove function.
>             (gimplify_parameters): Call gimplify_parm_sizes.
>             * gimplify.cc (gimplify_type_sizes): Make function static.
>             (gimplify_parm_sizes): New function.
>
>             gcc/testsuite/
>             * gcc.dg/pr109450-1.c: New test.
>             * gcc.dg/pr109450-2.c: New test.
>             * gcc.dg/vla-26.c: New test.
>
> diff --git a/gcc/c/c-decl.cc b/gcc/c/c-decl.cc
> index 494d3cf1747..c35347734b2 100644
> --- a/gcc/c/c-decl.cc
> +++ b/gcc/c/c-decl.cc
> @@ -6490,6 +6490,55 @@ smallest_type_quals_location (const location_t *locations,
>    return loc;
>  }
>
> +
> +/* We attach an artificial TYPE_DECL to pointed-to type
> +   and arrange for it to be included in a DECL_EXPR.  This
> +   forces the sizes evaluation at a safe point and ensures it
> +   is not deferred until e.g. within a deeper conditional context.
> +
> +   PARM contexts have no enclosing statement list that
> +   can hold the DECL_EXPR, so we need to use a BIND_EXPR
> +   instead, and add it to the list of expressions that
> +   need to be evaluated.
> +
> +   TYPENAME contexts do have an enclosing statement list,
> +   but it would be incorrect to use it, as the size should
> +   only be evaluated if the containing expression is
> +   evaluated.  We might also be in the middle of an
> +   expression with side effects on the pointed-to type size
> +   "arguments" prior to the pointer declaration point and
> +   the fake TYPE_DECL in the enclosing context would force
> +   the size evaluation prior to the side effects.  We therefore
> +   use BIND_EXPRs in TYPENAME contexts too.  */
> +static void
> +add_decl_expr(location_t loc, enum decl_context decl_context, tree type, tree *expr)
> +{
> +  tree bind = NULL_TREE;
> +  if (decl_context == TYPENAME || decl_context == PARM || decl_context == FIELD)
> +    {
> +      bind = build3 (BIND_EXPR, void_type_node, NULL_TREE, NULL_TREE, NULL_TREE);
> +      TREE_SIDE_EFFECTS (bind) = 1;
> +      BIND_EXPR_BODY (bind) = push_stmt_list ();
> +      push_scope ();
> +    }
> +
> +  tree decl = build_decl (loc, TYPE_DECL, NULL_TREE, type);
> +  pushdecl (decl);
> +  DECL_ARTIFICIAL (decl) = 1;
> +  add_stmt (build_stmt (DECL_SOURCE_LOCATION (decl), DECL_EXPR, decl));
> +  TYPE_NAME (type) = decl;
> +
> +  if (bind)
> +    {
> +      pop_scope ();
> +      BIND_EXPR_BODY (bind) = pop_stmt_list (BIND_EXPR_BODY (bind));
> +      if (*expr)
> +       *expr = build2 (COMPOUND_EXPR, void_type_node, *expr, bind);
> +      else
> +       *expr = bind;
> +    }
> +}
> +
>  /* Given declspecs and a declarator,
>     determine the name and type of the object declared
>     and construct a ..._DECL node for it.
> @@ -7474,58 +7523,9 @@ grokdeclarator (const struct c_declarator *declarator,
>
>                This is expected to happen automatically when the pointed-to
>                type has a name/declaration of it's own, but special attention
> -              is required if the type is anonymous.
> -
> -              We attach an artificial TYPE_DECL to such pointed-to type
> -              and arrange for it to be included in a DECL_EXPR.  This
> -              forces the sizes evaluation at a safe point and ensures it
> -              is not deferred until e.g. within a deeper conditional context.
> -
> -              PARM contexts have no enclosing statement list that
> -              can hold the DECL_EXPR, so we need to use a BIND_EXPR
> -              instead, and add it to the list of expressions that
> -              need to be evaluated.
> -
> -              TYPENAME contexts do have an enclosing statement list,
> -              but it would be incorrect to use it, as the size should
> -              only be evaluated if the containing expression is
> -              evaluated.  We might also be in the middle of an
> -              expression with side effects on the pointed-to type size
> -              "arguments" prior to the pointer declaration point and
> -              the fake TYPE_DECL in the enclosing context would force
> -              the size evaluation prior to the side effects.  We therefore
> -              use BIND_EXPRs in TYPENAME contexts too.  */
> -           if (!TYPE_NAME (type)
> -               && c_type_variably_modified_p (type))
> -             {
> -               tree bind = NULL_TREE;
> -               if (decl_context == TYPENAME || decl_context == PARM
> -                   || decl_context == FIELD)
> -                 {
> -                   bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
> -                                  NULL_TREE, NULL_TREE);
> -                   TREE_SIDE_EFFECTS (bind) = 1;
> -                   BIND_EXPR_BODY (bind) = push_stmt_list ();
> -                   push_scope ();
> -                 }
> -               tree decl = build_decl (loc, TYPE_DECL, NULL_TREE, type);
> -               pushdecl (decl);
> -               DECL_ARTIFICIAL (decl) = 1;
> -               add_stmt (build_stmt (DECL_SOURCE_LOCATION (decl), DECL_EXPR, decl));
> -               TYPE_NAME (type) = decl;
> -
> -               if (bind)
> -                 {
> -                   pop_scope ();
> -                   BIND_EXPR_BODY (bind)
> -                     = pop_stmt_list (BIND_EXPR_BODY (bind));
> -                   if (*expr)
> -                     *expr = build2 (COMPOUND_EXPR, void_type_node, *expr,
> -                                     bind);
> -                   else
> -                     *expr = bind;
> -                 }
> -             }
> +              is required if the type is anonymous. */
> +           if (!TYPE_NAME (type) && c_type_variably_modified_p (type))
> +             add_decl_expr (loc, decl_context, type, expr);
>
>             type = c_build_pointer_type (type);
>
> @@ -7787,6 +7787,11 @@ grokdeclarator (const struct c_declarator *declarator,
>             if (type_quals)
>               type = c_build_qualified_type (type, type_quals, orig_qual_type,
>                                              orig_qual_indirect);
> +
> +           /* The pointed-to type may need a decl expr (see above).  */
> +           if (!TYPE_NAME (type) && c_type_variably_modified_p (type))
> +             add_decl_expr (loc, decl_context, type, expr);
> +
>             type = c_build_pointer_type (type);
>             type_quals = array_ptr_quals;
>             if (type_quals)
> diff --git a/gcc/function.cc b/gcc/function.cc
> index f0ae641512d..5699b9d495d 100644
> --- a/gcc/function.cc
> +++ b/gcc/function.cc
> @@ -3872,30 +3872,6 @@ assign_parms (tree fndecl)
>      }
>  }
>
> -/* A subroutine of gimplify_parameters, invoked via walk_tree.
> -   For all seen types, gimplify their sizes.  */
> -
> -static tree
> -gimplify_parm_type (tree *tp, int *walk_subtrees, void *data)
> -{
> -  tree t = *tp;
> -
> -  *walk_subtrees = 0;
> -  if (TYPE_P (t))
> -    {
> -      if (POINTER_TYPE_P (t))
> -       *walk_subtrees = 1;
> -      else if (TYPE_SIZE (t) && !TREE_CONSTANT (TYPE_SIZE (t))
> -              && !TYPE_SIZES_GIMPLIFIED (t))
> -       {
> -         gimplify_type_sizes (t, (gimple_seq *) data);
> -         *walk_subtrees = 1;
> -       }
> -    }
> -
> -  return NULL;
> -}
> -
>  /* Gimplify the parameter list for current_function_decl.  This involves
>     evaluating SAVE_EXPRs of variable sized parameters and generating code
>     to implement callee-copies reference parameters.  Returns a sequence of
> @@ -3931,14 +3907,7 @@ gimplify_parameters (gimple_seq *cleanup)
>          SAVE_EXPRs (amongst others) onto a pending sizes list.  This
>          turned out to be less than manageable in the gimple world.
>          Now we have to hunt them down ourselves.  */
> -      walk_tree_without_duplicates (&data.arg.type,
> -                                   gimplify_parm_type, &stmts);
> -
> -      if (TREE_CODE (DECL_SIZE_UNIT (parm)) != INTEGER_CST)
> -       {
> -         gimplify_one_sizepos (&DECL_SIZE (parm), &stmts);
> -         gimplify_one_sizepos (&DECL_SIZE_UNIT (parm), &stmts);
> -       }
> +      gimplify_parm_sizes (parm, &stmts);
>
>        if (data.arg.pass_by_reference)
>         {
> diff --git a/gcc/gimplify.cc b/gcc/gimplify.cc
> index d0d16a24820..fd990c328eb 100644
> --- a/gcc/gimplify.cc
> +++ b/gcc/gimplify.cc
> @@ -242,6 +242,7 @@ static struct gimplify_omp_ctx *gimplify_omp_ctxp;
>  static bool in_omp_construct;
>
>  /* Forward declaration.  */
> +static void gimplify_type_sizes (tree type, gimple_seq *list_p);
>  static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
>  static hash_map<tree, tree> *oacc_declare_returns;
>  static enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
> @@ -17425,7 +17426,7 @@ gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
>  /* Look through TYPE for variable-sized objects and gimplify each such
>     size that we find.  Add to LIST_P any statements generated.  */
>
> -void
> +static void
>  gimplify_type_sizes (tree type, gimple_seq *list_p)
>  {
>    if (type == NULL || type == error_mark_node)
> @@ -17533,6 +17534,21 @@ gimplify_type_sizes (tree type, gimple_seq *list_p)
>      }
>  }
>
> +/* Gimplify sizes in parameter declarations.  */
> +
> +void
> +gimplify_parm_sizes (tree parm, gimple_seq *list_p)

Can you instead inline this at the single caller in gimplify_parameters?
It looks like both gimplify_type_sizes and gimplify_one_sizepos are
already exported.  So just add the missing gimplify_type_sizes () call
at the single call site.

The middle-end changes are OK with that change.

Thanks,
Richard.

> +{
> +  gimplify_type_sizes (TREE_TYPE (parm), list_p);
> +
> +  if (TREE_CODE (DECL_SIZE_UNIT (parm)) != INTEGER_CST)
> +    {
> +      gimplify_one_sizepos (&DECL_SIZE (parm), list_p);
> +      gimplify_one_sizepos (&DECL_SIZE_UNIT (parm), list_p);
> +    }
> +}
> +
> +
>  /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
>     a size or position, has had all of its SAVE_EXPRs evaluated.
>     We add any required statements to *STMT_P.  */
> diff --git a/gcc/gimplify.h b/gcc/gimplify.h
> index f4a3eea2606..17ea0580647 100644
> --- a/gcc/gimplify.h
> +++ b/gcc/gimplify.h
> @@ -78,7 +78,7 @@ extern enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
>
>  int omp_construct_selector_matches (enum tree_code *, int, int *);
>
> -extern void gimplify_type_sizes (tree, gimple_seq *);
> +extern void gimplify_parm_sizes (tree, gimple_seq *);
>  extern void gimplify_one_sizepos (tree *, gimple_seq *);
>  extern gbind *gimplify_body (tree, bool);
>  extern enum gimplify_status gimplify_arg (tree *, gimple_seq *, location_t,
> diff --git a/gcc/testsuite/gcc.dg/pr109450-1.c b/gcc/testsuite/gcc.dg/pr109450-1.c
> new file mode 100644
> index 00000000000..aec127f2afc
> --- /dev/null
> +++ b/gcc/testsuite/gcc.dg/pr109450-1.c
> @@ -0,0 +1,21 @@
> +/* PR c/109450
> + * { dg-do run }
> + * { dg-options "-std=gnu99" }
> + * */
> +
> +int bar(int n, struct foo* x)  /* { dg-warning "not be visible" } */
> +{
> +       int a = n;
> +       struct foo { char buf[n++]; }* p = x;
> +       return a;
> +}
> +
> +int main()
> +{
> +       if (1 != bar(1, 0))
> +               __builtin_abort();
> +}
> +
> +
> +
> +
> diff --git a/gcc/testsuite/gcc.dg/pr109450-2.c b/gcc/testsuite/gcc.dg/pr109450-2.c
> new file mode 100644
> index 00000000000..06799f6df23
> --- /dev/null
> +++ b/gcc/testsuite/gcc.dg/pr109450-2.c
> @@ -0,0 +1,18 @@
> +/* PR c/109450
> + * { dg-do run }
> + * { dg-options "-std=gnu99" }
> + * */
> +
> +int bar(int n, struct foo *x)  /* { dg-warning "not be visible" } */
> +{
> +       int a = n;
> +       struct foo { char buf[a++]; }* p = x;
> +       return n == a;
> +}
> +
> +int main()
> +{
> +       if (bar(1, 0))
> +               __builtin_abort();
> +}
> +
> diff --git a/gcc/testsuite/gcc.dg/vla-26.c b/gcc/testsuite/gcc.dg/vla-26.c
> new file mode 100644
> index 00000000000..5d2fa3e280a
> --- /dev/null
> +++ b/gcc/testsuite/gcc.dg/vla-26.c
> @@ -0,0 +1,15 @@
> +/* { dg-do compile } */
> +/* { dg-options "-std=c99 -O2" } */
> +
> +void ed(int n, float s[3][n])
> +{
> +       for (int i = 0; i < n; i++)
> +               s[1][i];
> +}
> +
> +void e(int n, float s[3][n])
> +{
> +       ed(n, s);
> +}
> +
> +
>
>
Martin Uecker May 23, 2023, 6:24 a.m. UTC | #3
Am Dienstag, dem 23.05.2023 um 08:13 +0200 schrieb Richard Biener:
> On Mon, May 22, 2023 at 7:24 PM Martin Uecker via Gcc-patches
> <gcc-patches@gcc.gnu.org> wrote:
> > 
> > 
> > 
> > This version contains the middle-end changes for PR109450
> > and test cases as before.  The main middle-end change is that
> > we use gimplify_type_sizes also for parameters and remove
> > the special code that also walked into pointers (which is
> > incorrect).
> > 
> > In addition, in the C FE this patch now also adds DECL_EXPR
> > for vm-types which are pointed-to by parameters declared
> > as arrays.  The new function created contains the exact
> > code previously used only for regular pointers, and is
> > now also called for parameters declared as arrays.
> > 
> > 
> > Martin
> > 
> > 
> > 
> > 
> > 
> > 
> > 
> >     Fix ICEs related to VM types in C 2/2 [PR109450]
> > 
> >     Size expressions were sometimes lost and not gimplified correctly,
> >     leading to ICEs and incorrect evaluation order.  Fix this by 1) not
> >     recursing pointers when gimplifying parameters in the middle-end
> >     (the code is merged with gimplify_type_sizes), which is incorrect
> >     because it might access variables declared later for incomplete
> >     structs, and 2) adding a decl expr for variably-modified arrays
> >     that are pointed to by parameters declared as arrays.
> > 
> >             PR c/109450
> > 
> >             gcc/
> >             * c/c-decl.cc (add_decl_expr): New function.
> >             (grokdeclarator): Add decl expr for size expression in
> >             types pointed to by parameters declared as arrays.
> >             * function.cc (gimplify_parm_type): Remove function.
> >             (gimplify_parameters): Call gimplify_parm_sizes.
> >             * gimplify.cc (gimplify_type_sizes): Make function static.
> >             (gimplify_parm_sizes): New function.
> > 
> >             gcc/testsuite/
> >             * gcc.dg/pr109450-1.c: New test.
> >             * gcc.dg/pr109450-2.c: New test.
> >             * gcc.dg/vla-26.c: New test.
> > 
> > diff --git a/gcc/c/c-decl.cc b/gcc/c/c-decl.cc
> > index 494d3cf1747..c35347734b2 100644
> > --- a/gcc/c/c-decl.cc
> > +++ b/gcc/c/c-decl.cc
> > @@ -6490,6 +6490,55 @@ smallest_type_quals_location (const location_t *locations,
> >    return loc;
> >  }
> > 
> > +
> > +/* We attach an artificial TYPE_DECL to pointed-to type
> > +   and arrange for it to be included in a DECL_EXPR.  This
> > +   forces the sizes evaluation at a safe point and ensures it
> > +   is not deferred until e.g. within a deeper conditional context.
> > +
> > +   PARM contexts have no enclosing statement list that
> > +   can hold the DECL_EXPR, so we need to use a BIND_EXPR
> > +   instead, and add it to the list of expressions that
> > +   need to be evaluated.
> > +
> > +   TYPENAME contexts do have an enclosing statement list,
> > +   but it would be incorrect to use it, as the size should
> > +   only be evaluated if the containing expression is
> > +   evaluated.  We might also be in the middle of an
> > +   expression with side effects on the pointed-to type size
> > +   "arguments" prior to the pointer declaration point and
> > +   the fake TYPE_DECL in the enclosing context would force
> > +   the size evaluation prior to the side effects.  We therefore
> > +   use BIND_EXPRs in TYPENAME contexts too.  */
> > +static void
> > +add_decl_expr(location_t loc, enum decl_context decl_context, tree type, tree *expr)
> > +{
> > +  tree bind = NULL_TREE;
> > +  if (decl_context == TYPENAME || decl_context == PARM || decl_context == FIELD)
> > +    {
> > +      bind = build3 (BIND_EXPR, void_type_node, NULL_TREE, NULL_TREE, NULL_TREE);
> > +      TREE_SIDE_EFFECTS (bind) = 1;
> > +      BIND_EXPR_BODY (bind) = push_stmt_list ();
> > +      push_scope ();
> > +    }
> > +
> > +  tree decl = build_decl (loc, TYPE_DECL, NULL_TREE, type);
> > +  pushdecl (decl);
> > +  DECL_ARTIFICIAL (decl) = 1;
> > +  add_stmt (build_stmt (DECL_SOURCE_LOCATION (decl), DECL_EXPR, decl));
> > +  TYPE_NAME (type) = decl;
> > +
> > +  if (bind)
> > +    {
> > +      pop_scope ();
> > +      BIND_EXPR_BODY (bind) = pop_stmt_list (BIND_EXPR_BODY (bind));
> > +      if (*expr)
> > +       *expr = build2 (COMPOUND_EXPR, void_type_node, *expr, bind);
> > +      else
> > +       *expr = bind;
> > +    }
> > +}
> > +
> >  /* Given declspecs and a declarator,
> >     determine the name and type of the object declared
> >     and construct a ..._DECL node for it.
> > @@ -7474,58 +7523,9 @@ grokdeclarator (const struct c_declarator *declarator,
> > 
> >                This is expected to happen automatically when the pointed-to
> >                type has a name/declaration of it's own, but special attention
> > -              is required if the type is anonymous.
> > -
> > -              We attach an artificial TYPE_DECL to such pointed-to type
> > -              and arrange for it to be included in a DECL_EXPR.  This
> > -              forces the sizes evaluation at a safe point and ensures it
> > -              is not deferred until e.g. within a deeper conditional context.
> > -
> > -              PARM contexts have no enclosing statement list that
> > -              can hold the DECL_EXPR, so we need to use a BIND_EXPR
> > -              instead, and add it to the list of expressions that
> > -              need to be evaluated.
> > -
> > -              TYPENAME contexts do have an enclosing statement list,
> > -              but it would be incorrect to use it, as the size should
> > -              only be evaluated if the containing expression is
> > -              evaluated.  We might also be in the middle of an
> > -              expression with side effects on the pointed-to type size
> > -              "arguments" prior to the pointer declaration point and
> > -              the fake TYPE_DECL in the enclosing context would force
> > -              the size evaluation prior to the side effects.  We therefore
> > -              use BIND_EXPRs in TYPENAME contexts too.  */
> > -           if (!TYPE_NAME (type)
> > -               && c_type_variably_modified_p (type))
> > -             {
> > -               tree bind = NULL_TREE;
> > -               if (decl_context == TYPENAME || decl_context == PARM
> > -                   || decl_context == FIELD)
> > -                 {
> > -                   bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
> > -                                  NULL_TREE, NULL_TREE);
> > -                   TREE_SIDE_EFFECTS (bind) = 1;
> > -                   BIND_EXPR_BODY (bind) = push_stmt_list ();
> > -                   push_scope ();
> > -                 }
> > -               tree decl = build_decl (loc, TYPE_DECL, NULL_TREE, type);
> > -               pushdecl (decl);
> > -               DECL_ARTIFICIAL (decl) = 1;
> > -               add_stmt (build_stmt (DECL_SOURCE_LOCATION (decl), DECL_EXPR, decl));
> > -               TYPE_NAME (type) = decl;
> > -
> > -               if (bind)
> > -                 {
> > -                   pop_scope ();
> > -                   BIND_EXPR_BODY (bind)
> > -                     = pop_stmt_list (BIND_EXPR_BODY (bind));
> > -                   if (*expr)
> > -                     *expr = build2 (COMPOUND_EXPR, void_type_node, *expr,
> > -                                     bind);
> > -                   else
> > -                     *expr = bind;
> > -                 }
> > -             }
> > +              is required if the type is anonymous. */
> > +           if (!TYPE_NAME (type) && c_type_variably_modified_p (type))
> > +             add_decl_expr (loc, decl_context, type, expr);
> > 
> >             type = c_build_pointer_type (type);
> > 
> > @@ -7787,6 +7787,11 @@ grokdeclarator (const struct c_declarator *declarator,
> >             if (type_quals)
> >               type = c_build_qualified_type (type, type_quals, orig_qual_type,
> >                                              orig_qual_indirect);
> > +
> > +           /* The pointed-to type may need a decl expr (see above).  */
> > +           if (!TYPE_NAME (type) && c_type_variably_modified_p (type))
> > +             add_decl_expr (loc, decl_context, type, expr);
> > +
> >             type = c_build_pointer_type (type);
> >             type_quals = array_ptr_quals;
> >             if (type_quals)
> > diff --git a/gcc/function.cc b/gcc/function.cc
> > index f0ae641512d..5699b9d495d 100644
> > --- a/gcc/function.cc
> > +++ b/gcc/function.cc
> > @@ -3872,30 +3872,6 @@ assign_parms (tree fndecl)
> >      }
> >  }
> > 
> > -/* A subroutine of gimplify_parameters, invoked via walk_tree.
> > -   For all seen types, gimplify their sizes.  */
> > -
> > -static tree
> > -gimplify_parm_type (tree *tp, int *walk_subtrees, void *data)
> > -{
> > -  tree t = *tp;
> > -
> > -  *walk_subtrees = 0;
> > -  if (TYPE_P (t))
> > -    {
> > -      if (POINTER_TYPE_P (t))
> > -       *walk_subtrees = 1;
> > -      else if (TYPE_SIZE (t) && !TREE_CONSTANT (TYPE_SIZE (t))
> > -              && !TYPE_SIZES_GIMPLIFIED (t))
> > -       {
> > -         gimplify_type_sizes (t, (gimple_seq *) data);
> > -         *walk_subtrees = 1;
> > -       }
> > -    }
> > -
> > -  return NULL;
> > -}
> > -
> >  /* Gimplify the parameter list for current_function_decl.  This involves
> >     evaluating SAVE_EXPRs of variable sized parameters and generating code
> >     to implement callee-copies reference parameters.  Returns a sequence of
> > @@ -3931,14 +3907,7 @@ gimplify_parameters (gimple_seq *cleanup)
> >          SAVE_EXPRs (amongst others) onto a pending sizes list.  This
> >          turned out to be less than manageable in the gimple world.
> >          Now we have to hunt them down ourselves.  */
> > -      walk_tree_without_duplicates (&data.arg.type,
> > -                                   gimplify_parm_type, &stmts);
> > -
> > -      if (TREE_CODE (DECL_SIZE_UNIT (parm)) != INTEGER_CST)
> > -       {
> > -         gimplify_one_sizepos (&DECL_SIZE (parm), &stmts);
> > -         gimplify_one_sizepos (&DECL_SIZE_UNIT (parm), &stmts);
> > -       }
> > +      gimplify_parm_sizes (parm, &stmts);
> > 
> >        if (data.arg.pass_by_reference)
> >         {
> > diff --git a/gcc/gimplify.cc b/gcc/gimplify.cc
> > index d0d16a24820..fd990c328eb 100644
> > --- a/gcc/gimplify.cc
> > +++ b/gcc/gimplify.cc
> > @@ -242,6 +242,7 @@ static struct gimplify_omp_ctx *gimplify_omp_ctxp;
> >  static bool in_omp_construct;
> > 
> >  /* Forward declaration.  */
> > +static void gimplify_type_sizes (tree type, gimple_seq *list_p);
> >  static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
> >  static hash_map<tree, tree> *oacc_declare_returns;
> >  static enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
> > @@ -17425,7 +17426,7 @@ gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
> >  /* Look through TYPE for variable-sized objects and gimplify each such
> >     size that we find.  Add to LIST_P any statements generated.  */
> > 
> > -void
> > +static void
> >  gimplify_type_sizes (tree type, gimple_seq *list_p)
> >  {
> >    if (type == NULL || type == error_mark_node)
> > @@ -17533,6 +17534,21 @@ gimplify_type_sizes (tree type, gimple_seq *list_p)
> >      }
> >  }
> > 
> > +/* Gimplify sizes in parameter declarations.  */
> > +
> > +void
> > +gimplify_parm_sizes (tree parm, gimple_seq *list_p)
> 
> Can you instead inline this at the single caller in gimplify_parameters?
> It looks like both gimplify_type_sizes and gimplify_one_sizepos are
> already exported.  So just add the missing gimplify_type_sizes () call
> at the single call site.
> 
> The middle-end changes are OK with that change.

Thanks Richard!  

I did this in this way because this was the only outside use of
gimplify_type_sizes. Then one can unexport gimplify_type_size.
In fact, it is declared static (see above) and removed from the
header (see below) in the patch. I thought this is better logical
encapsulation.   (BTW:  gimplify_one_sizepos then has only 
one remaining use in the Ada FE, so maybe we make a copy there
and also unexport it?).

What do you think?

Martin

> Thanks,
> Richard.
> 
> > +{
> > +  gimplify_type_sizes (TREE_TYPE (parm), list_p);
> > +
> > +  if (TREE_CODE (DECL_SIZE_UNIT (parm)) != INTEGER_CST)
> > +    {
> > +      gimplify_one_sizepos (&DECL_SIZE (parm), list_p);
> > +      gimplify_one_sizepos (&DECL_SIZE_UNIT (parm), list_p);
> > +    }
> > +}
> > +
> > +
> >  /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
> >     a size or position, has had all of its SAVE_EXPRs evaluated.
> >     We add any required statements to *STMT_P.  */
> > diff --git a/gcc/gimplify.h b/gcc/gimplify.h
> > index f4a3eea2606..17ea0580647 100644
> > --- a/gcc/gimplify.h
> > +++ b/gcc/gimplify.h
> > @@ -78,7 +78,7 @@ extern enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
> > 
> >  int omp_construct_selector_matches (enum tree_code *, int, int *);
> > 
> > -extern void gimplify_type_sizes (tree, gimple_seq *);
> > +extern void gimplify_parm_sizes (tree, gimple_seq *);
> >  extern void gimplify_one_sizepos (tree *, gimple_seq *);
> >  extern gbind *gimplify_body (tree, bool);
> >  extern enum gimplify_status gimplify_arg (tree *, gimple_seq *, location_t,
> > diff --git a/gcc/testsuite/gcc.dg/pr109450-1.c b/gcc/testsuite/gcc.dg/pr109450-1.c
> > new file mode 100644
> > index 00000000000..aec127f2afc
> > --- /dev/null
> > +++ b/gcc/testsuite/gcc.dg/pr109450-1.c
> > @@ -0,0 +1,21 @@
> > +/* PR c/109450
> > + * { dg-do run }
> > + * { dg-options "-std=gnu99" }
> > + * */
> > +
> > +int bar(int n, struct foo* x)  /* { dg-warning "not be visible" } */
> > +{
> > +       int a = n;
> > +       struct foo { char buf[n++]; }* p = x;
> > +       return a;
> > +}
> > +
> > +int main()
> > +{
> > +       if (1 != bar(1, 0))
> > +               __builtin_abort();
> > +}
> > +
> > +
> > +
> > +
> > diff --git a/gcc/testsuite/gcc.dg/pr109450-2.c b/gcc/testsuite/gcc.dg/pr109450-2.c
> > new file mode 100644
> > index 00000000000..06799f6df23
> > --- /dev/null
> > +++ b/gcc/testsuite/gcc.dg/pr109450-2.c
> > @@ -0,0 +1,18 @@
> > +/* PR c/109450
> > + * { dg-do run }
> > + * { dg-options "-std=gnu99" }
> > + * */
> > +
> > +int bar(int n, struct foo *x)  /* { dg-warning "not be visible" } */
> > +{
> > +       int a = n;
> > +       struct foo { char buf[a++]; }* p = x;
> > +       return n == a;
> > +}
> > +
> > +int main()
> > +{
> > +       if (bar(1, 0))
> > +               __builtin_abort();
> > +}
> > +
> > diff --git a/gcc/testsuite/gcc.dg/vla-26.c b/gcc/testsuite/gcc.dg/vla-26.c
> > new file mode 100644
> > index 00000000000..5d2fa3e280a
> > --- /dev/null
> > +++ b/gcc/testsuite/gcc.dg/vla-26.c
> > @@ -0,0 +1,15 @@
> > +/* { dg-do compile } */
> > +/* { dg-options "-std=c99 -O2" } */
> > +
> > +void ed(int n, float s[3][n])
> > +{
> > +       for (int i = 0; i < n; i++)
> > +               s[1][i];
> > +}
> > +
> > +void e(int n, float s[3][n])
> > +{
> > +       ed(n, s);
> > +}
> > +
> > +
> > 
> >
Richard Biener May 23, 2023, 8:18 a.m. UTC | #4
On Tue, May 23, 2023 at 8:24 AM Martin Uecker <uecker@tugraz.at> wrote:
>
> Am Dienstag, dem 23.05.2023 um 08:13 +0200 schrieb Richard Biener:
> > On Mon, May 22, 2023 at 7:24 PM Martin Uecker via Gcc-patches
> > <gcc-patches@gcc.gnu.org> wrote:
> > >
> > >
> > >
> > > This version contains the middle-end changes for PR109450
> > > and test cases as before.  The main middle-end change is that
> > > we use gimplify_type_sizes also for parameters and remove
> > > the special code that also walked into pointers (which is
> > > incorrect).
> > >
> > > In addition, in the C FE this patch now also adds DECL_EXPR
> > > for vm-types which are pointed-to by parameters declared
> > > as arrays.  The new function created contains the exact
> > > code previously used only for regular pointers, and is
> > > now also called for parameters declared as arrays.
> > >
> > >
> > > Martin
> > >
> > >
> > >
> > >
> > >
> > >
> > >
> > >     Fix ICEs related to VM types in C 2/2 [PR109450]
> > >
> > >     Size expressions were sometimes lost and not gimplified correctly,
> > >     leading to ICEs and incorrect evaluation order.  Fix this by 1) not
> > >     recursing pointers when gimplifying parameters in the middle-end
> > >     (the code is merged with gimplify_type_sizes), which is incorrect
> > >     because it might access variables declared later for incomplete
> > >     structs, and 2) adding a decl expr for variably-modified arrays
> > >     that are pointed to by parameters declared as arrays.
> > >
> > >             PR c/109450
> > >
> > >             gcc/
> > >             * c/c-decl.cc (add_decl_expr): New function.
> > >             (grokdeclarator): Add decl expr for size expression in
> > >             types pointed to by parameters declared as arrays.
> > >             * function.cc (gimplify_parm_type): Remove function.
> > >             (gimplify_parameters): Call gimplify_parm_sizes.
> > >             * gimplify.cc (gimplify_type_sizes): Make function static.
> > >             (gimplify_parm_sizes): New function.
> > >
> > >             gcc/testsuite/
> > >             * gcc.dg/pr109450-1.c: New test.
> > >             * gcc.dg/pr109450-2.c: New test.
> > >             * gcc.dg/vla-26.c: New test.
> > >
> > > diff --git a/gcc/c/c-decl.cc b/gcc/c/c-decl.cc
> > > index 494d3cf1747..c35347734b2 100644
> > > --- a/gcc/c/c-decl.cc
> > > +++ b/gcc/c/c-decl.cc
> > > @@ -6490,6 +6490,55 @@ smallest_type_quals_location (const location_t *locations,
> > >    return loc;
> > >  }
> > >
> > > +
> > > +/* We attach an artificial TYPE_DECL to pointed-to type
> > > +   and arrange for it to be included in a DECL_EXPR.  This
> > > +   forces the sizes evaluation at a safe point and ensures it
> > > +   is not deferred until e.g. within a deeper conditional context.
> > > +
> > > +   PARM contexts have no enclosing statement list that
> > > +   can hold the DECL_EXPR, so we need to use a BIND_EXPR
> > > +   instead, and add it to the list of expressions that
> > > +   need to be evaluated.
> > > +
> > > +   TYPENAME contexts do have an enclosing statement list,
> > > +   but it would be incorrect to use it, as the size should
> > > +   only be evaluated if the containing expression is
> > > +   evaluated.  We might also be in the middle of an
> > > +   expression with side effects on the pointed-to type size
> > > +   "arguments" prior to the pointer declaration point and
> > > +   the fake TYPE_DECL in the enclosing context would force
> > > +   the size evaluation prior to the side effects.  We therefore
> > > +   use BIND_EXPRs in TYPENAME contexts too.  */
> > > +static void
> > > +add_decl_expr(location_t loc, enum decl_context decl_context, tree type, tree *expr)
> > > +{
> > > +  tree bind = NULL_TREE;
> > > +  if (decl_context == TYPENAME || decl_context == PARM || decl_context == FIELD)
> > > +    {
> > > +      bind = build3 (BIND_EXPR, void_type_node, NULL_TREE, NULL_TREE, NULL_TREE);
> > > +      TREE_SIDE_EFFECTS (bind) = 1;
> > > +      BIND_EXPR_BODY (bind) = push_stmt_list ();
> > > +      push_scope ();
> > > +    }
> > > +
> > > +  tree decl = build_decl (loc, TYPE_DECL, NULL_TREE, type);
> > > +  pushdecl (decl);
> > > +  DECL_ARTIFICIAL (decl) = 1;
> > > +  add_stmt (build_stmt (DECL_SOURCE_LOCATION (decl), DECL_EXPR, decl));
> > > +  TYPE_NAME (type) = decl;
> > > +
> > > +  if (bind)
> > > +    {
> > > +      pop_scope ();
> > > +      BIND_EXPR_BODY (bind) = pop_stmt_list (BIND_EXPR_BODY (bind));
> > > +      if (*expr)
> > > +       *expr = build2 (COMPOUND_EXPR, void_type_node, *expr, bind);
> > > +      else
> > > +       *expr = bind;
> > > +    }
> > > +}
> > > +
> > >  /* Given declspecs and a declarator,
> > >     determine the name and type of the object declared
> > >     and construct a ..._DECL node for it.
> > > @@ -7474,58 +7523,9 @@ grokdeclarator (const struct c_declarator *declarator,
> > >
> > >                This is expected to happen automatically when the pointed-to
> > >                type has a name/declaration of it's own, but special attention
> > > -              is required if the type is anonymous.
> > > -
> > > -              We attach an artificial TYPE_DECL to such pointed-to type
> > > -              and arrange for it to be included in a DECL_EXPR.  This
> > > -              forces the sizes evaluation at a safe point and ensures it
> > > -              is not deferred until e.g. within a deeper conditional context.
> > > -
> > > -              PARM contexts have no enclosing statement list that
> > > -              can hold the DECL_EXPR, so we need to use a BIND_EXPR
> > > -              instead, and add it to the list of expressions that
> > > -              need to be evaluated.
> > > -
> > > -              TYPENAME contexts do have an enclosing statement list,
> > > -              but it would be incorrect to use it, as the size should
> > > -              only be evaluated if the containing expression is
> > > -              evaluated.  We might also be in the middle of an
> > > -              expression with side effects on the pointed-to type size
> > > -              "arguments" prior to the pointer declaration point and
> > > -              the fake TYPE_DECL in the enclosing context would force
> > > -              the size evaluation prior to the side effects.  We therefore
> > > -              use BIND_EXPRs in TYPENAME contexts too.  */
> > > -           if (!TYPE_NAME (type)
> > > -               && c_type_variably_modified_p (type))
> > > -             {
> > > -               tree bind = NULL_TREE;
> > > -               if (decl_context == TYPENAME || decl_context == PARM
> > > -                   || decl_context == FIELD)
> > > -                 {
> > > -                   bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
> > > -                                  NULL_TREE, NULL_TREE);
> > > -                   TREE_SIDE_EFFECTS (bind) = 1;
> > > -                   BIND_EXPR_BODY (bind) = push_stmt_list ();
> > > -                   push_scope ();
> > > -                 }
> > > -               tree decl = build_decl (loc, TYPE_DECL, NULL_TREE, type);
> > > -               pushdecl (decl);
> > > -               DECL_ARTIFICIAL (decl) = 1;
> > > -               add_stmt (build_stmt (DECL_SOURCE_LOCATION (decl), DECL_EXPR, decl));
> > > -               TYPE_NAME (type) = decl;
> > > -
> > > -               if (bind)
> > > -                 {
> > > -                   pop_scope ();
> > > -                   BIND_EXPR_BODY (bind)
> > > -                     = pop_stmt_list (BIND_EXPR_BODY (bind));
> > > -                   if (*expr)
> > > -                     *expr = build2 (COMPOUND_EXPR, void_type_node, *expr,
> > > -                                     bind);
> > > -                   else
> > > -                     *expr = bind;
> > > -                 }
> > > -             }
> > > +              is required if the type is anonymous. */
> > > +           if (!TYPE_NAME (type) && c_type_variably_modified_p (type))
> > > +             add_decl_expr (loc, decl_context, type, expr);
> > >
> > >             type = c_build_pointer_type (type);
> > >
> > > @@ -7787,6 +7787,11 @@ grokdeclarator (const struct c_declarator *declarator,
> > >             if (type_quals)
> > >               type = c_build_qualified_type (type, type_quals, orig_qual_type,
> > >                                              orig_qual_indirect);
> > > +
> > > +           /* The pointed-to type may need a decl expr (see above).  */
> > > +           if (!TYPE_NAME (type) && c_type_variably_modified_p (type))
> > > +             add_decl_expr (loc, decl_context, type, expr);
> > > +
> > >             type = c_build_pointer_type (type);
> > >             type_quals = array_ptr_quals;
> > >             if (type_quals)
> > > diff --git a/gcc/function.cc b/gcc/function.cc
> > > index f0ae641512d..5699b9d495d 100644
> > > --- a/gcc/function.cc
> > > +++ b/gcc/function.cc
> > > @@ -3872,30 +3872,6 @@ assign_parms (tree fndecl)
> > >      }
> > >  }
> > >
> > > -/* A subroutine of gimplify_parameters, invoked via walk_tree.
> > > -   For all seen types, gimplify their sizes.  */
> > > -
> > > -static tree
> > > -gimplify_parm_type (tree *tp, int *walk_subtrees, void *data)
> > > -{
> > > -  tree t = *tp;
> > > -
> > > -  *walk_subtrees = 0;
> > > -  if (TYPE_P (t))
> > > -    {
> > > -      if (POINTER_TYPE_P (t))
> > > -       *walk_subtrees = 1;
> > > -      else if (TYPE_SIZE (t) && !TREE_CONSTANT (TYPE_SIZE (t))
> > > -              && !TYPE_SIZES_GIMPLIFIED (t))
> > > -       {
> > > -         gimplify_type_sizes (t, (gimple_seq *) data);
> > > -         *walk_subtrees = 1;
> > > -       }
> > > -    }
> > > -
> > > -  return NULL;
> > > -}
> > > -
> > >  /* Gimplify the parameter list for current_function_decl.  This involves
> > >     evaluating SAVE_EXPRs of variable sized parameters and generating code
> > >     to implement callee-copies reference parameters.  Returns a sequence of
> > > @@ -3931,14 +3907,7 @@ gimplify_parameters (gimple_seq *cleanup)
> > >          SAVE_EXPRs (amongst others) onto a pending sizes list.  This
> > >          turned out to be less than manageable in the gimple world.
> > >          Now we have to hunt them down ourselves.  */
> > > -      walk_tree_without_duplicates (&data.arg.type,
> > > -                                   gimplify_parm_type, &stmts);
> > > -
> > > -      if (TREE_CODE (DECL_SIZE_UNIT (parm)) != INTEGER_CST)
> > > -       {
> > > -         gimplify_one_sizepos (&DECL_SIZE (parm), &stmts);
> > > -         gimplify_one_sizepos (&DECL_SIZE_UNIT (parm), &stmts);
> > > -       }
> > > +      gimplify_parm_sizes (parm, &stmts);
> > >
> > >        if (data.arg.pass_by_reference)
> > >         {
> > > diff --git a/gcc/gimplify.cc b/gcc/gimplify.cc
> > > index d0d16a24820..fd990c328eb 100644
> > > --- a/gcc/gimplify.cc
> > > +++ b/gcc/gimplify.cc
> > > @@ -242,6 +242,7 @@ static struct gimplify_omp_ctx *gimplify_omp_ctxp;
> > >  static bool in_omp_construct;
> > >
> > >  /* Forward declaration.  */
> > > +static void gimplify_type_sizes (tree type, gimple_seq *list_p);
> > >  static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
> > >  static hash_map<tree, tree> *oacc_declare_returns;
> > >  static enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
> > > @@ -17425,7 +17426,7 @@ gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
> > >  /* Look through TYPE for variable-sized objects and gimplify each such
> > >     size that we find.  Add to LIST_P any statements generated.  */
> > >
> > > -void
> > > +static void
> > >  gimplify_type_sizes (tree type, gimple_seq *list_p)
> > >  {
> > >    if (type == NULL || type == error_mark_node)
> > > @@ -17533,6 +17534,21 @@ gimplify_type_sizes (tree type, gimple_seq *list_p)
> > >      }
> > >  }
> > >
> > > +/* Gimplify sizes in parameter declarations.  */
> > > +
> > > +void
> > > +gimplify_parm_sizes (tree parm, gimple_seq *list_p)
> >
> > Can you instead inline this at the single caller in gimplify_parameters?
> > It looks like both gimplify_type_sizes and gimplify_one_sizepos are
> > already exported.  So just add the missing gimplify_type_sizes () call
> > at the single call site.
> >
> > The middle-end changes are OK with that change.
>
> Thanks Richard!
>
> I did this in this way because this was the only outside use of
> gimplify_type_sizes. Then one can unexport gimplify_type_size.
> In fact, it is declared static (see above) and removed from the
> header (see below) in the patch. I thought this is better logical
> encapsulation.   (BTW:  gimplify_one_sizepos then has only
> one remaining use in the Ada FE, so maybe we make a copy there
> and also unexport it?).
>
> What do you think?

I think any API streamlining should be done separately and as long
as gimplify_one_sizepos is still exported it's odd to focus on
gimplify_type_sizes, looking at the Ada FE use it doesn't look like
that can be removed.

Richard.

> Martin
>
> > Thanks,
> > Richard.
> >
> > > +{
> > > +  gimplify_type_sizes (TREE_TYPE (parm), list_p);
> > > +
> > > +  if (TREE_CODE (DECL_SIZE_UNIT (parm)) != INTEGER_CST)
> > > +    {
> > > +      gimplify_one_sizepos (&DECL_SIZE (parm), list_p);
> > > +      gimplify_one_sizepos (&DECL_SIZE_UNIT (parm), list_p);
> > > +    }
> > > +}
> > > +
> > > +
> > >  /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
> > >     a size or position, has had all of its SAVE_EXPRs evaluated.
> > >     We add any required statements to *STMT_P.  */
> > > diff --git a/gcc/gimplify.h b/gcc/gimplify.h
> > > index f4a3eea2606..17ea0580647 100644
> > > --- a/gcc/gimplify.h
> > > +++ b/gcc/gimplify.h
> > > @@ -78,7 +78,7 @@ extern enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
> > >
> > >  int omp_construct_selector_matches (enum tree_code *, int, int *);
> > >
> > > -extern void gimplify_type_sizes (tree, gimple_seq *);
> > > +extern void gimplify_parm_sizes (tree, gimple_seq *);
> > >  extern void gimplify_one_sizepos (tree *, gimple_seq *);
> > >  extern gbind *gimplify_body (tree, bool);
> > >  extern enum gimplify_status gimplify_arg (tree *, gimple_seq *, location_t,
> > > diff --git a/gcc/testsuite/gcc.dg/pr109450-1.c b/gcc/testsuite/gcc.dg/pr109450-1.c
> > > new file mode 100644
> > > index 00000000000..aec127f2afc
> > > --- /dev/null
> > > +++ b/gcc/testsuite/gcc.dg/pr109450-1.c
> > > @@ -0,0 +1,21 @@
> > > +/* PR c/109450
> > > + * { dg-do run }
> > > + * { dg-options "-std=gnu99" }
> > > + * */
> > > +
> > > +int bar(int n, struct foo* x)  /* { dg-warning "not be visible" } */
> > > +{
> > > +       int a = n;
> > > +       struct foo { char buf[n++]; }* p = x;
> > > +       return a;
> > > +}
> > > +
> > > +int main()
> > > +{
> > > +       if (1 != bar(1, 0))
> > > +               __builtin_abort();
> > > +}
> > > +
> > > +
> > > +
> > > +
> > > diff --git a/gcc/testsuite/gcc.dg/pr109450-2.c b/gcc/testsuite/gcc.dg/pr109450-2.c
> > > new file mode 100644
> > > index 00000000000..06799f6df23
> > > --- /dev/null
> > > +++ b/gcc/testsuite/gcc.dg/pr109450-2.c
> > > @@ -0,0 +1,18 @@
> > > +/* PR c/109450
> > > + * { dg-do run }
> > > + * { dg-options "-std=gnu99" }
> > > + * */
> > > +
> > > +int bar(int n, struct foo *x)  /* { dg-warning "not be visible" } */
> > > +{
> > > +       int a = n;
> > > +       struct foo { char buf[a++]; }* p = x;
> > > +       return n == a;
> > > +}
> > > +
> > > +int main()
> > > +{
> > > +       if (bar(1, 0))
> > > +               __builtin_abort();
> > > +}
> > > +
> > > diff --git a/gcc/testsuite/gcc.dg/vla-26.c b/gcc/testsuite/gcc.dg/vla-26.c
> > > new file mode 100644
> > > index 00000000000..5d2fa3e280a
> > > --- /dev/null
> > > +++ b/gcc/testsuite/gcc.dg/vla-26.c
> > > @@ -0,0 +1,15 @@
> > > +/* { dg-do compile } */
> > > +/* { dg-options "-std=c99 -O2" } */
> > > +
> > > +void ed(int n, float s[3][n])
> > > +{
> > > +       for (int i = 0; i < n; i++)
> > > +               s[1][i];
> > > +}
> > > +
> > > +void e(int n, float s[3][n])
> > > +{
> > > +       ed(n, s);
> > > +}
> > > +
> > > +
> > >
> > >
>
>
Martin Uecker May 23, 2023, 9:25 a.m. UTC | #5
Am Dienstag, dem 23.05.2023 um 10:18 +0200 schrieb Richard Biener:
> On Tue, May 23, 2023 at 8:24 AM Martin Uecker <uecker@tugraz.at>
> wrote:
> > 
> > Am Dienstag, dem 23.05.2023 um 08:13 +0200 schrieb Richard Biener:
> > > On Mon, May 22, 2023 at 7:24 PM Martin Uecker via Gcc-patches
> > > <gcc-patches@gcc.gnu.org> wrote:
> > > > 
> > > > 
> > > > 
> > > > This version contains the middle-end changes for PR109450
> > > > and test cases as before.  The main middle-end change is that
> > > > we use gimplify_type_sizes also for parameters and remove
> > > > the special code that also walked into pointers (which is
> > > > incorrect).
> > > > 
> > > > In addition, in the C FE this patch now also adds DECL_EXPR
> > > > for vm-types which are pointed-to by parameters declared
> > > > as arrays.  The new function created contains the exact
> > > > code previously used only for regular pointers, and is
> > > > now also called for parameters declared as arrays.
> > > > 
> > > > 
> > > > Martin
> > > > 
> > > > 
> > > > 
> > > > 
> > > > 
> > > > 
> > > > 
> > > >     Fix ICEs related to VM types in C 2/2 [PR109450]
> > > > 
> > > >     Size expressions were sometimes lost and not gimplified
> > > > correctly,
> > > >     leading to ICEs and incorrect evaluation order.  Fix this
> > > > by 1) not
> > > >     recursing pointers when gimplifying parameters in the
> > > > middle-end
> > > >     (the code is merged with gimplify_type_sizes), which is
> > > > incorrect
> > > >     because it might access variables declared later for
> > > > incomplete
> > > >     structs, and 2) adding a decl expr for variably-modified
> > > > arrays
> > > >     that are pointed to by parameters declared as arrays.
> > > > 
> > > >             PR c/109450
> > > > 
> > > >             gcc/
> > > >             * c/c-decl.cc (add_decl_expr): New function.
> > > >             (grokdeclarator): Add decl expr for size expression
> > > > in
> > > >             types pointed to by parameters declared as arrays.
> > > >             * function.cc (gimplify_parm_type): Remove
> > > > function.
> > > >             (gimplify_parameters): Call gimplify_parm_sizes.
> > > >             * gimplify.cc (gimplify_type_sizes): Make function
> > > > static.
> > > >             (gimplify_parm_sizes): New function.
> > > > 
> > > >             gcc/testsuite/
> > > >             * gcc.dg/pr109450-1.c: New test.
> > > >             * gcc.dg/pr109450-2.c: New test.
> > > >             * gcc.dg/vla-26.c: New test.
> > > > 
> > > > diff --git a/gcc/c/c-decl.cc b/gcc/c/c-decl.cc
> > > > index 494d3cf1747..c35347734b2 100644
> > > > --- a/gcc/c/c-decl.cc
> > > > +++ b/gcc/c/c-decl.cc
> > > > @@ -6490,6 +6490,55 @@ smallest_type_quals_location (const
> > > > location_t *locations,
> > > >    return loc;
> > > >  }
> > > > 
> > > > +
> > > > +/* We attach an artificial TYPE_DECL to pointed-to type
> > > > +   and arrange for it to be included in a DECL_EXPR.  This
> > > > +   forces the sizes evaluation at a safe point and ensures it
> > > > +   is not deferred until e.g. within a deeper conditional
> > > > context.
> > > > +
> > > > +   PARM contexts have no enclosing statement list that
> > > > +   can hold the DECL_EXPR, so we need to use a BIND_EXPR
> > > > +   instead, and add it to the list of expressions that
> > > > +   need to be evaluated.
> > > > +
> > > > +   TYPENAME contexts do have an enclosing statement list,
> > > > +   but it would be incorrect to use it, as the size should
> > > > +   only be evaluated if the containing expression is
> > > > +   evaluated.  We might also be in the middle of an
> > > > +   expression with side effects on the pointed-to type size
> > > > +   "arguments" prior to the pointer declaration point and
> > > > +   the fake TYPE_DECL in the enclosing context would force
> > > > +   the size evaluation prior to the side effects.  We
> > > > therefore
> > > > +   use BIND_EXPRs in TYPENAME contexts too.  */
> > > > +static void
> > > > +add_decl_expr(location_t loc, enum decl_context decl_context,
> > > > tree type, tree *expr)
> > > > +{
> > > > +  tree bind = NULL_TREE;
> > > > +  if (decl_context == TYPENAME || decl_context == PARM ||
> > > > decl_context == FIELD)
> > > > +    {
> > > > +      bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
> > > > NULL_TREE, NULL_TREE);
> > > > +      TREE_SIDE_EFFECTS (bind) = 1;
> > > > +      BIND_EXPR_BODY (bind) = push_stmt_list ();
> > > > +      push_scope ();
> > > > +    }
> > > > +
> > > > +  tree decl = build_decl (loc, TYPE_DECL, NULL_TREE, type);
> > > > +  pushdecl (decl);
> > > > +  DECL_ARTIFICIAL (decl) = 1;
> > > > +  add_stmt (build_stmt (DECL_SOURCE_LOCATION (decl),
> > > > DECL_EXPR, decl));
> > > > +  TYPE_NAME (type) = decl;
> > > > +
> > > > +  if (bind)
> > > > +    {
> > > > +      pop_scope ();
> > > > +      BIND_EXPR_BODY (bind) = pop_stmt_list (BIND_EXPR_BODY
> > > > (bind));
> > > > +      if (*expr)
> > > > +       *expr = build2 (COMPOUND_EXPR, void_type_node, *expr,
> > > > bind);
> > > > +      else
> > > > +       *expr = bind;
> > > > +    }
> > > > +}
> > > > +
> > > >  /* Given declspecs and a declarator,
> > > >     determine the name and type of the object declared
> > > >     and construct a ..._DECL node for it.
> > > > @@ -7474,58 +7523,9 @@ grokdeclarator (const struct
> > > > c_declarator *declarator,
> > > > 
> > > >                This is expected to happen automatically when
> > > > the pointed-to
> > > >                type has a name/declaration of it's own, but
> > > > special attention
> > > > -              is required if the type is anonymous.
> > > > -
> > > > -              We attach an artificial TYPE_DECL to such
> > > > pointed-to type
> > > > -              and arrange for it to be included in a
> > > > DECL_EXPR.  This
> > > > -              forces the sizes evaluation at a safe point and
> > > > ensures it
> > > > -              is not deferred until e.g. within a deeper
> > > > conditional context.
> > > > -
> > > > -              PARM contexts have no enclosing statement list
> > > > that
> > > > -              can hold the DECL_EXPR, so we need to use a
> > > > BIND_EXPR
> > > > -              instead, and add it to the list of expressions
> > > > that
> > > > -              need to be evaluated.
> > > > -
> > > > -              TYPENAME contexts do have an enclosing statement
> > > > list,
> > > > -              but it would be incorrect to use it, as the size
> > > > should
> > > > -              only be evaluated if the containing expression
> > > > is
> > > > -              evaluated.  We might also be in the middle of an
> > > > -              expression with side effects on the pointed-to
> > > > type size
> > > > -              "arguments" prior to the pointer declaration
> > > > point and
> > > > -              the fake TYPE_DECL in the enclosing context
> > > > would force
> > > > -              the size evaluation prior to the side effects. 
> > > > We therefore
> > > > -              use BIND_EXPRs in TYPENAME contexts too.  */
> > > > -           if (!TYPE_NAME (type)
> > > > -               && c_type_variably_modified_p (type))
> > > > -             {
> > > > -               tree bind = NULL_TREE;
> > > > -               if (decl_context == TYPENAME || decl_context ==
> > > > PARM
> > > > -                   || decl_context == FIELD)
> > > > -                 {
> > > > -                   bind = build3 (BIND_EXPR, void_type_node,
> > > > NULL_TREE,
> > > > -                                  NULL_TREE, NULL_TREE);
> > > > -                   TREE_SIDE_EFFECTS (bind) = 1;
> > > > -                   BIND_EXPR_BODY (bind) = push_stmt_list ();
> > > > -                   push_scope ();
> > > > -                 }
> > > > -               tree decl = build_decl (loc, TYPE_DECL,
> > > > NULL_TREE, type);
> > > > -               pushdecl (decl);
> > > > -               DECL_ARTIFICIAL (decl) = 1;
> > > > -               add_stmt (build_stmt (DECL_SOURCE_LOCATION
> > > > (decl), DECL_EXPR, decl));
> > > > -               TYPE_NAME (type) = decl;
> > > > -
> > > > -               if (bind)
> > > > -                 {
> > > > -                   pop_scope ();
> > > > -                   BIND_EXPR_BODY (bind)
> > > > -                     = pop_stmt_list (BIND_EXPR_BODY (bind));
> > > > -                   if (*expr)
> > > > -                     *expr = build2 (COMPOUND_EXPR,
> > > > void_type_node, *expr,
> > > > -                                     bind);
> > > > -                   else
> > > > -                     *expr = bind;
> > > > -                 }
> > > > -             }
> > > > +              is required if the type is anonymous. */
> > > > +           if (!TYPE_NAME (type) && c_type_variably_modified_p
> > > > (type))
> > > > +             add_decl_expr (loc, decl_context, type, expr);
> > > > 
> > > >             type = c_build_pointer_type (type);
> > > > 
> > > > @@ -7787,6 +7787,11 @@ grokdeclarator (const struct
> > > > c_declarator *declarator,
> > > >             if (type_quals)
> > > >               type = c_build_qualified_type (type, type_quals,
> > > > orig_qual_type,
> > > >                                             
> > > > orig_qual_indirect);
> > > > +
> > > > +           /* The pointed-to type may need a decl expr (see
> > > > above).  */
> > > > +           if (!TYPE_NAME (type) && c_type_variably_modified_p
> > > > (type))
> > > > +             add_decl_expr (loc, decl_context, type, expr);
> > > > +
> > > >             type = c_build_pointer_type (type);
> > > >             type_quals = array_ptr_quals;
> > > >             if (type_quals)
> > > > diff --git a/gcc/function.cc b/gcc/function.cc
> > > > index f0ae641512d..5699b9d495d 100644
> > > > --- a/gcc/function.cc
> > > > +++ b/gcc/function.cc
> > > > @@ -3872,30 +3872,6 @@ assign_parms (tree fndecl)
> > > >      }
> > > >  }
> > > > 
> > > > -/* A subroutine of gimplify_parameters, invoked via walk_tree.
> > > > -   For all seen types, gimplify their sizes.  */
> > > > -
> > > > -static tree
> > > > -gimplify_parm_type (tree *tp, int *walk_subtrees, void *data)
> > > > -{
> > > > -  tree t = *tp;
> > > > -
> > > > -  *walk_subtrees = 0;
> > > > -  if (TYPE_P (t))
> > > > -    {
> > > > -      if (POINTER_TYPE_P (t))
> > > > -       *walk_subtrees = 1;
> > > > -      else if (TYPE_SIZE (t) && !TREE_CONSTANT (TYPE_SIZE (t))
> > > > -              && !TYPE_SIZES_GIMPLIFIED (t))
> > > > -       {
> > > > -         gimplify_type_sizes (t, (gimple_seq *) data);
> > > > -         *walk_subtrees = 1;
> > > > -       }
> > > > -    }
> > > > -
> > > > -  return NULL;
> > > > -}
> > > > -
> > > >  /* Gimplify the parameter list for current_function_decl. 
> > > > This involves
> > > >     evaluating SAVE_EXPRs of variable sized parameters and
> > > > generating code
> > > >     to implement callee-copies reference parameters.  Returns a
> > > > sequence of
> > > > @@ -3931,14 +3907,7 @@ gimplify_parameters (gimple_seq
> > > > *cleanup)
> > > >          SAVE_EXPRs (amongst others) onto a pending sizes
> > > > list.  This
> > > >          turned out to be less than manageable in the gimple
> > > > world.
> > > >          Now we have to hunt them down ourselves.  */
> > > > -      walk_tree_without_duplicates (&data.arg.type,
> > > > -                                   gimplify_parm_type,
> > > > &stmts);
> > > > -
> > > > -      if (TREE_CODE (DECL_SIZE_UNIT (parm)) != INTEGER_CST)
> > > > -       {
> > > > -         gimplify_one_sizepos (&DECL_SIZE (parm), &stmts);
> > > > -         gimplify_one_sizepos (&DECL_SIZE_UNIT (parm),
> > > > &stmts);
> > > > -       }
> > > > +      gimplify_parm_sizes (parm, &stmts);
> > > > 
> > > >        if (data.arg.pass_by_reference)
> > > >         {
> > > > diff --git a/gcc/gimplify.cc b/gcc/gimplify.cc
> > > > index d0d16a24820..fd990c328eb 100644
> > > > --- a/gcc/gimplify.cc
> > > > +++ b/gcc/gimplify.cc
> > > > @@ -242,6 +242,7 @@ static struct gimplify_omp_ctx
> > > > *gimplify_omp_ctxp;
> > > >  static bool in_omp_construct;
> > > > 
> > > >  /* Forward declaration.  */
> > > > +static void gimplify_type_sizes (tree type, gimple_seq
> > > > *list_p);
> > > >  static enum gimplify_status gimplify_compound_expr (tree *,
> > > > gimple_seq *, bool);
> > > >  static hash_map<tree, tree> *oacc_declare_returns;
> > > >  static enum gimplify_status gimplify_expr (tree *, gimple_seq
> > > > *, gimple_seq *,
> > > > @@ -17425,7 +17426,7 @@ gimplify_expr (tree *expr_p, gimple_seq
> > > > *pre_p, gimple_seq *post_p,
> > > >  /* Look through TYPE for variable-sized objects and gimplify
> > > > each such
> > > >     size that we find.  Add to LIST_P any statements
> > > > generated.  */
> > > > 
> > > > -void
> > > > +static void
> > > >  gimplify_type_sizes (tree type, gimple_seq *list_p)
> > > >  {
> > > >    if (type == NULL || type == error_mark_node)
> > > > @@ -17533,6 +17534,21 @@ gimplify_type_sizes (tree type,
> > > > gimple_seq *list_p)
> > > >      }
> > > >  }
> > > > 
> > > > +/* Gimplify sizes in parameter declarations.  */
> > > > +
> > > > +void
> > > > +gimplify_parm_sizes (tree parm, gimple_seq *list_p)
> > > 
> > > Can you instead inline this at the single caller in
> > > gimplify_parameters?
> > > It looks like both gimplify_type_sizes and gimplify_one_sizepos
> > > are
> > > already exported.  So just add the missing gimplify_type_sizes ()
> > > call
> > > at the single call site.
> > > 
> > > The middle-end changes are OK with that change.
> > 
> > Thanks Richard!
> > 
> > I did this in this way because this was the only outside use of
> > gimplify_type_sizes. Then one can unexport gimplify_type_size.
> > In fact, it is declared static (see above) and removed from the
> > header (see below) in the patch. I thought this is better logical
> > encapsulation.   (BTW:  gimplify_one_sizepos then has only
> > one remaining use in the Ada FE, so maybe we make a copy there
> > and also unexport it?).
> > 
> > What do you think?
> 
> I think any API streamlining should be done separately and as long
> as gimplify_one_sizepos is still exported it's odd to focus on
> gimplify_type_sizes, looking at the Ada FE use it doesn't look like
> that can be removed.
> 
> Richard.


Ok, then I will make the change you described and commit it.
Thanks!

Martin


> > Martin
> > 
> > > Thanks,
> > > Richard.
> > > 
> > > > +{
> > > > +  gimplify_type_sizes (TREE_TYPE (parm), list_p);
> > > > +
> > > > +  if (TREE_CODE (DECL_SIZE_UNIT (parm)) != INTEGER_CST)
> > > > +    {
> > > > +      gimplify_one_sizepos (&DECL_SIZE (parm), list_p);
> > > > +      gimplify_one_sizepos (&DECL_SIZE_UNIT (parm), list_p);
> > > > +    }
> > > > +}
> > > > +
> > > > +
> > > >  /* A subroutine of gimplify_type_sizes to make sure that
> > > > *EXPR_P,
> > > >     a size or position, has had all of its SAVE_EXPRs
> > > > evaluated.
> > > >     We add any required statements to *STMT_P.  */
> > > > diff --git a/gcc/gimplify.h b/gcc/gimplify.h
> > > > index f4a3eea2606..17ea0580647 100644
> > > > --- a/gcc/gimplify.h
> > > > +++ b/gcc/gimplify.h
> > > > @@ -78,7 +78,7 @@ extern enum gimplify_status gimplify_expr
> > > > (tree *, gimple_seq *, gimple_seq *,
> > > > 
> > > >  int omp_construct_selector_matches (enum tree_code *, int, int
> > > > *);
> > > > 
> > > > -extern void gimplify_type_sizes (tree, gimple_seq *);
> > > > +extern void gimplify_parm_sizes (tree, gimple_seq *);
> > > >  extern void gimplify_one_sizepos (tree *, gimple_seq *);
> > > >  extern gbind *gimplify_body (tree, bool);
> > > >  extern enum gimplify_status gimplify_arg (tree *, gimple_seq
> > > > *, location_t,
> > > > diff --git a/gcc/testsuite/gcc.dg/pr109450-1.c
> > > > b/gcc/testsuite/gcc.dg/pr109450-1.c
> > > > new file mode 100644
> > > > index 00000000000..aec127f2afc
> > > > --- /dev/null
> > > > +++ b/gcc/testsuite/gcc.dg/pr109450-1.c
> > > > @@ -0,0 +1,21 @@
> > > > +/* PR c/109450
> > > > + * { dg-do run }
> > > > + * { dg-options "-std=gnu99" }
> > > > + * */
> > > > +
> > > > +int bar(int n, struct foo* x)  /* { dg-warning "not be
> > > > visible" } */
> > > > +{
> > > > +       int a = n;
> > > > +       struct foo { char buf[n++]; }* p = x;
> > > > +       return a;
> > > > +}
> > > > +
> > > > +int main()
> > > > +{
> > > > +       if (1 != bar(1, 0))
> > > > +               __builtin_abort();
> > > > +}
> > > > +
> > > > +
> > > > +
> > > > +
> > > > diff --git a/gcc/testsuite/gcc.dg/pr109450-2.c
> > > > b/gcc/testsuite/gcc.dg/pr109450-2.c
> > > > new file mode 100644
> > > > index 00000000000..06799f6df23
> > > > --- /dev/null
> > > > +++ b/gcc/testsuite/gcc.dg/pr109450-2.c
> > > > @@ -0,0 +1,18 @@
> > > > +/* PR c/109450
> > > > + * { dg-do run }
> > > > + * { dg-options "-std=gnu99" }
> > > > + * */
> > > > +
> > > > +int bar(int n, struct foo *x)  /* { dg-warning "not be
> > > > visible" } */
> > > > +{
> > > > +       int a = n;
> > > > +       struct foo { char buf[a++]; }* p = x;
> > > > +       return n == a;
> > > > +}
> > > > +
> > > > +int main()
> > > > +{
> > > > +       if (bar(1, 0))
> > > > +               __builtin_abort();
> > > > +}
> > > > +
> > > > diff --git a/gcc/testsuite/gcc.dg/vla-26.c
> > > > b/gcc/testsuite/gcc.dg/vla-26.c
> > > > new file mode 100644
> > > > index 00000000000..5d2fa3e280a
> > > > --- /dev/null
> > > > +++ b/gcc/testsuite/gcc.dg/vla-26.c
> > > > @@ -0,0 +1,15 @@
> > > > +/* { dg-do compile } */
> > > > +/* { dg-options "-std=c99 -O2" } */
> > > > +
> > > > +void ed(int n, float s[3][n])
> > > > +{
> > > > +       for (int i = 0; i < n; i++)
> > > > +               s[1][i];
> > > > +}
> > > > +
> > > > +void e(int n, float s[3][n])
> > > > +{
> > > > +       ed(n, s);
> > > > +}
> > > > +
> > > > +
> > > > 
> > > > 
> > 
> >
diff mbox series

Patch

diff --git a/gcc/c/c-decl.cc b/gcc/c/c-decl.cc
index 494d3cf1747..c35347734b2 100644
--- a/gcc/c/c-decl.cc
+++ b/gcc/c/c-decl.cc
@@ -6490,6 +6490,55 @@  smallest_type_quals_location (const location_t *locations,
   return loc;
 }
 
+
+/* We attach an artificial TYPE_DECL to pointed-to type
+   and arrange for it to be included in a DECL_EXPR.  This
+   forces the sizes evaluation at a safe point and ensures it
+   is not deferred until e.g. within a deeper conditional context.
+
+   PARM contexts have no enclosing statement list that
+   can hold the DECL_EXPR, so we need to use a BIND_EXPR
+   instead, and add it to the list of expressions that
+   need to be evaluated.
+
+   TYPENAME contexts do have an enclosing statement list,
+   but it would be incorrect to use it, as the size should
+   only be evaluated if the containing expression is
+   evaluated.  We might also be in the middle of an
+   expression with side effects on the pointed-to type size
+   "arguments" prior to the pointer declaration point and
+   the fake TYPE_DECL in the enclosing context would force
+   the size evaluation prior to the side effects.  We therefore
+   use BIND_EXPRs in TYPENAME contexts too.  */
+static void
+add_decl_expr(location_t loc, enum decl_context decl_context, tree type, tree *expr)
+{
+  tree bind = NULL_TREE;
+  if (decl_context == TYPENAME || decl_context == PARM || decl_context == FIELD)
+    {
+      bind = build3 (BIND_EXPR, void_type_node, NULL_TREE, NULL_TREE, NULL_TREE);
+      TREE_SIDE_EFFECTS (bind) = 1;
+      BIND_EXPR_BODY (bind) = push_stmt_list ();
+      push_scope ();
+    }
+
+  tree decl = build_decl (loc, TYPE_DECL, NULL_TREE, type);
+  pushdecl (decl);
+  DECL_ARTIFICIAL (decl) = 1;
+  add_stmt (build_stmt (DECL_SOURCE_LOCATION (decl), DECL_EXPR, decl));
+  TYPE_NAME (type) = decl;
+
+  if (bind)
+    {
+      pop_scope ();
+      BIND_EXPR_BODY (bind) = pop_stmt_list (BIND_EXPR_BODY (bind));
+      if (*expr)
+	*expr = build2 (COMPOUND_EXPR, void_type_node, *expr, bind);
+      else
+	*expr = bind;
+    }
+}
+
 /* Given declspecs and a declarator,
    determine the name and type of the object declared
    and construct a ..._DECL node for it.
@@ -7474,58 +7523,9 @@  grokdeclarator (const struct c_declarator *declarator,
 
 	       This is expected to happen automatically when the pointed-to
 	       type has a name/declaration of it's own, but special attention
-	       is required if the type is anonymous.
-
-	       We attach an artificial TYPE_DECL to such pointed-to type
-	       and arrange for it to be included in a DECL_EXPR.  This
-	       forces the sizes evaluation at a safe point and ensures it
-	       is not deferred until e.g. within a deeper conditional context.
-
-	       PARM contexts have no enclosing statement list that
-	       can hold the DECL_EXPR, so we need to use a BIND_EXPR
-	       instead, and add it to the list of expressions that
-	       need to be evaluated.
-
-	       TYPENAME contexts do have an enclosing statement list,
-	       but it would be incorrect to use it, as the size should
-	       only be evaluated if the containing expression is
-	       evaluated.  We might also be in the middle of an
-	       expression with side effects on the pointed-to type size
-	       "arguments" prior to the pointer declaration point and
-	       the fake TYPE_DECL in the enclosing context would force
-	       the size evaluation prior to the side effects.  We therefore
-	       use BIND_EXPRs in TYPENAME contexts too.  */
-	    if (!TYPE_NAME (type)
-		&& c_type_variably_modified_p (type))
-	      {
-		tree bind = NULL_TREE;
-		if (decl_context == TYPENAME || decl_context == PARM
-		    || decl_context == FIELD)
-		  {
-		    bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
-				   NULL_TREE, NULL_TREE);
-		    TREE_SIDE_EFFECTS (bind) = 1;
-		    BIND_EXPR_BODY (bind) = push_stmt_list ();
-		    push_scope ();
-		  }
-		tree decl = build_decl (loc, TYPE_DECL, NULL_TREE, type);
-		pushdecl (decl);
-		DECL_ARTIFICIAL (decl) = 1;
-		add_stmt (build_stmt (DECL_SOURCE_LOCATION (decl), DECL_EXPR, decl));
-		TYPE_NAME (type) = decl;
-
-		if (bind)
-		  {
-		    pop_scope ();
-		    BIND_EXPR_BODY (bind)
-		      = pop_stmt_list (BIND_EXPR_BODY (bind));
-		    if (*expr)
-		      *expr = build2 (COMPOUND_EXPR, void_type_node, *expr,
-				      bind);
-		    else
-		      *expr = bind;
-		  }
-	      }
+	       is required if the type is anonymous. */
+	    if (!TYPE_NAME (type) && c_type_variably_modified_p (type))
+	      add_decl_expr (loc, decl_context, type, expr);
 
 	    type = c_build_pointer_type (type);
 
@@ -7787,6 +7787,11 @@  grokdeclarator (const struct c_declarator *declarator,
 	    if (type_quals)
 	      type = c_build_qualified_type (type, type_quals, orig_qual_type,
 					     orig_qual_indirect);
+
+	    /* The pointed-to type may need a decl expr (see above).  */
+	    if (!TYPE_NAME (type) && c_type_variably_modified_p (type))
+	      add_decl_expr (loc, decl_context, type, expr);
+
 	    type = c_build_pointer_type (type);
 	    type_quals = array_ptr_quals;
 	    if (type_quals)
diff --git a/gcc/function.cc b/gcc/function.cc
index f0ae641512d..5699b9d495d 100644
--- a/gcc/function.cc
+++ b/gcc/function.cc
@@ -3872,30 +3872,6 @@  assign_parms (tree fndecl)
     }
 }
 
-/* A subroutine of gimplify_parameters, invoked via walk_tree.
-   For all seen types, gimplify their sizes.  */
-
-static tree
-gimplify_parm_type (tree *tp, int *walk_subtrees, void *data)
-{
-  tree t = *tp;
-
-  *walk_subtrees = 0;
-  if (TYPE_P (t))
-    {
-      if (POINTER_TYPE_P (t))
-	*walk_subtrees = 1;
-      else if (TYPE_SIZE (t) && !TREE_CONSTANT (TYPE_SIZE (t))
-	       && !TYPE_SIZES_GIMPLIFIED (t))
-	{
-	  gimplify_type_sizes (t, (gimple_seq *) data);
-	  *walk_subtrees = 1;
-	}
-    }
-
-  return NULL;
-}
-
 /* Gimplify the parameter list for current_function_decl.  This involves
    evaluating SAVE_EXPRs of variable sized parameters and generating code
    to implement callee-copies reference parameters.  Returns a sequence of
@@ -3931,14 +3907,7 @@  gimplify_parameters (gimple_seq *cleanup)
 	 SAVE_EXPRs (amongst others) onto a pending sizes list.  This
 	 turned out to be less than manageable in the gimple world.
 	 Now we have to hunt them down ourselves.  */
-      walk_tree_without_duplicates (&data.arg.type,
-				    gimplify_parm_type, &stmts);
-
-      if (TREE_CODE (DECL_SIZE_UNIT (parm)) != INTEGER_CST)
-	{
-	  gimplify_one_sizepos (&DECL_SIZE (parm), &stmts);
-	  gimplify_one_sizepos (&DECL_SIZE_UNIT (parm), &stmts);
-	}
+      gimplify_parm_sizes (parm, &stmts);
 
       if (data.arg.pass_by_reference)
 	{
diff --git a/gcc/gimplify.cc b/gcc/gimplify.cc
index d0d16a24820..fd990c328eb 100644
--- a/gcc/gimplify.cc
+++ b/gcc/gimplify.cc
@@ -242,6 +242,7 @@  static struct gimplify_omp_ctx *gimplify_omp_ctxp;
 static bool in_omp_construct;
 
 /* Forward declaration.  */
+static void gimplify_type_sizes (tree type, gimple_seq *list_p);
 static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
 static hash_map<tree, tree> *oacc_declare_returns;
 static enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
@@ -17425,7 +17426,7 @@  gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
 /* Look through TYPE for variable-sized objects and gimplify each such
    size that we find.  Add to LIST_P any statements generated.  */
 
-void
+static void
 gimplify_type_sizes (tree type, gimple_seq *list_p)
 {
   if (type == NULL || type == error_mark_node)
@@ -17533,6 +17534,21 @@  gimplify_type_sizes (tree type, gimple_seq *list_p)
     }
 }
 
+/* Gimplify sizes in parameter declarations.  */
+
+void
+gimplify_parm_sizes (tree parm, gimple_seq *list_p)
+{
+  gimplify_type_sizes (TREE_TYPE (parm), list_p);
+
+  if (TREE_CODE (DECL_SIZE_UNIT (parm)) != INTEGER_CST)
+    {
+      gimplify_one_sizepos (&DECL_SIZE (parm), list_p);
+      gimplify_one_sizepos (&DECL_SIZE_UNIT (parm), list_p);
+    }
+}
+
+
 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
    a size or position, has had all of its SAVE_EXPRs evaluated.
    We add any required statements to *STMT_P.  */
diff --git a/gcc/gimplify.h b/gcc/gimplify.h
index f4a3eea2606..17ea0580647 100644
--- a/gcc/gimplify.h
+++ b/gcc/gimplify.h
@@ -78,7 +78,7 @@  extern enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
 
 int omp_construct_selector_matches (enum tree_code *, int, int *);
 
-extern void gimplify_type_sizes (tree, gimple_seq *);
+extern void gimplify_parm_sizes (tree, gimple_seq *);
 extern void gimplify_one_sizepos (tree *, gimple_seq *);
 extern gbind *gimplify_body (tree, bool);
 extern enum gimplify_status gimplify_arg (tree *, gimple_seq *, location_t,
diff --git a/gcc/testsuite/gcc.dg/pr109450-1.c b/gcc/testsuite/gcc.dg/pr109450-1.c
new file mode 100644
index 00000000000..aec127f2afc
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/pr109450-1.c
@@ -0,0 +1,21 @@ 
+/* PR c/109450
+ * { dg-do run }
+ * { dg-options "-std=gnu99" }
+ * */
+
+int bar(int n, struct foo* x)	/* { dg-warning "not be visible" } */
+{
+	int a = n;
+	struct foo { char buf[n++]; }* p = x;
+	return a;
+}
+
+int main()
+{
+	if (1 != bar(1, 0))
+		__builtin_abort();
+}
+
+
+
+
diff --git a/gcc/testsuite/gcc.dg/pr109450-2.c b/gcc/testsuite/gcc.dg/pr109450-2.c
new file mode 100644
index 00000000000..06799f6df23
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/pr109450-2.c
@@ -0,0 +1,18 @@ 
+/* PR c/109450
+ * { dg-do run }
+ * { dg-options "-std=gnu99" }
+ * */
+
+int bar(int n, struct foo *x)	/* { dg-warning "not be visible" } */
+{
+	int a = n;
+	struct foo { char buf[a++]; }* p = x;
+	return n == a;
+}
+
+int main()
+{
+	if (bar(1, 0))
+		__builtin_abort();
+}
+
diff --git a/gcc/testsuite/gcc.dg/vla-26.c b/gcc/testsuite/gcc.dg/vla-26.c
new file mode 100644
index 00000000000..5d2fa3e280a
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/vla-26.c
@@ -0,0 +1,15 @@ 
+/* { dg-do compile } */
+/* { dg-options "-std=c99 -O2" } */
+
+void ed(int n, float s[3][n])
+{
+	for (int i = 0; i < n; i++)
+		s[1][i];
+}
+
+void e(int n, float s[3][n])
+{
+	ed(n, s);	
+}
+
+