diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 792200974e0ff8a42fbac7117c1652dbddb772fa..78bfd9af82d042064250001d624ea4f689ae2f82 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,28 @@
+2018-06-17  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gimplify.c (nonlocal_vlas): Delete.
+	(nonlocal_vla_vars): Likewise.
+	(gimplify_var_or_parm_decl): Do not add debug VAR_DECLs for non-local
+	referenced VLAs.
+	(gimplify_body): Do not create and destroy nonlocal_vlas.
+	* tree-nested.c: Include diagnostic.h.
+	(use_pointer_in_frame): Tweak.
+	(lookup_field_for_decl): Add assertion and declare the transformation.
+	(convert_nonlocal_reference_op) <PARM_DECL>: Rework and issue an
+	internal error when the reference is in a wrong context.  Do not
+	create a debug decl by default.
+	(note_nonlocal_block_vlas): Delete.
+	(convert_nonlocal_reference_stmt) <GIMPLE_BIND>: Do not call it.
+	(convert_local_reference_op) <PARM_DECL>: Skip the frame decl.  Do not
+	create a debug decl by default.
+	(convert_gimple_call) <GIMPLE_CALL>: Issue an internal error when the
+	call is in a wrong context.
+	(fixup_vla_decls): New function.
+	(finalize_nesting_tree_1): Adjust comment.  Call fixup_vla_decls if no
+	debug variables were created.
+	* tree.c (decl_value_expr_lookup): Add checking assertion.
+	(decl_value_expr_insert): Likewise.
+
 2018-06-16  Kugan Vivekanandarajah  <kuganv@linaro.org>
 
 	PR middle-end/82479
diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 05397b92dfa9ec46d4d4a953c04895502ba775c3..fdf8f0aee1c86056c998ed03ad49a93c4ea320cb 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,14 @@
+2018-06-17  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* fortran/trans-decl.c (nonlocal_dummy_decl_pset): Delete.
+	(nonlocal_dummy_decls): Likewise.
+	(gfc_nonlocal_dummy_array_decl): Likewise.
+	(gfc_get_symbol_decl): Do not call gfc_nonlocal_dummy_array_decl.
+	(gfc_get_fake_result_decl): Do not generate a new DECL if simply
+	reusing the result of a recursive call.
+	(gfc_generate_function_code): Do not create, insert and destroy
+	nonlocal_dummy_decls.
+
 2018-06-13  Steven G. Kargl  <kargl@gcc.gnu.org>
 
 	PR fortran/86110
diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c
index cd23c2d5eae4eab754fb9a5e606293f4fd959f62..79ff01fc76dcce6e8b68cc82613cdf4d8b54c248 100644
--- a/gcc/fortran/trans-decl.c
+++ b/gcc/fortran/trans-decl.c
@@ -61,9 +61,6 @@ static GTY(()) tree parent_fake_result_decl;
 static GTY(()) tree saved_function_decls;
 static GTY(()) tree saved_parent_function_decls;
 
-static hash_set<tree> *nonlocal_dummy_decl_pset;
-static GTY(()) tree nonlocal_dummy_decls;
-
 /* Holds the variable DECLs that are locals.  */
 
 static GTY(()) tree saved_local_decls;
@@ -1284,39 +1281,6 @@ gfc_build_dummy_array_decl (gfc_symbol * sym, tree dummy)
   return decl;
 }
 
