1 ! { dg-do run { target fd_truncate } }
2 ! { dg-add-options ieee }
3 ! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
7 ! Check that namelists and the real values Inf, NaN, Infinity
12 real , DIMENSION(11) ::foo
15 NAMELIST /nl
/ infinity
19 open (10, status
="scratch")
21 write (10,*) " &nl foo = 5, 5, 5, nan, infinity, infinity "
23 write (10,*) " = 1, /"
28 if(infinity
/= 1) call abort()
29 if(any(foo(1:3) /= [5.0, 5.0, 5.0]) .or
. .not
.isnan(foo(4)) &
30 .or
. foo(5) <= huge(foo
) .or
. any(foo(6:11) /= -1.0)) &
36 open (10, status
="scratch")
38 write (10,'(a)') "&nl foo = 5, 5, 5, nan, infinity, infinity"
39 write (10,'(a)') "=1,/"
44 if(infinity
/= 1) call abort()
45 if(any(foo(1:3) /= [5.0, 5.0, 5.0]) .or
. .not
.isnan(foo(4)) &
46 .or
. foo(5) <= huge(foo
) .or
. any(foo(6:11) /= -1.0)) &