Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

pointer memory management with (de)allocate

7 views
Skip to first unread message

Ned C

unread,
Sep 13, 2009, 9:07:27 AM9/13/09
to
Hi all,

Was playing around with using pointers and allocatables the other day,
but got quite confused. All the programs listed below could be
compiled using NAG 5.2. Any help is very much appreciated! (I am
under time pressure to resolve this issue). Thanks very much in
advance!

I have a function that assigns a pointer by calling another pointer
function:

=============================main.f03===========================
program main

use f90_unix_env, only : iArgc, getArg
use type1_type
use extended2A_type
use extended2B_type

implicit none
integer :: iErr, i
integer :: numArgs
character, dimension(:), allocatable :: tempArgs*(100)
class(type1), allocatable :: thisType1

numArgs = iargc()
allocate (tempArgs(numArgs))
allocate (Type1::thisType1)
do i = 1, numArgs
call getArg(i,tempArgs(i))
enddo
iErr = thisType1%initProc()

deallocate (thisType1% type2Ptr) ! What happens here??? See
questions below.
! now the pointer should be dangling and needs to be nullified /
reassigned

end program main
============================================================

=======================type1_type.f03===========================
module type1_type
use type2_type
implicit none

type Type1
class(type2), pointer :: type2Ptr => null()
contains
procedure :: initProc => Type1_initProc
end type Type1

contains
function Type1_initProc(this) result(iError)
use extended2A_type
use extended2B_type
implicit none
class(Type1) :: this
integer :: iError
this% type2Ptr => extended2A_new()
if ( .not.( associated(this% type2Ptr))) then
iError = 1
write(*,'(A)') "Something Wrong."
else
iError = 0
endif
end function Type1_initProc

end module type1_type
============================================================

=======================type2_type.f03===========================
module type2_type
implicit none

type, abstract :: Type2
character :: typeName*(30) = "unknown"
contains
procedure :: setName => Type2_setName
procedure :: coeff => Type2_coeff
end type Type2

contains
subroutine Type2_setName(this)
class(Type2) :: this
write(*,'(A)') 'No setName implementation in
Type2.'
end subroutine Type2_setName

function Type2_coeff(this,coeffName) result(thisCoeff)
class(Type2) :: this
character, intent(in) :: coeffName*(*)
real(kind(1.0D0)) :: thisCoeff
write(*,'(A)') 'No implementation in Type2.'
ThisCoeff = 0.
end function Type2_coeff

end module type2_type
============================================================

==================extended2A_type.f03===========================
module extended2A_type

use type2_type
implicit none

type, extends(Type2) :: Extended2A
real(kind(1.0D0)) :: coeff1 = 1.
real(kind(1.0D0)) :: coeff2 = 2.
contains
procedure :: setCoeff1 => Extended2A_setCoeff1
procedure :: setCoeff2 => Extended2A_setCoeff2
procedure :: setName => Extended2A_setName
procedure :: coeff => Extended2A_coeff
end type Extended2A

contains
function Extended2A_new(c1, c2) result(typePtr_)
real(kind(1.0D0)), optional, intent(in) :: c1
real(kind(1.0D0)), optional, intent(in) :: c2
type(Extended2A), pointer :: typePtr_
type(Extended2A), save, allocatable, target :: type_

allocate(type_)
typePtr_ => null()
if (present(c1)) call type_%setCoeff1(c1)
if (present(c2)) call type_%setCoeff2(c2)
call type_%setName()
typePtr_ => type_
if ( .not.(associated (typePtr_))) then
stop 'Error initializing Extended2A Pointer.'
endif

end function Extended2A_new


subroutine Extended2A_setCoeff1(this,c1)
class(Extended2A) :: this
real(kind(1.0D0)), intent(in) :: c1
this% coeff1 = c1
end subroutine Extended2A_setCoeff1


subroutine Extended2A_setCoeff2(this,c2)
class(Extended2A) :: this
real(kind(1.0D0)), intent(in) :: c2
this% coeff2 = c2
end subroutine Extended2A_setCoeff2


subroutine Extended2A_setName(this)
class(Extended2A) :: this
this% typeName = "Extended2A"
write(*,'(A)') ' this% typeName = "Extended2A"'
end subroutine Extended2A_setName


function Extended2A_coeff(this,coeffName) result (thisCoeff)
class(Extended2A) :: this
character, intent(in) :: coeffName*(*)
real(kind(1.0D0)) :: thisCoeff
if (coeffName == "coeff1") then
thisCoeff = this%coeff1
else if (coeffName == "coeff2") then
thisCoeff = this%coeff2
else
stop 'Error: invalid coeffcient name.'
endif
end function Extended2A_coeff

end module extended2A_type
============================================================

==================extended2B_type.f03===========================
module extended2B_type
use type2_type
implicit none

