On Wed, Jan 08, 2025 at 01:40:20PM +0100, Mikael Morin wrote:
> Le 08/01/2025 à 11:42, Jakub Jelinek a écrit :
> >
> > The full list of changes with the posted patches is
> > (first a.mod, then b.mod, 14 -> 15) below.
> > I have no idea what adds those __copy_* elts etc. and whether they could be
> > forced to be in the middle rather than at the end and what is an ABI break
> > and what is not.
> >
> I think the numbers starting symbol definitions don't matter, the numbers
> represent pointers, so what matters is the structure, not the value; that is
> the number can change, and in that case it should be changed everywhere it
> is used.
All I know is that
--- xc_f03_lib_m.mod 2025-01-07 18:47:44.155602052 +0100
+++ xc_f03_lib_m.mod 2025-01-07 18:47:53.307400792 +0100
@@ -647,12 +647,12 @@ UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0)
UNKNOWN UNKNOWN 0 0 IS_BIND_C IS_C_INTEROP PRIVATE_COMP) ((818 'c_address'
(INTEGER 8 0 1 0 INTEGER ()) () () () (UNKNOWN-FL UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN UNKNOWN 0 0) PRIVATE ())) PRIVATE (DERIVED 6 0 1 1
-VOID ()) 0 0 () () 0 () () () 2 42 0)
+VOID ()) 0 0 () () 0 () () () 2 63 0)
10 'C_funptr' '__iso_c_binding' '' 1 ((DERIVED UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 IS_BIND_C IS_C_INTEROP PRIVATE_COMP) (
(819 'c_address' (INTEGER 8 0 1 0 INTEGER ()) () () () (UNKNOWN-FL
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0) PRIVATE ())) PRIVATE (
-DERIVED 10 0 1 1 VOID ()) 0 0 () () 0 () () () 2 44 0)
+DERIVED 10 0 1 1 VOID ()) 0 0 () () 0 () () () 2 65 0)
30 '__copy___iso_c_binding_C_funptr' 'xc_f03_lib_m' '' 820 ((PROCEDURE
UNKNOWN-INTENT UNKNOWN-PROC DECL UNKNOWN 0 0 ARTIFICIAL SUBROUTINE
ELEMENTAL PURE ALWAYS_EXPLICIT) () (UNKNOWN 0 0 0 0 UNKNOWN ()) 0 0 (
changes in libxc-devel xc_f03_lib_m.mod cause various ICEs as I wrote in the
PR when using the GCC 14 compiled mod file with GCC 15.
Here is a short reproducer:
/usr/src/gcc-15/obj/gcc/f951 -quiet libxc_master.f90
/usr/src/gcc-15/obj/gcc/f951 -quiet fu.f90
This compiles fine
/usr/src/gcc-14/obj/gcc/f951 -quiet libxc_master.f90
/usr/src/gcc-15/obj/gcc/f951 -quiet fu.f90
fu.f90:10:18:
10 | end subroutine foo
| 1
internal compiler error: tree check: expected record_type or union_type or
qual_union_type, have pointer_type in gfc_trans_structure_assign, at
fortran/trans-expr.cc:9906
0x2d322df internal_error(char const*, ...)
../../gcc/diagnostic-global-context.cc:517
0x12fd1d3 tree_check_failed(tree_node const*, char const*, int, char const*,
...)
../../gcc/tree.cc:9044
0x5b6939 tree_check3(tree_node*, char const*, int, char const*, tree_code,
tree_code, tree_code)
../../gcc/tree.h:3705
0x602a93 gfc_trans_structure_assign(tree_node*, gfc_expr*, bool, bool)
../../gcc/fortran/trans-expr.cc:9906
0x6033c3 gfc_conv_structure(gfc_se*, gfc_expr*, int)
../../gcc/fortran/trans-expr.cc:10063
0x603bb3 gfc_conv_expr(gfc_se*, gfc_expr*)
../../gcc/fortran/trans-expr.cc:10231
0x602815 gfc_trans_subcomponent_assign
../../gcc/fortran/trans-expr.cc:9864
0x60303e gfc_trans_structure_assign(tree_node*, gfc_expr*, bool, bool)
../../gcc/fortran/trans-expr.cc:9997
0x6033c3 gfc_conv_structure(gfc_se*, gfc_expr*, int)
../../gcc/fortran/trans-expr.cc:10063
0x603bb3 gfc_conv_expr(gfc_se*, gfc_expr*)
../../gcc/fortran/trans-expr.cc:10231
0x60cad7 gfc_trans_assignment_1
../../gcc/fortran/trans-expr.cc:12806
0x60dfc8 gfc_trans_assignment(gfc_expr*, gfc_expr*, bool, bool, bool, bool)
../../gcc/fortran/trans-expr.cc:13213
0x5ce01c gfc_init_default_dt(gfc_symbol*, stmtblock_t*, bool)
../../gcc/fortran/trans-decl.cc:4487
0x5d0cdc gfc_trans_deferred_vars(gfc_symbol*, gfc_wrapped_block*)
../../gcc/fortran/trans-decl.cc:5266
0x5dc20b gfc_generate_function_code(gfc_namespace*)
../../gcc/fortran/trans-decl.cc:8148
0x58e092 gfc_generate_module_code(gfc_namespace*)
../../gcc/fortran/trans.cc:2764
0x5058b8 translate_all_program_units
../../gcc/fortran/parse.cc:7216
0x5062b7 gfc_parse_file()
../../gcc/fortran/parse.cc:7546
0x573b33 gfc_be_parse_file
../../gcc/fortran/f95-lang.cc:241
Please submit a full bug report, with preprocessed source (by using
-freport-bug).
Please include the complete backtrace with any bug report.
See <https://gcc.gnu.org/bugs/> for instructions.
Jakub
module xc_f03_lib_m
use, intrinsic :: iso_c_binding
implicit none
private
public :: xc_f03_func_t, xc_f03_func_info_t, &
xc_f03_func_init
integer(c_int), parameter, public :: XC_UNPOLARIZED = 1
type :: xc_f03_func_t
private
type(c_ptr) :: ptr = C_NULL_PTR
end type xc_f03_func_t
type :: xc_f03_func_info_t
private
type(c_ptr) :: ptr = C_NULL_PTR
end type xc_f03_func_info_t
interface
type(c_ptr) function xc_func_alloc() bind(c)
import
end function xc_func_alloc
integer(c_int) function xc_func_init(p, functional, nspin) bind(c)
import
type(c_ptr), value :: p
integer(c_int), value :: functional, nspin
end function xc_func_init
end interface
contains
subroutine xc_f03_func_init(p, functional, nspin, err)
type(xc_f03_func_t), intent(inout) :: p
integer(c_int), intent(in) :: functional
integer(c_int), intent(in) :: nspin
integer(c_int), optional, intent(out) :: err
integer(c_int) :: ierr
p%ptr = xc_func_alloc()
ierr = xc_func_init(p%ptr, functional, nspin)
if(present(err)) err = ierr
end subroutine xc_f03_func_init
end module xc_f03_lib_m
module fu
implicit none
private
public :: foo
contains
subroutine foo()
use xc_f03_lib_m, only: xc_f03_func_info_t, xc_f03_func_init, xc_f03_func_t,
XC_UNPOLARIZED
type(xc_f03_func_t) :: func
call xc_f03_func_init(func,1_4,xc_unpolarized)
end subroutine foo
end module fu