-/* For symbol SYM with GFC_DECL_SAVED_DESCRIPTOR used in contained
-   function add a VAR_DECL to the current function with DECL_VALUE_EXPR
-   pointing to the artificial variable for debug info purposes.  */
-
-static void
-gfc_nonlocal_dummy_array_decl (gfc_symbol *sym)
-{
-  tree decl, dummy;
-
-  if (! nonlocal_dummy_decl_pset)
-    nonlocal_dummy_decl_pset = new hash_set<tree>;
-
-  if (nonlocal_dummy_decl_pset->add (sym->backend_decl))
-    return;
-
-  dummy = GFC_DECL_SAVED_DESCRIPTOR (sym->backend_decl);
-  decl = build_decl (input_location, VAR_DECL, DECL_NAME (dummy),
-		     TREE_TYPE (sym->backend_decl));
-  DECL_ARTIFICIAL (decl) = 0;
-  TREE_USED (decl) = 1;
-  TREE_PUBLIC (decl) = 0;
-  TREE_STATIC (decl) = 0;
-  DECL_EXTERNAL (decl) = 0;
-  if (DECL_BY_REFERENCE (dummy))
-    DECL_BY_REFERENCE (decl) = 1;
-  DECL_LANG_SPECIFIC (decl) = DECL_LANG_SPECIFIC (sym->backend_decl);
-  SET_DECL_VALUE_EXPR (decl, sym->backend_decl);
-  DECL_HAS_VALUE_EXPR_P (decl) = 1;
-  DECL_CONTEXT (decl) = DECL_CONTEXT (sym->backend_decl);
-  DECL_CHAIN (decl) = nonlocal_dummy_decls;
-  nonlocal_dummy_decls = decl;
-}
-
 /* Return a constant or a variable to use as a string length.  Does not
    add the decl to the current scope.  */
 
@@ -1643,12 +1607,6 @@ gfc_get_symbol_decl (gfc_symbol * sym)
 	  gfc_add_assign_aux_vars (sym);
 	}
 
-      if ((sym->attr.dimension || IS_CLASS_ARRAY (sym))
-	  && DECL_LANG_SPECIFIC (sym->backend_decl)
-	  && GFC_DECL_SAVED_DESCRIPTOR (sym->backend_decl)
-	  && DECL_CONTEXT (sym->backend_decl) != current_function_decl)
-	gfc_nonlocal_dummy_array_decl (sym);
-
       if (sym->ts.type == BT_CLASS && sym->backend_decl)
 	GFC_DECL_CLASS(sym->backend_decl) = 1;
 
@@ -2950,13 +2908,14 @@ gfc_get_fake_result_decl (gfc_symbol * sym, int parent_flag)
       && sym->ns->proc_name->attr.entry_master
       && sym != sym->ns->proc_name)
     {
-      tree t = NULL, var;
+      tree t = NULL, var, field;
       if (this_fake_result_decl != NULL)
 	for (t = TREE_CHAIN (this_fake_result_decl); t; t = TREE_CHAIN (t))
 	  if (strcmp (IDENTIFIER_POINTER (TREE_PURPOSE (t)), sym->name) == 0)
 	    break;
       if (t)
 	return TREE_VALUE (t);
+
       decl = gfc_get_fake_result_decl (sym->ns->proc_name, parent_flag);
 
       if (parent_flag)
@@ -2964,20 +2923,17 @@ gfc_get_fake_result_decl (gfc_symbol * sym, int parent_flag)
       else
 	this_fake_result_decl = current_fake_result_decl;
 
-      if (decl && sym->ns->proc_name->attr.mixed_entry_master)
-	{
-	  tree field;
+      if (!sym->ns->proc_name->attr.mixed_entry_master)
+	return decl;
 
-	  for (field = TYPE_FIELDS (TREE_TYPE (decl));
-	       field; field = DECL_CHAIN (field))
-	    if (strcmp (IDENTIFIER_POINTER (DECL_NAME (field)),
-		sym->name) == 0)
-	      break;
+      for (field = TYPE_FIELDS (TREE_TYPE (decl));
+	   field; field = DECL_CHAIN (field))
+	if (strcmp (IDENTIFIER_POINTER (DECL_NAME (field)), sym->name) == 0)
+	  break;
 
-	  gcc_assert (field != NULL_TREE);
-	  decl = fold_build3_loc (input_location, COMPONENT_REF,
-				  TREE_TYPE (field), decl, field, NULL_TREE);
-	}
+      gcc_assert (field != NULL_TREE);
+      decl = fold_build3_loc (input_location, COMPONENT_REF,
+			      TREE_TYPE (field), decl, field, NULL_TREE);
 
       var = create_tmp_var_raw (TREE_TYPE (decl), sym->name);
       if (parent_flag)
@@ -6442,9 +6398,6 @@ gfc_generate_function_code (gfc_namespace * ns)
 
   gfc_generate_contained_functions (ns);
 
-  nonlocal_dummy_decls = NULL;
-  nonlocal_dummy_decl_pset = NULL;
-
   has_coarray_vars = false;
   generate_local_vars (ns);
 
@@ -6644,15 +6597,6 @@ gfc_generate_function_code (gfc_namespace * ns)
     = build3_v (BIND_EXPR, decl, DECL_SAVED_TREE (fndecl),
 		DECL_INITIAL (fndecl));
 
-  if (nonlocal_dummy_decls)
-    {
-      BLOCK_VARS (DECL_INITIAL (fndecl))
-	= chainon (BLOCK_VARS (DECL_INITIAL (fndecl)), nonlocal_dummy_decls);
-      delete nonlocal_dummy_decl_pset;
-      nonlocal_dummy_decls = NULL;
-      nonlocal_dummy_decl_pset = NULL;
-    }
-
   /* Output the GENERIC tree.  */
   dump_function (TDI_original, fndecl);
 
diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index 32d7ad63ac99e0f57a7d1df5a8b8e3070c6069e2..4bcdf440d7677552af10df93752b3422e86f50d2 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -2674,12 +2674,6 @@ gimplify_conversion (tree *expr_p)
   return GS_OK;
 }
 
