PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / streamio_8.f90
blobf4f8eba1ba96a54e2bb4dc2fca5ce1130f6676e0
1 ! { dg-do run }
2 ! PR25828 Stream IO test 8
3 ! Contributed by Jerry DeLisle <jvdelisle@verizon.net>.
4 PROGRAM stream_io_8
5 IMPLICIT NONE
6 integer(kind=8) mypos
7 character(10) mystring
8 real(kind=8) r
9 mypos = 0
10 mystring = "not yet"
11 r = 12.25d0
12 OPEN(UNIT=11, ACCESS="stream")
13 inquire(unit=11, pos=mypos)
14 if (mypos.ne.1) STOP 1
15 WRITE(11) "first"
16 inquire(unit=11, pos=mypos)
17 if (mypos.ne.6) STOP 2
18 WRITE(11) "second"
19 inquire(unit=11, pos=mypos)
20 if (mypos.ne.12) STOP 3
21 WRITE(11) 1234567_4
22 inquire(unit=11, pos=mypos)
23 if (mypos.ne.16) STOP 4
24 write(11) r
25 r = 0.0
26 inquire (11, pos=mypos)
27 read(11,pos=16)r
28 if (abs(r-12.25d0)>1e-10) STOP 5
29 inquire(unit=11, pos=mypos)
30 inquire(unit=11, access=mystring)
31 if (mypos.ne.24) STOP 6
32 if (mystring.ne."STREAM") STOP 7
33 CLOSE(UNIT=11, status="delete")
34 END PROGRAM stream_io_8