Ifort bug for overloaded type constructor?

Here is MWE where a derived type constructor sometype is overloaded by a function newsometype()

module somemodule
implicit none

type sometype
	integer :: n
	real, pointer :: p(:)
end type
! overloading the constructor
interface sometype
	module procedure newsometype
end interface

contains

type(sometype) function newsometype(a) result(x)
real, pointer, intent(in) :: a(:)
x%p => a(:)
x%n = size(x%p)
end function

end module


program someprogram
use somemodule
implicit none

real, target :: a(1000)
type(sometype), allocatable :: x

a(:) = 1.0
x = sometype(a)

write(*,*) loc(a(1)), loc(x%p(1)), x%n, x%p(1)

end program

gfortran compiles it, and it runs as expected. With ifort (19) however I get a compilation error:

typeinit.f90(33): error #8212: Omitted field is not initialized. Field initialization missing:   [P]
x = sometype(a)
-------------^
compilation aborted for typeinit.f90 (code 1)

It looks like ifort does not recognize that newsometype() matches the call, and fall back to the default constructor. However, if I replace the call by the true function name (hence not using the overload) it compiles and run:

! x = sometype(a)
x = newsometype(a)    ! with this one it's ok

Also, if I change the dummy argument, being a target instead of a pointer, it also compiles and run:

! real, pointer, intent(in) :: a(:)
real, target, intent(in) :: a(:)    ! with this one it's ok

Similarly, if I use an intermediate pointer to pass to the contructor, it compiles and run:

real, pointer :: b(:)
b => a(:)
! x = sometype(a)
x = sometype(b)   ! with this one it's ok

So, it looks like ifort has trouble passing a non pointer actual argument to a pointer dummy argument in an overloaded constructor…

Is it a bug in ifort (I think so), or is gfortran too permissive here? I’ve just learnt today that non pointer actual arguments could be passed to pointer dummy arguments, so maybe I’m missing something…

Encountered the same error recently with ifort in someone else’s code. There is no excuse in any compiler for these kinds of regressions. The standard has allowed this from day one if I remember correctly. You should report it to Intel. I normally add an _ (ie sometype_) to user defined constructors to distinguish them from the intrinsic ones to avoid confusion between the two anyway so I don’t see this in my own codes.

Try replacing

interface sometype

with

interface sometype_

@rwmsu Appending an underscore doesn’t solve the problem

interface sometype_
...
x = sometype_(a)

typeinit.f90(35): error #6284: There is no matching specific function for this generic function reference.   [SOMETYPE_]
x = sometype_(a)
----^
compilation aborted for typeinit.f90 (code 1)

So it’s not even linked to the fact this is a constructor, it’s a more general issue in generic interfaces.

Try Intel oneAPI 2023.0, their current version.

In Intel’s defense, they appear to have gone through extensive changes with IFX achieving parity with IFORT with a common front-end whilst achieving full Fortran 2018 compliance, both major achievements really. And there also appear considerable rehaul of some standard features in IFORT over the last few years in light of Interps and improved understanding and appreciation of standard semantics and user feedback with tons of code submissions. Thus with Intel there is a good business case to keep up with the latest even as some ICE regressions surface every now and then which they seem to address quickly.

@PierU

Is the constructor code in a submodule. Just remembered that the program I had problems with had the constructor routine in a submodule. I had to move it out of the submodule back into the main moduel to get it to work.

I don’t have access to a more recent ifort version than 19, so I can’t check if the bug has corrected or not since then…

Nope (the MWE above has no submodule)

It is available for “free” download:
https://www.intel.com/content/www/us/en/developer/articles/release-notes/fortran-compiler-release-notes.html

Yeah, but I am using ifort at work, where I can’t install what I want, and my main computer at home has macOS 10.13, which is not supported by the Intel 2023 installer.

There is godbolt.org where one can try out such code snippets online with certain newer vintage compilers.

1 Like

OK… So in godbolt I can see that the bug has been corrected and that the code compiles successfully starting with ifort 2021.7.0 or ifx 2022.2.0

1 Like