URL
https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk
Subversion Repositories openrisc_me
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [bind_c_usage_9.f03] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do compile }! { dg-options "-std=f2003" }! PR fortran/34133!! The compiler should reject internal procedures with BIND(c) attribute! for Fortran 2003.!subroutine foo() bind(c)containssubroutine 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" }subroutine foo2() bind(c)use iso_c_bindingcontainsinteger(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" }function one() bind(c)use iso_c_bindinginteger(c_int) :: oneone = 1containsinteger(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" }function one2() bind(c)use iso_c_bindinginteger(c_int) :: one2one2 = 1containssubroutine 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" }program mainuse iso_c_bindingimplicit nonecontainssubroutine 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" }
