- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
I have an issue with a pointer which becomes wrong. I cannot share the code, but I have tried to reproduce the situation here:
! -- Calling code ----------------------
FUNCTION constructor( this ) RESULT(this)
TYPE(Tcase), TARGET :: this
ALLOCATE( this%objects(1) )
this%objects(1) = constructorObject( )
CALL attach( this%objectRef, this%objects )
END FUNCTION constructor
! -- Def of TObject ------------------
TYPE TObject
REAL, ALLOCATABLE :: array(:)
END TYPE TObject
! -------------------------------------
MODULE objectRef_module
TYPE objectPointer
TYPE(TObject), POINTER :: ptr
END TYPE TobjectRef
TYPE, PUBLIC :: TobjectRef
TYPE(objectPointer), ALLOCATABLE :: objPtrs
END TYPE
SUBROUTINE attach( this, objects )
TYPE(TobjectRef), INTENT(inout) :: this
TYPE(Tobject), TARGET, INTENT(in) :: objects(:)
ALLOCATE( this%objPtrs(1) )
this%objPtrs(1)%ptr => objects(1)
END SUBROUTINE
END MODULE objectRef_module
The calling code is the part that constructs the array this%objects(:) (Here with size 1 as an example), and then build an object reference structure pointing to those objects. The reason for doing this is not important here, though there could be a better way to solve my issue (getting access to an object which is contained in a different Tcase-instance). The object reference structure is built as an array of allocatable containing pointers to objects. This is a workaround to be able to have an allocatable array of pointers.
What happens is that later in the calling code, this%objectRef%objPtrs%ptr%array(:) is not reachable. Using LOC(), I can see that when exiting the constructor in the calling code, the address of this%objects changes, as well as this%object%array. But the address of this%objectRef%objPtrs%ptr stays unchanged and the same for this%objectRef%objPtrs%ptr%array. This is with the 2017 fortran compiler, we are lagging behind on this one... This code runs without problem with the NAG fortran compiler, which we generally use to find all code issues that ifort does not find.
Now if I split the constructor like this, and then call successively constructor and attachObjectRef, the issue disappears.
! -- Calling code ----------------------
FUNCTION constructor( this ) RESULT(this)
TYPE(Tcase), TARGET :: this
ALLOCATE( this%objects(1) )
this%objects(1) = constructorObject( )
END FUNCTION constructor
SUBROUTINE attachObjectRef( this )
TYPE(Tcase), INTENT(inout) :: this
CALL attach( this%objectRef, this%objects )
END FUNCTION constructor
I also earlier had an issue with a pointer pointing directly to the result of a constructor, the code ran properly but deallocation failed. This looks similar to me.
Are there similar issues which have already been fixed? Is it more likely a problem in my code? I know it is difficult to answer without a minimum failing example, but I really can't make one.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@Amorin1 wrote:
This is a little off-topic for this thread, but what is the standard way to define a class with a constructor for an object oriented design?
Unfortunately, as things stand with the Fortran standard, there really are no good options when it comes to "constructor"s - note this typically signifies FUNCTION subprograms.
About the only good option is a SUBROUTINE subprogram for, say, something like the INITIALIZATION of an object once it has come into existence i.e., when an object of an "class" has been instantiated per OO parlance. Note in Fortran
- in a given program or subprogram, a type declaration statement such as `type(TCase) c` brings the object `c` into existence when the program's scope comes into execution.
- Or, with the `ALLOCATABLE` or `POINTER` attribute of the object, once the object is allocated in any number of ways e.g., an ALLOCATE statement
Then something like `call init_tcase( c )` where the subroutine `init_tcase` does the needful toward the actual "construction" of the object is the way to go to be safe.
In the context of this thread, both the actual argument `c` and the received argument (termed questionably as dummy argument in the standard) shall have the TARGET attribute for standard-conforming behavior. However a compiler is of little to of no help if a programmer fails to apply the TARGET attribute on the actual argument and this is a MASSIVE PROBLEM in actual practice because the actual argument can be coded by any end-user programmer and who can easily OVERLOOK this crucial aspect and then encounter unexpected / inconsistent behavior with the program and end up with possibly terrible consequences.
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I noticed a small glitch in the code you sent - "subroutine ... end function". This suggests to me that you did not actually build the program. For us to help out, it would be very convenient to have something that builds without editing, and that is "guaranteed" to show the problem. I can imagine the problem of constructing a reproducer, but it is all too easy to describe a problem and make a mistake in that ;).
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
I did not think I could reproduce, but actually I did.
In the program below, there is a preprocessor option (split) in the build script. Without split, this is the output
Use non-split
Using non-split constructor
Loc before attach 2564097948464 2564097964464
Loc after attach 2564097948464 2564097964464
Loc in objectRef 2564097948464 2564097964464
Loc after return 2564097948240 2564097964864
Loc in objectRef 2564097948464 0
The last 0 is where the pointer to the array in object is lost. Also the pointer to the object did not follow the address change.
With -Dsplit=1, it will return from the subroutine where the object is constructed, then construct the object reference, and this is the output
Use split
Using split constructor
Loc before attach 1736011594768 1736011611184
Loc after attach 1736011594208 1736011610544
Loc in objectRef 1736011594208 1736011610544
Loc after return 1736011594208 1736011610544
Loc in objectRef 1736011594208 1736011610544
The actual object has also changed address at some point, but the pointer is able to follow.
Here is the program:
*** compile.sh ****************
#/bin/bash
#ifort -fpp -Dsplit=1 -c object.f90 objectRef.f90 case.f90 main.f90
ifort -fpp -c object.f90 objectRef.f90 case.f90 main.f90
ifort object.obj objectRef.obj case.obj main.obj -o testPointer
*** main.f90 *********
PROGRAM testPointer
USE caseClass, ONLY : TCase
#ifdef split
USE caseClass, ONLY : makeObjectRef
#endif
IMPLICIT NONE
TYPE(TCase) :: c
#ifndef split
WRITE(*,*) "Use non-split"
#else
WRITE(*,*) "Use split"
#endif
c = TCase(1, 10)
#ifdef split
CALL makeObjectRef(c)
#endif
WRITE(*,*) "Loc after return ",LOC(c%objects), LOC(c%objects(1)%array)
WRITE(*,*) "Loc in objectRef ",LOC(c%objectRef%objPtrs(1)%ptr), LOC(c%objectRef%objPtrs(1)%ptr%array)
END PROGRAM testPointer
*** case.90 **********
MODULE caseClass
USE objectClass, ONLY : TObject
USE objectRefClass, ONLY : TObjectRef, attach
IMPLICIT NONE
PRIVATE
TYPE, PUBLIC :: TCase
TYPE(TObject), ALLOCATABLE :: objects(:)
TYPE(TObjectRef) :: objectRef
END TYPE TCase
INTERFACE TCase
MODULE PROCEDURE construct1
END INTERFACE
#ifdef split
PUBLIC makeObjectRef
#endif
CONTAINS
#ifndef split
TYPE(TCase) FUNCTION construct1(N, M) RESULT(this)
INTEGER, INTENT(in) :: N, M
INTEGER :: i
WRITE(*,*) "Using non-split constructor"
ALLOCATE( this%objects(N) )
DO i = 1, N
this%objects(i) = TObject( M )
END DO
WRITE(*,*) "Loc before attach",LOC(this%objects), LOC(this%objects(1)%array)
CALL attach( this%objectRef, this%objects )
WRITE(*,*) "Loc after attach",LOC(this%objects), LOC(this%objects(1)%array)
WRITE(*,*) "Loc in objectRef ",LOC(this%objectRef%objPtrs(1)%ptr), LOC(this%objectRef%objPtrs(1)%ptr%array)
END FUNCTION construct1
#else
TYPE(TCase) FUNCTION construct1(N, M) RESULT(this)
INTEGER, INTENT(in) :: N, M
INTEGER :: i
WRITE(*,*) "Using split constructor"
ALLOCATE( this%objects(N) )
DO i = 1, N
this%objects(i) = TObject( M )
END DO
WRITE(*,*) "Loc before attach",LOC(this%objects), LOC(this%objects(1)%array)
END FUNCTION construct1
SUBROUTINE makeObjectRef( this )
TYPE(TCase), INTENT(inout) :: this
CALL attach( this%objectRef, this%objects )
WRITE(*,*) "Loc after attach",LOC(this%objects), LOC(this%objects(1)%array)
WRITE(*,*) "Loc in objectRef ",LOC(this%objectRef%objPtrs(1)%ptr), LOC(this%objectRef%objPtrs(1)%ptr%array)
END SUBROUTINE makeObjectRef
#endif
END MODULE caseClass
*** object.f90 *************
MODULE objectClass
IMPLICIT NONE
PRIVATE
TYPE, PUBLIC :: TObject
REAL, ALLOCATABLE :: array(:)
END TYPE TObject
INTERFACE TObject
MODULE PROCEDURE construct1
END INTERFACE
CONTAINS
TYPE(TObject) FUNCTION construct1(N) RESULT(this)
INTEGER, INTENT(in) :: N
ALLOCATE( this%array(N) )
END FUNCTION construct1
END MODULE objectClass
*** objectRef.f90 ************
MODULE objectRefClass
USE objectClass, ONLY : TObject
IMPLICIT NONE
PRIVATE
TYPE objectPointer
TYPE(TObject), POINTER :: ptr
END TYPE objectPointer
TYPE, PUBLIC :: TObjectRef
TYPE(objectPointer), ALLOCATABLE :: objPtrs(:)
END TYPE
PUBLIC attach
CONTAINS
SUBROUTINE attach( this, objects )
TYPE(TobjectRef), INTENT(inout) :: this
TYPE(Tobject), ALLOCATABLE, TARGET, INTENT(in) :: objects(:)
INTEGER :: i
ALLOCATE( this%objPtrs(SIZE(objects)) )
DO i = 1, SIZE(objects)
this%objPtrs(i)%ptr => objects(i)
END DO
END SUBROUTINE attach
END MODULE objectRefClass
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@Amorin1 ,
You may want to review the Fortran standard and/or Modern Fortran Explained closely regarding the `TARGET` attribute, especially when it comes to received arguments in procedures.
In essence, you want to ensure the actual argument has the `TARGET` attribute also (e.g., object `c` in your main program) and all the subprograms carry through the attribute. This effectively requires you to eschew `FUNCTION` subprograms (e.g., the so-called constructor procedures) because the function result itself does not have such an attribute.
Your entire program "model" reduces to setting a reference to an object, like so:
module m
private
type :: t
real, allocatable :: x(:)
end type
type :: c
type(t), pointer :: p
end type
type :: r
type(c), allocatable :: l(:)
end type
type :: u
type(t), allocatable :: d(:)
type(r) :: dr
end type
public :: u, setdat
contains
subroutine setdat( a, n1, n2 )
type(u), target, intent(inout) :: a !<-- Note TARGET attribute: important
integer, intent(in) :: n1
integer, intent(in) :: n2
integer :: i
! checking elided
allocate( a%d(n1) )
do i = 1, n1
allocate( a%d(i)%x(n2) )
call random_number( a%d(i)%x )
end do
call setref( a )
end subroutine
subroutine setref( a )
type(u), target, intent(inout) :: a !<-- Note TARGET attribute: important
integer :: i
! checking elided
allocate( a%dr%l(size(a%d)) )
do i = 1, size(a%d)
a%dr%l(i)%p => a%d(i)
end do
end subroutine
end module
use m, only : u, setdat
type(u), target :: a !<-- Note TARGET attribute: important
integer :: i
call setdat( a, 2, 3 )
do i = 1, size( a%d )
print *, "a%d%x = ", a%d(i)%x
print *, "a%dr%l(i)%p%x = ", a%dr%l(i)%p%x
end do
end
But you may be able to avoid the complexity by letting go of the language advantage with components of `ALLOCATABLE` attribute and use `POINTER` instead. Yes, it requires close attention to pointer semantics and safety and but in this case, it may be simpler than all the circus with object references.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thank you for your input.
So the reason why it is working in the "split" solution could be that I am calling 'attach' inside a subroutine and not a function.
Still, if I define the function like this, I can use the TARGET attribute on the function result:
FUNCTION construct1(N, M) RESULT(this)
TYPE(TCase), TARGET :: this
INTEGER, INTENT(in) :: N, M
The compiler does not complain, but it does not fix the issue. Is the TARGET attribute ignored in this situation?
As to changing the design of the code, that may not be possible for me. The reason it is unnecessarily complex here is that it is a very small excerpt of the code, in reality the different parts of the example code are scattered around. I am implementing a new solving principle in an existing code, and sometimes have to do things that the original code design was not supposed to support.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@Amorin1 wrote:..The compiler does not complain, but it does not fix the issue. Is the TARGET attribute ignored in this situation?
As to changing the design of the code, that may not be possible for me. The reason it is unnecessarily complex here is that it is a very small excerpt of the code, in reality the different parts of the example code are scattered around. I am implementing a new solving principle in an existing code, and sometimes have to do things that the original code design was not supposed to support.
@Amorin1 ,
Note the characteristics of a function result are of little to NO relevance to those of the object itself. It is those of the object that matter.
You likely have a major problem on your hands if the code you are working on is "unnecessarily complex here" and the kind of code design you show in the original post and your follow-up post are any indication.
For, if there is a need to establish a "reference" (say with a type such as TObjectRef) to the "data" (the "stuff" in your TObject type) and your means to do so is with the kind of FUNCTION subprograms (e.g., `construct1`) and with all the "gymnastics" as shown above, you have really have NO guarantee it will work as intended.
And note the Fortran compilers will be of very limited help here because the Fortran standard does not require the processors to detect and report many of the underlying issues and therefore, most compilers do NOT do so. It is really up to the Fortran programmer(s) to take all the "right" steps in their code; an example of this is the code snippet I show upthread using SUBROUTINE subprograms and with consistent use of the TARGET attribute.
- 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
@Amorin1 wrote:
This is a little off-topic for this thread, but what is the standard way to define a class with a constructor for an object oriented design?
Unfortunately, as things stand with the Fortran standard, there really are no good options when it comes to "constructor"s - note this typically signifies FUNCTION subprograms.
About the only good option is a SUBROUTINE subprogram for, say, something like the INITIALIZATION of an object once it has come into existence i.e., when an object of an "class" has been instantiated per OO parlance. Note in Fortran
- in a given program or subprogram, a type declaration statement such as `type(TCase) c` brings the object `c` into existence when the program's scope comes into execution.
- Or, with the `ALLOCATABLE` or `POINTER` attribute of the object, once the object is allocated in any number of ways e.g., an ALLOCATE statement
Then something like `call init_tcase( c )` where the subroutine `init_tcase` does the needful toward the actual "construction" of the object is the way to go to be safe.
In the context of this thread, both the actual argument `c` and the received argument (termed questionably as dummy argument in the standard) shall have the TARGET attribute for standard-conforming behavior. However a compiler is of little to of no help if a programmer fails to apply the TARGET attribute on the actual argument and this is a MASSIVE PROBLEM in actual practice because the actual argument can be coded by any end-user programmer and who can easily OVERLOOK this crucial aspect and then encounter unexpected / inconsistent behavior with the program and end up with possibly terrible consequences.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for the answer. Does this apply to more properly designed code too (using allocatables in types, not pointers)?
I may be giving the wrong impression here, most of the code is using allocatables in types, like c%objects(:)%array in my example. I am using this pointer-based object reference because I need to go fishing for a few values in other 'TCase' instances, which were in the original design not supposed to be accessible across different 'TCase'.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@FortranFan It took its time, but I think I understand your answer now, and why it should be like that. Thanks!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
"...similar issues which have already been fixed?" You said you are using a 2017 compiler? Since that time we've practically rewritten the entire front end of the compiler.
So you have one reason to upgrade: a newer compiler will probably not exhibit this bug. Since it's impossible for you to share the actual code, only you can run this test.
Second reason: ifort is deprecated and will be removed from products next year. It is time to move to ifx. This is a great incentive to at least try the 2024.0 version of ifx.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
So I tried with ifx 2024 and the result is the same. Do you think it is a bug or is it not supposed to work according to the standard?
~/testPointer$ ./compile.sh
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.0.0 Build 20231017
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.0.0 Build 20231017
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.
Microsoft (R) Incremental Linker Version 14.16.27024.1
Copyright (C) Microsoft Corporation. All rights reserved.
-out:testPointer.exe
-subsystem:console
object.obj
objectRef.obj
case.obj
main.obj
~/testPointer$ ./testPointer.exe
Use non-split
Using non-split constructor
Loc before attach 2527781698000 2527781683072
Loc after attach 2527781698000 2527781683072
Loc in objectRef 2527781698000 2527781683072
Loc after return 2527781699232 2527781683552
Loc in objectRef 2527781698000 0
I know we should upgrade anyway but this is competing with other priorities...
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Can you please attach the current reproducer? There was some discussion of changes.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It is still the same as in my post from the 11-24-2023 01:08 AM. I tried with ifx v2024 and it still fails. I tried to add the TARGET attribute at different places, but it did not make any difference. It was argued above that, for a pointer that should survive after return, a more robust way of doing pointer association is to add the POINTER attribute to both the pointer and the object to be pointed at. However I can't do that since my pointers and objects are contained in types. I can't give an POINTER attribute to specific elements of the type, I am passing the whole type to the subroutine.
In the reproducer, there is a preprocessor variable to alternate between 2 ways of attaching the object reference. The "non-split" fails and the "split" works. The difference is that in the split version, it returns from the constructor before calling the subroutine that associates the pointer, while in the non-split it calls everything in the constructor.
My question is: is the reproducer supposed to work also with the pointer association inside the constructor ("non-split"), or is my way of doing it not supposed to be supported?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
After some analysis, my colleague believes this is a compiler bug. I filed CMPLRLLVM-54174 on your behalf.
Thanks for submitting this and for a workaround! The workaround helps both of us.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Ok, thanks for your help! I will be waiting for the fix.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi @Amorin1
sorry for the delay. After long internal discussion we came to the point that this is not supposed to work.
In 15.6.2.2 of the F2023 standard, there is a note:
The function result is similar to any other entity (variable or procedure pointer) local to a function subprogram.
Its existence begins when execution of the function is initiated and ends when execution of the function is
terminated. However, because the final value of this entity is used subsequently in the evaluation of the
expression that invoked the function, an implementation might defer releasing the storage occupied by that
entity until after its value has been used in expression evaluation.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
Thanks for the update.
So this note seems to apply only to function results. I thought
a=func(b)
and
CALL subr(a,b)
were exactly the same. But if 'a' is an instance of a derived type, obviously (in hindsight), the 'func' syntax has to handle allocation of 'a', while the 'subr' syntax will not. What is the expected behaviour here? Does the 'func' syntax check whether 'a' is allocated, and have a different behaviour if it is or not? Or is it always allocating a new 'a' and deleting the old one?
Also is there is a difference in where it ends up between the two syntaxes (heap/stack)?
Anyway, I could make my reproducer work by making all objects ALLOCATABLE, and then instead of a constructor being a FUNCTION, I make it a SUBROUTINE, which takes 'this' as an INOUT dummy parameter instead of a function result. Then I have to change the construction of the objects from
TYPE(TObject) :: object
...
! 'func' syntax, does not work
object = TObject(...initialisation parameters...)
to
TYPE(TObject), ALLOCATABLE :: object
...
! 'subr' syntax, works
ALLOCATE(object)
CALL TObject(object, ...initialisation parameters...)
This also applies to the object 'c' of type TCase in the reproducer.
The next question, in the case of nested derived types, is: when I construct/initialise c as
ALLOCATE(c)
CALL TCase(c, 1, 10)
then in 'c', c%objects(:) is allocated while calling 'TCase'. Is c%objects garanteed to persist when returning from 'TCase' to the main program?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
So I came upon an answer in an unrelated discussion on https://stackoverflow.com/questions/42817307/proper-way-to-copy-a-complex-derived-type-in-fortran
I quote the relevant comment so other interested readers get the answer:
intent(out) and a function result are not the same. Especially here. With a function you don't have any access to the left hand side. The function result is not!!! the left hand side variable. First, a temporary object is created for the function result and that one is then assigned to the left hand side. And during the assignment the pointer on the left hand side gets overwritten.
So I think my issue is caused by the fact that pointers are not properly handled when copying the temporary object (which is created to contain the function result) into the left hand side variable. And it is allowed by the standard not to handle it properly due to the note in 15.6.2.2 of the F2023 standard (but the NAG Fortran compiler seems to handle it anyway). When using a subroutine with an intent([in]out), the variable of the calling routine itself is sent to the subroutine, there is no temporary object and hence no copying to handle.
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page