I come across the SciVision website when searching for other things. It contains a nice list of posts on Fortran.
In particular, I note the post entitled “Fortran allocate large variable memory”. It motivates me to ask the following two questions (note that there is a Question 2).
Question 1. What is the best practice of allocating memory in Fortran?
Personally, I wrap up a generic procedure named safealloc
to do the job. Below is the implementation of safealloc
to allocate the memory for a rank-1 REAL(SP)
array with a size given by a variable n
of kind INTEGER(IK)
. We can imagine, for example, the module consts_mod
defines SP=kind(0.0)
and IK=kind(0)
. In addition, validate
is a subroutine that stops the program when an assertion fails, akin to the assert
function in C or Python.
subroutine alloc_rvector_sp(x, n)
!--------------------------------------------------------------------------------------------------!
! Allocate space for an allocatable REAL(SP) vector X, whose size is N after allocation.
!--------------------------------------------------------------------------------------------------!
use, non_intrinsic :: consts_mod, only : SP, IK ! Kinds of real and integer variables
use, non_intrinsic :: debug_mod, only : validate ! An `assert`-like subroutine
implicit none
! Inputs
integer(IK), intent(in) :: n
! Outputs
real(SP), allocatable, intent(out) :: x(:)
! Local variables
integer :: alloc_status
character(len=*), parameter :: srname = 'ALLOC_RVECTOR_SP'
! Preconditions
call validate(n >= 0, 'N >= 0', srname)
! According to the Fortran 2003 standard, when a procedure is invoked, any allocated ALLOCATABLE
! object that is an actual argument associated with an INTENT(OUT) ALLOCATABLE dummy argument is
! deallocated. So it is unnecessary to write the following line since F2003 as X is INTENT(OUT):
!!if (allocated(x)) deallocate (x)
! Allocate memory for X
allocate (x(n), stat=alloc_status)
call validate(alloc_status == 0, 'Memory allocation succeeds (ALLOC_STATUS == 0)', srname)
call validate(allocated(x), 'X is allocated', srname)
! Initialize X to a strange value independent of the compiler; it can be costly for a large N.
x = -huge(x)
! Postconditions
call validate(size(x) == n, 'SIZE(X) == N', srname)
end subroutine alloc_rvector_sp
[Update (2022-01-25): I shuffled the lines a bit, moving validate(allocated(x), 'X is allocated', srname)
to the above of x = -huge(x)
.]
What do you think about this implementation? Any comments, suggestions, and criticism will be appreciated.
A related and more particular question is the following.
Question 2. What is the best practice of allocating large memory in Fortran?
The question can be further detailed as follows.
2.1. What does “large” mean under a modern and practical setting?
To be precise, let us consider a PC/computing node with >= 4GB of RAM. In addition, the hardware (RAM, CPU, hard storage, etc), the compiler, and the system are reasonably mainstream and modern, e.g., not more than 10 years old.
2.2. What special caution should be taken when the memory to allocate is large by the answer to 2.1?
Thank you very much for your input and insights.