type, extends(type2) :: Extended2B
contains
procedure :: coeff => Extended2B_coeff
end type Extended2B

contains

function Extended2B_coeff(this,coeffName) result (thisCoeff)
class(Extended2B) :: this
character, intent(in) :: coeffName*(*)
real(kind(1.0D0)) :: thisCoeff
stop 'Error: No coeffcient in Extended2B.'
end function Extended2B_coeff

end module extended2B_type

============================================================

My questions:

1) What exactly does the deallocate do here?
a) Does it simply disassociate the pointer with the target* (i.e.
possibly causing a memory leak)?
b) Does it release the space occupied by the allocatable target**
(no memory leak, and I can associate
the pointer with another type2 object when I call "initProc" or
"new" somewhere else?
2) Any alternatives to the code I wrote? I was hoping that type1
objects would contain pointers, but not actual
objects, so that over the course of the execution of the program, I
can access different type2 objects through
one instance of type 1.

============================================================
*In the fortran 2003 FCD it stated that:

>(Section 6.3.3.2 Deallocation of pointer targets)
> If a pointer appears in a DEALLOCATE statement, its association status shall be defined. Deallocating
> a pointer that is disassociated or whose target was not created by an ALLOCATE statement causes an
> error condition in the DEALLOCATE statement. If a pointer is associated with an allocatable entity,
> the pointer shall not be deallocated.

My code compiles and runs. The last sentence seems to suggest that
what I am doing is wrong. Any workaround if that is the case?

> If a pointer appears in a DEALLOCATE statement, it shall be associated with the whole of an object>
> that was created by allocation. Deallocating a pointer target causes the pointer association status of
> any other pointer that is associated with the target or a portion of the target to become undefined.

But then my "target" was actually created by "allocation". Am I fine
then??


(Section C3.3)
> DEALLOCATE may only be used to release space that was created by a previous ALLOCATE. Thus
> the following is invalid:

> REAL, TARGET :: T
> REAL, POINTER :: P
> ...
> P = > T
> DEALLOCATE (P) ! Not allowed: P’s target was not allocated

============================================================

**language reference from IBM system info center (although I'm not
using IBM compiler...)
An allocatable object with the TARGET attribute cannot be deallocated
through an associated pointer. Deallocation of such an object causes
the association status of any associated pointer to become undefined.
An allocatable object that has an undefined allocation status cannot
be subsequently referenced, defined, allocated, or deallocated.
Successful execution of a DEALLOCATE statement causes the allocation
status of an allocatable object to become not allocated.

============================================================

Regards,
Ned

Jason Blevins

unread,
Sep 13, 2009, 11:52:29 AM9/13/09
to

I think your deallocate statement is fine and that the last sentence
above, with the "allocatable entity" bit, is not applicable to your
situation. If I understand correctly, that sentence refers to something
like the following, which is different than what you're doing:

program main
real, dimension(:), allocatable, target :: x
real, dimension(:), pointer :: p

allocate(x(10))
p => x
deallocate(p) ! incorrect
end program main

Here, x is the "allocatable entity" and p is the pointer which "shall not
be deallocated."

Your type2Ptr pointer isn't associated with an allocatable entity since
you are simply allocating memory for a new Type2 object. Such an object
is given the TARGET attribute automatically, so that other pointers can
refer to it, but it is not ALLOCATABLE.

>> If a pointer appears in a DEALLOCATE statement, it shall be
>> associated with the whole of an object> that was created by
>> allocation. Deallocating a pointer target causes the pointer
>> association status of any other pointer that is associated with the
>> target or a portion of the target to become undefined.
>
> But then my "target" was actually created by "allocation". Am I fine
> then??

This is referring to pointers that point to array sections. You have to
deallocate the whole array, so you can't call deallocate on a pointer
that points to an array section.

--
Jason Blevins
Ph.D. Candidate, Department of Economics, Duke University
http://jblevins.org/

Richard Maine

unread,
Sep 13, 2009, 1:13:58 PM9/13/09
to
Ned C <dnomde...@gmail.com> wrote:
[code elided]

> My questions:
>
> 1) What exactly does the deallocate do here?
> a) Does it simply disassociate the pointer with the target* (i.e.
> possibly causing a memory leak)?
> b) Does it release the space occupied by the allocatable target**
> (no memory leak, and I can associate
> the pointer with another type2 object when I call "initProc" or
> "new" somewhere else?

The answer is (b). That's *ALWAYS* what deallocate does. I don't even
have to look at the "here" part to figure out the details of the
context. Your (a) is what nulify does - not deallocate.

> 2) Any alternatives to the code I wrote? I was hoping that type1
> objects would contain pointers, but not actual
> objects, so that over the course of the execution of the program, I
> can access different type2 objects through
> one instance of type 1.

