This is the mail archive of the gcc-patches@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

Re: [Patch, fortran] PR66929 fix iso_varying_string ICE


Le 21/07/2015 23:10, Paul Richard Thomas a Ãcrit :
Hi Mikael,

This looks fine to me - OK for trunk.

Thanks for the patch

Paul

On 21 July 2015 at 14:53, Mikael Morin <mikael.morin@sfr.fr> wrote:
Hello,

The fix for PR61831 committed recently [1] introduced/uncovered a NULLL
pointer dereference with iso_varying_string, because a generic symbol (which
has a NULL result) is used as procedure symbol, instead of the specific one.
Fixed by using esym if it's available.

Regression-tested on x86_64-linux. OK for trunk?

Mikael

[1]: https://gcc.gnu.org/ml/gcc-patches/2015-06/msg01389.html


Hello,

I would like to backport the patch.
As the bug was discovered with the patch [1] above, the test generic_30.f90 works on the branches, which don't have that patch. Meanwhile, I have managed to find a test generic_31.f90 that exhibits a wrong code already on the branch, which justifies the backport.

Regression tested on the 5 branch, OK for 5 and 4.9?

Mikael


Attachment: pr66929_1_backport.CL
Description: Text document

Index: trans-array.c
===================================================================
--- trans-array.c	(révision 225979)
+++ trans-array.c	(copie de travail)
@@ -9166,7 +9166,11 @@ gfc_get_proc_ifc_for_expr (gfc_expr *procedure_ref
     return NULL;
 
   /* Normal procedure case.  */
-  sym = procedure_ref->symtree->n.sym;
+  if (procedure_ref->expr_type == EXPR_FUNCTION
+      && procedure_ref->value.function.esym)
+    sym = procedure_ref->value.function.esym;
+  else
+    sym = procedure_ref->symtree->n.sym;
 
   /* Typebound procedure case.  */
   for (ref = procedure_ref->ref; ref; ref = ref->next)

! { dg-do compile }
!
! PR fortran/66929
! Generic procedures as actual argument used to lead to
! a NULL pointer dereference in gfc_get_proc_ifc_for_expr
! because the generic symbol was used as procedure symbol,
! instead of the specific one.

module iso_varying_string
  type, public :: varying_string
     character(LEN=1), dimension(:), allocatable :: chars
  end type varying_string
  interface operator(/=)
     module procedure op_ne_VS_CH
  end interface operator (/=)
  interface trim
     module procedure trim_
  end interface
contains
  elemental function op_ne_VS_CH (string_a, string_b) result (op_ne)
    type(varying_string), intent(in) :: string_a
    character(LEN=*), intent(in)     :: string_b
    logical                          :: op_ne
    op_ne = .true.
  end function op_ne_VS_CH
  elemental function trim_ (string) result (trim_string)
    type(varying_string), intent(in) :: string
    type(varying_string)             :: trim_string
    trim_string = varying_string(["t", "r", "i", "m", "m", "e", "d"])
  end function trim_
end module iso_varying_string
module syntax_rules
  use iso_varying_string, string_t => varying_string
contains
  subroutine set_rule_type_and_key
    type(string_t) :: key
    if (trim (key) /= "") then
      print *, "non-empty"
    end if
  end subroutine set_rule_type_and_key
end module syntax_rules

! { dg-do run }
!
! PR fortran/66929
! Check that the specific FIRST symbol is used for the call to FOO,
! so that the J argument is not assumed to be present

module m
  interface foo
    module procedure first
  end interface foo
contains
  elemental function bar(j) result(r)
    integer, intent(in), optional :: j
    integer :: r, s(2)
    ! We used to have NULL dereference here, in case of a missing J argument
    s = foo(j, [3, 7])
    r = sum(s)
  end function bar
  elemental function first(i, j) result(r)
    integer, intent(in), optional :: i
    integer, intent(in) :: j
    integer :: r
    if (present(i)) then
      r = i
    else
      r = -5
    end if
  end function first
end module m
program p
  use m
  integer :: i
  i = bar()
  if (i /= -10) call abort
end program p


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]