URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [global_references_1.f90] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do compile }! This program tests the patch for PRs 20881, 23308, 25538 & 25710! Assembled from PRs by Paul Thomas <pault@gcc.gnu.org>module mcontainssubroutine g(x) ! Local entityREAL :: xx = 1.0end subroutine gend module m! Error only appears once but testsuite associates with both lines.function f(x) ! { dg-error "is already being used as a FUNCTION" }REAL :: f, xf = xend function ffunction g(x) ! Global entityREAL :: g, xg = x! PR25710==========================================================! Lahey -2607-S: "SOURCE.F90", line 26:! Function 'f' cannot be referenced as a subroutine. The previous! definition is in 'line 12'.call f(g) ! { dg-error "is already being used as a FUNCTION" }end function g! Error only appears once but testsuite associates with both lines.function h(x) ! { dg-error "is already being used as a FUNCTION" }REAL :: h, xh = xend function hSUBROUTINE TT()CHARACTER(LEN=10), EXTERNAL :: j ! { dg-error "Return type mismatch" }CHARACTER(LEN=10) :: T! PR20881===========================================================! Error only appears once but testsuite associates with both lines.T = j (1.0) ! { dg-error "is already being used as a SUBROUTINE" }print *, TEND SUBROUTINE TTuse m ! Main programreal xinteger a(10)! PR23308===========================================================! Lahey - 2604-S: "SOURCE.F90", line 52:! The name 'foo' cannot be specified as both external procedure name! and common block name. The previous appearance is in 'line 68'.! Error only appears once but testsuite associates with both lines.common /foo/ a ! { dg-error "is already being used as a COMMON" }call f (x) ! OK - reference to local entitycall g (x) ! -ditto-! PR25710===========================================================! Lahey - 2607-S: "SOURCE.F90", line 62:! Function 'h' cannot be referenced as a subroutine. The previous! definition is in 'line 29'.call h (x) ! { dg-error "is already being used as a FUNCTION" }! PR23308===========================================================! Lahey - 2521-S: "SOURCE.F90", line 68: Intrinsic procedure name or! external procedure name same as common block name 'foo'.call foo () ! { dg-error "is already being used as a COMMON" }containsSUBROUTINE f (x) ! Local entityreal xx = 2end SUBROUTINE fend! PR20881===========================================================! Lahey - 2636-S: "SOURCE.F90", line 81:! Subroutine 'j' is previously referenced as a function in 'line 39'.SUBROUTINE j (x) ! { dg-error "is already being used as a SUBROUTINE" }integer a(10)common /bar/ a ! Global entity fooreal xx = bar(1.0) ! OK for local procedure to have common block namecontainsfunction bar (x)real bar, xbar = 2.0*xend function barEND SUBROUTINE j! PR25538===========================================================! would ICE with entry and procedure having same names.subroutine link2 (namef) ! { dg-error "is already being used as a SUBROUTINE" }entry link2 (nameg) ! { dg-error "is already being used as a SUBROUTINE" }returnend! { dg-final { cleanup-modules "m" } }
