blob: 5fe47c28ef0525d615381dcfead4d45ee7b9a295 [file] [log] [blame]
! { dg-do run }
! { dg-options "-pedantic" }
! This test verifies the most basic sequential unformatted I/O
! with convert="swap".
! Adapted from seq_io.f.
! write 3 records of various sizes
! then read them back
program main
implicit none
integer size
parameter(size=100)
logical debug
data debug /.FALSE./
! set debug to true for help in debugging failures.
integer m(2)
integer n
real r(size)
integer i
character*4 str
m(1) = Z'11223344'
m(2) = Z'55667788'
n = Z'77AABBCC'
str = 'asdf'
do i = 1,size
r(i) = i
end do
open(9,form="unformatted",access="sequential",convert="swap") ! { dg-warning "Extension: CONVERT" }
write(9) m ! an array of 2
write(9) n ! an integer
write(9) r ! an array of reals
write(9)str ! String
! zero all the results so we can compare after they are read back
do i = 1,size
r(i) = 0
end do
m(1) = 0
m(2) = 0
n = 0
str = ' '
rewind(9)
read(9) m
read(9) n
read(9) r
read(9) str
!
! check results
if (m(1).ne.Z'11223344') then
if (debug) then
print '(A,Z8)','m(1) incorrect. m(1) = ',m(1)
else
call abort
endif
endif
if (m(2).ne.Z'55667788') then
if (debug) then
print '(A,Z8)','m(2) incorrect. m(2) = ',m(2)
else
call abort
endif
endif
if (n.ne.Z'77AABBCC') then
if (debug) then
print '(A,Z8)','n incorrect. n = ',n
else
call abort
endif
endif
do i = 1,size
if (int(r(i)).ne.i) then
if (debug) then
print*,'element ',i,' was ',r(i),' should be ',i
else
call abort
endif
endif
end do
if (str .ne. 'asdf') then
if (debug) then
print *,'str incorrect, str = ', str
else
call abort
endif
end if
! use hexdump to look at the file "fort.9"
if (debug) then
close(9)
else
close(9,status='DELETE')
endif
end program main