public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch, fortran] PR83118 - [8/9/10/11 Regression] Bad intrinsic assignment of class(*) array component of derived type
@ 2020-10-29 15:59 Paul Richard Thomas
  2020-11-03  8:42 ` Paul Richard Thomas
                   ` (2 more replies)
  0 siblings, 3 replies; 7+ messages in thread
From: Paul Richard Thomas @ 2020-10-29 15:59 UTC (permalink / raw)
  To: fortran, gcc-patches; +Cc: Damian Rouson, Tobias Burnus

[-- Attachment #1: Type: text/plain, Size: 4362 bytes --]

Hi Everyone,

I am afraid that this is a rather long sad story, mainly due to my efforts
with gfortran being interrupted by daytime work. I posted the first version
of the patch nearly a year ago but this was derailed by Tobias's question
at: https://gcc.gnu.org/legacy-ml/fortran/2019-11/msg00098.html

(i) The attached fixes the original problem and is tested by
gfortran.dg/unlimited_polymorphic_32.f03.
(ii) In fixing the original problem, a fair amount of effort was required
to get the element length correct for class temporaries produced by
dependencies in class assignment (see footnote). This is reflected in the
changes to trans_array.c(gfc_alloc_allocatable_for_assignment).
(iii) Tobias's testcase in the above posting to the list didn't address
itself to class arrays of the original problem. However, it revealed that
reallocation was not occuring at all for scalar assignments.  This is fixed
by the large chunk in trans-expr.c(trans_class_assignment). The array case
is 'fixed' by testing for unequal element sizes between lhs and rhs before
reallocation in gfc_alloc_allocatable_for_assignment. This is difficult to
test for since, in most cases, the system returns that same address after
reallocation.
(iv) dependency_57.f90 segfaulted at runtime. The other work in
trans_class_assignment was required to fix this.
(v) A number of minor tidy ups were done including the new function
gfc_resize_class_size_with_len to eliminate some repeated code.

This all bootstraps and regtests on FC31/x86_64 - OK for master?

Cheers

Paul

This patch fixes PR83118 and fixes one or two other niggles in handling
class objects - most importantly class array temporaries required, where
dependences occur in class assignment, and a correct implementation of
reallocation on assignment.

2020-10-29  Paul Thomas  <pault@gcc.gnu.org>

gcc/fortran
PR fortran/83118
* resolve.c (resolve_ordinary_assign): Generate a vtable if
necessary for scalar non-polymorphic rhs's to unlimited lhs's.
* trans-array.c (gfc_trans_allocate_array_storage): Defer
obtaining class element type until all sources of class exprs.
are tried. Use class API rather than TREE_OPERAND. Look for
class expressions in ss->info. After this, obtain the element
size for class payloads. Cast the data as character(len=size)
to overcome unlimited polymorphic problems.
(structure_alloc_comps): Replace code that replicates the new
function gfc_resize_class_size_with_len.
(gfc_alloc_allocatable_for_assignment): Obtain element size
for lhs in cases of deferred characters and class enitities.
Move code for the element size of rhs to start of block. Clean
up extraction of class parmateres throughout this function.
After the shape check test whether or not the lhs and rhs
element sizes are the same. Use earlier evaluation of
'cond_null'. Reallocation of lhs only to happen if siz changes
or element size changes.
* trans-expr.c (gfc_resize_class_size_with_len): New function.
(gfc_conv_procedure_call): Ensure the vtable is present for
passing a non-class actual to an unlimited formal.
(trans_class_vptr_len_assignment): For expressions of type
BT_CLASS, extract the class expression if necessary. Use a
statement block outside the loop body. Ensure that 'rhs' is
of the correct type. Obtain rhs vptr in all circumstances.
(gfc_trans_assignment_1): Simplify some of the logic with
'realloc_flag'. Set 'vptr_copy' for all array assignments to
unlimited polymorphic lhs.
* trans-c (gfc_build_array_ref): Call gfc_resize_class_size_
with_len to correct span for unlimited polymorphic decls.
* trans.h : Add prototype for gfc_resize_class_size_with_len.

gcc/testsuite/
PR fortran/83118
* gfortran.dg/dependency_57.f90: Change to dg-run and test
for correct result.
* gfortran.dg/unlimited_polymorphic_32.f03: New test.

Footnote: I have come to the conclusion that
gfc_trans_allocate_array_storage is the last place that we should be
dealing with class array temporaries, or directly at least. I will give
some thought as to how to do it better. Also, chunks of code are coming
within scalarization loops that should be outside:
                  x->_vptr = (struct __vtype__STAR * {ref-all})
&__vtab_INTEGER_4_;
                  x->_len = 0;
                  D.3977 = x->_vptr->_size;
                  D.3978 = x->_len;
                  D.3979 = D.3978 > 0 ? D.3977 * D.3978 : D.3977;

[-- Attachment #2: Change2.Logs --]
[-- Type: application/octet-stream, Size: 2279 bytes --]

This patch fixes PR83118 and fixes one or two other niggles in handling
class objects - most importantly class array temporaries required, where
dependences occur in class assignment, and a correct implementation of
reallocation on assignment.

2020-10-29  Paul Thomas  <pault@gcc.gnu.org>

gcc/fortran
	PR fortran/83118
	* resolve.c (resolve_ordinary_assign): Generate a vtable if
	necessary for scalar non-polymorphic rhs's to unlimited lhs's.
	* trans-array.c (gfc_trans_allocate_array_storage): Defer
	obtaining class element type until all sources of class exprs.
	are tried. Use class API rather than TREE_OPERAND. Look for
	class expressions in ss->info. After this, obtain the element
	size for class payloads. Cast the data as character(len=size)
	to overcome unlimited polymorphic problems.
	(structure_alloc_comps): Replace code that replicates the new
	function gfc_resize_class_size_with_len.
	(gfc_alloc_allocatable_for_assignment): Obtain element size
	for lhs in cases of deferred characters and class enitities.
	Move code for the element size of rhs to start of block. Clean
	up extraction of class parmateres throughout this function.
	After the shape check test whether or not the lhs and rhs
	element sizes are the same. Use earlier evaluation of
	'cond_null'. Reallocation of lhs only to happen if siz changes
	or element size changes.
	* trans-expr.c (gfc_resize_class_size_with_len): New function.
	(gfc_conv_procedure_call): Ensure the vtable is present for
	passing a non-class actual to an unlimited formal.
	(trans_class_vptr_len_assignment): For expressions of type
	BT_CLASS, extract the class expression if necessary. Use a
	statement block outside the loop body. Ensure that 'rhs' is
	of the correct type. Obtain rhs vptr in all circumstances.
	(gfc_trans_assignment_1): Simplify some of the logic with
	'realloc_flag'. Set 'vptr_copy' for all array assignments to
	unlimited polymorphic lhs.
	* trans-c (gfc_build_array_ref): Call gfc_resize_class_size_
	with_len to correct span for unlimited polymorphic decls.
	* trans.h : Add prototype for gfc_resize_class_size_with_len.

gcc/testsuite/
	PR fortran/83118
	* gfortran.dg/dependency_57.f90: Change to dg-run and test
	for correct result.
	* gfortran.dg/unlimited_polymorphic_31.f03: New test.

[-- Attachment #3: unlimited_polymorphic_32.f03 --]
[-- Type: application/octet-stream, Size: 1608 bytes --]

! { dg-do run }
!
! Test the fix of the test case referenced in comment 17 of PR83118.
!
! Contributed by Damian Rouson  <damian@sourceryinstitute.org>
!
  implicit none
  type Wrapper
    class(*), allocatable :: elements(:)
  end type
  type Mytype
    real(4) :: r = 42.0
  end type

  call driver
contains
  subroutine driver
    class(*), allocatable :: obj
    type(Wrapper) w
    integer(4) :: expected4(2) = [42_4, 43_4]
    integer(8) :: expected8(3) = [42_8, 43_8, 44_8]

    w = new_wrapper (expected4)
    obj = w
    call test (obj, 0)
    obj =  new_wrapper (expected8) ! Used to generate a linker error
    call test (obj, 10)
    obj = new_wrapper ([mytype (99.0)])
    call test (obj, 100)
    obj = Mytype (42.0) ! Used to generate a linker error
    call test (obj, 1000)
  end subroutine
  function new_wrapper(array) result (res)
    class(*) :: array(:)
    type(Wrapper) :: res
    res%elements = array ! Used to runtime segfault
  end function
  subroutine test (arg, idx)
    class(*) :: arg
    integer :: idx
    select type (arg)
      type is (wrapper)
        select type (z => arg%elements)
          type is (integer(4))
            if (any (z .ne. [42_4, 43_4])) stop 1 + idx
          type is (integer(8))
            if (any (z .ne. [42_8, 43_8, 44_8])) stop 1 + idx
          type is (Mytype)
            if (abs (z(1)%r - 99.0) .ge. 1e-6) stop 1 + idx
        class default
          stop 2 + idx
        end select
      type is (Mytype)
        if (abs (arg%r - 42.0) .ge. 1e-6) stop 1 + idx
      class default
        stop 3 + idx
    end select
  end subroutine
end

^ permalink raw reply	[flat|nested] 7+ messages in thread

end of thread, other threads:[~2020-11-11 11:58 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2020-10-29 15:59 [Patch, fortran] PR83118 - [8/9/10/11 Regression] Bad intrinsic assignment of class(*) array component of derived type Paul Richard Thomas
2020-11-03  8:42 ` Paul Richard Thomas
2020-11-06 17:48 ` Tobias Burnus
2020-11-10 13:25 ` Paul Richard Thomas
2020-11-10 22:16   ` Thomas Koenig
2020-11-11  9:47     ` Paul Richard Thomas
2020-11-11 11:58   ` Tobias Burnus

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).