How to add new element to dynamical array in Fortran 90
Asked Answered
D

2

5

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.

Doralia answered 20/1, 2015 at 14:59 Comment(6)
what problem/error do you have?Demimondaine
program freezes on deallocate(list) and nothing runs any further. There are no errors printed out, it just freeze and do nothing.Doralia
You probably don't mean Fortran 90, but in DArray an explicit interface must be available for AddToList: it has allocatable dummy arguments.Pacifist
I updated question with implemented interfaces. But they still not work properly for me...Doralia
Please do not change the question that much and do not use any [SOLVED] labels. The question is a reference for future readers and it is visible by other means that it has an accepted answer. This is not a discussion forum.Kessel
Thanks, Vladimir. So in that case how it would be best to place the final solution, which we approached? In separate answer maybe?Doralia
P
6

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.

Pacifist answered 20/1, 2015 at 18:46 Comment(3)
Oh, wow, it works now very nicely with a correction of clist(isize+1) = element (I didn't know that in fortran last index after end do becomes isize+1). P.S. Do you know if it would be possible to avoid 6 lines of these interfaces at the beginning of each subroutine, where I want to use dynamical arrays? Maybe it's possible somehow to put them upon USE statement and modules?Doralia
A module would be my preferred (over interface blocks) way of providing the explicit interface, and examples will be easy to find searching here. And as we've moved on to code recommendations, I'll also bring up the move_alloc intrinsic. And perhaps even considering linked lists rather than dynamic resizing.Pacifist
Thanks a lot. I just added module corrections and now things looks nicer. There is also correction that array does not need to be allocated initially and move_alloc. I used changes on the top of question that other users could easily find the complete code. Let's actually keep linked lists for another story :)Doralia
U
2

I know this question is very old, but I recently had to build such a subroutine, and I found out that, starting from Fortran2003, there is a beautiful one liner:

    SUBROUTINE append_int(vec, val)
    !***********************************************************************
    !> \brief Appends val in vec if not already present
    !> \date 05 2020
    !***********************************************************************
    INTEGER, DIMENSION(:), ALLOCATABLE, INTENT(INOUT)    :: vec
    INTEGER, INTENT(IN)                                  :: val

    ! Remove this test if you don't mind not having unique values
    IF (.NOT. ANY(vec .EQ. val)) THEN
        vec = [vec, val]
    END IF

    END SUBROUTINE

Your array will be automatically reallocated at the appropriate size. Plus, you can generate equivalent routines for Reals, for appending an array to another ... and then wrap all of them in an interface, so that you always can call the same subroutine whatever the type of your data.

Untraveled answered 26/5, 2020 at 8:53 Comment(4)
Yes, it is probably useful to have it here even when the question requested Fortran 90. We do have that in the more generic questions and answers though #38758716Kessel
Eventually this will surprise someone who finds that the lower bound of an array has changed after appending an element.Pacifist
@Pacifist what do you mean? This procedure is not safe?Ascending
@HermanToothrot, the procedure is "safe", but it potentially changes things in unexpected ways. Consider allocate (vec(0:5), source=[1,2,3,4,5,6]); print*, lbound(vec); call append_int(vec, 6); print*, lbound(vec); call append_int(vec, 7); print*, lbound(vec).Pacifist

© 2022 - 2025 — McMap. All rights reserved.