111
|
1 ! { dg-do run }
|
|
2 ! { dg-add-options ieee }
|
|
3 ! { dg-skip-if "NaN not supported" { spu-*-* } }
|
|
4 !
|
|
5 ! PR fortran/34427
|
|
6 !
|
|
7 ! Check that namelists and the real values Inf, NaN, Infinity
|
|
8 ! properly coexist with interceding line ends and spaces.
|
|
9 !
|
|
10 PROGRAM TEST
|
|
11 IMPLICIT NONE
|
|
12 real , DIMENSION(10) ::foo
|
|
13 integer :: infinity
|
|
14 integer :: numb
|
|
15 NAMELIST /nl/ foo
|
|
16 NAMELIST /nl/ infinity
|
|
17 foo = -1.0
|
|
18 infinity = -1
|
|
19
|
|
20 open (10, status="scratch")
|
|
21
|
|
22 write (10,'(a)') " &nl foo(1:6) = 5, 5, 5, nan, infinity"
|
|
23 write (10,'(a)')
|
|
24 write (10,'(a)')
|
|
25 write (10,'(a)')
|
|
26 write (10,'(a)')
|
|
27 write (10,'(a)') "infinity"
|
|
28 write (10,'(a)')
|
|
29 write (10,'(a)')
|
|
30 write (10,'(a)') " "
|
|
31 write (10,'(a)')
|
|
32 write (10,'(a)')
|
|
33 write (10,'(a)')
|
|
34 write (10,'(a)')
|
|
35 write (10,'(a)')
|
|
36 write (10,'(a)')
|
|
37 write (10,'(a)')
|
|
38 write (10,'(a)')
|
|
39 write (10,'(a)') "=1/"
|
|
40 rewind (10)
|
|
41 READ (10, NML = nl)
|
|
42 CLOSE (10)
|
131
|
43 if(infinity /= 1) STOP 1
|
111
|
44 if(any(foo(1:3) /= [5.0, 5.0, 5.0]) .or. .not.isnan(foo(4)) &
|
|
45 .or. (foo(5) <= huge(foo)) .or. any(foo(6:10) /= -1.0)) &
|
131
|
46 STOP 2
|
111
|
47 END PROGRAM TEST
|