 |
forums.silverfrost.com Welcome to the Silverfrost forums
|
View previous topic :: View next topic |
Author |
Message |
dpannhorst
Joined: 29 Aug 2005 Posts: 165 Location: Berlin, Germany
|
Posted: Fri Nov 23, 2012 10:04 am Post subject: Passing dynamically allocated arrays to a subroutine |
|
|
How can I pass a dynamically allocated array to a subroutine and get the actual bounds of this array?
I tried this:
Code: | 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 |
|
Back to top |
|
 |
PaulLaidler Site Admin
Joined: 21 Feb 2005 Posts: 8210 Location: Salford, UK
|
Posted: Fri Nov 23, 2012 10:50 am Post subject: |
|
|
Code: | 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 |
|
|
Back to top |
|
 |
dpannhorst
Joined: 29 Aug 2005 Posts: 165 Location: Berlin, Germany
|
Posted: Fri Nov 23, 2012 11:58 am Post subject: |
|
|
Hi Paul,
thank you very much; this is working.
But the next stage for my code is to resize this array. Therefore I tried:
Code: | 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 |
|
Back to top |
|
 |
PaulLaidler Site Admin
Joined: 21 Feb 2005 Posts: 8210 Location: Salford, UK
|
Posted: Fri Nov 23, 2012 4:58 pm Post subject: |
|
|
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? |
|
Back to top |
|
 |
mecej4
Joined: 31 Oct 2006 Posts: 1899
|
Posted: Fri Nov 23, 2012 5:44 pm Post subject: Re: |
|
|
dpannhorst wrote: | Hi Paul,
But the next stage for my code is to resize this array. Therefore I tried:
Code: | 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. |
|
Back to top |
|
 |
PaulLaidler Site Admin
Joined: 21 Feb 2005 Posts: 8210 Location: Salford, UK
|
Posted: Fri Nov 23, 2012 6:01 pm Post subject: |
|
|
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...
Code: | 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
|
|
|
Back to top |
|
 |
davidb
Joined: 17 Jul 2009 Posts: 560 Location: UK
|
Posted: Fri Nov 23, 2012 6:09 pm Post subject: |
|
|
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.
Code: |
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
|
Edit: Oops I see Paul has posted a similar solution. _________________ Programmer in: Fortran 77/95/2003/2008, C, C++ (& OpenMP), java, Python, Perl
Last edited by davidb on Fri Nov 23, 2012 11:01 pm; edited 1 time in total |
|
Back to top |
|
 |
dpannhorst
Joined: 29 Aug 2005 Posts: 165 Location: Berlin, Germany
|
Posted: Fri Nov 23, 2012 6:44 pm Post subject: |
|
|
Thanks for all the help. The workaround with POINTER is very useful.
This code is working in my intention:
Code: | 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 |
|
Back to top |
|
 |
JohnCampbell
Joined: 16 Feb 2006 Posts: 2615 Location: Sydney
|
Posted: Fri Nov 23, 2012 10:56 pm Post subject: |
|
|
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
Last edited by JohnCampbell on Fri Nov 23, 2012 11:05 pm; edited 1 time in total |
|
Back to top |
|
 |
davidb
Joined: 17 Jul 2009 Posts: 560 Location: UK
|
Posted: Fri Nov 23, 2012 11:04 pm Post subject: |
|
|
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.
Code: |
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
|
_________________ Programmer in: Fortran 77/95/2003/2008, C, C++ (& OpenMP), java, Python, Perl |
|
Back to top |
|
 |
JohnCampbell
Joined: 16 Feb 2006 Posts: 2615 Location: Sydney
|
Posted: Fri Nov 23, 2012 11:12 pm Post subject: |
|
|
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 |
|
Back to top |
|
 |
davidb
Joined: 17 Jul 2009 Posts: 560 Location: UK
|
Posted: Fri Nov 23, 2012 11:14 pm Post subject: Re: |
|
|
JohnCampbell wrote: |
I only ever change the allocatable array at the top of the scope where it is used. |
Me too, its more efficient that way. _________________ Programmer in: Fortran 77/95/2003/2008, C, C++ (& OpenMP), java, Python, Perl |
|
Back to top |
|
 |
|
|
You cannot post new topics in this forum You cannot reply to topics in this forum You cannot edit your posts in this forum You cannot delete your posts in this forum You cannot vote in polls in this forum
|
Powered by phpBB © 2001, 2005 phpBB Group
|