Initialization constant

I don’t know if it has been already proposed. Basically if I have a procedure that has an assumed shape array as an argument, I can define the size of an additional array using the information that I can get from the arguments of my procedure, like:

subroutine my_sub(a)
real :: a(:)
real :: c(size(a)*2 + 7*size(a)**2), d( 2*(size(a)*2 + 7*size(a)**2))
...

It would be nice to write something like:

subroutine my_sub(a)
real :: a(:)
integer, init_expression :: n = size(a)*2 + 7*size(a)**2
integer, init_expression :: m = 2*n
real :: c(n), d(m)

Where n and m will be like a constants inside the routine, while they will be different at each invocation of the procedure.

Obviously, the same can be easily obtained with allocatables, I know that.

There have been several discussions about allowing for variables to be
initialized in the declarations at the time of the call of the procedure,
instead of the current situation where they are essentially initialized
at program initialization and then SAVED (assuming they are variables
and not parameter constants). But I do not remember anyone proposing
anything exactly like this. People coming to Fortran with previous C experience in
particular argue for something similiar where

subroutine A(n)
integer :: i=10*n
end subroutine A

would set “i” on entry and allow for variables in the initialization, more like C; instead of acting more like a FORTRAN DATA statement and requiring constants.

Note that as well as an allocatable array (as you mentioned) you can pass
the dimensions as arguments, call a routine that declares the values
and then calls another routine (which could be a CONTAINED routine,
or use BLOCK and ASSOCIATE. Not exactly the same, but somewhat in the
same spirit. Might be others, but these are the closest standard methods
that came to mind that are somewhat similar …

Using BLOCK …

subroutine my_sub(a,w)
real,intent(in)  :: a(:)
real,intent(out) :: w
integer :: m,n
   m=size(a)*2
   n=7*size(a)**2
   block
   real :: e(m), f(n)
      w = size(e)+size(f)
   end block

end subroutine my_sub

Using ASSOCIATE and BLOCK …

subroutine my_sub(a,w)
real,intent(in)  :: a(:)
real,intent(out) :: w
associate ( m=>size(a)*2, n=>7*size(a)**2)
block
   real :: e(m), f(n)
      w = size(e)+size(f)
end block
end associate
end subroutine my_sub

CONTAINED …

module m_subs
contains 
   subroutine my_sub(a,w)
   implicit none
   real,intent(in)  :: a(:)
   real,intent(out) :: w
   call real_my_sub(  m = size(a)*2,  n = 7*size(a)**2  )
   contains 
      subroutine real_my_sub(m,n)
      integer :: m,n
      real :: e(m), f(n)
            w = size(e)+size(f)
      end subroutine real_my_sub
   end subroutine my_sub

end module m_subs
program testit
use m_subs, only : my_sub
implicit none
real :: a(10)
real :: w

   call my_sub(a,w)
   write(*,*)w
end program testit

I would not rate any of those highly intuitive or succinct; but they do something similar.

Here is another way to achieve the result.

subroutine my_sub(a,w)
#define m size(a)*2
#define n 7*size(a)**2
real,intent(in)  :: a(:)
real,intent(out) :: w
real :: e(m), f(n)
w = size(e)+size(f)
end subroutine my_sub

I would not necessarily recommend this approach either, but it does work as expected. Of course, the preprocessor directives are not part of the fortran standard, but they are a decades-old de facto standard, and in my opinion should have been standardized in the formal sense some three decades ago. If you do something like this, at least change the macros from “m” and “n” to something else that stands out and is less likely to cause problems elsewhere in the file.

One other thing should be mentioned. As a practical matter, this is not exactly equivalent to declaring the arrays as allocatable and allocating them within the body of the subroutine. In this code, the arrays are automatic. Automatic arrays typically live on the stack, while allocatable arrays live in the heap. There are advantages and disadvantages to both approaches. In particular, if the arrays are small enough to not exceed the stack, then the automatic array approach is probably more efficient.

2 Likes

I haven’t thought at the block construct.
Nice idea!