Search code examples
fortranfortran90dynamic-arraysintel-fortran

How to add new element to dynamical array in Fortran 90


I need to use dynamical arrays in Fortran 90 for cases when I can't predict exact size of array initially. So I wrote a code, which should expand allocatable array each time new element is added to the end of array:

  subroutine DArray()

  double precision, dimension(:), allocatable :: list

  allocate(list(1))

  list(1) = 1.1

  call AddToList(list, 2.2)
  call AddToList(list, 3.2)
  call AddToList(list, 4.2)
  call AddToList(list, 5.2)

  print *, list(1)
  print *, list(2)
  print *, list(3)
  print *, list(4)
  print *, list(5)


  end



  subroutine AddToList(list, element)

  double precision :: element
  double precision, dimension(:), allocatable :: list
  double precision, dimension(:), allocatable :: clist

  if(allocated(list)) then
    isize = size(list)
    allocate(clist(isize+1))
    do i=1,isize
        clist(i) = list(i)
    end do
    clist(i+1) = element

    deallocate(list)
    allocate(list(isize+1))

    do i=1,isize+1
        list(i) = clist(i)
    end do

    deallocate(clist)

  end if


  end

So does anyone see if I missing something here?


Solved by francescalus.

Working code for double precision dynamical arrays is:

  module DynamicalArrays

  contains

      subroutine AddToList(list, element)

          IMPLICIT NONE

          integer :: i, isize
          double precision, intent(in) :: element
          double precision, dimension(:), allocatable, intent(inout) :: list
          double precision, dimension(:), allocatable :: clist


          if(allocated(list)) then
              isize = size(list)
              allocate(clist(isize+1))
              do i=1,isize          
              clist(i) = list(i)
              end do
              clist(isize+1) = element

              deallocate(list)
              call move_alloc(clist, list)

          else
              allocate(list(1))
              list(1) = element
          end if


      end subroutine AddToList


  end module DynamicalArrays

The demo subroutine, from which array can be filled would be:

  subroutine UserDArrayTest()

  use DynamicalArrays


  integer :: i
  double precision, dimension(:), allocatable :: list
  double precision :: temp

  temp = 0.1
  do i=1,10
    temp = temp+1
    call AddToList(list, temp)
  end do

  do i=1,10
    print *, i, list(i)
  end do


  end

Note that it's best to keep module code in the separate file, but I also find out that it works when module code is above main program and subroutine codes.


Solution

  • I suspect, looking at an artefact, that you noticed the problem - but quickly moved on.

    The suspicious line, to me is:

        allocate(clist(isize+2))
    

    Why isn't the new size isize+1? I guess that you tried that, but then the program failed.

    Seeing why the program failed (possibly crashed) is key to why you aren't getting the correct result. Look closely at the loop (print statement removed for clarity).

    do i=1,isize
        clist(i) = list(i)
    end do
    clist(i+1) = element
    

    You want to say "copy all elements from list to clist, then append element". Which is correct. However

    do i=1,isize
        clist(i) = list(i)
    end do
    ! Here, i=isize+1
    clist(i+1) = element
    ! Which means
    ! clist(isize+2) = element.
    

    In summary, after the loop the loop index variable doesn't have the value it had in the final iteration.