-/* Nonlocal VLAs seen in the current function.  */
-static hash_set<tree> *nonlocal_vlas;
-
-/* The VAR_DECLs created for nonlocal VLAs for debug info purposes.  */
-static tree nonlocal_vla_vars;
-
 /* Gimplify a VAR_DECL or PARM_DECL.  Return GS_OK if we expanded a
    DECL_VALUE_EXPR, and it's worth re-examining things.  */
 
@@ -2710,38 +2704,7 @@ gimplify_var_or_parm_decl (tree *expr_p)
   /* If the decl is an alias for another expression, substitute it now.  */
   if (DECL_HAS_VALUE_EXPR_P (decl))
     {
-      tree value_expr = DECL_VALUE_EXPR (decl);
-
-      /* For referenced nonlocal VLAs add a decl for debugging purposes
-	 to the current function.  */
-      if (VAR_P (decl)
-	  && TREE_CODE (DECL_SIZE_UNIT (decl)) != INTEGER_CST
-	  && nonlocal_vlas != NULL
-	  && TREE_CODE (value_expr) == INDIRECT_REF
-	  && TREE_CODE (TREE_OPERAND (value_expr, 0)) == VAR_DECL
-	  && decl_function_context (decl) != current_function_decl)
-	{
-	  struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
-	  while (ctx
-		 && (ctx->region_type == ORT_WORKSHARE
-		     || ctx->region_type == ORT_SIMD
-		     || ctx->region_type == ORT_ACC))
-	    ctx = ctx->outer_context;
-	  if (!ctx && !nonlocal_vlas->add (decl))
-	    {
-	      tree copy = copy_node (decl);
-
-	      lang_hooks.dup_lang_specific_decl (copy);
-	      SET_DECL_RTL (copy, 0);
-	      TREE_USED (copy) = 1;
-	      DECL_CHAIN (copy) = nonlocal_vla_vars;
-	      nonlocal_vla_vars = copy;
-	      SET_DECL_VALUE_EXPR (copy, unshare_expr (value_expr));
-	      DECL_HAS_VALUE_EXPR_P (copy) = 1;
-	    }
-	}
-
-      *expr_p = unshare_expr (value_expr);
+      *expr_p = unshare_expr (DECL_VALUE_EXPR (decl));
       return GS_OK;
     }
 
@@ -12591,7 +12554,6 @@ gimplify_body (tree fndecl, bool do_parms)
   gimple_seq parm_stmts, parm_cleanup = NULL, seq;
   gimple *outer_stmt;
   gbind *outer_bind;
