mattiav27
mattiav27

Reputation: 685

Need help to understand this function

I have to work with arrays, but I do not know at the beginning the size of these arrays, I only know it is finite. I was suggested to use the dynamical arrays described in this question. I am not sure how to use it. What I need to do is something like this:

REAL,pointer,dimension(:,:)array
do i=1, max
   array(i)=value
end do

When I use the following code, which in my mind should add 2's to my array

  PROGRAM dynamic_array
  IMPLICIT NONE
  INTEGER,pointer,dimension(:)::vettore
  integer i,val

  allocate(vettore(1))
  vettore(1)=1
  do i=1,10
        array(i)=append(i,vettore,2)
  end do

  do i=1, 20
        write(*,*) array(i)
  end do

  deallocate(array)
  Contains
  (...)
  end program

I get the following output:

           1
           2
 -1216226408
           4
           0
           6
           0
           8
          48
          10
          81
           0
  1836017711
  1634545509
  1634301044
  1919111983
  1851881065
  1160733033
  1414808908
  1229868882

What am I doing wrong?

Upvotes: 0

Views: 94

Answers (1)

Ian Bush
Ian Bush

Reputation: 7433

In Fortran don't use pointers - allocatable arrays are the way to do this and almost all dynamic memory management. Allocatable arrays are easier to use and safer, it is impossible for them to have a number of bugs which pointers make it very easy to introduce into your code. One such bug is memory leaks - it is impossible to have a memory leak with an allocatable array as they automatically get deallocated once they go out of scope; it's not wrong to deallocate an array explicitly, and sometimes you might want to to save memory, and some might even consider it good style, but more often than not just hitting the end of the (sub)program and relying on the automatic deallocation is enough.

On the other hand Pointers can cause memory leaks, amongst a number of other problems which allocatable arrays simply do not suffer from. Pointers to data should only be used for a very small number of corner cases, which if you are only just learning the language you can forget about. In fact if you are learning the language it is very close to the truth to say that you should never use pointers, allocatable arrays are the way to go.

OK that said how do you do you write your code in modern Fortran. Well here's a simple version for the one dimensional case - it could be made more efficient but this is the basis of what should be done

ian@eris:~/work/stack$ cat append.f90
Program append

  Implicit None

  Integer, Dimension( : ), Allocatable :: vettore
  Integer :: i

  ! Allocate vettore to size zero
  Allocate( vettore( 1:0 ) )

  ! Repeatedly append to the vector
  ! The alloctable array will automatically resize appropriately
  Do i = 1, 20
     vettore = [ vettore, 2 * i ]
  End Do

  ! Print out the vector
  Do i = 1, 20
     Write( *, * ) i, vettore( i )
  End Do

End Program append
ian@eris:~/work/stack$ gfortran-8 -fcheck=all -Wall -Wextra -pedantic -std=f2008 append.f90 
ian@eris:~/work/stack$ ./a.out
           1           2
           2           4
           3           6
           4           8
           5          10
           6          12
           7          14
           8          16
           9          18
          10          20
          11          22
          12          24
          13          26
          14          28
          15          30
          16          32
          17          34
          18          36
          19          38
          20          40
ian@eris:~/work/stack$ 

In real, production code I would avoid some of the copies and memory allocations by storing the new data in a temporary buffer, and once the buffer is full appending all of that in one go

The multiple dimension case is harder as in Fortran array constructors (the [] stuff) can only be one dimensional. You can do "clever" things with the RESHAPE intrinsic to work around this, but I think the resulting code is not just ugly, but very confusing as well. Thus in this case I would prefer to use a subprogram. A simple version is below

ian@eris:~/work/stack$ cat append_2d.f90
Module append_module

  Implicit None

  Public :: append_2d

  Private

Contains

  Subroutine append_2d( existing, new )

    Implicit None

    Integer, Dimension( :, : ), Allocatable, Intent( InOut ) :: existing
    Integer, Dimension( :    ),              Intent( In    ) :: new

    Integer, Dimension( :, : ), Allocatable :: tmp

    Integer :: n1, n2

    ! Get size of the EXISTING data
    n1 = Size( existing, Dim = 1 )
    n2 = Size( existing, Dim = 2 )

    ! Allocate the temporary to the new size
    Allocate( tmp( 1:n1, 1:n2 + 1 ) )

    ! Copy over the exisiting data
    tmp( 1:n1, 1:n2 ) = existing

    ! Add the new data
    tmp( :, n2 + 1 ) = new

    ! Move the allocation back 
    Call Move_alloc( tmp, existing )

  End Subroutine append_2d

End Module append_module

Program test_append_2d

  Use append_module, Only : append_2d

  Implicit None

  Integer, Dimension( :, : ), Allocatable :: vettore
  Integer :: i

  ! Allocate vettore to size zero
  Allocate( vettore( 1:2, 1:0 ) )

  ! Repeatedly append to the vector
  Do i = 1, 20
     Call append_2d( vettore, [ i, 2 * i ] )
  End Do

  ! Print out the vector
  Do i = 1, 20
     Write( *, * ) i, vettore( :, i )
  End Do

End Program test_append_2d
ian@eris:~/work/stack$ gfortran-8 -fcheck=all -Wall -Wextra -pedantic -std=f2008 append_2d.f90
ian@eris:~/work/stack$ ./a.out
           1           1           2
           2           2           4
           3           3           6
           4           4           8
           5           5          10
           6           6          12
           7           7          14
           8           8          16
           9           9          18
          10          10          20
          11          11          22
          12          12          24
          13          13          26
          14          14          28
          15          15          30
          16          16          32
          17          17          34
          18          18          36
          19          19          38
          20          20          40
ian@eris:~/work/stack$ 

Again in real code I would append multiple lines at once.

Upvotes: 3

Related Questions