[Patch, fortran] PR114535 - [13/14 regression] ICE with elemental finalizer
Hi All, This one is blazingly 'obvious'. I haven't had the heart to investigate why somebody thought that it is a good idea to check if unreferenced symbols are finalizable because, I suspect, that 'somebody' was me. Worse, I tried a couple of other fixes before I hit on the 'obvious' one :-( The ChangeLog says it all. OK for mainline and then backporting in a couple of weeks? Paul Fortran: Fix ICE in trans-stmt.cc(gfc_trans_call) [PR114535] 2024-04-08 Paul Thomas gcc/fortran PR fortran/114535 * resolve.cc (resolve_symbol): Remove last chunk that checked for finalization of unreferenced symbols. gcc/testsuite/ PR fortran/114535 * gfortran.dg/pr114535d.f90: New test. * gfortran.dg/pr114535iv.f90: Additional source. diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc index 43315a6a550..4cbf7186119 100644 --- a/gcc/fortran/resolve.cc +++ b/gcc/fortran/resolve.cc @@ -17069,15 +17069,6 @@ resolve_symbol (gfc_symbol *sym) if (sym->param_list) resolve_pdt (sym); - - if (!sym->attr.referenced - && (sym->ts.type == BT_CLASS || sym->ts.type == BT_DERIVED)) -{ - gfc_expr *final_expr = gfc_lval_expr_from_sym (sym); - if (gfc_is_finalizable (final_expr->ts.u.derived, NULL)) - gfc_set_sym_referenced (sym); - gfc_free_expr (final_expr); -} } diff --git a/gcc/testsuite/gfortran.dg/pr114535d.f90 b/gcc/testsuite/gfortran.dg/pr114535d.f90 new file mode 100644 index 000..7ce178a1e30 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/pr114535d.f90 @@ -0,0 +1,42 @@ +! { dg-do compile } +! { dg-compile-aux-modules "pr114535iv.f90" } +! Contributed by Andrew Benson +! +module d + implicit none +contains + function en() result(dd) +use :: iv +implicit none +type(vs) :: dd +dd%i = 1 + end function en +end module d + +! Delete line 1 and all brands complain that 'vs' is an undefined type. +! Delete lines 1 and line 2 recreates the original problem. +module ni + implicit none +contains + subroutine iss1() +!use :: iv! line 1 +use :: d +implicit none +!type(vs) :: ans; ans = en(); ! line 2 + end subroutine iss1 + subroutine iss2() +use :: d +implicit none + end subroutine iss2 +end module ni ! Used to give an ICE: in gfc_trans_call, at fortran/trans-stmt.cc:400 + + use ni + use iv + type(vs) :: x + call iss1() + call iss1() + if ((ctr .eq. 0) .or. (ctr .ne. 6)) stop 1 ! Depends whether lines 1 & 2 are present + call iss2() + x = vs(42) + if ((ctr .eq. 1) .or. (ctr .ne. 7)) stop 2 ! Make sure destructor available here +end diff --git a/gcc/testsuite/gfortran.dg/pr114535iv.f90 b/gcc/testsuite/gfortran.dg/pr114535iv.f90 new file mode 100644 index 000..be629991023 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/pr114535iv.f90 @@ -0,0 +1,18 @@ +! Compiled with pr114535d.f90 +! Contributed by Andrew Benson +! +module iv + type, public :: vs + integer :: i + contains + final :: destructor + end type vs + integer :: ctr = 0 +contains + impure elemental subroutine destructor(s) +type(vs), intent(inout) :: s +s%i = 0 +ctr = ctr + 1 + end subroutine destructor +end module iv +
[Patch] Fortran: List-directed read - accept again tab as alternative to space as separator [PR114304] (was: [patch, libgfortran] PR114304 - [13/14 Regression] libgfortran I/O – bogus "Semicolon not a
Jerry D wrote: See attached updated patch. It turned rather quickly out that this patch – committed as r14-9822-g93adf88cc6744a – caused regressions. Namely, real-world code use tab(s) as separator instead of spaces. [For instance, PR114304 which contains a named-list input file from SPEC CPU 2017; that example uses tabs before the '=' sign, but the issue is more generic.] I think the ISO Fortran standard only permits spaces, but as it feels natural and is widely supported, tabs are used and should remain supported. It is not quite clear how '\r' are or should be handled, but as eat_spaces did use it, I thought I would add one testcase using them as well. That test is not affected by my change; it did work before with GCC and still does – but it does fail with ifort/ifx/flang. I have not thought deeply whether it should be supported or not – and looking at the libgfortran source file, it often but (→ testcase) not consistently requires that an \n follows the \r. OK for mainline? [And: When the previous patch gets backported, this surely needs to be included as well.] Tobias Fortran: Accept again tab as alternative to space as separator [PR114304] This fixes a side-effect of/regression caused by r14-9822-g93adf88cc6744a, which was for the same PR. PR libfortran/114304 libgfortran/ChangeLog: * io/list_read.c (eat_separator): Accept tab as alternative to space. gcc/testsuite/ChangeLog: * gfortran.dg/pr114304-2.f90: New test. gcc/testsuite/gfortran.dg/pr114304-2.f90 | 82 libgfortran/io/list_read.c | 2 +- 2 files changed, 83 insertions(+), 1 deletion(-) diff --git a/gcc/testsuite/gfortran.dg/pr114304-2.f90 b/gcc/testsuite/gfortran.dg/pr114304-2.f90 new file mode 100644 index 000..5ef5874f528 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/pr114304-2.f90 @@ -0,0 +1,82 @@ +! { dg-do run } +! +! PR fortran/114304 +! +! Ensure that '\t' (tab) is supported as separator in list-directed input +! While not really standard conform, this is widely used in user input and +! widely supported. +! + +use iso_c_binding +implicit none +character(len=*,kind=c_char), parameter :: tab = C_HORIZONTAL_TAB + +! Accept '' as variant to ' ' as separator +! Check that and are handled + +character(len=*,kind=c_char), parameter :: nml_str & + = '&inparm'//C_CARRIAGE_RETURN // C_NEW_LINE // & + 'first'//tab//'='//tab//' .true.'// C_NEW_LINE // & + ' , other'//tab//' ='//tab//'3'//tab//', 2'//tab//'/' + +! Check that is handled, + +! Note: For new line, Unix uses \n, Windows \r\n but old Apple systems used '\r' +! +! Gfortran does not seem to support all \r, but the following is supported +! since ages, ! which seems to be a gfortran extension as ifort and flang don't like it. + +character(len=*,kind=c_char), parameter :: nml_str2 & + = '&inparm'//C_CARRIAGE_RETURN // C_NEW_LINE // & + 'first'//C_NEW_LINE//'='//tab//' .true.'// C_CARRIAGE_RETURN // & + ' , other'//tab//' ='//tab//'3'//tab//', 2'//tab//'/' + +character(len=*,kind=c_char), parameter :: str & + = tab//'1'//tab//'2,'//tab//'3'//tab//',4'//tab//','//tab//'5'//tab//'/' +character(len=*,kind=c_char), parameter :: str2 & + = tab//'1'//tab//'2;'//tab//'3'//tab//';4'//tab//';'//tab//'5'//tab//'/' +logical :: first +integer :: other(4) +integer :: ints(6) +namelist /inparm/ first , other + +other = 1 + +open(99, file="test.inp") +write(99, '(a)') nml_str +rewind(99) +read(99,nml=inparm) +close(99, status="delete") + +if (.not.first .or. any (other /= [3,2,1,1])) stop 1 + +other = 9 + +open(99, file="test.inp") +write(99, '(a)') nml_str2 +rewind(99) +read(99,nml=inparm) +close(99, status="delete") + +if (.not.first .or. any (other /= [3,2,9,9])) stop 2 + +ints = 66 + +open(99, file="test.inp", decimal='point') +write(99, '(a)') str +rewind(99) +read(99,*) ints +close(99, status="delete") + +if (any (ints /= [1,2,3,4,5,66])) stop 3 + +ints = 77 + +open(99, file="test.inp", decimal='comma') +write(99, '(a)') str2 +rewind(99) +read(99,*) ints +close(99, status="delete") + +if (any (ints /= [1,2,3,4,5,77])) stop 4 +end diff --git a/libgfortran/io/list_read.c b/libgfortran/io/list_read.c index b56f2a4e6d6..5bbbef26c26 100644 --- a/libgfortran/io/list_read.c +++ b/libgfortran/io/list_read.c @@ -463,7 +463,7 @@ eat_separator (st_parameter_dt *dtp) dtp->u.p.comma_flag = 0; c = next_char (dtp); - if (c == ' ') + if (c == ' ' || c == '\t') { eat_spaces (dtp); c = next_char (dtp);
Re: [Patch] Fortran: List-directed read - accept again tab as alternative to space as separator [PR114304]
On 4/8/24 2:53 AM, Tobias Burnus wrote: Jerry D wrote: See attached updated patch. It turned rather quickly out that this patch – committed as r14-9822-g93adf88cc6744a – caused regressions. Namely, real-world code use tab(s) as separator instead of spaces. [For instance, PR114304 which contains a named-list input file from SPEC CPU 2017; that example uses tabs before the '=' sign, but the issue is more generic.] I think the ISO Fortran standard only permits spaces, but as it feels natural and is widely supported, tabs are used and should remain supported. It is not quite clear how '\r' are or should be handled, but as eat_spaces did use it, I thought I would add one testcase using them as well. That test is not affected by my change; it did work before with GCC and still does – but it does fail with ifort/ifx/flang. I have not thought deeply whether it should be supported or not – and looking at the libgfortran source file, it often but (→ testcase) not consistently requires that an \n follows the \r. OK for mainline? [And: When the previous patch gets backported, this surely needs to be included as well.] Tobias Good catch. I did not even think about tabs. OK to commit and I will take care of it when I do the backport to 13. Thanks! Jerry
Re: [Patch, fortran] PR114535 - [13/14 regression] ICE with elemental finalizer
On 4/8/24 2:45 AM, Paul Richard Thomas wrote: Hi All, This one is blazingly 'obvious'. I haven't had the heart to investigate why somebody thought that it is a good idea to check if unreferenced symbols are finalizable because, I suspect, that 'somebody' was me. Worse, I tried a couple of other fixes before I hit on the 'obvious' one :-( The ChangeLog says it all. OK for mainline and then backporting in a couple of weeks? Paul Fortran: Fix ICE in trans-stmt.cc(gfc_trans_call) [PR114535] 2024-04-08 Paul Thomas mailto:pa...@gcc.gnu.org>> gcc/fortran PR fortran/114535 * resolve.cc (resolve_symbol): Remove last chunk that checked for finalization of unreferenced symbols. gcc/testsuite/ PR fortran/114535 * gfortran.dg/pr114535d.f90: New test. * gfortran.dg/pr114535iv.f90: Additional source. Yes, OK Paul. Don't feel bad. It wasn't Tabs. LOL Jerry
[PATCH] Fortran: fix argument checking of intrinsics C_SIZEOF, C_F_POINTER [PR106500]
Dear all, the attached patch fixes argument checking of: - C_SIZEOF - rejects-valid (see below) and ICE-on-valid - C_F_POINTER - ICE-on-invalid The interesting part is that C_SIZEOF was not well specified until after F2018, where an interp request lead to an edit that actually loosened restrictions and makes the checking much more straightforward, since expressions and function results are now allowed. I've added references to the relevant text and interp in the commit message. While updating the checking code shared between C_SIZEOF and C_F_POINTER, I figured that the latter missed a check preventing an ICE-on-invalid when a function returning a pointer was passed. Regtested on x86_64-pc-linux-gnu. OK for mainline? Thanks, Harald From 6f412a6399a7e125db835584d3d2489a52150c27 Mon Sep 17 00:00:00 2001 From: Harald Anlauf Date: Mon, 8 Apr 2024 21:43:24 +0200 Subject: [PATCH] Fortran: fix argument checking of intrinsics C_SIZEOF, C_F_POINTER [PR106500] The interpretation of the F2018 standard regarding valid arguments to the intrinsic C_SIZEOF(X) was clarified in an edit to 18-007r1: https://j3-fortran.org/doc/year/22/22-101r1.txt loosening restrictions and giving examples. The F2023 text has: ! F2023:18.2.3.8 C_SIZEOF (X) ! ! X shall be a data entity with interoperable type and type parameters, ! and shall not be an assumed-size array, an assumed-rank array that ! is associated with an assumed-size array, an unallocated allocatable ! variable, or a pointer that is not associated. where ! 3.41 data entity ! data object, result of the evaluation of an expression, or the ! result of the execution of a function reference Update the checking code for interoperable arguments accordingly, and extend to reject functions returning pointer as FPTR argument to C_F_POINTER. gcc/fortran/ChangeLog: PR fortran/106500 * check.cc (is_c_interoperable): Fix checks for C_SIZEOF. (gfc_check_c_f_pointer): Reject function returning a pointer as FPTR. gcc/testsuite/ChangeLog: PR fortran/106500 * gfortran.dg/c_sizeof_6.f90: Remove wrong dg-error. * gfortran.dg/c_f_pointer_tests_9.f90: New test. * gfortran.dg/c_sizeof_7.f90: New test. --- gcc/fortran/check.cc | 21 ++ .../gfortran.dg/c_f_pointer_tests_9.f90 | 21 ++ gcc/testsuite/gfortran.dg/c_sizeof_6.f90 | 2 +- gcc/testsuite/gfortran.dg/c_sizeof_7.f90 | 42 +++ 4 files changed, 76 insertions(+), 10 deletions(-) create mode 100644 gcc/testsuite/gfortran.dg/c_f_pointer_tests_9.f90 create mode 100644 gcc/testsuite/gfortran.dg/c_sizeof_7.f90 diff --git a/gcc/fortran/check.cc b/gcc/fortran/check.cc index db74dcf3f40..b7f60575c67 100644 --- a/gcc/fortran/check.cc +++ b/gcc/fortran/check.cc @@ -5299,18 +5299,14 @@ is_c_interoperable (gfc_expr *expr, const char **msg, bool c_loc, bool c_f_ptr) return false; } - if (!c_loc && expr->rank > 0 && expr->expr_type != EXPR_ARRAY) + /* Checks for C_SIZEOF need to take into account edits to 18-007r1, see + https://j3-fortran.org/doc/year/22/22-101r1.txt . */ + if (!c_loc && !c_f_ptr && expr->rank > 0 && expr->expr_type == EXPR_VARIABLE) { gfc_array_ref *ar = gfc_find_array_ref (expr); - if (ar->type != AR_FULL) + if (ar->type == AR_FULL && ar->as->type == AS_ASSUMED_SIZE) { - *msg = "Only whole-arrays are interoperable"; - return false; - } - if (!c_f_ptr && ar->as->type != AS_EXPLICIT - && ar->as->type != AS_ASSUMED_SIZE) - { - *msg = "Only explicit-size and assumed-size arrays are interoperable"; + *msg = "Assumed-size arrays are not interoperable"; return false; } } @@ -5475,6 +5471,13 @@ gfc_check_c_f_pointer (gfc_expr *cptr, gfc_expr *fptr, gfc_expr *shape) return false; } + if (attr.function) +{ + gfc_error ("FPTR at %L to C_F_POINTER is a function returning a pointer", + &fptr->where); + return false; +} + if (fptr->rank > 0 && !is_c_interoperable (fptr, &msg, false, true)) return gfc_notify_std (GFC_STD_F2018, "Noninteroperable array FPTR " "at %L to C_F_POINTER: %s", &fptr->where, msg); diff --git a/gcc/testsuite/gfortran.dg/c_f_pointer_tests_9.f90 b/gcc/testsuite/gfortran.dg/c_f_pointer_tests_9.f90 new file mode 100644 index 000..bb6d3281b02 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/c_f_pointer_tests_9.f90 @@ -0,0 +1,21 @@ +! { dg-do compile } +! +! A function returning a pointer cannot be interoperable +! and cannot be used as FPTR argument to C_F_POINTER. + +subroutine s () + use, intrinsic :: iso_c_binding + implicit none + type(c_ptr) :: cPtr + call c_f_pointer (cPtr, p0)! { dg-error "function returning a pointer" } + call c_f_pointer (cPtr, p1, shape=[2]) ! { dg-error "function returning a pointer" } +contains + function p0 () +integer, pointer :: p0 +nullify (p0) + end + function p1 () +integer, pointer :: p1(:) +nullify (p1) + end +end diff --g