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/] [import2.f90] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do compile }! { dg-options "-std=f95" }! { dg-shouldfail "Fortran 2003 feature with -std=f95" }! Test whether import does not work with -std=f95! PR fortran/29601subroutine test(x)type myType3sequenceinteger :: iend type myType3type(myType3) :: xif(x%i /= 7) call abort()x%i = 1end subroutine testsubroutine bar(x,y)type myTypesequenceinteger :: iend type myTypetype(myType) :: xinteger(8) :: yif(y /= 8) call abort()if(x%i /= 2) call abort()x%i = 5y = 42end subroutine barmodule testmodimplicit noneinteger, parameter :: kind = 8type modTypereal :: rvend type modTypeinterfacesubroutine other(x,y)import ! { dg-error "Fortran 2003: IMPORT statement" }type(modType) :: y ! { dg-error "not been declared within the interface" }real(kind) :: x ! { dg-error "has not been declared" }end subroutineend interfaceend module testmodprogram foointeger, parameter :: dp = 8type myTypesequenceinteger :: iend type myTypetype myType3sequenceinteger :: iend type myType3interfacesubroutine bar(x,y)import ! { dg-error "Fortran 2003: IMPORT statement" }type(myType) :: x ! { dg-error "not been declared within the interface" }integer(dp) :: y ! { dg-error "has not been declared" }end subroutine barsubroutine test(x)import :: myType3 ! { dg-error "Fortran 2003: IMPORT statement" }import myType3 ! { dg-error "Fortran 2003: IMPORT statement" }type(myType3) :: x ! { dg-error "not been declared within the interface" }end subroutine testend interfacetype(myType) :: ytype(myType3) :: zinteger(dp) :: i8y%i = 2i8 = 8call bar(y,i8) ! { dg-error "Type mismatch in argument" }if(y%i /= 5 .or. i8/= 42) call abort()z%i = 7call test(z) ! { dg-error "Type mismatch in argument" }if(z%i /= 1) call abort()end program foo! { dg-final { cleanup-modules "testmod" } }
