+2016-07-14 Steven G. Kargl <kargl@gcc.gnu.org>
+
+ PR fortran/29819
+ * parse.c (parse_contained): Use proper locus.
+
2016-07-14 Andre Vehreschild <vehre@gcc.gnu.org>
PR fortran/70842
gfc_statement st;
gfc_symbol *sym;
gfc_entry_list *el;
+ locus old_loc;
int contains_statements = 0;
int seen_error = 0;
next:
/* Process the next available statement. We come here if we got an error
and rejected the last statement. */
+ old_loc = gfc_current_locus;
st = next_statement ();
switch (st)
pop_state ();
if (!contains_statements)
gfc_notify_std (GFC_STD_F2008, "CONTAINS statement without "
- "FUNCTION or SUBROUTINE statement at %C");
+ "FUNCTION or SUBROUTINE statement at %L", &old_loc);
}
+2016-07-14 Steven G. Kargl <kargl@gcc.gnu.org>
+
+ PR fortran/29819
+ * gfortran.dg/bind_c_usage_9.f03: Move dg-error.
+ * gfortran.dg/contains.f90: Ditto.
+ * gfortran.dg/contains_empty_1.f03: Ditto.
+ * gfortran.dg/submodule_3.f08: Ditto.
+
2016-07-14 Jakub Jelinek <jakub@redhat.com>
PR testsuite/71865
! for Fortran 2003.
!
subroutine foo() bind(c)
-contains
+contains ! { dg-error "Fortran 2008: CONTAINS statement" }
subroutine bar() bind (c) ! { dg-error "may not be specified for an internal" }
end subroutine bar ! { dg-error "Expected label" }
-end subroutine foo ! { dg-error "Fortran 2008: CONTAINS statement" }
+end subroutine foo
subroutine foo2() bind(c)
use iso_c_binding
-contains
+contains ! { dg-error "Fortran 2008: CONTAINS statement" }
integer(c_int) function barbar() bind (c) ! { dg-error "may not be specified for an internal" }
end function barbar ! { dg-error "Expecting END SUBROUTINE" }
-end subroutine foo2 ! { dg-error "Fortran 2008: CONTAINS statement" }
+end subroutine foo2
function one() bind(c)
use iso_c_binding
integer(c_int) :: one
one = 1
-contains
+contains ! { dg-error "Fortran 2008: CONTAINS statement" }
integer(c_int) function two() bind (c) ! { dg-error "may not be specified for an internal" }
end function two ! { dg-error "Expected label" }
-end function one ! { dg-error "Fortran 2008: CONTAINS statement" }
+end function one
function one2() bind(c)
use iso_c_binding
integer(c_int) :: one2
one2 = 1
-contains
+contains ! { dg-error "Fortran 2008: CONTAINS statement" }
subroutine three() bind (c) ! { dg-error "may not be specified for an internal" }
end subroutine three ! { dg-error "Expecting END FUNCTION statement" }
-end function one2 ! { dg-error "Fortran 2008: CONTAINS statement" }
+end function one2
program main
use iso_c_binding
implicit none
-contains
+contains ! { dg-error "Fortran 2008: CONTAINS statement" }
subroutine test() bind(c) ! { dg-error "may not be specified for an internal" }
end subroutine test ! { dg-error "Expecting END PROGRAM" }
integer(c_int) function test2() bind (c) ! { dg-error "may not be specified for an internal" }
end function test2 ! { dg-error "Expecting END PROGRAM" }
-end program main ! { dg-error "Fortran 2008: CONTAINS statement" }
+end program main
! Check whether empty contains are allowd
! PR fortran/29806
module x
- contains
-end module x ! { dg-error "CONTAINS statement without FUNCTION or SUBROUTINE statement" }
+ contains ! { dg-error "CONTAINS statement without FUNCTION or SUBROUTINE statement" }
+end module x
program y
- contains
-end program y ! { dg-error "CONTAINS statement without FUNCTION or SUBROUTINE statement" }
+ contains ! { dg-error "CONTAINS statement without FUNCTION or SUBROUTINE statement" }
+end program y
! { dg-options "-std=f2003 -pedantic" }
program test
print *, 'hello there'
-contains
-end program test ! { dg-error "Fortran 2008: CONTAINS statement without" }
+contains ! { dg-error "Fortran 2008: CONTAINS statement without" }
+end program test
module truc
integer, parameter :: answer = 42
-contains
-end module truc ! { dg-error "Fortran 2008: CONTAINS statement without" }
+contains ! { dg-error "Fortran 2008: CONTAINS statement without" }
+end module truc
!
SUBMODULE (foo_interface) foo_interface_son ! { dg-error "SUBMODULE declaration" }
!
- contains
+ contains ! { dg-error "CONTAINS statement without FUNCTION or SUBROUTINE" }
module function array1 (this) result(that) ! { dg-error "MODULE prefix" }
end function ! { dg-error "Expecting END PROGRAM" }
end SUBMODULE foo_interface_son ! { dg-error "Expecting END PROGRAM" }
-end ! { dg-error "CONTAINS statement without FUNCTION or SUBROUTINE" }
+end