blob: 0eead9c2011c3a56e15f80aefe7b522124149b4b [file] [log] [blame]
! { dg-do run }
! { dg-add-options ieee }
!
! PR fortran/34427
!
! Check that namelists and the real values Inf, NaN, Infinity
! properly coexist with interceding line ends and spaces.
!
PROGRAM TEST
IMPLICIT NONE
real , DIMENSION(10) ::foo
integer :: infinity
integer :: numb
NAMELIST /nl/ foo
NAMELIST /nl/ infinity
foo = -1.0
infinity = -1
open (10, status="scratch")
write (10,'(a)') " &nl foo(1:6) = 5, 5, 5, nan, infinity"
write (10,'(a)')
write (10,'(a)')
write (10,'(a)')
write (10,'(a)')
write (10,'(a)') "infinity"
write (10,'(a)')
write (10,'(a)')
write (10,'(a)') " "
write (10,'(a)')
write (10,'(a)')
write (10,'(a)')
write (10,'(a)')
write (10,'(a)')
write (10,'(a)')
write (10,'(a)')
write (10,'(a)')
write (10,'(a)') "=1/"
rewind (10)
READ (10, NML = nl)
CLOSE (10)
if(infinity /= 1) STOP 1
if(any(foo(1:3) /= [5.0, 5.0, 5.0]) .or. .not.isnan(foo(4)) &
.or. (foo(5) <= huge(foo)) .or. any(foo(6:10) /= -1.0)) &
STOP 2
END PROGRAM TEST