MOVE_ALLOC to grow an array

Separately in the context of those coding in anger with Fortran and coming to this Discourse for information and guidance, what will be useful is to realize

  • a need to dynamically grow/shrink an array will be helped by containerizing it suitably, perhaps in a derived type;
  • the growth or shrinkage should follow a scheme suitable for the need at hand; a default scheme is usually to double/halve the size of the object in the container but there may be other better schemes depending on the program and the processor.

So then the approach should be to study the options vis-a-vis the needs while paying careful attention to the instrumentation around what is one is measuring and how so. The code in the original post has issues in this aspect as pointed out upthread.

A quick go-by can be as follows where the scheme to double the size each time is considered. To make it somewhat more interesting the option with RESHAPE intrinsic is also thrown in. One can then see the performance variation with the option and the shape and relate that to one’s need in actual code.

Click to see
   integer, parameter :: WP = selected_real_kind( p=12 )
   character(len=*), parameter :: fmth = "(g0,t10,g0,t30,g0,t50,g0,t70,g0)"
   character(len=*), parameter :: fmtg = "(g0,t10,g0,t30,g0.3,t50,g0.3,t70,g0)"
   integer, parameter :: nstart = 100000
   integer, parameter :: nruns = 12
   integer :: i, n(nruns)
   real(WP) :: t1, t2
   real(WP), allocatable :: a(:),xran(:)
   allocate (xran(nstart*(2**nruns)))
   call random_number( xran )
   n = [( nstart*2**(i-1), i=1,nruns )]
   blk1: block
      a = [real(WP) :: ]
      print *, "Method: Array constructor"
      print fmth, "i", "Array Size", "Time (sec)", "Max|a-xran|", "a(n/2)"
      do i = 1, nruns
         call my_cpu_time(t1)
         a = [ a, xran(size(a)+1:n(i)) ]
         call my_cpu_time(t2)
         print fmtg, i, size(a), (t2-t1), maxval(abs(a-xran)), a(size(a)/2)
      end do
   end block blk1
   blk2: block
      a = [real(WP) :: ]
      print *, "Method: RESHAPE intrinsic"
      print fmth, "i", "Array Size", "Time (sec)", "Max|a-xran|", "a(n/2)"
      do i = 1, nruns
         call my_cpu_time(t1)
         a = reshape( a, shape=[n(i)], pad=xran(size(a)+1:n(i)) )
         call my_cpu_time(t2)
         print fmtg, i, size(a), (t2-t1), maxval(abs(a-xran)), a(size(a)/2)
      end do
   end block blk2
   blk3: block
      a = [real(WP) :: ]
      print *, "Method: MOVE_ALLOC"
      print fmth, "i", "Array Size", "Time (sec)", "Max|a-xran|", "a(n/2)"
      do i = 1, nruns
         block
            real(WP), allocatable :: tmp(:)
            call my_cpu_time(t1)
            allocate( tmp(n(i)) )
            tmp(1:size(a)) = a
            tmp(size(a)+1:) = xran(size(a)+1:size(tmp))
            call move_alloc( from=tmp, to=a )
            call my_cpu_time(t2)
         end block
         print fmtg, i, size(a), (t2-t1), maxval(abs(a-xran)), a(size(a)/2)
      end do
   end block blk3
contains
   subroutine my_cpu_time( time )
      use, intrinsic :: iso_fortran_env, only : I8 => int64
      ! Argument list
      real(WP), intent(inout) :: time
      ! Local variables
      integer(I8) :: tick
      integer(I8) :: rate
      call system_clock (tick, rate)
      time = real(tick, kind=kind(time) ) / real(rate, kind=kind(time) )
      return
   end subroutine my_cpu_time
end
  • Expected program behavior
C:\Temp>gfortran -O3 p.f90 -o p.exe

C:\Temp>p.exe
 Method: Array constructor
i        Array Size          Time (sec)          Max|a-xran|         a(n/2)
1        100000              0.157E-2            0.00                0.14632783894497925
2        200000              0.216E-2            0.00                0.93604658738074942
3        400000              0.383E-2            0.00                0.38816074699824510E-2
4        800000              0.780E-2            0.00                0.48353192216229768
5        1600000             0.154E-1            0.00                0.17707306405838441
6        3200000             0.316E-1            0.00                0.34672021796550934
7        6400000             0.619E-1            0.00                0.49127175384201527E-2
8        12800000            0.123               0.00                0.41832146544600479
9        25600000            0.274               0.00                0.34490797395681683
10       51200000            0.499               0.00                0.43429002560932473
11       102400000           1.01                0.00                0.92205452988951198
12       204800000           6.73                0.00                0.86448646582845623
 Method: RESHAPE intrinsic
i        Array Size          Time (sec)          Max|a-xran|         a(n/2)
1        100000              0.230E-1            0.00                0.14632783894497925
2        200000              0.170E-2            0.00                0.93604658738074942
3        400000              0.343E-2            0.00                0.38816074699824510E-2
4        800000              0.784E-2            0.00                0.48353192216229768
5        1600000             0.143E-1            0.00                0.17707306405838441
6        3200000             0.273E-1            0.00                0.34672021796550934
7        6400000             0.547E-1            0.00                0.49127175384201527E-2
8        12800000            0.107               0.00                0.41832146544600479
9        25600000            0.201               0.00                0.34490797395681683
10       51200000            0.351               0.00                0.43429002560932473
11       102400000           0.646               0.00                0.92205452988951198
12       204800000           1.41                0.00                0.86448646582845623
 Method: MOVE_ALLOC
i        Array Size          Time (sec)          Max|a-xran|         a(n/2)
1        100000              0.263E-1            0.00                0.14632783894497925
2        200000              0.636E-3            0.00                0.93604658738074942
3        400000              0.187E-2            0.00                0.38816074699824510E-2
4        800000              0.316E-2            0.00                0.48353192216229768
5        1600000             0.552E-2            0.00                0.17707306405838441
6        3200000             0.123E-1            0.00                0.34672021796550934
7        6400000             0.243E-1            0.00                0.49127175384201527E-2
8        12800000            0.472E-1            0.00                0.41832146544600479
9        25600000            0.843E-1            0.00                0.34490797395681683
10       51200000            0.163               0.00                0.43429002560932473
11       102400000           0.225               0.00                0.92205452988951198
12       204800000           0.463               0.00                0.86448646582845623
6 Likes