]> git.ipfire.org Git - thirdparty/gcc.git/blame - gcc/testsuite/gfortran.dg/namelist_96.f90
2019-01-22 Manfred Schwarb <manfred99@gmx.ch>
[thirdparty/gcc.git] / gcc / testsuite / gfortran.dg / namelist_96.f90
CommitLineData
cc41270a 1! { dg-do run }
77aa0989 2program pr88776
3 implicit none
4 character(*), parameter :: file = "pr88776.dat"
5 type t_chan
6 integer :: ichan = -1
7 character(len=8) :: flag = ''
8 integer :: band = -1
9 end type t_chan
10 type(t_chan) :: chan
11 namelist /NML/ chan
12 open (11,file=file)
13 write(11,'(a)') trim("&nml chan = 1 '#1 ' 10 /")
14 write(11,'(a)') trim("&nml chan = 2 '#2 ' 42.36/")
15 write(11,'(a)') trim("&nml chan = 3 '#3 ' 30 /")
16 close(11)
17 call read (unit=10) ! No problem
18 call read (unit=5) ! problem, now fixed
19 open (11,file=file)
20 close (11, status="delete")
21contains
22 subroutine read (unit)
23 integer, intent(in) :: unit
24 integer :: stat
25 open (unit, file=file, action="read")
26 chan = t_chan(-1,'',-1)
27 stat = 0
28 read (unit, nml=NML, iostat=stat)
29 if (stat /= 0) stop 1
30 chan = t_chan(-1,'',-1)
31 read (unit, nml=NML, iostat=stat)
32 if (stat == 0) stop 2
33 if (chan% ichan /= 2) then
34 stop 3
35 end if
36 close (unit)
37 end subroutine read
38end program pr88776