PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / direct_io_1.f90
blob96ae49035063a24c969781c2f4584532c4063e6b
1 ! { dg-do run }
2 ! PR 16908
3 ! Segfaulted on second set of writes. We weren't handling partial records
4 ! properly when calculating the file position.
5 program direct_io_1
6 implicit none
8 integer n, nt, mt, m
9 real dt, tm, w
10 real, allocatable :: p(:)
12 nt = 2049 ! if nt < 2049, then everything works.
14 allocate(p(nt))
15 p = 0.e0
17 inquire(iolength=mt) (p(m), m=1, nt)
19 open(unit=12, file='syn.sax', access='direct', recl=mt)
20 n = 1
21 write(12, rec=n) mt, nt
22 write(12, rec=n+1) (p(m), m=1, nt)
23 close(12)
25 inquire(iolength=mt) (p(m), m=1, nt)
27 open(unit=12, file='syn.sax', access='direct', recl=mt)
28 n = 1
29 write(12, rec=n) mt, nt
30 write(12, rec=n+1) (p(m), m=1, nt)
31 close(12, status='delete')
32 end program