nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr71649.f90
blobc01389acfcf743049f71a664e19a2f0492b53778
1 ! { dg-do compile }
2 ! PR71649 Internal Compiler Error
3 SUBROUTINE Compiler_Options ( Options, Version, WriteOpt ) ! { dg-error "\(1\)" }
4 USE ISO_FORTRAN_ENV, ONLY : Compiler_Version, Compiler_Options ! { dg-error "conflicts with the" }
5 IMPLICIT NONE
6 CHARACTER (LEN=*), INTENT(OUT) :: Options
7 CHARACTER (LEN=*), INTENT(OUT) :: Version
8 LOGICAL, INTENT(IN), OPTIONAL :: WriteOpt
9 Version = Compiler_Version() ! { dg-error "has no IMPLICIT type" }
10 Options = Compiler_Options() ! { dg-error "Unexpected use of subroutine name" }
11 RETURN
12 END SUBROUTINE Compiler_Options