2

I am a little puzzled with the PGI Fortran compiler.

When I try to compiler the following simple module stored in the file named test.f90, with pgfortran 19.10 I get errors that I do not understand. While compiling with gfortran or ifort run well.

The file test.f90:

MODULE CT
    IMPLICIT NONE
    integer, parameter :: si   = SELECTED_INT_KIND(4)
    integer(kind=si), public, parameter :: strlen   = 256


    type, public :: CMT
       integer (kind=si) :: nbTot 
       character(len=strlen), dimension(:), allocatable  :: condi 
    CONTAINS
       procedure :: find_line_condi 
    endtype CMT


 CONTAINS
    PURE function find_line_condi( table, cara ) result(k)
       IMPLICIT NONE
       class(CMT), intent(in)    :: table
       character(len=*), intent(in)  :: cara
       integer  (kind=si)   :: k
       integer  (kind=si)   :: j

       k=-1
       do j=1,table%nbTot
          if (trim(table%condi(j)) .eq. cara)  then
             k=j
             RETURN
          else if ( j == table%nbTot ) then
             k=-1
             RETURN
          endif
       enddo
    end function find_line_condi

END MODULE CT

The compilation with pgfortran -c test.f90 returns me the following error message:

/opt/pgi/linux86-64-llvm/19.10/share/llvm/bin/llc: error: /opt/pgi/linux86-64-llvm/19.10/share/llvm/bin/llc: /tmp/pgfortranr2qeZBujkwvA.ll:23:77: error: invalid forward reference to function 'ct_find_line_condi_' with wrong type: expected 'i32 (i64*, i64*, i64*, i64)*' but was 'i16 (i64*, i64*, i64*, i64)*'
@ct$cmt$td$vft = global [1 x i8*] [i8* bitcast(i16 (i64*, i64*, i64*, i64)* @ct_find_line_condi_ to i8*)]

Does anyone has some ideas where this problem comes from?

francescalus
  • 30,576
  • 16
  • 61
  • 96
R. N
  • 707
  • 11
  • 31
  • 2
    That's the sort of error message from a compiler which, even if you have terrible Fortran code, is so incomprehensible as a diagnostic message to be worth a bug report to the vendor. If you have a support agreement with PGI please report to them. – francescalus Dec 11 '19 at 22:37
  • 1
    `SELECTED_INT_KIND(4)` do you really want half-precision integer? I suspect that error has something to do with this... Try using `si = INT32` from `iso_fortran_env` intrinsic module and see if it compiles. – jcerar Dec 11 '19 at 23:13
  • @jcerar yes I need it. But you are right using iso_fortran_env int32 is a way to avoid the problem. – R. N Dec 12 '19 at 09:25

1 Answers1

4

This is a bug in the compiler. Consider the module

MODULE CT
    IMPLICIT NONE

    type CMT
    CONTAINS
      procedure, nopass :: find_line_condi 
    endtype CMT

 CONTAINS
    function find_line_condi()
       integer(SELECTED_INT_KIND(4)) find_line_condi
       find_line_condi=0
    end function find_line_condi

END MODULE CT

which is quite a bit simpler than that of that question. Compiled with pgfortran 19.10 there is a similar gibberish output. It's left as an exercise to the reader/PGI support desk whether this simpler code is valid Fortran which should be accepted but I would consider the poor diagnostic to be something PGI would prefer to avoid.

However, this appears to be a weakness in the LLVM frontend of PGI: consider compiling with pgfortran -c -Mnollvm .... There are also ways to rewrite the code to attempt to work around this bug, such as changing the kind of the function result.


More widely, PGI introduced in the 2019 releases the LLVM code generator. This seems to be going through a number of teething difficulties. If you have code unexpectedly failing with PGI 2019 (which may have worked with 2018), then compiling with -Mnollvm to use the non-LLVM generator is worth a try.

francescalus
  • 30,576
  • 16
  • 61
  • 96
  • according to your comment, I will create an account and report this problem. Otherwise, the option `-Mnollvm` solves the problem, but since the LLVM seems to become their new standard (and might be the only option in the future) it worth mention them the situation. – R. N Dec 12 '19 at 09:30
  • 1
    Thanks: as a very active user of Fortran compilers I encourage people to report bugs. Even if you have a workaround other people benefit from better compilers. – francescalus Dec 12 '19 at 10:00
  • 1
    It is done, and I completely agree about this community behaviour. – R. N Dec 12 '19 at 10:06