- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
This is a continuation of the discussion in Issue with pointer to object constructed in same subroutine. It is now clear to me that one should never use functions to construct derived type.
But when experimenting with the Intel compiler, I saw that Intel lets me overload the "constructor" with a subroutine, that is, define an interface with the same name as the type:
MODULE caseClass
USE objectClass, ONLY : TObject
IMPLICIT NONE
PRIVATE
TYPE, PUBLIC :: TCase
TYPE(TObject), ALLOCATABLE :: objects(:)
END TYPE TCase
INTERFACE TCase
MODULE PROCEDURE construct1
END INTERFACE
CONTAINS
SUBROUTINE construct1(this, N, M)
CLASS(TCase), TARGET, INTENT(inout) :: this
INTEGER, INTENT(in) :: N, M
...
END SUBROUTINE construct1
END MODULE caseClass
Another compiler, which is strictly standard-complying, complains that it is not allowed to overload a derived type name with a subroutine. Is this an Intel extension? What is the exact behaviour when calling this:
CALL TCase(c, 1, 10)
Fortran 2003/2008 was supposed to make Fortran suitable for object-oriented design, but I see there are non-intuitive aspects that are quite dangerous. It seems constructing an object with a constructor-overload (using a function) is not supposed to work, or at least the standard does not garantee that it should work. Is there somewhere a best practice to make standard-complying object-oriented design in Fortran in a safe manner?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The quoted snippet is talking about implementation options for a Fortran processor (the snippet appears in a note - not in normative text).
In terms of language semantics, things are quite clear - pointers that reference the function result (or any other unsaved local variable) become undefined when execution of the function is terminated. But the value of the function result can still be used after the function terminates (15.5.3) - getting a value is, in most ways, the whole point of functions. For the definition of the value of an object of derived type - see 7.5.8.
So the result of calling the "construct1" function in module caseClass in the other thread is a value that ultimately contains lots of arrays of real (the values of those arrays has not been specified - which is a different problem), and lots of undefined pointer association status. If you then use that value on the right hand side of an intrinsic assignment, then that value is copied to the variable on the left of the assignment - i.e. the value is preserved, but you are perhaps preserving something that isn't very useful.
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The language permits that, within a scoping unit, a generic name for a function can be the same as the name of a type (F2023 15.4.3.4.1p4). If so, the function "overloads" the structure constructor for the type. This has been part of the language since Fortran 2003 - as much as any language feature described by the standard it is guaranteed to work, compiler bugs aside.
In a scoping unit, the standard prohibits having a generic name for a subroutine be the same as the name of a type (F2023 19.3.1p3 - both generic names and non-intrinsic type names are class (1) local identifiers, and the 7.5.10 exception is a rather obtuse way of referencing for the function overloading constructor feature in the first paragraph). Compilers are required to diagnose violations of the scoping rules in clause 19 (F2023 4.2p2 (6)) - failure to diagnose this when standard conformance is requested is a compiler bug.
You can quite happily use functions as object constructors! For objects that are intended to be used in expressions (they behave like values, they are not huge) that is the idiomatic way.
The issues in the other thread relate more to understanding of the events that cause undefined pointer association status and the semantics of intrinsic assignment, rather than functions as constructors.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for the precise references to the standard.
Concerning functions as constructor, what makes me unsure is the answer from TobiasK in the thread I linked: 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.
Independently of whether the result is stored into a variable with '=' or pointed at with '=>', there is nothing saying that this newly allocated function result will survive for the remainder of the program execution. So if my program is
- Construct and initialise case structure (the whole arborescence of objects), then return to main program
- Then run the case
I am not sure it garantees that everything that is allocated during construct will survive when running the case. Of course it makes sense that it should mostly work, but could there be some marginal effects that are not handled, like when memory is reorganised/garbage collected? (amongst them, the pointer issue discussed in the other thread).
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The quoted snippet is talking about implementation options for a Fortran processor (the snippet appears in a note - not in normative text).
In terms of language semantics, things are quite clear - pointers that reference the function result (or any other unsaved local variable) become undefined when execution of the function is terminated. But the value of the function result can still be used after the function terminates (15.5.3) - getting a value is, in most ways, the whole point of functions. For the definition of the value of an object of derived type - see 7.5.8.
So the result of calling the "construct1" function in module caseClass in the other thread is a value that ultimately contains lots of arrays of real (the values of those arrays has not been specified - which is a different problem), and lots of undefined pointer association status. If you then use that value on the right hand side of an intrinsic assignment, then that value is copied to the variable on the left of the assignment - i.e. the value is preserved, but you are perhaps preserving something that isn't very useful.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Ok, I understand now. I see the difference between pointing to the temporary function result, and copying the result into a (more) permanent variable with a '='. So a function involves an extra allocation and copying compared to a subroutine, that is good to know.
By the way, if pointing to function result is not supposed to work, I think it should not be allowed to do it. It should return an error, at least a warning.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The complication is that there are valid reasons to point at function results, so long as the pointer doesn't escape the scoping unit of the function. Things like:
function f(...)
integer, target :: f
integer, target :: not_f
integer, pointer :: p
if (some_condition) then
p => f
else
p => not_f
end if
! stuff with p, because you don't want `if (some_condition)` everywhere
...
f = 0
end function f
What would be good is for the compiler associated memory analysis tools that pick up things like dangling pointers to detect this stuff (like they should for an escaped reference to any local variable). Perhaps they do - haven't checked.
(Yes - there may be additional copying associated with object values being spat out of functions - but this depends somewhat on compiler optimisation capability. This is the reason for the "not huge" criteria in my first reply.)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The example violates this rule in the standard (emphasis mine): "A generic name may be the same as a derived-type name, in which case all of the procedures in the generic interface shall be functions." (F2023 15.4.3.4.1p4 Generic Identifiers). The compiler should give an error for this - I doubt it is intended as an extension, especially as there's no obvious meaning for it.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I may have sinned here... This is with an old compiler version (not me who decides, but we are in the process of upgrading), so it could be that this is fixed in a newer version.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
So I checked with ifx 2024, and it still does not complain about the "constructor" being a subroutine. Here is the code:
PROGRAM testPointer
USE caseClass, ONLY : TCase
IMPLICIT NONE
TYPE(TCase) :: c
CALL TCase(c, 10)
END PROGRAM testPointer
!***************************************************
MODULE caseClass
IMPLICIT NONE
PRIVATE
TYPE, PUBLIC :: TCase
REAL, ALLOCATABLE :: var(:)
END TYPE TCase
INTERFACE TCase
MODULE PROCEDURE construct1
END INTERFACE
CONTAINS
SUBROUTINE construct1(this, N)
CLASS(TCase), INTENT(inout) :: this
INTEGER, INTENT(in ) :: N
WRITE(*,*) "Constructor called"
ALLOCATE( this%var(N) )
END SUBROUTINE construct1
END MODULE caseClass
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Yes, I tested this before I wrote earlier that the compiler is wrong in not complaining about this. I see that Devorah liked my response, so perhaps she escalated this to the development team.

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