2013-05-05 Tobias Burnus <burnus@net-b.de>
PR fortran/57141
* decl.c (gfc_match_null): Permit use-associated
NULL intrinsic.
2013-05-05 Tobias Burnus <burnus@net-b.de>
PR fortran/57141
* gfortran.dg/null_8.f90: New.
From-SVN: r198609
+2013-05-05 Tobias Burnus <burnus@net-b.de>
+
+ PR fortran/57141
+ * decl.c (gfc_match_null): Permit use-associated
+ NULL intrinsic.
+
2013-05-04 Tobias Burnus <burnus@net-b.de>
* decl.c (gfc_verify_c_interop_param): Permit allocatable
gfc_intrinsic_symbol (sym);
if (sym->attr.proc != PROC_INTRINSIC
+ && !(sym->attr.use_assoc && sym->attr.intrinsic)
&& (!gfc_add_procedure(&sym->attr, PROC_INTRINSIC, sym->name, NULL)
|| !gfc_add_function (&sym->attr, sym->name, NULL)))
return MATCH_ERROR;
+2013-05-05 Tobias Burnus <burnus@net-b.de>
+
+ PR fortran/57141
+ * gfortran.dg/null_8.f90: New.
+
2013-05-04 Paolo Carlini <paolo.carlini@oracle.com>
PR c++/53745
end subroutine sub3
subroutine foo (x,n)
- integer :: x(7,n,2,*), n
+ integer :: n
+ integer :: x(7,n,2,*)
if (ubound(x,1) /= 7 .or. ubound(x,2) /= 4 .or. ubound(x,3) /= 2) call abort
end subroutine foo
--- /dev/null
+! { dg-do compile }
+!
+! PR fortran/57141
+!
+! Contributed by Roger Ferrer Ibanez
+!
+MODULE M
+ INTRINSIC :: NULL
+END MODULE M
+
+MODULE M_INTERN
+ USE M
+ IMPLICIT NONE
+ REAL, POINTER :: ARR(:) => NULL()
+END MODULE M_INTERN