OSDN Git Service

abad355b9ae68f68391b128aa512ed41cf7e1cb4
[pf3gnuchains/pf3gnuchains3x.git] / gcc / testsuite / gfortran.dg / namelist_43.f90
1 ! { dg-do run { target fd_truncate } }
2 ! { dg-options "-mieee" { target sh*-*-* } }
3 !
4 ! PR fortran/34427
5 !
6 ! Check that namelists and the real values Inf, NaN, Infinity
7 ! properly coexist with interceding line ends and spaces.
8 !
9 PROGRAM TEST
10   IMPLICIT NONE
11   real , DIMENSION(10) ::foo 
12   integer :: infinity
13   integer :: numb
14   NAMELIST /nl/ foo
15   NAMELIST /nl/ infinity
16   foo = -1.0
17   infinity = -1
18
19   open (10, status="scratch")
20
21   write (10,'(a)') " &nl foo(1:6) = 5, 5, 5, nan, infinity"
22   write (10,'(a)')
23   write (10,'(a)')
24   write (10,'(a)')
25   write (10,'(a)')
26   write (10,'(a)') "infinity"
27   write (10,'(a)')
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)') "=1/"
39   rewind (10)
40   READ (10, NML = nl)
41   CLOSE (10)
42   if(infinity /= 1) call abort
43   if(any(foo(1:3) /= [5.0, 5.0, 5.0]) .or. .not.isnan(foo(4)) &
44      .or. (foo(5) <= huge(foo)) .or. any(foo(6:10) /= -1.0)) &
45     call abort
46 END PROGRAM TEST