Silverfrost Forums

Welcome to our forums

Passing dynamically allocated arrays to a subroutine

23 Nov 2012 9:04 #11161

How can I pass a dynamically allocated array to a subroutine and get the actual bounds of this array?

I tried this:

      PROGRAM MYPROG
!
      IMPLICIT NONE
!
      INTEGER*4, ALLOCATABLE :: I4(:)
!-----------------------------------------------------------------------
      ALLOCATE(I4(10))
      I4=1
!
      CALL MYSUB(I4)
!
      DEALLOCATE(I4)
      END
!***********************************************************************
      SUBROUTINE MYSUB(IARRAY)
!
      IMPLICIT NONE
!
      INTEGER*4  N1,N2
      INTEGER*4, ALLOCATABLE :: IARRAY(:)
!-----------------------------------------------------------------------
      IF(ALLOCATED(IARRAY))THEN
        N1=LBOUND(IARRAY,1)
        N2=UBOUND(IARRAY,1)
      ENDIF
!
      RETURN
      END
!***********************************************************************

and I got the following compiler error:

*** Error 941: IARRAY is a dummy argument and so cannot be ALLOCATABLE

The IVF-Compiler allows this code without problems.

Detlef Pannhorst

23 Nov 2012 9:50 #11162
      PROGRAM MYPROG 
      INTEGER, ALLOCATABLE :: I4(:) 
!----------------------------------------------------------------------- 
      INTERFACE
      SUBROUTINE MYSUB(IARRAY) 
      INTEGER :: IARRAY(:) 
      END SUBROUTINE MYSUB
      END INTERFACE   
!----------------------------------------------------------------------- 
      ALLOCATE(I4(10)) 
      CALL MYSUB(I4) 
      END 
!----------------------------------------------------------------------- 
      SUBROUTINE MYSUB(IARRAY) 
      INTEGER :: IARRAY(:) 
      PRINT*,LBOUND(IARRAY,1),UBOUND(IARRAY,1)
      END 
23 Nov 2012 10:58 #11164

Hi Paul,

thank you very much; this is working.

But the next stage for my code is to resize this array. Therefore I tried:

      PROGRAM MYPROG
!
      IMPLICIT NONE
!
      INTEGER*4, ALLOCATABLE :: I4(:)
!
      INTERFACE
        SUBROUTINE MYSUB(IARRAY)
        INTEGER :: IARRAY(:)
        END SUBROUTINE MYSUB
      END INTERFACE
!-----------------------------------------------------------------------
      ALLOCATE(I4(10))
      I4=1
!
      CALL MYSUB(I4)
!
      DEALLOCATE(I4)
      END
!***********************************************************************
      SUBROUTINE MYSUB(IARRAY)
!
      IMPLICIT NONE
!
      INTEGER*4 N1,N2
      INTEGER*4 IARRAY(:)
!-----------------------------------------------------------------------
      IF(ALLOCATED(IARRAY))THEN
        N1=LBOUND(IARRAY,1)
        N2=UBOUND(IARRAY,1)
!
        DEALLOCATE(ARRAY)
      ENDIF
!
      RETURN
      END
!***********************************************************************

But unfortunately again I am getting a compiler error?

Could you help once more?

Detlef Pannhorst

23 Nov 2012 3:58 #11165

I am not sure if you can do what you are aiming to do.

My Fortran is a bit rusty in this area.

I think that you can ALLOCATE in a subroutine and pass a pointer back but maybe the reverse is not sensible.

Do you have to DEALLOCATE at a lower subroutine level?

23 Nov 2012 4:44 #11166

Quoted from dpannhorst Hi Paul,

But the next stage for my code is to resize this array. Therefore I tried:

      PROGRAM MYPROG
!
      IMPLICIT NONE
!
      INTEGER*4, ALLOCATABLE :: I4(:)
!
      INTERFACE
        SUBROUTINE MYSUB(IARRAY)
        INTEGER :: IARRAY(:)
        END SUBROUTINE MYSUB
      END INTERFACE
!-----------------------------------------------------------------------
      ALLOCATE(I4(10))
      I4=1
!
      CALL MYSUB(I4)
!
      DEALLOCATE(I4)
      END
!***********************************************************************
      SUBROUTINE MYSUB(IARRAY)
!
      IMPLICIT NONE
!
      INTEGER*4 N1,N2
      INTEGER*4 IARRAY(:)
!-----------------------------------------------------------------------
      IF(ALLOCATED(IARRAY))THEN
        N1=LBOUND(IARRAY,1)
        N2=UBOUND(IARRAY,1)
!
        DEALLOCATE(ARRAY)
      ENDIF
!
      RETURN
      END
!***********************************************************************

But unfortunately again I am getting a compiler error?

Could you help once more?

Detlef Pannhorst

There are two problems with achieving this with FTN95. You have an error: the formal argument IARRAY is not declared with the ALLOCATABLE attribute, so there is a mismatch between the actual subroutine and the declared interface. This is easily fixed by adding ALLOCATABLE in the type statement for IARRAY in the subroutine.

Unfortunately, allocatable array arguments are an extension to Fortran 95 that FTN95 does not support.

23 Nov 2012 5:01 #11167

If the extension is in the 2003 Standard then maybe it can be added to FTN95.

