From ed42adef4426b71f8f8fecac981a19c29335d454 Mon Sep 17 00:00:00 2001
From: Daniel Kraft <d@domob.eu>
Date: Sun, 12 Oct 2008 12:51:11 +0200
Subject: [PATCH] re PR fortran/37688 (Relax "Symbol is used before it is
 typed" checking)

2008-10-12  Daniel Kraft  <d@domob.eu>

	PR fortran/37688
	* expr.c (gfc_expr_check_typed): Extend permission of untyped
	expressions to both top-level variable and basic arithmetic expressions.

2008-10-12  Daniel Kraft  <d@domob.eu>

	PR fortran/37688
	* gfortran.dg/used_before_typed_6.f90: New test.

From-SVN: r141074
---
 gcc/fortran/ChangeLog                         |  6 +++++
 gcc/fortran/expr.c                            | 27 ++++++++++++++++---
 gcc/testsuite/ChangeLog                       |  5 ++++
 .../gfortran.dg/used_before_typed_6.f90       | 20 ++++++++++++++
 4 files changed, 54 insertions(+), 4 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/used_before_typed_6.f90

diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index ac1eaf63bcf5..5bcfb6446ba3 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,9 @@
+2008-10-12  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37688
+	* expr.c (gfc_expr_check_typed): Extend permission of untyped
+	expressions to both top-level variable and basic arithmetic expressions.
+
 2008-10-12  Paul Thomas  <pault@gcc.gnu.org>
 
 	PR fortran/37787
diff --git a/gcc/fortran/expr.c b/gcc/fortran/expr.c
index 5a167b7067f8..73f2c40a36c4 100644
--- a/gcc/fortran/expr.c
+++ b/gcc/fortran/expr.c
@@ -3429,9 +3429,11 @@ gfc_expr_set_symbols_referenced (gfc_expr *expr)
 
 /* Walk an expression tree and check each variable encountered for being typed.
    If strict is not set, a top-level variable is tolerated untyped in -std=gnu
-   mode; this is for things in legacy-code like:
+   mode as is a basic arithmetic expression using those; this is for things in
+   legacy-code like:
 
      INTEGER :: arr(n), n
+     INTEGER :: arr(n + 1), n
 
    The namespace is needed for IMPLICIT typing.  */
 
@@ -3458,9 +3460,26 @@ gfc_expr_check_typed (gfc_expr* e, gfc_namespace* ns, bool strict)
 {
   bool error_found;
 
-  /* If this is a top-level variable, do the check with strict given to us.  */
-  if (!strict && e->expr_type == EXPR_VARIABLE && !e->ref)
-    return gfc_check_symbol_typed (e->symtree->n.sym, ns, strict, e->where);
+  /* If this is a top-level variable or EXPR_OP, do the check with strict given
+     to us.  */
+  if (!strict)
+    {
+      if (e->expr_type == EXPR_VARIABLE && !e->ref)
+	return gfc_check_symbol_typed (e->symtree->n.sym, ns, strict, e->where);
+
+      if (e->expr_type == EXPR_OP)
+	{
+	  gfc_try t = SUCCESS;
+
+	  gcc_assert (e->value.op.op1);
+	  t = gfc_expr_check_typed (e->value.op.op1, ns, strict);
+
+	  if (t == SUCCESS && e->value.op.op2)
+	    t = gfc_expr_check_typed (e->value.op.op2, ns, strict);
+
+	  return t;
+	}
+    }
 
   /* Otherwise, walk the expression and do it strictly.  */
   check_typed_ns = ns;
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 81512ef1e693..a3f773803bf5 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2008-10-12  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37688
+	* gfortran.dg/used_before_typed_6.f90: New test.
+
 2008-10-12  Paul Thomas  <pault@gcc.gnu.org>
 
 	PR fortran/37787
diff --git a/gcc/testsuite/gfortran.dg/used_before_typed_6.f90 b/gcc/testsuite/gfortran.dg/used_before_typed_6.f90
new file mode 100644
index 000000000000..abcac8cf96db
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/used_before_typed_6.f90
@@ -0,0 +1,20 @@
+! { dg-do compile }
+! { dg-options "-std=gnu" }
+
+! Allow legacy code to work even if not only a single symbol is used as
+! expression but a basic arithmetic expression.
+
+SUBROUTINE test (n, m)
+  IMPLICIT NONE
+
+  ! These should go fine.
+  INTEGER :: arr1(n + 1) ! { dg-bogus "used before it is typed" }
+  INTEGER :: arr2(n / (2 * m**5)) ! { dg-bogus "used before it is typed" }
+
+  ! These should fail for obvious reasons.
+  INTEGER :: arr3(n * 1.1) ! { dg-error "must be of INTEGER type" }
+  INTEGER :: arr4(REAL (m)) ! { dg-error "used before it is typed" }
+  INTEGER :: arr5(SIN (m)) ! { dg-error "used before it is typed" }
+
+  INTEGER :: n, m
+END SUBROUTINE test
-- 
GitLab