From 945a98a4b2deb725bdd3f93801a2eeb8e262cca0 Mon Sep 17 00:00:00 2001
From: Tobias Burnus <burnus@gcc.gnu.org>
Date: Fri, 16 Mar 2007 11:57:45 +0100
Subject: [PATCH] [multiple changes]

2007-03-16  Paul Thomas  <pault@gcc.gnu.org>
	    Tobias Burnus  <burnus@net-b.de>

	PR fortran/31188
	* expr.c (find_array_section): Allow
	  non-expression-constant variables.

2007-03-16  Tobias Burnus  <burnus@net-b.de>

	PR fortran/31188
	* gfortran.dg/parameter_array_dummy.f90: New test.

From-SVN: r122987
---
 gcc/fortran/expr.c                            |  8 ++++++-
 .../gfortran.dg/parameter_array_dummy.f90     | 21 +++++++++++++++++++
 2 files changed, 28 insertions(+), 1 deletion(-)
 create mode 100644 gcc/testsuite/gfortran.dg/parameter_array_dummy.f90

diff --git a/gcc/fortran/expr.c b/gcc/fortran/expr.c
index 06f4d20ef45c..bf5b74dab061 100644
--- a/gcc/fortran/expr.c
+++ b/gcc/fortran/expr.c
@@ -1063,7 +1063,13 @@ find_array_section (gfc_expr *expr, gfc_ref *ref)
       if (ref->u.ar.dimen_type[d] == DIMEN_VECTOR)  /* Vector subscript.  */
 	{
 	  gcc_assert (begin);
-	  gcc_assert (begin->expr_type == EXPR_ARRAY); 
+
+	  if (begin->expr_type != EXPR_ARRAY)
+	    {
+	      t = FAILURE;
+	      goto cleanup;
+	    }
+
 	  gcc_assert (begin->rank == 1);
 	  gcc_assert (begin->shape);
 
diff --git a/gcc/testsuite/gfortran.dg/parameter_array_dummy.f90 b/gcc/testsuite/gfortran.dg/parameter_array_dummy.f90
new file mode 100644
index 000000000000..2aa3ad8ef8cf
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/parameter_array_dummy.f90
@@ -0,0 +1,21 @@
+! { dg-do run}
+! PR fortran/31188
+program foo_mod
+  implicit none
+  character (len=1), parameter :: letters(2) = (/"a","b"/)
+  call concat(1, [1])
+  call concat(2, [2])
+  call concat(3, [1,2])
+  call concat(4, [2,1])
+  call concat(5, [2,2,2])
+contains
+  subroutine concat(i, ivec)
+    integer, intent(in)  :: i, ivec(:)
+    write (*,*) i, "a" // letters(ivec)
+  end subroutine concat
+end program foo_mod
+! { dg-output "1 aa" }
+! { dg-output "2 ab" }
+! { dg-output "3 aaab" }
+! { dg-output "4 abaa" }
+! { dg-output "5 ababab" }
-- 
GitLab