There exist two major methods to save arrays. Suppose we have 2D REAL*4 array Arr4(nA,nB). First method is when we explicitly save each element or each dimension individually
open (11, file='LargeFile.dat', FORM='UNFORMATTED')
do i=1,nB
write(11) Arr4(:,i)
enddo
close(11)
and the second method is when we save the entire array as a whole
open (11, file='LargeFile.dat', FORM='UNFORMATTED')
write(11) Arr4
close(11)
.
Second method can be an order of magnitude faster reaching speeds 3GB per second on current hardware (with m2 NVMe PCIe 4.0) drives. But it fails to save, flashing the Silverfrost exception, if array is larger than ~4GB while first slow method works with no problems. Here is demo which allocates OK any size and saves files using second method when file size is 4GB (array size nB =1e8) but fails to save with nB=2e8 and file size twice larger. It fails also to save even REAL*8 arrays. Compilation with /64 switch.
! compilation: ftn95 aaa.f90 /link /64 >z
!
real*4, dimension(:,:), allocatable :: Arr4
nA = 11
nB = 2.e8
!...Allocating array
Print*, 'Trying to allocate GB of RAM :', 1.d-9 * 4. * nA * nB
allocate ( Arr4 (nA, nB), stat = ierr)
if (ierr.eq.0) then
Print*,'Allocation success'
else
Pause 'Fail to allocate'
goto 1000
endif
!...Filling the array with some data
do i=1,nB
Arr4(:,i) = [1,2,3,4,5,6,7,8,9,10,11]
enddo
! __ __ ____ ____ _ _ _____ ____ __
! ( \/ )( ___)(_ _)( )_( )( _ )( _ \ / )
! ) ( )__) )( ) _ ( )(_)( )(_) ) )(
! (_/\/\_)(____) (__) (_) (_)(_____)(____/ (__)
!....................................................
Print*,'Trying to save the data Method 1 '
call cpu_time(t0)
open (11, file='LargeFile.dat', FORM='UNFORMATTED', access='STREAM', err=900)
do i=1,nB
write(11) Arr4(:,i)
enddo
close(11)
call cpu_time(t1)
!...Speeed of writing method 1
SpeedGBps = 1.d-9 * 4. * nA * nB / (t1-t0+1.e-10)
print*,' Speed of write Method 1 =', SpeedGBps ! typically ~0.5 GB/s
! __ __ ____ ____ _ _ _____ ____ ___
! ( \/ )( ___)(_ _)( )_( )( _ )( _ \ (__ \
! ) ( )__) )( ) _ ( )(_)( )(_) ) / _/
! (_/\/\_)(____) (__) (_) (_)(_____)(____/ (____)
!....................................................
Print*,'Trying to save the data Method 2'
call cpu_time(t0)
open (11, file='LargeFile.dat', FORM='UNFORMATTED', access='STREAM', err=900)
write(11) Arr4
close(11)
call cpu_time(t1)
!...Speeed of writing Method 2
SpeedGBps = 1.d-9 * 4. * nA * nB / (t1-t0+1.e-10)
print*,' Speed of write Method 2=', SpeedGBps ! typically ~2.6 GB/s
pause 'File LargeFile.dat created OK'
goto 1000
!...............
!...Errors
900 Print*,'Can not open file LargeFile.dat'
goto 1000
910 Print*,'Can not save file LargeFile.dat'
1000 Continue
End