Redimensioning local array based upon passed array

I have a subroutine that takes two different size arrays as input.

I have currently set this up as follows:

	subroutine copacity(t, rho, realk, rkapparef, rhoref, tref, its, irhs)
	    
	    implicit none
	    
	    double precision :: realk, rho, t, rhoref(irhs), tref(its), rkapparef(irhs, its)
	    integer          :: irhs, its
	    
	    save

		ALL CODE HERE
		
		return
	end subroutine

The two final parameters (its and irhs) are simply the dimensions of the arrays.

I cannot appear to define the arrays ‘on the fly’ as such; I have to have the parameters. I originally thought that passing the arrays would cause the system to define the local arrays accordingly, but this is not the case. I could define a single parameter, that defines which case to use (there are only two potential arrays that could be passed), but then I cannot use an if statement to select the relevant integer values, prior to the arrays being defined.

Is there a method by which the local array could easily be set to the dimensions of the passed array?
Or is the passing of the two integer dimensions the best (only) approach?

Use the function size.

its=size(tref)

If you want to get rid of integer parameters to pass the dimensions of an argument-array, you need to use assumed-shape mechanism. You then declare the argument-arrays using colons (one for each dimension), as in:
double precision :: rhoref(:), tref(:), rkapparef(:,:)

But this requires the procedure (here, your subroutine) to have explicit interface in the program segment where it gets called.

Then, you can declare local arrays in one of two ways: as automatic or allocatable arrays. Automatic arrays cannot be saved, however, they are created on every entry to the subroutine and destroyed on exit. Allocatable local arrays are deallocated on exit if not saved. So if you want your local arrays to be also saved, use allocatables but be aware that the subroutine would have to be called with arrays of the same shape to stay consistent with the allocatable locals.

program m
  implicit none
  interface
    subroutine copacity(t, rho, realk, rkapparef, rhoref, tref)
      double precision :: realk, rho, t
      double precision :: rhoref(:), tref(:), rkapparef(:,:)
    end subroutine copacity
  end interface
  ! [...]
  call copacity(...)
  ! [...] 
end program m
subroutine copacity(t, rho, realk, rkapparef, rhoref, tref)
  implicit none
  double precision :: realk, rho, t
  double precision :: rhoref(:), tref(:), rkapparef(:,:)  ! assumed shape argument-arrays
  double precision :: auto_tref(size(tref))  ! automatic local
  double precision :: auto_rkappa(size(rkapparef,1),size(rkapparef,2)) ! automatic local
  double precision, allocatable :: all_rkappa(:,:), all_tref(:)  ! allocatable local
! [...]
  if (.not. allocated(all_rkappa)) allocate(all_rkappa, mold=rkapparef)
  if (.not. allocated(all_tref)) allocate(all_tref, mold=tref)
! [...]
end subroutine copacity

The destruction, or not, of the array is not of concern (I believe). However, I was led to believe that the allocatable approach would only work on the first dimension of a 2D array; that the second dimension had to be a fixed value?

I’m trying the size trick first; see how that comes out. :slight_smile:

I did this…

	subroutine copacity(t, rho, realk, rkapparef, rhoref, tref)
	    
	    implicit none
	    
	    integer          :: icool, ihot, irhs = size(rhoref), iterx, its = size(tref), jdense, jrare, mode
	    double precision :: condmin, dense, rare, realk, rho, t, rhoref(irhs), tref(its), rkapparef(irhs, its)
	    character(8)     :: term
	    
	    save

	    SOME CODE HERE
	    return
	end subroutine

However, this generated a whole series of errors; primarily caused by this…

stelcor.f90:5439:53:

 5439 |         subroutine copacity(t, rho, realk, rkapparef, rhoref, tref)
      |                                                            1
Error: Symbol ‘rhoref’ at (1) has no IMPLICIT type
stelcor.f90:5444:73:

 5444 |             double precision :: condmin, dense, rare, realk, rho, t, rhoref(irhs), tref(its), rkapparef(irhs, its)
      |                                                                                1
Error: Symbol ‘irhs’ at (1) has no IMPLICIT type; did you mean ‘rho’?
stelcor.f90:5444:84:

 5444 |             double precision :: condmin, dense, rare, realk, rho, t, rhoref(irhs), tref(its), rkapparef(irhs, its)
      |                                                                                           1
Error: Symbol ‘its’ at (1) has no IMPLICIT type

So, using size as I have hasn’t worked.
Did I misunderstand?

I would follow the suggestion from @msz. You can find there how to use the size function.

Here you have another example

I would just declare

integer :: irhs
real(kind=real64), dimension(:slight_smile: :: rhoref

and then, in the code

irhs = size(rhoref)

Adapted from other examples, here is a very cut down example of what is required:

      Function test( x ) Result( sum_sq )
        Real :: sum_sq
        Real, Dimension( : ), Intent( In ) :: x
        Real, Dimension( size(x) ) :: y

        y = x
        sum_sq = dot_product ( x, y )

      End Function test

Test needs an explicit interface or be contained.

I used to have trouble like yours. I would now write

double precision :: realk, rho, t, rhoref(:), tref(:), rkapparef(:,:)

instead of

double precision :: realk, rho, t, rhoref(irhs), tref(its), rkapparef(irhs, its)

because those : tell the dummy arguments to use the actual argument upper bounds, If you don’t want the lower bound to be 1 you must say what it is, e.g. a(0:) to start at 0.

Note that you may mislead Fortran users by calling arguments parameters, because PARAMETER is used when declaring a constant in Fortran, e.g.

real,parameter:: pi = 4.0*atan(1.0) 

Unfortunately some other languages call an argument a parameter.

It’s also a good idea to use intent(in) or intent(out) or intent(inout) when specifying dummy arguments.

subroutine copacity(t, rho, realk, rkapparef, rhoref, tref)	    
implicit none
double precision :: realk, rho, t, rhoref(:), tref(:), rkapparef(:, :) 
          
double precision :: aaa(size(rhoref)), bbb(size(rhoref),size(tref)) ! automatic arrays
double precision, allocatable :: ccc(:), ddd(:,:)

integer          :: irhs, its

irhs = size(rhoref)
its = size(its)

allocate( ccc(irhs), ddd(irhs,its) ) ! allocatable arrays
...
		
end subroutine

Thanks for all the replies. I went for the tref(:) etc approach and this worked fantastically. I then used the size to set the other two variables, which also worked. I was then able to tidy up the variables, reducing the overall number by 2, marked the inputs with intent and converted the subroutine into a function. Just testing now but this seems to have worked well.

Once confirmed I will document what I have done and move on to the next subroutine. 3 down; 26 to go! Hahahaha!

1 Like