https://gcc.gnu.org/bugzilla/show_bug.cgi?id=119889

anlauf at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |anlauf at gcc dot gnu.org

--- Comment #4 from anlauf at gcc dot gnu.org ---
It fails for all gfortran versions since at least 7.

NAG says:

Panic: pr119889.f90, line 59: Impossible no interface
Internal Error -- please report this bug

This might give a hint where to look.

Interestingly, replacing

    procedure(dlsym), pointer :: tmp_fun

by

    procedure(), pointer      :: tmp_fun

lets the code compile.  And comparing the fortran-dump:

Failing:

    symtree: 'tmp_fun'     || symbol: 'tmp_fun'      
      type spec : (UNKNOWN 0)
      attributes: (PROCEDURE  EXTERNAL FUNCTION ARRAY-OUTER-DEPENDENCY
ALWAYS-EXPLICIT PROC-POINTER UNTYPED IFSRC-IFBODY)
      result: tmp_fun

Workaround:

    symtree: 'tmp_fun'     || symbol: 'tmp_fun'      
      type spec : (UNKNOWN 0)
      attributes: (PROCEDURE  EXTERNAL SUBROUTINE ARRAY-OUTER-DEPENDENCY
PROC-POINTER)



Playing around, I arrive at the following reduced testcase:

module ol_dlfcn
  use, intrinsic :: iso_c_binding, only: c_ptr, c_null_ptr
  implicit none

  type process_handle
    type(c_ptr) :: library_handle = c_null_ptr
  end type process_handle

contains

  function dlsym() result(f_funp)
    procedure(), pointer :: f_funp
    f_funp => null()
  end function dlsym

  function get_process_handle()
    type(process_handle) :: get_process_handle
    procedure(dlsym), pointer :: tmp_fun   ! -> ICE
!   procedure(), pointer      :: tmp_fun   ! -> no ICE
    ! number of external particles
    !!! Triggers the ICE
    tmp_fun => dlsym()
  end function get_process_handle

end module ol_dlfcn


This gives the same failures with NAG, Intel, and gfortran.

We need to check if the code is standard conforming.

Reply via email to