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…