Fortran derived type (mostly structure constructor) bugs

Here are some bugs I’ve seen recently in PGI 14.1. I’m not sure if these are all still in 14.3, since I don’t have an updated installation handy. Several of these test cases also break with ifort, so I have open bugs with Intel as well, but they still work with the NAG compiler and gfortran.

The bugs are all apparent by compiling these cases with no flags, or with no flags except “-c” for those that have no main program.

  1. There’s an ICE when compiling the following simple (but invalid) Fortran module. The module is invalid because either do_nothing should accept a class(foo) argument, or the “nopass” attribute should be present on its binding. But the compiler segfaults instead of reporting a useful error.
module test_types

type :: foo
 contains
   procedure :: do_nothing
end type foo

contains

  subroutine do_nothing()
  end subroutine do_nothing

end module test_types
  1. PGI has some problem with structure constructors for types that extend types with bound procedures. In short, it rejects the following valid code:
module test_types

implicit none

type :: foo
 contains
   procedure :: do_nothing
end type foo

type, extends(foo) :: bar
   integer :: a
end type bar

contains

  subroutine do_nothing(self)
    class(foo) :: self
  end subroutine do_nothing

end module test_types

program test_pgi_construct

use test_types

implicit none

type(bar) :: x

x = bar(1)

print *, x%a

end program test_pgi_construct
  1. PGI 14.1 also gives a spurious warning in the following case, though the compiled code appears to work correctly:
program test_section_constructor

implicit none
 
type, abstract :: foo_base
end type foo_base

type, extends(foo_base) :: foo
   integer, allocatable :: a(:)
end type foo

type(foo) :: b

integer :: a1(2) = 0
integer :: a2(2,2) = 0

b = foo(a1)      ! OK
b = foo(a2(:,1)) ! Spurious warning

end program test_section_constructor
  1. Using a structure constructor for a type with a procedure pointer gives a spurious warning, but more importantly, calling the function bound to that pointer produces an ICE.
module int_getter

implicit none

contains

  integer function foo_int()
    foo_int = 0
  end function foo_int

end module int_getter

program test_function_constructor

use int_getter, only: foo_int

implicit none

abstract interface
   integer function get_int()
   end function get_int
end interface

type :: foo
   procedure(get_int), nopass, pointer :: get => null()
end type foo

type(foo) :: bar

bar = foo(foo_int) ! This gives a warning, but shouldn't.
bar%get => foo_int ! No warning (this is my current workaround for Intel)

print *, bar%get() ! Internal compiler error

end program test_function_constructor
  1. This is similar code to case (4), but it has a different problem; the apparently valid structure constructor is rejected outright. I think this is just an unimplemented feature?
module int_getter

implicit none

contains

  subroutine foo_int(a)
    integer, intent(out) :: a
    a = 0
  end subroutine foo_int

end module int_getter

program test_function_constructor

use int_getter, only: foo_int

implicit none

abstract interface
   subroutine get_int(a)
     integer, intent(out) :: a
   end subroutine get_int
end interface

type :: foo
   procedure(get_int), nopass, pointer :: get => null()
end type foo

type(foo) :: bar
integer :: x

! This line is valid code, but is rejected.
bar = foo(foo_int)
bar%get => foo_int

call bar%get(x)

print *, x

end program test_function_constructor

The ICE in (4) goes away if you remove the default initialization (=> null()) in the type definition.

But here’s one more I found when testing workarounds for that one.

  1. Abstract interfaces defined before a type that they import cause an internal compiler error. NAG rejects this code as invalid unless the interface and type definition are traded, and this also fixes the PGI ICE.
module int_getter

implicit none

abstract interface
   integer function get_int(self)
     import :: foo
     class(foo) :: self
   end function get_int
end interface

type :: foo
   procedure(get_int), pointer :: get
end type foo

end module int_getter

Apparently, this is my day to find bugs.

  1. “Select type” seems to treat types beginning with the word “Record” specially:
program pgi_record

  type :: Recorder
     integer :: a
  end type Recorder

  class(Recorder), allocatable :: foo

  allocate(foo, source=Recorder(1))

  select type (foo)
  type is (Recorder)
     print *, "Hi!"
  end select

end program pgi_record

This yields the message:

PGF90-S-0034-Syntax error at or near RECORD (pgi_record.F90: 12)
  0 inform,   0 warnings,   1 severes, 0 fatal for pgi_record

Another couple:

  1. A generic binding to an abstract type, where the only specific binding it includes is deferred, can be erroneously rejected if there is no “contains” inside the module:
module int_getter

implicit none

type, abstract :: foo
 contains
   procedure(get_int), deferred :: get
   generic :: generic_get => get
end type foo

abstract interface
   integer function get_int(self)
     import :: foo
     class(foo) :: self
   end function get_int
end interface

! Uncommenting this makes the error go away.
!contains

end module int_getter
  1. A recursive type (or a type which has a component of an ancestor class) can have issues with actions like allocating a component, or forwarding functions, if “save” is specified in the module where the type is defined.

Edit: This is on Linux on x86-64.

module foo_bar_types

implicit none

! Commenting this save gets rid of the linking error.
save

! This type doesn't have to be recursive. The same problem arises if the
! "child_foo" component is of a type that foo extends.
type :: foo
   class(foo), pointer :: child_foo
 contains
   procedure :: bar
end type foo

contains

recursive subroutine bar(self)
  class(foo) :: self

  call self%child_foo%bar()

end subroutine bar

end module foo_bar_types


program do_nothing

end program do_nothing

Hi Sean,

Thanks for all the reports. I am working to reproduce all of these here, and I will file reports on them. This is a big help for us - we really appreciate your feedback.

Best regards,

+chris

One other note: case #6 has been fixed as of 14.3, and PGI no longer produces an ICE. Now you get an error message:

cparrott@galaxy ~/UF $ pgf90 -c int_getter.f90
PGF90-S-0155-Cannot IMPORT foo (int_getter.f90: 7)
PGF90-S-0155-Derived type has not been declared - foo (int_getter.f90: 8)
0 inform, 0 warnings, 2 severes, 0 fatal for int_getter

Best regards,

+chris

Ah, thanks for the information.

TPR 20212 - linking error when recursive type specified in a module that uses “save”

Has been fixed in the current 14.6 release.

Thanks,
dave

TPR 20211 - “Generic binding to an abstract type erroneously rejected if there is no 'contains” inside’ the module" has been corrected in the 14.6 release.


Thanks,
dave

TPR 20207 - Apparently valid structure constructor is rejected outright by pgfortran
is fixed in the current 14.6 release.

Thnaks for your submission.

regards,
dave

TPR 20203 - “Potentially valid structure constructor rejected by pgfortran”

has been fixed in the current 14.6 release.

thanks,
dave

TPR 20202 - “Improper module triggers segfault in compiler instead of error message” has been fixed in the current 14.6 release.

Thanks for the original report.

dave

TPR 20567 - UF: F2003 code with abstract interface causes segv
which is one of several TPRs associated with this UF entry, has been fixed in the 14.7 release.

thanks,
dave