+2016-09-28 Steven G. Kargl <kargl@gcc.gnu.org>
+
+ backport from trunk
+ PR fortran/71730
+ * decl.c (char_len_param_value): Check return value of
+ gfc_reduce_init_expr().
+
+ PR fortran/77612
+ * decl.c (char_len_param_value): Check parent namespace for
+ seen_implicit_none.
+
2016-09-28 Steven G. Kargl <kargl@gcc.gnu.org>
backport from trunk
goto syntax;
else if ((*expr)->expr_type == EXPR_VARIABLE)
{
+ bool t;
gfc_expr *e;
e = gfc_copy_expr (*expr);
&& e->ref->u.ar.dimen_type[0] == DIMEN_RANGE)
goto syntax;
- gfc_reduce_init_expr (e);
+ t = gfc_reduce_init_expr (e);
+
+ if (!t && e->ts.type == BT_UNKNOWN
+ && e->symtree->n.sym->attr.untyped == 1
+ && (e->symtree->n.sym->ns->seen_implicit_none == 1
+ || e->symtree->n.sym->ns->parent->seen_implicit_none == 1))
+ {
+ gfc_free_expr (e);
+ goto syntax;
+ }
if ((e->ref && e->ref->type == REF_ARRAY
&& e->ref->u.ar.type != AR_ELEMENT)
+2016-09-28 Steven G. Kargl <kargl@gcc.gnu.org>
+
+ backport from trunk
+ PR fortran/71730
+ * gfortran.dg/pr71730.f90: New test.
+ * gfortran.dg/bounds_check_strlen_2.f90: Fix invalid code.
+ * gfortran.dg/array_constructor_27.f03: Update dg-error message.
+ * gfortran.dg/array_constructor_26.f03: Ditto.
+
+ PR fortran/77612
+ * gfortran.dg/pr77612.f90: New test.
+
2016-09-28 Steven G. Kargl <kargl@gcc.gnu.org>
backport from trunk
INTEGER (1), PARAMETER :: MAXFLD = 25_1, MAXHED = 5_1, MAXCHR = 80_1
integer :: i
TYPE TWindowData
- CHARACTER (MAX_FLD_HED, 1) :: DWFdHd(MAXFLD) = [(" ", i = 1, MAXFLD)]
- ! { dg-error "specification expression" "" { target *-*-* } 13 }
+ CHARACTER (MAX_FLD_HED, 1) :: DWFdHd(MAXFLD) = [(" ", i = 1, MAXFLD)] ! { dg-error "Scalar INTEGER expression" }
END TYPE TWindowData
END MODULE WinData
implicit none
type t
- character (a) :: arr (1) = [ "a" ]
- ! { dg-error "specification expression" "" { target *-*-* } 11 }
+ character (a) :: arr (1) = [ "a" ] ! { dg-error "Scalar INTEGER expression" }
end type t
end
SUBROUTINE test (str, n)
IMPLICIT NONE
- CHARACTER(len=n) :: str
INTEGER :: n
+ CHARACTER(len=n) :: str
END SUBROUTINE test
SUBROUTINE test2 (str)
--- /dev/null
+! { dg-do compile }
+subroutine foo
+ implicit none
+ character(len=bar) :: a ! { dg-error "Scalar INTEGER expression" }
+end subroutine foo
--- /dev/null
+! { dg-do compile }
+
+program bad_len
+
+ implicit none
+
+contains
+
+ subroutine sub
+ character(len = ICE) :: line ! { dg-error "INTEGER expression expected" }
+ end subroutine
+
+end program