I didn't spend enough time with the code to work out what it was doing
in detail. I think it probably does that. I do note that the code
appears to make use of function side effects in a C style. Be aware that
there are controversies about the legalities of depending on such
function side effects (but I'd be fairly sure they would work in
practice in your case, regardless of the controversy, even though I tend
to be on the side that claims the usage is technically invalid).
Legalities aside, the practice does, if nothing else, slow down my
ability to follow the code.

> *In the fortran 2003 FCD it stated that:
>
> >(Section 6.3.3.2 Deallocation of pointer targets) If a pointer appears in
> >a DEALLOCATE statement, its association status shall be defined.
> >Deallocating a pointer that is disassociated or whose target was not
> >created by an ALLOCATE statement causes an error condition in the
> >DEALLOCATE statement. If a pointer is associated with an allocatable
> >entity, the pointer shall not be deallocated.
>
> My code compiles and runs. The last sentence seems to suggest that
> what I am doing is wrong.

Maybe I missed them, but I didn't notice you having any pointers
associated with allocatable entities. The only allocatable entities I
spotted were tempArgs (which you don't appear to do anything with - was
this left in accidentaly?) and thisType1. I don't see any deallocation
of thisType1, so unless I missed something, this doesn't apply). Note
that

1. The terminology is slightly confusing in that "allocatable" does not
mean capable of being allocated. It means having the allocatable
attribute. Things with the allocatable attribute are capable of being
allocated, but there are also other things (notably pointers) that are
capable of being allocated. A pointer does not count as allocatable,
even though it can be allocated; I hate that particular mess in the
terminology.

2. The allocatable attribute is not inherited by components. Your
thisType1 is allocatable, but that does *NOT* mean that
thisType1%type2Ptr is allocatable; it is a pointer.

> > If a pointer appears in a DEALLOCATE statement, it shall be associated
> > with the whole of an object> that was created by allocation.
> > Deallocating a pointer target causes the pointer association status of
> > any other pointer that is associated with the target or a portion of the
> > target to become undefined.
>
> But then my "target" was actually created by "allocation". Am I fine
> then??

This is a separate requirement from the one you cited before. Just
because you meet one requirement, that doesn't negate any others. If the
standard says something must be green, and later also says that it must
be a sphere, then you can't say that your red sphere is ok because it
meets the second requirement; you syll have to meet the other one also.

