URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [intrinsic_shadow_1.f03] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do compile }! { dg-options "-std=f2003 -Wintrinsic-shadow" }! PR fortran/33141! Check that the expected warnings are emitted if a user-procedure has the same! name as an intrinsic, but only if it is matched by the current -std=*.MODULE testmodIMPLICIT NONECONTAINS! ASIN is an intrinsicREAL FUNCTION asin (arg) ! { dg-warning "shadow the intrinsic" }IMPLICIT NONEREAL :: argEND FUNCTION asin! ASINH is one but not in F2003REAL FUNCTION asinh (arg) ! { dg-bogus "shadow the intrinsic" }IMPLICIT NONEREAL :: argEND FUNCTION asinhEND MODULE testmod! ACOS is an intrinsicREAL FUNCTION acos (arg) ! { dg-warning "of an intrinsic" }IMPLICIT NONEREAL :: argEND FUNCTION acos! ACOSH not for F2003REAL FUNCTION acosh (arg) ! { dg-bogus "of an intrinsic" }IMPLICIT NONEREAL :: argEND FUNCTION acosh! A subroutine with the same name as an intrinsic subroutineSUBROUTINE random_number (arg) ! { dg-warning "of an intrinsic" }IMPLICIT NONEREAL, INTENT(OUT) :: argEND SUBROUTINE random_number! But a subroutine with the name of an intrinsic function is ok.SUBROUTINE atan (arg) ! { dg-bogus "of an intrinsic" }IMPLICIT NONEREAL :: argEND SUBROUTINE atan! As should be a function with the name of an intrinsic subroutine.REAL FUNCTION random_seed () ! { dg-bogus "of an intrinsic" }END FUNCTION random_seed! We do only compile, so no main program needed.! { dg-final { cleanup-modules "testmod" } }
