
1. Deal with BIND(C,NAME="") BIND(C,NAME="") is different from BIND(C). The latter implies that there us a binding label which is the Fortran symbol name (no Fortran mangling must be added like underscores). The former implies there is no binding label (the name in the object file must be the same as if it there was no BIND(C) attribute at all). This is correctly implemented in the front-end, but lowering mistakenly overrode this in the code dealing with the case where BIND(C) is inherited from a procedure interface. Handling of this last case is moved into name resolution. 2. Deal with BIND(C) internal procedure Also according to 18.10.2, BIND(C) does not give a p prevent name resolution from adding a label to them, otherwise, bindc_internal_proc.f90 was not going through semantics (bogus error about conflicting global names). Nothing TODO in lowering other than removing the TODO.
24 lines
684 B
Fortran
24 lines
684 B
Fortran
! Test that lowering makes a difference between NAME="" and no NAME
|
|
! in BIND(C). See Fortran 2018 standard 18.10.2 point 2.
|
|
! BIND(C, NAME="") implies there is no binding label, meaning that
|
|
! the Fortran mangled name has to be used.
|
|
! RUN: bbc -emit-hlfir %s -o - | FileCheck %s
|
|
|
|
!CHECK: func.func @_QPfoo(%{{.*}}: !fir.ref<i16>
|
|
subroutine foo(x) bind(c, name="")
|
|
integer(2) :: x
|
|
end subroutine
|
|
|
|
!CHECK: func.func @bar(%{{.*}}: !fir.ref<i32>
|
|
subroutine foo(x) bind(c, name="bar")
|
|
integer(4) :: x
|
|
end subroutine
|
|
|
|
!CHECK: func.func @_QMinamodule1Pfoo(%{{.*}}: !fir.ref<i64>
|
|
module inamodule1
|
|
contains
|
|
subroutine foo(x) bind(c, name="")
|
|
integer(8) :: x
|
|
end subroutine
|
|
end module
|