You look to be ok on this, but I think your argument above is all
confused as to why. This requirement means that as Jason mentioned, you
can't deallocate something like a slice of an allocated array; you have
to do the whole array. It also means that you can't deallocate plain old
static targets, which could have a pointer pointing to them (that's the
example that you showed from C3.3.

I'm afraid I didn't spend the time to try to figure out what the code
was doing as a whole. I did try to answer (most of) the specific
questions, though, as I think they looked answerable in (relative)
isolation. I'll punt on the question about whether there is another
(better?) way to do things though, as I think I'd have to spend more
time to figure out that one. Someone else?

--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain

Ned C

unread,
Sep 13, 2009, 6:59:09 PM9/13/09
to jrbl...@sdf.lonestar.org
> >     function Extended2A_new(c1, c2) result(typePtr_)
> >        real(kind(1.0D0)), optional, intent(in) :: c1
> >        real(kind(1.0D0)), optional, intent(in) :: c2
> >        type(Extended2A), pointer  :: typePtr_
> >        type(Extended2A), save, allocatable, target  :: type_
>
> >        allocate(type_)
> >        typePtr_ => null()
> >        if (present(c1)) call type_%setCoeff1(c1)
> >        if (present(c2)) call type_%setCoeff2(c2)
> >        call type_%setName()
> >        typePtr_ => type_
> >        if ( .not.(associated (typePtr_))) then
> >           stop 'Error initializing Extended2A Pointer.'
> >        endif
>
> >     end function Extended2A_new

>


> I think your deallocate statement is fine and that the last sentence
> above, with the "allocatable entity" bit, is not applicable to your
> situation.  If I understand correctly, that sentence refers to something
> like the following, which is different than what you're doing:
>
>     program main
>       real, dimension(:), allocatable, target :: x
>       real, dimension(:), pointer :: p
>
>       allocate(x(10))
>       p => x
>       deallocate(p)      ! incorrect
>     end program main
>
> Here, x is the "allocatable entity" and p is the pointer which "shall not
> be deallocated."
>
> Your type2Ptr pointer isn't associated with an allocatable entity since
> you are simply allocating memory for a new Type2 object.  Such an object
> is given the TARGET attribute automatically, so that other pointers can
> refer to it, but it is not ALLOCATABLE.

Thanks for the reply, Jason.

But I think my "type2Ptr" is associated with the allocatable entity in
the function extended2A_new.

if we extract the relevant statements from different files, we have

type(Extended2A), pointer :: typePtr_
type(Extended2A), save, allocatable, target :: type_

allocate(type_) ! just like allocate(x(10)) you said
typePtr_ => null()
! blah blah ...


call type_%setName()
typePtr_ => type_

! then afterwards in the main program
deallocate(type2Ptr)

Is that a problem?

Ned C

unread,
Sep 13, 2009, 7:20:11 PM9/13/09
to ma...@summertriangle.net
Thanks Richard. Yup I understand the difference between allocatable
and pointer.
Nice notes 1&2 though.

> Maybe I missed them, but I didn't notice you having any pointers
> associated with allocatable entities. The only allocatable entities I
> spotted were tempArgs (which you don't appear to do anything with - was
> this left in accidentaly?) and thisType1. I don't see any deallocation
> of thisType1, so unless I missed something, this doesn't apply).

As I replied to Jason, in my extended2A_new function, I associated the
pointer
to "type_", which is a "target" with an "allocatable" attribute.

type(Extended2A), pointer :: typePtr_
type(Extended2A), save, allocatable, target :: type_

allocate(type_)
typePtr_ => null()
if (present(c1)) call type_%setCoeff1(c1)
if (present(c2)) call type_%setCoeff2(c2)
call type_%setName()
typePtr_ => type_

I was suspecting that this might cause a problem. Does it matter that
these statements are in a separate function instead of being in the
main program?

Also, care to elaborate on the legality issue? Thanks again!

Regards,
Ned

Richard Maine

unread,
Sep 13, 2009, 7:24:13 PM9/13/09
to
Ned C <dnomde...@gmail.com> wrote:

> But I think my "type2Ptr" is associated with the allocatable entity in
> the function extended2A_new.
>
> if we extract the relevant statements from different files, we have
>
> type(Extended2A), pointer :: typePtr_
> type(Extended2A), save, allocatable, target :: type_
>
> allocate(type_) ! just like allocate(x(10)) you said
> typePtr_ => null()
> ! blah blah ...
> call type_%setName()
> typePtr_ => type_
> ! then afterwards in the main program
> deallocate(type2Ptr)
>
> Is that a problem?

I'm not Jason, but I missed the same thing. I didn't see that
allocatablel buried down there. Yes, that most definitely is a problem.
That is exactly one of the kinds of thing the prohibition is about.

Do not confuse allocatables and pointers. An allocatable can be
deallocated only by deallocating it directly (or by automatic
deallocation in some cases) - not by deallocating a pointer to it.

If you deallocate a pointer, it must point to something that was
allocated by allocating a pointer - not an allocatable.

I'm puzzled as to why you have type_ as an allocatable anyway. That
doesn't make much sense to me. I suspect you want it to be a pointer.

Jason Blevins

unread,
Sep 13, 2009, 7:30:30 PM9/13/09
to

I failed to read the code carefully enough and missed that
'save, allocatable'. I think what you want instead is the
following:

type(Extended2A), pointer :: type_

Then you can still allocate type_ and it will persist after
Extended2A_new() finishes (which it seems you were accomplishing in with
the 'save' attribute, though not quite in the manner you needed). If
you use a pointer instead, you will be able to legally deallocate it
elsewhere, as you do in your main program.

Jim Xia

unread,
Sep 15, 2009, 9:02:04 PM9/15/09
to
> **language reference from IBM system info center (although I'm not
> using IBM compiler...)
> An allocatable object with the TARGET attribute cannot be deallocated
> through an associated pointer. Deallocation of such an object causes
> the association status of any associated pointer to become undefined.
> An allocatable object that has an undefined allocation status cannot
> be subsequently referenced, defined, allocated, or deallocated.
> Successful execution of a DEALLOCATE statement causes the allocation
> status of an allocatable object to become not allocated.
>


Since you referred IBM language reference you should really try to
compile your program to see what happens :-)

Here is what XLF will tell you during the runtime for your program

> a.out
this% typeName = "Extended2A"
"test.f", line 29: 1525-109 Error encountered while attempting to
deallocate a data object. The program will stop.

The line number points to where the program failed. (Since I modified
your program and merged into one piece, the line number is different
from what you would see if all source code compiled seperately.) The
line 29 points to here

" module extended2A_type"

This is really puzzling and I'd like to see improvement later :-).
However I was able to track the problem to function Extended2A_new in
this module as it uses an saved allocatable target for a function
pointer return. And the only deallocate statement is in the main
program.

The reason for disallowing allocatable to be deallocated via pointers
is because Fortran language mandates the active memory management for
allocatable variables (auto-deallocation or auto-reallocation).
Pointers are left for programmer to manage. Users are not allowed to
mess around with the memory allocated for allocatables.

Cheers,

Jim

0 new messages