Fortran: Error: Type mismatch between actual argument at (1) and actual argument at (2) (INTEGER(8)/INTEGER(2))

I am a beginner of Fortran and running a model written by Fortran. When I tried to compile it, I got an error message like:

libtool: link: (cd ".libs" && rm -f "libgrib_api_f77.so" && ln -s "libgrib_api_f77.so.1.0.0" "libgrib_api_f77.so")
libtool: link: ar cru .libs/libgrib_api_f77.a  grib_fortran.o grib_f77.o
libtool: link: ranlib .libs/libgrib_api_f77.a
libtool: link: ( cd ".libs" && rm -f "libgrib_api_f77.la" && ln -s "../libgrib_api_f77.la" "libgrib_api_f77.la" )
gfortran   -c -o same_int_long.o same_int_long.f90
same_int_long.f90:23:18:
 
   17 |   call check_long(x2(1),x2(2),ret)
      |                  2
......
   23 |   call check_long(x4(1),x4(2),ret)
      |                  1
Error: Type mismatch between actual argument at (1) and actual argument at (2) (INTEGER(4)/INTEGER(2)).
same_int_long.f90:29:18:
 
   17 |   call check_long(x2(1),x2(2),ret)
      |                  2
......
   29 |   call check_long(x8(1),x8(2),ret)
      |                  1
Error: Type mismatch between actual argument at (1) and actual argument at (2) (INTEGER(8)/INTEGER(2)).
same_int_long.f90:51:17:
 
   45 |   call check_int(x2(1),x2(2),ret)
      |                 2
......
   51 |   call check_int(x4(1),x4(2),ret)
      |                 1
Error: Type mismatch between actual argument at (1) and actual argument at (2) (INTEGER(4)/INTEGER(2)).
same_int_long.f90:57:17:
 
   45 |   call check_int(x2(1),x2(2),ret)
      |                 2
......
   57 |   call check_int(x8(1),x8(2),ret)
      |                 1
Error: Type mismatch between actual argument at (1) and actual argument at (2) (INTEGER(8)/INTEGER(2)).
make[2]: *** [Makefile:546: same_int_long.o] Error 1
make[2]: Leaving directory '/gpfs/home3/eccei339/snellius_surfex/open_SURFEX_V8_1/src/LIB/grib_api-1.17.0-Source/fortran'
make[1]: *** [Makefile:604: all-recursive] Error 1
make[1]: Leaving directory '/gpfs/home3/eccei339/snellius_surfex/open_SURFEX_V8_1/src/LIB/grib_api-1.17.0-Source'
make: *** [Makefile:398: /home/eccei339/snellius_surfex/open_SURFEX_V8_1/src/LIB/grib_api-1.17.0-Source-LXgfortran/include/grib_api.mod] Error 2

What I did is basically following the installation of the model:

Step1

(base) [eccei339@int3 ~]$ mkdir snellius_surfex
(base) [eccei339@int3 ~]$ cp open_surfex_v8_1_20200107.tar-2.gz snellius_surfex/
(base) [eccei339@int3 ~]$ cd snellius_surfex/
(base) [eccei339@int3 snellius_surfex]$ tar zxvf open_surfex_v8_1_20200107.tar-2.gz

ā€¦(omit the tar zxvf logging information)

Step 2: some essential env variable

(base) [eccei339@int3 snellius_surfex]$ export VER_MPI="NOMPI"
(base) [eccei339@int3 snellius_surfex]$ export OMP_NUM_THREADS=1
(base) [eccei339@int3 snellius_surfex]$ module load 2021
(base) [eccei339@int3 snellius_surfex]$ module load GCC/10.3.0
(base) [eccei339@int3 snellius_surfex]$ ls
open_SURFEX_V8_1  open_surfex_v8_1_20200107.tar-2.gz

(here I exported some necessary envi var following the instructions of installation of the software)

Step 3: configure

(base) [eccei339@int3 snellius_surfex]$ cd open_SURFEX_V8_1/src/
(base) [eccei339@int3 src]$ ls
ASSIM      Makefile            Rules.bullXI15.mk    Rules.MCgfortran.mk  SURFEX
configure  Makefile.SURFEX.mk  Rules.bullXI16.mk    Rules.SX8.mk
FORC       OFFLIN              Rules.LXgfortran.mk  Rules.zgfortran.mk
include    Rules.AIX64.mk      Rules.LXifort.mk     Rules.zifort.mk
LIB        Rules.bgfortran.mk  Rules.LXpgi.mk       scripts
(base) [eccei339@int3 src]$ ./configure

(omit the long logging info of the ā€œconfigureā€ command)

(base) [eccei339@int3 src]$ . ../conf/profile_surfex-LXgfortran-SFX-V8-1-1-NOMPI-OMP-O2-X0

(an essential step following the instructions of installation of the software)

Step 4: make the master

(base) [eccei339@int3 src]$ make
find: ā€˜/home/eccei339/snellius_surfex/open_SURFEX_V8_1/src/dir_obj-LXgfortran-SFX-V8-1-1-NOMPI-OMP-O2-X0/MASTERā€™: No such file or directory
cd /home/eccei339/snellius_surfex/open_SURFEX_V8_1/src/LIB/grib_api-1.17.0-Source && LDFLAGS= FCFLAGS= CPPFLAGS="" \
 ./configure --disable-jpeg --prefix=/home/eccei339/snellius_surfex/open_SURFEX_V8_1/src/LIB/grib_api-1.17.0-Source-LXgfortran FC="gfortran" && \
 make -j 1 clean && \
 make -j 1 && \
 make -j 1 install && \
 make -j 1 clean
