https://gcc.gnu.org/bugzilla/show_bug.cgi?id=122644
Bug ID: 122644
Summary: gfortran incorrectly treats parameterized derived
types extending abstract types as abstract
Product: gcc
Version: 15.2.0
Status: UNCONFIRMED
Severity: normal
Priority: P3
Component: fortran
Assignee: unassigned at gcc dot gnu.org
Reporter: maxkadat at gmail dot com
Target Milestone: ---
When a parameterized derived type (PDT) extends an abstract type and implements
all deferred procedures, gfortran incorrectly flags CLASS(generic_type(*)) as
abstract in procedure implementations.
The type generic_type(lenParam) is concrete because it provides implementations
for all deferred procedures from its abstract parent abstract_base. However,
gfortran treats CLASS(generic_type(*)) as abstract, causing compilation errors.
This code compiles successfully with Intel Fortran Compiler (IFX), indicating
that gfortran's behavior is incorrect according to the Fortran standard.
Compilation fails with:
test_pdt_abstract_bug.f90:38:26:
38 | CLASS(generic_type(*)), INTENT(INOUT) :: self
| 1
Error: 'abstract_base' at (1) is of the ABSTRACT type 'abstract_base'
! Minimal example to reproduce gfortran bug with parameterized derived types
! extending abstract types
!
! This demonstrates the bug where gfortran incorrectly flags
! CLASS(generic_type(*)) as abstract even though generic_type is concrete
MODULE test_module
IMPLICIT NONE
! Abstract base type
TYPE, ABSTRACT :: abstract_base
CONTAINS
PROCEDURE(init_interface), DEFERRED :: init
END TYPE abstract_base
! Abstract interface for deferred procedure
ABSTRACT INTERFACE
SUBROUTINE init_interface(self, n)
IMPORT :: abstract_base
CLASS(abstract_base), INTENT(INOUT) :: self
INTEGER, INTENT(IN) :: n
END SUBROUTINE init_interface
END INTERFACE
! Parameterized derived type extending abstract type
TYPE, EXTENDS(abstract_base) :: generic_type(lenParam)
INTEGER, LEN :: lenParam
INTEGER, ALLOCATABLE :: data(:)
CONTAINS
PROCEDURE :: init => init_impl
END TYPE generic_type
CONTAINS
! Implementation of the deferred procedure
! This is where gfortran incorrectly flags the error
SUBROUTINE init_impl(self, n)
CLASS(generic_type(*)), INTENT(INOUT) :: self ! <-- BUG: gfortran says
this is abstract
INTEGER, INTENT(IN) :: n
IF (ALLOCATED(self%data)) DEALLOCATE(self%data)
ALLOCATE(self%data(n))
self%data = 0
END SUBROUTINE init_impl
END MODULE test_module
PROGRAM test_program
USE test_module
IMPLICIT NONE
CLASS(abstract_base), ALLOCATABLE :: obj
TYPE(generic_type(10)) :: temp
! Create instance of concrete type
ALLOCATE(obj, SOURCE=temp)
CALL obj%init(5)
PRINT *, "Test completed successfully!"
END PROGRAM test_program