OSDN Git Service

2010-07-24 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / bind_c_usage_9.f03
1 ! { dg-do compile }
2 ! { dg-options "-std=f2003" }
3 ! PR fortran/34133
4 !
5 ! The compiler should reject internal procedures with BIND(c) attribute
6 ! for Fortran 2003.
7 !
8 subroutine foo() bind(c)
9 contains
10   subroutine bar() bind (c) ! { dg-error "may not be specified for an internal" }
11   end subroutine bar ! { dg-error "Expected label" }
12 end subroutine foo ! { dg-error "Fortran 2008: CONTAINS statement" }
13
14 subroutine foo2() bind(c)
15   use iso_c_binding
16 contains
17   integer(c_int) function barbar() bind (c) ! { dg-error "may not be specified for an internal" }
18   end function barbar ! { dg-error "Expecting END SUBROUTINE" }
19 end subroutine foo2 ! { dg-error "Fortran 2008: CONTAINS statement" }
20
21 function one() bind(c)
22   use iso_c_binding
23   integer(c_int) :: one
24   one = 1
25 contains
26   integer(c_int) function two() bind (c) ! { dg-error "may not be specified for an internal" }
27   end function two ! { dg-error "Expected label" }
28 end function one ! { dg-error "Fortran 2008: CONTAINS statement" }
29
30 function one2() bind(c)
31   use iso_c_binding
32   integer(c_int) :: one2
33   one2 = 1
34 contains
35   subroutine three() bind (c) ! { dg-error "may not be specified for an internal" }
36   end subroutine three ! { dg-error "Expecting END FUNCTION statement" }
37 end function one2 ! { dg-error "Fortran 2008: CONTAINS statement" }
38
39 program main
40   use iso_c_binding
41   implicit none
42 contains
43   subroutine test() bind(c) ! { dg-error "may not be specified for an internal" }
44   end subroutine test ! { dg-error "Expecting END PROGRAM" }
45   integer(c_int) function test2() bind (c) ! { dg-error "may not be specified for an internal" }
46   end function test2  ! { dg-error "Expecting END PROGRAM" }
47 end program main ! { dg-error "Fortran 2008: CONTAINS statement" }