view gcc/testsuite/gfortran.dg/namelist_43.f90 @ 158:494b0b89df80 default tip

...
author Shinji KONO <kono@ie.u-ryukyu.ac.jp>
date Mon, 25 May 2020 18:13:55 +0900
parents 1830386684a0
children
line wrap: on
line source

! { 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