OSDN Git Service

2011-09-26 Janus Weil <janus@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / streamio_1.f90
1 ! { dg-do run }
2 ! PR25828 Stream IO test 1
3 ! Contributed by Jerry DeLisle <jvdelisle@verizon.net>.
4 PROGRAM stream_io_1
5   IMPLICIT NONE
6   integer(kind=4) i
7   real(kind=8) r
8   OPEN(UNIT=11, ACCESS="stream")
9   WRITE(11) "first"
10   WRITE(11) "second"
11   WRITE(11) 1234567
12   write(11) 3.14159_8
13   read(11, pos=12)i
14   if (i.ne.1234567) call abort()
15   read(11) r
16   if (r-3.14159 .gt. 0.00001) call abort()
17   CLOSE(UNIT=11, status="delete")
18 END PROGRAM stream_io_1