This is not really what you asked, @fish830911, but I have written a small module to do I/O based on Gabriel MATLAB/Fortran workflow tips.
module m
use iso_fortran_env, only: dp=>real64
implicit none
interface writeBinary
module procedure writeBinary1, writeBinary2
end interface
interface readBinary
module procedure readBinary1, readBinary2
end interface
contains
subroutine writeBinary1(x,file_name)
!Write double precision array x into a BINARY file file_name
implicit none
!Declare inputs:
real(dp), intent(in) :: x(:)
character(len=*), intent(in) :: file_name
integer :: unitno,i, ierr
!Note the commands FORM="unformatted", ACCESS="stream"
!and the fact that write(unitno) instead of write(unitno,*)
OPEN(NEWUNIT=unitno, FILE=file_name, FORM="unformatted", ACCESS="stream", STATUS="unknown", iostat=ierr)
if (ierr/=0) then
error stop "Error: writeBinary: cannot open file"
endif
write(unitno) x
close(unitno)
end subroutine writeBinary1
subroutine writeBinary2(x,file_name)
!Write double precision array x into a BINARY file file_name
implicit none
!Declare inputs:
real(dp), intent(in) :: x(:,:)
character(len=*), intent(in) :: file_name
integer :: unitno,i, ierr
!Note the commands FORM="unformatted", ACCESS="stream"
!and the fact that write(unitno) instead of write(unitno,*)
OPEN(NEWUNIT=unitno, FILE=file_name, FORM="unformatted", ACCESS="stream", STATUS="unknown", iostat=ierr)
if (ierr/=0) then
error stop "Error: writeBinary: cannot open file"
endif
write(unitno) x
close(unitno)
end subroutine writeBinary2
subroutine readBinary1(x,file_name)
!Write double precision array x into a BINARY file file_name
implicit none
!Declare inputs:
real(dp), intent(out) :: x(:)
character(len=*), intent(in) :: file_name
integer :: unitno,i, ierr
!Note the commands FORM="unformatted", ACCESS="stream"
!and the fact that write(unitno) instead of write(unitno,*)
OPEN(NEWUNIT=unitno, FILE=file_name, FORM="unformatted", ACCESS="stream", STATUS="old", iostat=ierr)
if (ierr/=0) then
error stop "Error: readBinary: cannot open file"
endif
read(unitno) x
close(unitno)
end subroutine readBinary1
subroutine readBinary2(x,file_name)
!Write double precision array x into a BINARY file file_name
implicit none
!Declare inputs:
real(dp), intent(out) :: x(:,:)
character(len=*), intent(in) :: file_name
integer :: unitno,i, ierr
!Note the commands FORM="unformatted", ACCESS="stream"
!and the fact that write(unitno) instead of write(unitno,*)
OPEN(NEWUNIT=unitno, FILE=file_name, FORM="unformatted", ACCESS="stream", STATUS="old", iostat=ierr)
if (ierr/=0) then
error stop "Error: readBinary: cannot open file"
endif
read(unitno) x
close(unitno)
end subroutine readBinary2
end module m
program main
use m, only: writeBinary, readBinary, dp
implicit none
real(dp), allocatable :: x(:,:), x_out(:,:)
integer :: ii,i
write(*,*) "This program writes a binary file containing a 1D array of double precision numbers"
allocate(x(10,2))
x(:,1) = [1.0_dp,2.0_dp,3.0_dp,4.0_dp,5.0_dp,6.0_dp,7.0_dp,8.0_dp,9.0_dp,10.0_dp]
x(:,2) = [1.0_dp,2.0_dp,3.0_dp,4.0_dp,5.0_dp,6.0_dp,7.0_dp,8.0_dp,9.0_dp,10.0_dp]+10.0_dp
write(*,*) "Array to be written:"
do ii=1,size(x,1)
write(*,*) x(ii,:)
enddo
write(*,*) "Writing array to binary..."
call writeBinary(x,'x_array.bin')
write(*,*) "Reading array from binary file..."
allocate( x_out(size(x,1),size(x,2)) )
call readBinary(x_out,'x_array.bin')
write(*,*) "Display array read from binary file"
do ii=1,size(x_out,1)
write(*,*) x_out(ii,:)
enddo
end program main
The generic procedures writeBinary
and readBinary
(should) work with double-precision arrays with arbitrary shape. As of now, they work only with 1 dim and 2 dim arrays. Indeed, I wrote a generic interface as follows:
interface writeBinary
module procedure writeBinary1, writeBinary2, etc UHMMMM
end interface
interface readBinary
module procedure readBinary1, readBinary2
end interface
but it is a bit tedious… In principle I should write many versions of the same routine, just to accomodate 2-dim, 3-dim, etc arrays.
My question: Is there a way to do this in a cleaner way i.e. to avoid repeating my code so many times? In my work sometimes I have arrays with 6 or 7 state variables
Thanks!
P.S. One trick would be to reshape the possibly multi-dim array I want to write as a 1-dim array:
x_1dim = reshape(x,size(x))
and then pass x1_dim
to writeBinary
. But I prefer not to do this since for large arrays reshape gives me a runtime error in Windows.