In the mean time the following works. It just means that you have to pass your own flag to say whether or not the array has been allocated...

      PROGRAM MYPROG 
      INTEGER, ALLOCATABLE :: I4(:) 
      INTERFACE 
        SUBROUTINE MYSUB(IARRAY) 
        INTEGER,POINTER :: IARRAY(:) 
        END SUBROUTINE MYSUB 
      END INTERFACE 
!----------------------------------------------------------------------- 
      ALLOCATE(I4(10)) 
      CALL MYSUB(I4)
      I4=1 !Fails so the DEALLOCATE has worked.
      END 
!*********************************************************************** 
      SUBROUTINE MYSUB(IARRAY) 
      INTEGER N1,N2 
      INTEGER,POINTER::IARRAY(:) 
      N1=LBOUND(IARRAY,1) 
      N2=UBOUND(IARRAY,1) 
      PRINT*, N1,N2
      DEALLOCATE(IARRAY) 
      END 
23 Nov 2012 5:09 (Edited: 23 Nov 2012 10:01) #11168

Allocatable dummy array arguments are only available in Fortran 2003 and Fortran 2008 (as Paul has guessed).

You can get almost exactly the same functionality in Fortran 95 using pointers. The following code gives a simple example of how to do it.

Here I create the array to be of size 10 in the subroutine, but you can use a variable and make it variable size.

module mmm
contains

   subroutine sss(a)
   
      real, pointer :: a(:)
      
      ! Allocate size of array required
      allocate(a(10))
      
      ! Do something with array to define it.
      do i=1, size(a)
         a(i) = real(i)
      end do
   
   end subroutine sss
   
end module mmm

program main

   use mmm, only: sss
   
   integer i
   real, pointer :: a(:)

   ! Create array
   call sss(a)   
   
   ! Print the array
   do i=1, size(a)
      print *, a(i)
   end do   

   deallocate(a)
   
end program main

[u:4fcedf45d2]Edit[/u:4fcedf45d2]: Oops I see Paul has posted a similar solution.

23 Nov 2012 5:44 #11170

Thanks for all the help. The workaround with POINTER is very useful.

This code is working in my intention:

      PROGRAM MYPROG
!
      IMPLICIT NONE
!
      INTEGER*4, ALLOCATABLE :: I4(:)
!
      INTERFACE
        SUBROUTINE MYSUB(IARRAY)
        INTEGER, POINTER :: IARRAY(:)
        END SUBROUTINE MYSUB
      END INTERFACE
!-----------------------------------------------------------------------
      ALLOCATE(I4(10))
      I4=1
!
      CALL MYSUB(I4)
!
      DEALLOCATE(I4)
      END
!***********************************************************************
      SUBROUTINE MYSUB(IARRAY)
!
      IMPLICIT NONE
!
      INTEGER*4 N1,N2
      INTEGER*4, POINTER :: IARRAY(:)
      INTEGER*4, ALLOCATABLE :: ITEMP(:)
!-----------------------------------------------------------------------
      IF(ALLOCATED(IARRAY))THEN
        N1=LBOUND(IARRAY,1)
        N2=UBOUND(IARRAY,1)
!
        ALLOCATE(ITEMP(N1:N2))
!
        ITEMP=IARRAY
!
        DEALLOCATE(IARRAY)
        DEALLOCATE(ITEMP)
!
        ALLOCATE(IARRAY(N1:N2+5))
        IARRAY=2
      ENDIF
!
      RETURN
      END
!***********************************************************************

Detlef Pannhorst

23 Nov 2012 9:56 (Edited: 23 Nov 2012 10:05) #11172

Another solution might be to define the allocatable array in a module then access the module via USE. With this approach, you can resize the array. I'm not sure if this is what you want, but you can resize the array, by: -allocate a temporary array the same as the old size, -store the old values (assuming that you need them) -deallocate the array -allocate the array for the new size -define the new array from the values in the temporary array -deallocate the temporaty array.

This approach requires storage for 2-3 x the array size, which can be a significant problem. You can always write the array to disk !! (32-bit solution), or resort to LOC and CORE4.

I use this approach if I have to increase the size of a key database array, such as the list of node coordinates or the node list index. By having these allocatable arrays in a MODULE, this approach avoids the use of pointers. Allocatable arrays defined in a module provide a very flexible approach to adjusting problem size.

John

23 Nov 2012 10:04 #11173

Detlef,

What does ITEMP do in your latest code?

This is John's algorithm to make an array bigger using your POINTER dummy argument approach.

subroutine extend(a)
   real, pointer :: a
   if (allocated(a)) then
      allocate(tmp(size(a)))     ! Temp array same size as a
      tmp = a                         ! Copy the array
      deallocate(a)                  ! Delete old array
      allocate(a(size(tmp)+5))  ! Extend array by 5 elements
      a(1:size(tmp)) = tmp      ! Copy elements of tmp to elements of a
      deallocate(tmp)              ! Delete temp array
   end if
end subroutine extend
23 Nov 2012 10:12 #11174

Another point for this post, is that I use the ALLOCATABLE status only associated with where the array is origionally defined and sized. I then restrict my use of the array in any argument list to having flexible dimension, such as: integer, dimension(:) :: array or integer array(*)

Both declarations work well for me, but might not be utilising some capability of fortran you are searching for. I only ever change the allocatable array at the top of the scope where it is used. ( I'm not sure you can change it lower down where it is being supplied via an argument list)

John

23 Nov 2012 10:14 #11175

Quoted from JohnCampbell

I only ever change the allocatable array at the top of the scope where it is used.

Me too, its more efficient that way.

Please login to reply.