- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Dear all,
I see the following problem with the attached code: the amount of memory used
during the execution is proportional to the number of iterations in the DO loop
in the main program "ctrl_model", so that (on my machine, at least) the third
loop fails for insufficient memory. On the other hand, using an allocatable
variable in the SUBROUTINE "step" gives no problem: the required memory seems to
be independent from the number of iterations. Overall, my impression is that
this is a memory leak due to the compiler. Am I correct?
Thank you,
Marco
ifort -V
Intel Fortran Compiler Professional for applications running on IA-32,
Version 11.0 Build 20090318 Package ID: l_cprof_p_11.0.083
uname -a
Linux XXX 2.6.18-6-686 XXX i686 GNU/Linux
module mo_kind
implicit none
integer, parameter :: wp = selected_real_kind(12,307)
end module mo_kind
!ooooooooooooooooooooooooooooo
module mo_hy
use mo_kind, only: wp
implicit none
private
public :: my_type
type my_type
real(wp), allocatable :: &
f1(:,:), &
f2(:,:,:), &
f3(:,:,:), &
f4(:,:,:), &
f5(:,:,:,:)
end type my_type
end module mo_hy
!ooooooooooooooooooooooooooooo
module mo_time
use mo_hy, only: my_type
implicit none
private
public :: step
contains
subroutine step(uu)
type(my_type), intent(in) :: uu
integer, parameter :: n = 5
integer :: i
type(my_type) :: vv(n)
!type(my_type), allocatable :: vv(:)
!allocate(vv(n))
do i=1,n
vv(i) = uu
enddo
!deallocate(vv)
end subroutine step
end module mo_time
!ooooooooooooooooooooooooooooo
program ctrl_model
use mo_hy, only: my_type
use mo_time, only: step
implicit none
type(my_type) :: x
integer :: j
allocate(x%f1(1,5120))
allocate(x%f2(1,1,7680))
allocate(x%f3(1,1,5120))
do j=1,10
call step(x)
enddo
write(*,*) 'Done 1'
do j=1,100
call step(x)
enddo
write(*,*) 'Done 2'
do j=1,10000
call step(x)
enddo
write(*,*) 'Done 3'
end program ctrl_model
I see the following problem with the attached code: the amount of memory used
during the execution is proportional to the number of iterations in the DO loop
in the main program "ctrl_model", so that (on my machine, at least) the third
loop fails for insufficient memory. On the other hand, using an allocatable
variable in the SUBROUTINE "step" gives no problem: the required memory seems to
be independent from the number of iterations. Overall, my impression is that
this is a memory leak due to the compiler. Am I correct?
Thank you,
Marco
ifort -V
Intel Fortran Compiler Professional for applications running on IA-32,
Version 11.0 Build 20090318 Package ID: l_cprof_p_11.0.083
uname -a
Linux XXX 2.6.18-6-686 XXX i686 GNU/Linux
module mo_kind
implicit none
integer, parameter :: wp = selected_real_kind(12,307)
end module mo_kind
!ooooooooooooooooooooooooooooo
module mo_hy
use mo_kind, only: wp
implicit none
private
public :: my_type
type my_type
real(wp), allocatable :: &
f1(:,:), &
f2(:,:,:), &
f3(:,:,:), &
f4(:,:,:), &
f5(:,:,:,:)
end type my_type
end module mo_hy
!ooooooooooooooooooooooooooooo
module mo_time
use mo_hy, only: my_type
implicit none
private
public :: step
contains
subroutine step(uu)
type(my_type), intent(in) :: uu
integer, parameter :: n = 5
integer :: i
type(my_type) :: vv(n)
!type(my_type), allocatable :: vv(:)
!allocate(vv(n))
do i=1,n
vv(i) = uu
enddo
!deallocate(vv)
end subroutine step
end module mo_time
!ooooooooooooooooooooooooooooo
program ctrl_model
use mo_hy, only: my_type
use mo_time, only: step
implicit none
type(my_type) :: x
integer :: j
allocate(x%f1(1,5120))
allocate(x%f2(1,1,7680))
allocate(x%f3(1,1,5120))
do j=1,10
call step(x)
enddo
write(*,*) 'Done 1'
do j=1,100
call step(x)
enddo
write(*,*) 'Done 2'
do j=1,10000
call step(x)
enddo
write(*,*) 'Done 3'
end program ctrl_model
Link Copied
8 Replies
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
This looks like a bug to me. I'll report it to the developers. Thanks for the nice test case. The problem is actually that the compiler does not deallocate the components of vv before leaving routine step. Our issue ID is DPD200121498.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The developers tell me that they have fixed this bug. We hope to include the fix in an update later this year - I'll update this thread when the fix is available.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Marco, while waiting for the fix, you can deallocate at the end of subroutine "step" explicitly:
do i=1,n
deallocate(vv(i)%f1, vv(i)%f2, vv(i)%f3, vv(i)%f4, vv(i)%f5)
enddo
I've used similar derived types in my programs (not with the latest compiler version, though), and noticed that in procedures all local variables with allocatable components must be deallocated explicitly, if they are not ALLOCATABLE or POINTER themselves. My guess (based on Metcalf & Reid 90/95, not seeing the standard) is that it is only required that automatic deallocation works recursively. Maybe the preferred action in this kind of situation has not been standardized. Please someone correct me if I am wrong.
regards,
Teemu Laakso
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The wording of the standard here is somewhat obtuse, and indeed I found myself second-guessing whether this really was a bug or not. However, I came to the eventual conclusion that the standard unambiguously (if indirectly) says that the allocatable subcomponents must get automatically deallocated.
First, here's text from 6.3.3.1:
5 When the execution of a procedure is terminated by execution of a RETURN or END statement, an
6 allocatable variable that is a named local variable of the procedure retains its allocation and definition
7 status if it has the SAVE attribute or is a function result variable or a subobject thereof; otherwise, it
8 is deallocated.
The question I found myself asking this morning, though, was: is a subcomponent of a variable a "named local variable"? At first I thought no, but when I saw the "or a subobject thereof" I caught myself and started to dive into the standard again. I found this:
A variable can have a value or be undefined; during execution of a program it can be defined and redefined.
...
NOTE 2.11
A subobject of a local variable is also a local variable.
So it ends up that even if the parent variable isn't allocatable, the allocatable subcomponent is "an allocatable variable that is a named local variable of the procedure" and therefore the compiler is required to deallocate it on exit (if not SAVEd.)
First, here's text from 6.3.3.1:
5 When the execution of a procedure is terminated by execution of a RETURN or END statement, an
6 allocatable variable that is a named local variable of the procedure retains its allocation and definition
7 status if it has the SAVE attribute or is a function result variable or a subobject thereof; otherwise, it
8 is deallocated.
The question I found myself asking this morning, though, was: is a subcomponent of a variable a "named local variable"? At first I thought no, but when I saw the "or a subobject thereof" I caught myself and started to dive into the standard again. I found this:
A variable can have a value or be undefined; during execution of a program it can be defined and redefined.
...
NOTE 2.11
A subobject of a local variable is also a local variable.
So it ends up that even if the parent variable isn't allocatable, the allocatable subcomponent is "an allocatable variable that is a named local variable of the procedure" and therefore the compiler is required to deallocate it on exit (if not SAVEd.)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve,
>>So it ends up that even if the parent variable isn't allocatable, the allocatable subcomponent is "an allocatable variable that is a named local variable of the procedure" and therefore the compiler is required to deallocate it on exit (if not SAVEd.)
Are you saying a user defined type can contain SAVEd members?
type foo
real :: r
integer, save :: i
real, allocatable, save :: rSave(:)
end type foo
...
type(foo) :: foo1
type(foo) :: foo2
and there is one instance of i and one array descriptor
i.e.
foo1%i is equivilent to foo2%i
foo1%rSave is equivilent to foo2%rSave
?? is this what you just said ??
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
No - I meant that a SAVEd variables can have subcomponents, so if an ALLOCATABLE array is a component of a SAVEd variable, it would not be automatically deallocated. It is not possible to apply the SAVE attribute to individual components.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
>>It is not possible to apply the SAVE attribute to individual components.
It wasn't clear to me that the Fortran standard wasn't incorporating some of the language characteristics of C++ such as class/struct containing a static member which is essentially what was depicted by my last post.
Jim
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
This problem was fixed in 11.1 Update 2.

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