- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I tried the following gotten from this discussion group:
real, allocatable :: c(:)
kmax=5
allocate(c(kmax))
nmax=10
call realloc(c,nmax)
stop
end
SUBROUTINE ReAlloc(A, n)
REAL, ALLOCATABLE:: A(:)
INTEGER:: n, nOld
REAL, ALLOCATABLE:: Temp(:)
nOld = SIZE(A)
IF (nOld > n) RETURN
ALLOCATE(Temp(nOld))
Temp=A
DEALLOCATE(A)
ALLOCATE(A(n))
A(1:nOld) = Temp
END SUBROUTINE Realloc
and I get:
--------------------------------------
D:sigfit-devv2006>ifl realloc-code.f
Intel Fortran Compiler for 32-bit applications, Version 7.1 Build 20030307Z
Copyright (C) 1985-2003 Intel Corporation. All rights reserved.
EPC Fortran-95 Version F95 Intel:200200:131124
Copyright (c) 1993-2000 EPCL. All Rights Reserved.
realloc-code.f
main program
external subroutine REALLOC
DEALLOCATE(A)
^
realloc-code.f(16): Error 230 : This entity is not a pointer to an array nor an allocatable array
ALLOCATE(A(n))
^
realloc-code.f(17): Error 230 : This entity is not a pointer to an array nor an allocatable array
realloc-code.f: Error 374 : Dummy argument A of procedure REALLOC must not be ALLOCATABLE
3 Errors
compilation aborted for realloc-code.f (code 1)
--------------------------------------
We are interpreting this to mean that since A is in the argument list, it may not be allocatable in the subroutine.
The questions are:
1. Are we interpreting the problem correctly and an upgrade will allow us to reallocate data structures in a subroutines after being passed through the argument list?
2. With the latest version will we be able to perform reallocation on structures in COMMON?
3. With the latest version is the above method the best way to reallocate data structures?
Thanks
Greg
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Message Edited by tim18 on 01-31-2006 09:52 AM
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Yes. This is an extension to F95, called TR15581 (aka "allocatable TR"), and incorporated in the new Fortran 2003 standard. It is supported since IVF8 and CVF6.6 (I think), but not in IFC 7.
2. With the latest version will we be able to perform reallocation on structures in COMMON?
Hmm? As far as I know, COMMON and ALLOCATABLE attributes have always been (and will be) incompatible. COMMON implies static storage, and ALLOCATABLE is dynamic by definition. A POINTER variable may be in COMMON, but not with the "obvious" semantics -- it "equivalences" the pointer(s) rather than their targets.
3. With the latest version is the above method the best way to reallocate data structures?
Yes, more or less. In F2003, there is new, more efficient, MOVE_ALLOC intrinsic, but not yet implemented in VF. I once "cooked my own" and posted it in this Forum, but a) it's a low-level non-portable tweak b) I'm not sure if I got the syntax and semantics right. I can dig out the reference if you want.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The following code is an approach taken from Numerical Recipies - maybe it will work with IVF Version 7 - Edmund
! NRTYPE.F90
MODULE nrtype
INTEGER, PARAMETER :: I4B = SELECTED_INT_KIND(9)
INTEGER, PARAMETER :: I2B = SELECTED_INT_KIND(4)
INTEGER, PARAMETER :: I1B = SELECTED_INT_KIND(2)
INTEGER, PARAMETER :: SP = KIND(1.0)
INTEGER, PARAMETER :: DP = KIND(1.0D0)
INTEGER, PARAMETER :: SPC = KIND((1.0,1.0))
INTEGER, PARAMETER :: DPC = KIND((1.0D0,1.0D0))
INTEGER, PARAMETER :: LGT = KIND(.true.)
REAL(SP), PARAMETER :: PI=3.141592653589793238462643383279502884197_sp
REAL(SP), PARAMETER :: PIO2=1.57079632679489661923132169163975144209858_sp
REAL(SP), PARAMETER :: TWOPI=6.283185307179586476925286766559005768394_sp
REAL(SP), PARAMETER :: SQRT2=1.41421356237309504880168872420969807856967_sp
REAL(SP), PARAMETER :: EULER=0.5772156649015328606065120900824024310422_sp
REAL(DP), PARAMETER :: PI_D=3.141592653589793238462643383279502884197_dp
REAL(DP), PARAMETER :: PIO2_D=1.57079632679489661923132169163975144209858_dp
REAL(DP), PARAMETER :: TWOPI_D=6.283185307179586476925286766559005768394_dp
TYPE sprs2_sp
INTEGER(I4B) :: n,len
REAL(SP), DIMENSION(:), POINTER :: val
INTEGER(I4B), DIMENSION(:), POINTER :: irow
INTEGER(I4B), DIMENSION(:), POINTER :: jcol
END TYPE sprs2_sp
TYPE sprs2_dp
INTEGER(I4B) :: n,len
REAL(DP), DIMENSION(:), POINTER :: val
INTEGER(I4B), DIMENSION(:), POINTER :: irow
INTEGER(I4B), DIMENSION(:), POINTER :: jcol
END TYPE sprs2_dp
END MODULE nrtype
! NRUTIL.F90
MODULE nrutil
USE nrtype
IMPLICIT NONE
INTERFACE reallocate
MODULE PROCEDURE reallocate_rv,reallocate_rm,&
reallocate_iv,reallocate_im,reallocate_hv
END INTERFACE
CONTAINS
!BL
SUBROUTINE nrerror(string)
CHARACTER(LEN=*), INTENT(IN) :: string
write (*,*) 'nrerror: ',string
STOP 'program terminated by nrerror'
END SUBROUTINE nrerror
!BL
FUNCTION reallocate_rv(p,n)
REAL(SP), DIMENSION(:), POINTER :: p, reallocate_rv
INTEGER(I4B), INTENT(IN) :: n
INTEGER(I4B) :: nold,ierr
allocate(reallocate_rv(n),stat=ierr)
if (ierr /= 0) call &
nrerror('reallocate_rv: problem in attempt to allocate memory')
if (.not. associated(p)) RETURN
nold=size(p)
reallocate_rv(1:min(nold,n))=p(1:min(nold,n))
deallocate(p)
END FUNCTION reallocate_rv
!BL
FUNCTION reallocate_iv(p,n)
INTEGER(I4B), DIMENSION(:), POINTER :: p, reallocate_iv
INTEGER(I4B), INTENT(IN) :: n
INTEGER(I4B) :: nold,ierr
allocate(reallocate_iv(n),stat=ierr)
if (ierr /= 0) call &
nrerror('reallocate_iv: problem in attempt to allocate memory')
if (.not. associated(p)) RETURN
nold=size(p)
reallocate_iv(1:min(nold,n))=p(1:min(nold,n))
deallocate(p)
END FUNCTION reallocate_iv
!BL
FUNCTION realloca
te_hv(p,n)
CHARACTER(1), DIMENSION(:), POINTER :: p, reallocate_hv
INTEGER(I4B), INTENT(IN) :: n
INTEGER(I4B) :: nold,ierr
allocate(reallocate_hv(n),stat=ierr)
if (ierr /= 0) call &
nrerror('reallocate_hv: problem in attempt to allocate memory')
if (.not. associated(p)) RETURN
nold=size(p)
reallocate_hv(1:min(nold,n))=p(1:min(nold,n))
deallocate(p)
END FUNCTION reallocate_hv
!BL
FUNCTION reallocate_rm(p,n,m)
REAL(SP), DIMENSION(:,:), POINTER :: p, reallocate_rm
INTEGER(I4B), INTENT(IN) :: n,m
INTEGER(I4B) :: nold,mold,ierr
allocate(reallocate_rm(n,m),stat=ierr)
if (ierr /= 0) call &
nrerror('reallocate_rm: problem in attempt to allocate memory')
if (.not. associated(p)) RETURN
nold=size(p,1)
mold=size(p,2)
reallocate_rm(1:min(nold,n),1:min(mold,m))=&
p(1:min(nold,n),1:min(mold,m))
deallocate(p)
END FUNCTION reallocate_rm
!BL
FUNCTION reallocate_im(p,n,m)
INTEGER(I4B), DIMENSION(:,:), POINTER :: p, reallocate_im
INTEGER(I4B), INTENT(IN) :: n,m
INTEGER(I4B) :: nold,mold,ierr
allocate(reallocate_im(n,m),stat=ierr)
if (ierr /= 0) call &
nrerror('reallocate_im: problem in attempt to allocate memory')
if (.not. associated(p)) RETURN
nold=size(p,1)
mold=size(p,2)
reallocate_im(1:min(nold,n),1:min(mold,m))=&
p(1:min(nold,n),1:min(mold,m))
deallocate(p)
END FUNCTION reallocate_im
!BL
END MODULE nrutil
!BL
program Realloc
USE nrtype; USE nrutil
IMPLICIT NONE
REAL(SP), DIMENSION(:), POINTER :: x
INTEGER(I4B) :: i
allocate(x(10))
forall(i=1:ubound(x,1)) x(i)=i
write(*,"(10F6.2)") x
x => reallocate(x,20)
forall(i=1:ubound(x,1)) x(i)=2*i
write(*,"(20F6.2)") x
end program Realloc

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page