PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / read_list_eof_1.f90
bloba82e94f231a19c791e9879f74d54818e8ea551e4
1 ! { dg-do run }
2 ! PR 49296 List formatted read of file without EOR marker (\n).
3 program read_list_eof_1
4 implicit none
5 character(len=100) :: s
6 integer :: ii
7 real :: rr
8 logical :: ll
10 call genfil ('a')
11 open (unit=20, file='read.dat', form='FORMATTED', action='READ', &
12 status='OLD')
13 read (20, fmt=*) s
14 close (20, status='delete')
15 if (trim(s) /= "a") then
16 STOP 1
17 end if
19 call genfil ('1')
20 open (unit=20, file='read.dat', form='FORMATTED', action='READ', &
21 status='OLD')
22 read (20, fmt=*) ii
23 close (20, status='delete')
24 if (ii /= 1) then
25 STOP 2
26 end if
28 call genfil ('1.5')
29 open (unit=20, file='read.dat', form='FORMATTED', action='READ', &
30 status='OLD')
31 read (20, fmt=*) rr
32 close (20, status='delete')
33 if (rr /= 1.5) then
34 STOP 3
35 end if
37 call genfil ('T')
38 open (unit=20, file='read.dat', form='FORMATTED', action='READ', &
39 status='OLD')
40 read (20, fmt=*) ll
41 close (20, status='delete')
42 if (.not. ll) then
43 STOP 4
44 end if
46 contains
47 subroutine genfil(str)
48 character(len=*), intent(in) :: str
49 open(10, file='read.dat', form='unformatted', action='write', &
50 status='replace', access='stream')
51 write(10) str
52 close(10)
53 end subroutine genfil
54 end program read_list_eof_1