Update ChangeLog and version files for release
[official-gcc.git] / gcc / testsuite / gfortran.dg / intrinsic_std_4.f90
blobe83ed4c884d7cb1c1aa24ac94612f605c5d3bd90
1 ! { dg-do run }
2 ! { dg-options "-std=f95 -Wno-intrinsics-std" }
4 ! PR fortran/33141
5 ! Check that calls to intrinsics not in the current standard are "allowed" and
6 ! linked to external procedures with that name.
7 ! Addionally, this checks that -Wno-intrinsics-std turns off the warning.
9 SUBROUTINE abort ()
10 IMPLICIT NONE
11 WRITE (*,*) "Correct"
12 END SUBROUTINE abort
14 REAL FUNCTION asinh (arg)
15 IMPLICIT NONE
16 REAL :: arg
18 WRITE (*,*) "Correct"
19 asinh = arg
20 END FUNCTION asinh
22 SUBROUTINE implicit_none
23 IMPLICIT NONE
24 REAL :: asinh ! { dg-bogus "Fortran 2008" }
25 REAL :: x
27 ! Both times our version above should be called
28 CALL abort () ! { dg-bogus "extension" }
29 x = ASINH (1.) ! { dg-bogus "Fortran 2008" }
30 END SUBROUTINE implicit_none
32 SUBROUTINE implicit_type
33 ! ASINH has implicit type here
34 REAL :: x
36 ! Our version should be called
37 x = ASINH (1.) ! { dg-bogus "Fortran 2008" }
38 END SUBROUTINE implicit_type
40 PROGRAM main
41 ! This should give a total of three "Correct"s
42 CALL implicit_none ()
43 CALL implicit_type ()
44 END PROGRAM main
46 ! { dg-output "Correct\.*Correct\.*Correct" }