-  struct cgraph_node *cgn;
 
   timevar_push (TV_TREE_GIMPLIFY);
 
@@ -12618,10 +12580,6 @@ gimplify_body (tree fndecl, bool do_parms)
   unshare_body (fndecl);
   unvisit_body (fndecl);
 
-  cgn = cgraph_node::get (fndecl);
-  if (cgn && cgn->origin)
-    nonlocal_vlas = new hash_set<tree>;
-
   /* Make sure input_location isn't set to something weird.  */
   input_location = DECL_SOURCE_LOCATION (fndecl);
 
@@ -12674,27 +12632,6 @@ gimplify_body (tree fndecl, bool do_parms)
 	  }
     }
 
-  if (nonlocal_vlas)
-    {
-      if (nonlocal_vla_vars)
-	{
-	  /* tree-nested.c may later on call declare_vars (..., true);
-	     which relies on BLOCK_VARS chain to be the tail of the
-	     gimple_bind_vars chain.  Ensure we don't violate that
-	     assumption.  */
-	  if (gimple_bind_block (outer_bind)
-	      == DECL_INITIAL (current_function_decl))
-	    declare_vars (nonlocal_vla_vars, outer_bind, true);
-	  else
-	    BLOCK_VARS (DECL_INITIAL (current_function_decl))
-	      = chainon (BLOCK_VARS (DECL_INITIAL (current_function_decl)),
-			 nonlocal_vla_vars);
-	  nonlocal_vla_vars = NULL_TREE;
-	}
-      delete nonlocal_vlas;
-      nonlocal_vlas = NULL;
-    }
-
   if ((flag_openacc || flag_openmp || flag_openmp_simd)
       && gimplify_omp_ctxp)
     {
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 1b6e062db5069e286296f6b55ea4dfac708797a6..dfb167bdb6009ede63808dca44b615f612c0cf33 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,9 @@
+2018-06-17  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc.dg/debug/dwarf2/pr37726.c: Move to...
+	* gcc.dg/guality/pr37726.c: ...here and turn into GDB test.
+	* gnat.dg/stack_usage5.adb: New test.
+
 2018-06-16  Kugan Vivekanandarajah  <kuganv@linaro.org>
 
 	PR middle-end/82479
diff --git a/gcc/testsuite/gcc.dg/debug/dwarf2/pr37726.c b/gcc/testsuite/gcc.dg/debug/dwarf2/pr37726.c
deleted file mode 100644
index 622fbcf64017b93ab1b085b56fd572dd2adca3f2..0000000000000000000000000000000000000000
--- a/gcc/testsuite/gcc.dg/debug/dwarf2/pr37726.c
+++ /dev/null
@@ -1,25 +0,0 @@
-/* PR debug/37726 */
-/* { dg-do compile } */
-/* { dg-options "-gdwarf -O0 -dA -fno-merge-debug-strings" } */
-
-int foo (int parm)
-{
-  int var = 0;
-  int bar (void)
-  {
-    return parm + var;
-  }
-  parm++;
-  var++;
-  return bar ();
-}
-
-int
-main (void)
-{
-  return foo (4) - 6;
-}
-
-/* Both parm and var variables should be in debug info for both foo and bar.  */
-/* { dg-final { scan-assembler-times "\"parm\[^\n\]*\"\[^\n\]*DW_AT_name" 2 } } */
-/* { dg-final { scan-assembler-times "\"var\[^\n\]*\"\[^\n\]*DW_AT_name" 2 } } */
diff --git a/gcc/testsuite/gcc.dg/guality/pr37726.c b/gcc/testsuite/gcc.dg/guality/pr37726.c
new file mode 100644
index 0000000000000000000000000000000000000000..509d2d4c84a6affcb690a63d378e62101b50e23f
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/guality/pr37726.c
@@ -0,0 +1,27 @@
+/* PR debug/37726 */
+/* { dg-do run } */
+/* { dg-options "-g" } */
+/* { dg-skip-if "" { *-*-* }  { "*" } { "-O0" } } */
+
+int foo (int parm)
+{
+  int var = 0;
+  int bar (void)
+  {
+    return parm + var; /* BREAK */
+  }
+  parm++;              /* BREAK */
+  var++;
+  return bar ();
+}
+
+int
+main (void)
+{
+  return foo (4) - 6;
+}
+
+/* { dg-final { gdb-test 11 "parm" "5" } } */
+/* { dg-final { gdb-test 11 "var"  "1" } } */
+/* { dg-final { gdb-test 13 "parm" "4" } } */
+/* { dg-final { gdb-test 13 "var"  "0" } } */
diff --git a/gcc/testsuite/gnat.dg/stack_usage5.adb b/gcc/testsuite/gnat.dg/stack_usage5.adb
new file mode 100644
index 0000000000000000000000000000000000000000..55d0f13e1fa64d0196d90b00444f748ac8460331
--- /dev/null
+++ b/gcc/testsuite/gnat.dg/stack_usage5.adb
@@ -0,0 +1,15 @@
+-- { dg-do compile }
+-- { dg-options "-Wstack-usage=512" }
+
+procedure Stack_Usage5 (C : Character) is
+
+  S : String (1 .. 300);
+
+  procedure Set is
+  begin
+    S (1) := C;
+  end;
+
+begin
+  Set;
+end;
diff --git a/gcc/tree-nested.c b/gcc/tree-nested.c
index f1557c986b7f87c80f0b6b0f13b5b7eef46995a8..b335d6b0afefd0ac3077df0c48e5b693400ad68a 100644
--- a/gcc/tree-nested.c
+++ b/gcc/tree-nested.c
@@ -41,6 +41,7 @@
 #include "langhooks.h"
 #include "gimple-low.h"
 #include "gomp-constants.h"
+#include "diagnostic.h"
 
 
 /* The object of this pass is to lower the representation of a set of nested
@@ -236,23 +237,25 @@ get_frame_type (struct nesting_info *info)
   return type;
 }
 
-/* Return true if DECL should be referenced by pointer in the non-local
-   frame structure.  */
+/* Return true if DECL should be referenced by pointer in the non-local frame
+   structure.  */
 
 static bool
 use_pointer_in_frame (tree decl)
 {
   if (TREE_CODE (decl) == PARM_DECL)
     {
-      /* It's illegal to copy TREE_ADDRESSABLE, impossible to copy variable
-         sized decls, and inefficient to copy large aggregates.  Don't bother
-         moving anything but scalar variables.  */
+      /* It's illegal to copy TREE_ADDRESSABLE, impossible to copy variable-
+	 sized DECLs, and inefficient to copy large aggregates.  Don't bother
+	 moving anything but scalar parameters.  */
       return AGGREGATE_TYPE_P (TREE_TYPE (decl));
     }
   else
     {
-      /* Variable sized types make things "interesting" in the frame.  */
-      return DECL_SIZE (decl) == NULL || !TREE_CONSTANT (DECL_SIZE (decl));
+      /* Variable-sized DECLs can only come from OMP clauses at this point
+	 since the gimplifier has already turned the regular variables into
+	 pointers.  Do the same as the gimplifier.  */
+      return !DECL_SIZE (decl) || TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST;
     }
 }
 
@@ -263,6 +266,8 @@ static tree
 lookup_field_for_decl (struct nesting_info *info, tree decl,
 		       enum insert_option insert)
 {
+  gcc_checking_assert (decl_function_context (decl) == info->context);
+
   if (insert == NO_INSERT)
     {
       tree *slot = info->field_map->get (decl);
@@ -272,6 +277,7 @@ lookup_field_for_decl (struct nesting_info *info, tree decl,
   tree *slot = &info->field_map->get_or_insert (decl);
   if (!*slot)
     {
+      tree type = get_frame_type (info);
       tree field = make_node (FIELD_DECL);
       DECL_NAME (field) = DECL_NAME (decl);
 
@@ -290,9 +296,35 @@ lookup_field_for_decl (struct nesting_info *info, tree decl,
           TREE_ADDRESSABLE (field) = TREE_ADDRESSABLE (decl);
           DECL_NONADDRESSABLE_P (field) = !TREE_ADDRESSABLE (decl);
           TREE_THIS_VOLATILE (field) = TREE_THIS_VOLATILE (decl);
+
+	  /* Declare the transformation and adjust the original DECL.  For a
+	     variable or for a parameter when not optimizing, we make it point
+	     to the field in the frame directly.  For a parameter, we don't do
+	     it when optimizing because the variable tracking pass will already
+	     do the job,  */
+	  if (VAR_P (decl) || !optimize)
+	    {
+	      tree x
+		= build3 (COMPONENT_REF, TREE_TYPE (field), info->frame_decl,
+			  field, NULL_TREE);
+
+	      /* If the next declaration is a PARM_DECL pointing to the DECL,
+		 we need to adjust its VALUE_EXPR directly, since chains of
+		 VALUE_EXPRs run afoul of garbage collection.  This occurs
+		 in Ada for Out parameters that aren't copied in.  */
+	      tree next = DECL_CHAIN (decl);
+	      if (next
+		  && TREE_CODE (next) == PARM_DECL
+		  && DECL_HAS_VALUE_EXPR_P (next)
+		  && DECL_VALUE_EXPR (next) == decl)
+		SET_DECL_VALUE_EXPR (next, x);
+
+	      SET_DECL_VALUE_EXPR (decl, x);
+	      DECL_HAS_VALUE_EXPR_P (decl) = 1;
+	    }
 	}
 
-      insert_field_into_struct (get_frame_type (info), field);
+      insert_field_into_struct (type, field);
       *slot = field;
 
       if (TREE_CODE (decl) == PARM_DECL)
@@ -990,37 +1022,48 @@ convert_nonlocal_reference_op (tree *tp, int *walk_subtrees, void *data)
       /* FALLTHRU */
 
     case PARM_DECL:
-      if (decl_function_context (t) != info->context)
-	{
-	  tree x;
-	  wi->changed = true;
+      {
+	tree x, target_context = decl_function_context (t);
 
-	  x = get_nonlocal_debug_decl (info, t);
-	  if (!bitmap_bit_p (info->suppress_expansion, DECL_UID (t)))
-	    {
-	      tree target_context = decl_function_context (t);
-	      struct nesting_info *i;
-	      for (i = info->outer; i->context != target_context; i = i->outer)
-		continue;
-	      x = lookup_field_for_decl (i, t, INSERT);
-	      x = get_frame_field (info, target_context, x, &wi->gsi);
-	      if (use_pointer_in_frame (t))
-		{
-		  x = init_tmp_var (info, x, &wi->gsi);
-		  x = build_simple_mem_ref (x);
-		}
-	    }
+	if (info->context == target_context)
+	  break;
 
-	  if (wi->val_only)
-	    {
-	      if (wi->is_lhs)
-		x = save_tmp_var (info, x, &wi->gsi);
-	      else
+	wi->changed = true;
+
+	if (bitmap_bit_p (info->suppress_expansion, DECL_UID (t)))
+	  x = get_nonlocal_debug_decl (info, t);
+	else
+	  {
+	    struct nesting_info *i = info;
+	    while (i && i->context != target_context)
+	      i = i->outer;
+	    /* If none of the outer contexts is the target context, this means
+	       that the VAR or PARM_DECL is referenced in a wrong context.  */
+	    if (!i)
+	      internal_error ("%s from %s referenced in %s",
+			      IDENTIFIER_POINTER (DECL_NAME (t)),
+			      IDENTIFIER_POINTER (DECL_NAME (target_context)),
+			      IDENTIFIER_POINTER (DECL_NAME (info->context)));
+
+	    x = lookup_field_for_decl (i, t, INSERT);
+	    x = get_frame_field (info, target_context, x, &wi->gsi);
+	    if (use_pointer_in_frame (t))
+	      {
 		x = init_tmp_var (info, x, &wi->gsi);
-	    }
+		x = build_simple_mem_ref (x);
+	      }
+	  }
 
-	  *tp = x;
-	}
+	if (wi->val_only)
+	  {
+	    if (wi->is_lhs)
+	      x = save_tmp_var (info, x, &wi->gsi);
+	    else
+	      x = init_tmp_var (info, x, &wi->gsi);
+	  }
+
+	*tp = x;
+      }
       break;
 
     case LABEL_DECL:
@@ -1406,22 +1449,6 @@ note_nonlocal_vla_type (struct nesting_info *info, tree type)
     }
 }
 
-/* Create nonlocal debug decls for nonlocal VLA array bounds for VLAs
-   in BLOCK.  */
-
-static void
-note_nonlocal_block_vlas (struct nesting_info *info, tree block)
-{
-  tree var;
-
-  for (var = BLOCK_VARS (block); var; var = DECL_CHAIN (var))
-    if (VAR_P (var)
-	&& variably_modified_type_p (TREE_TYPE (var), NULL)
-	&& DECL_HAS_VALUE_EXPR_P (var)
-	&& decl_function_context (var) != info->context)
-      note_nonlocal_vla_type (info, TREE_TYPE (var));
-}
-
 /* Callback for walk_gimple_stmt.  Rewrite all references to VAR and
    PARM_DECLs that belong to outer functions.  This handles statements
    that are not handled via the standard recursion done in
@@ -1566,8 +1593,6 @@ convert_nonlocal_reference_stmt (gimple_stmt_iterator *gsi, bool *handled_ops_p,
     case GIMPLE_BIND:
       {
       gbind *bind_stmt = as_a <gbind *> (stmt);
-      if (!optimize && gimple_bind_block (bind_stmt))
-	note_nonlocal_block_vlas (info, gimple_bind_block (bind_stmt));
 
       for (tree var = gimple_bind_vars (bind_stmt); var; var = DECL_CHAIN (var))
 	if (TREE_CODE (var) == NAMELIST_DECL)
@@ -1683,7 +1708,7 @@ convert_local_reference_op (tree *tp, int *walk_subtrees, void *data)
       /* FALLTHRU */
 
     case PARM_DECL:
-      if (decl_function_context (t) == info->context)
+      if (t != info->frame_decl && decl_function_context (t) == info->context)
 	{
 	  /* If we copied a pointer to the frame, then the original decl
 	     is used unchanged in the parent function.  */
@@ -1697,8 +1722,9 @@ convert_local_reference_op (tree *tp, int *walk_subtrees, void *data)
 	    break;
 	  wi->changed = true;
 
-	  x = get_local_debug_decl (info, t, field);
-	  if (!bitmap_bit_p (info->suppress_expansion, DECL_UID (t)))
+	  if (bitmap_bit_p (info->suppress_expansion, DECL_UID (t)))
+	    x = get_local_debug_decl (info, t, field);
+	  else
 	    x = get_frame_field (info, info->context, field, &wi->gsi);
 
 	  if (wi->val_only)
@@ -2620,6 +2646,17 @@ convert_gimple_call (gimple_stmt_iterator *gsi, bool *handled_ops_p,
       target_context = decl_function_context (decl);
       if (target_context && DECL_STATIC_CHAIN (decl))
 	{
+	  struct nesting_info *i = info;
+	  while (i && i->context != target_context)
+	    i = i->outer;
+	  /* If none of the outer contexts is the target context, this means
+	     that the function is called in a wrong context.  */
+	  if (!i)
+	    internal_error ("%s from %s called in %s",
+			    IDENTIFIER_POINTER (DECL_NAME (decl)),
+			    IDENTIFIER_POINTER (DECL_NAME (target_context)),
+			    IDENTIFIER_POINTER (DECL_NAME (info->context)));
+
 	  gimple_call_set_chain (as_a <gcall *> (stmt),
 				 get_static_chain (info, target_context,
 						   &wi->gsi));
@@ -2941,6 +2978,33 @@ remap_vla_decls (tree block, struct nesting_info *root)
   delete id.cb.decl_map;
 }
 
+/* Fixup VLA decls in BLOCK and subblocks if remapped variables are
+   involved.  */
+
+static void
+fixup_vla_decls (tree block)
+{
+  for (tree var = BLOCK_VARS (block); var; var = DECL_CHAIN (var))
+    if (VAR_P (var) && DECL_HAS_VALUE_EXPR_P (var))
+      {
+	tree val = DECL_VALUE_EXPR (var);
+
+	if (!(TREE_CODE (val) == INDIRECT_REF
+	      && VAR_P (TREE_OPERAND (val, 0))
+	      && DECL_HAS_VALUE_EXPR_P (TREE_OPERAND (val, 0))))
+	  continue;
+
+	/* Fully expand value expressions.  This avoids having debug variables
+	   only referenced from them and that can be swept during GC.  */
+	val = build1 (INDIRECT_REF, TREE_TYPE (val),
+		      DECL_VALUE_EXPR (TREE_OPERAND (val, 0)));
+	SET_DECL_VALUE_EXPR (var, val);
+      }
+
+  for (tree sub = BLOCK_SUBBLOCKS (block); sub; sub = BLOCK_CHAIN (sub))
+    fixup_vla_decls (sub);
+}
+
 /* Fold the MEM_REF *E.  */
 bool
 fold_mem_refs (tree *const &e, void *data ATTRIBUTE_UNUSED)
@@ -3065,9 +3129,8 @@ finalize_nesting_tree_1 (struct nesting_info *root)
 		    gimple_seq_first_stmt (gimple_body (context)), true);
     }
 
-  /* If any parameters were referenced non-locally, then we need to
-     insert a copy.  Likewise, if any variables were referenced by
-     pointer, we need to initialize the address.  */
+  /* If any parameters were referenced non-locally, then we need to insert
+     a copy or a pointer.  */
   if (root->any_parm_remapped)
     {
       tree p;
@@ -3243,6 +3306,8 @@ finalize_nesting_tree_1 (struct nesting_info *root)
 	  = chainon (BLOCK_VARS (DECL_INITIAL (root->context)),
 		     root->debug_var_chain);
     }
+  else
+    fixup_vla_decls (DECL_INITIAL (root->context));
 
   /* Fold the rewritten MEM_REF trees.  */
   root->mem_refs->traverse<void *, fold_mem_refs> (NULL);
diff --git a/gcc/tree.c b/gcc/tree.c
index 2d3b26ed66b29df68bab3835b4a7dea8a3116ebf..8082932988ba4c8238abd1dfb6fbf69957de6677 100644
--- a/gcc/tree.c
+++ b/gcc/tree.c
@@ -6337,7 +6337,15 @@ decl_value_expr_lookup (tree from)
 
   h = value_expr_for_decl->find_with_hash (&in, DECL_UID (from));
   if (h)
-    return h->to;
+    {
+      /* Chains of value expressions may run afoul of garbage collection.  */
+      gcc_checking_assert (!(h->to
+			     && (TREE_CODE (h->to) == PARM_DECL
+				 || TREE_CODE (h->to) == VAR_DECL)
+			     && DECL_HAS_VALUE_EXPR_P (h->to)));
+      return h->to;
+    }
+
   return NULL_TREE;
 }
 
@@ -6348,6 +6356,12 @@ decl_value_expr_insert (tree from, tree to)
 {
   struct tree_decl_map *h;
 
+  /* Chains of value expressions may run afoul of garbage collection.  */
+  gcc_checking_assert (!(to
+			 && (TREE_CODE (to) == PARM_DECL
+			     || TREE_CODE (to) == VAR_DECL)
+			 && DECL_HAS_VALUE_EXPR_P (to)));
+
   h = ggc_alloc<tree_decl_map> ();
   h->base.from = from;
   h->to = to;