checking build system type... x86_64-unknown-linux-gnu
checking host system type... x86_64-unknown-linux-gnu
checking how to print strings... printf
checking for gcc... gcc
checking whether the C compiler works... yes
checking for C compiler default output file name... a.out
checking for suffix of executables... 
checking whether we are cross compiling... no

(omit the long logging information, and the final lines are the error message shown in the beginning of this question description.)

I searched the Internet that this could be due to the GCC 10 is more strict than older GCC (I compiled this model last year with older GCC and made it, but failed this time because our server is transferred to a new system, thus the GCC is upgraded from older version to a new version). Some information from Google said that I could add something like this:

export FCFLAGS="-w -fallow-argument-mismatch -O2"
export FFLAGS="-w -fallow-argument-mismatch -O2"

But I tried it in the step 2 where I export some essential environmental variables, it still does not work. So I am wondering is there anybody who can help me? Thanks a lot!

Updates: the source code of grib_api-1.17.0-Source/fortran/same_int_long.f90 from Index of /grib_api is as following:

! Copyright 2005-2016 ECMWF.
!
! This software is licensed under the terms of the Apache Licence Version 2.0
! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
! 
! In applying this licence, ECMWF does not waive the privileges and immunities granted to it by
! virtue of its status as an intergovernmental organisation nor does it submit to any jurisdiction.

integer function kind_of_long()
  integer(2), dimension(2) :: x2 = (/1, 2/)
  integer(4), dimension(2) :: x4 = (/1, 2/)
  integer(8), dimension(2) :: x8 = (/1, 2/)
  character(len=1) :: ret

  kind_of_long=-1

  call check_long(x2(1),x2(2),ret)
  if (ret == 't') then
   kind_of_long=2
   return
  endif

  call check_long(x4(1),x4(2),ret)
  if (ret == 't') then
   kind_of_long=4
   return
  endif

  call check_long(x8(1),x8(2),ret)
  if (ret == 't') then
   kind_of_long=8
   return
  endif

end function kind_of_long

integer function kind_of_int()
  integer(2), dimension(2) :: x2 = (/1, 2/)
  integer(4), dimension(2) :: x4 = (/1, 2/)
  integer(8), dimension(2) :: x8 = (/1, 2/)
  character(len=1) :: ret

  kind_of_int=-1

  call check_int(x2(1),x2(2),ret)
  if (ret == 't') then
   kind_of_int=2
   return
  endif

  call check_int(x4(1),x4(2),ret)
  if (ret == 't') then
   kind_of_int=4
   return
  endif

  call check_int(x8(1),x8(2),ret)
  if (ret == 't') then
   kind_of_int=8
   return
  endif

end function kind_of_int

program same_int_long
  integer ki,kl

  ki=kind_of_int()
  kl=kind_of_long()
  if (ki /= kl) then
    write (*,'(i1)') 0
  else
    write (*,'(i1)') 1
  endif
end program same_int_long


Here is the full log information of make: build.log - Google Drive

1 Like

As far as I can see, the compiler detects differences in the kind (byte-length) of actual arguments used in different calls to the same subroutine. Iā€™d guess that this means that there is no interface of the subroutines in use, otherwise the compiler would rather compare the types of actual and dummy arguments. It might help to see the source of the check_int and check_long subroutines. Unless they are generic (but the compiler does not know it), there is a real inconsistency between (some) calls to those subroutines and their definition - the types of an actual argument is different than that of the dummy argument. This is a usually a bad idea and forcing the compiler to accept it with some extra options is equally bad idea.

Thanks @msz59 for your reply! Now I have updated the source code for check_long subroutine. And also a full document for the logging information of make

We still do not see the source for check_long and check_int subroutines but from what we now do see in the source calling them, I would guess that both of those subroutines play with integer values bitwise using the memory not necessarily belonging to the real argument and looking for bit patterns corresponding to value ā€˜1ā€™ and ā€˜2ā€™. If I am right, it would be extremely implementation-dependent.

Consider what would happen when a subprogram has a dummy argument that is an 8-byte integer with intent OUT or IN OUT, and the actual argument is a 2-byte integer.

Thanks, but I think it should be due to the ā€œmismatchā€ problemā€¦which involves the new GCC. Last year I complied this model with an older GCC and it workedā€¦but this time our server is replaced to a new one, which is GCC 10, and I failedā€¦

this is the description of the option, taken from GNU Fortran page:

As for the gfortran versions, I can confirm the change of the default behavior. I compiled the following snippet:

  integer, parameter :: long = selected_int_kind(15)
  integer(long) :: l(2)=[1,2]
  integer :: i(2)=[1,3], ret
  call check_int(l(1),l(2),ret)
  call check_int(i(1),i(2),ret)
end

with old gfortran 4.4.7 - no even warnings. Gfortran v. 10 - error by default, exactly as in your logs. With the -fallow-argument-mismatch error replaced by warning. So, Iā€™d guess that you have to check how to properly add this option to your build system. If-and-only-if you are sure you know what youā€™re doing.

Thanks @msz59! I will try to contact the developer of this model and state this problem. thanks again!