I am testing the PGI Fortran 19.10 compiler.
And I get a segmentation fault
after compilation with PGI when I run the file named test.f90
; while when I compile and run with gfortran or ifort I get no problem.
the filetest.f90
:
MODULE modu
IMPLICIT NONE
! Format
type, abstract :: FormatFile
contains
procedure(File_open_file),nopass, deferred :: open_files
end type FormatFile
type, extends(FormatFile) :: FormatA
contains
procedure, nopass :: open_files => open_fileA
end type FormatA
! Type
type, abstract :: TypeFile
class(FormatFile), allocatable :: format
end type TypeFile
type, extends(TypeFile) :: TypeB
end type TypeB
! FileHandler
type, public :: FileHandler
private
class(TypeFile), allocatable :: type
contains
procedure, pass(fd), public :: open_file
end type FileHandler
abstract interface
subroutine File_open_file( fd )
import FileHandler
class(FileHandler), intent(inout) :: fd
end subroutine
end interface
CONTAINS
subroutine write_output()
IMPLICIT NONE
type(FileHandler) :: FileH
!-------------------------------------------------------------------------
print*, 'write_output: start.'
allocate(TypeB :: FileH%type)
allocate( FormatA :: FileH%type%format)
call FileH%open_file()
print*, 'write_output: end.'
end subroutine write_output
subroutine open_file( fd )
implicit none
class(FileHandler), intent(inout) :: fd
!-------------------------------------------------------------------------
print *, 'open_file: start'
call fd%type%format%open_files(fd)
print *, 'open_file: end'
end subroutine open_file
subroutine open_fileA( fd )
implicit none
class(FileHandler), intent(inout) :: fd
!-------------------------------------------------------------------------
print *, 'open_fileA: start'
!print*, 'job done'
print *, 'open_fileA: end'
end subroutine open_fileA
end module modu
PROGRAM main_prog
USE modu
print*, "Start main"
call write_output()
print*, "End main"
END PROGRAM main_prog
Therefore the command pgfortran -c test.f90 && pgfortran -o main_test test.o && ./main_test
returns me:
Start main
write_output: start.
open_file: start
Segmentation fault (core dumped)
While it run as expected with gfortran or ifort. Otherwise I also tested this code with the option -Mnollvm
of the PGI compiler, and it yields the same segmentation fault.
Of course in this simple example I could remove the intermediate object TypeFile
, which remove the segmentation fault problem ; but I really need it in some bigger project.
So am I missing something ? or is it a bug of the PGI compiler ?