http://gcc.gnu.org/bugzilla/show_bug.cgi?id=59202

            Bug ID: 59202
           Summary: Erroneous argument aliasing with defined assignment
           Product: gcc
           Version: unknown
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: ian_harvey at bigpond dot com

gfortran build from very recent trunk does not appear to be correctly handling
the case when an object with allocatable components is self assigned and
defined assignment is accessible.

For example:

MODULE DefinedAssignmentModule
  IMPLICIT NONE
  TYPE :: t
    INTEGER, ALLOCATABLE :: array(:)
  END TYPE t
  INTERFACE ASSIGNMENT(=)
    MODULE PROCEDURE def_assign
  END INTERFACE ASSIGNMENT(=)
CONTAINS
  SUBROUTINE def_assign(lhs, rhs)
    TYPE(t), INTENT(OUT) :: lhs   ! Investigate INOUT too.
    TYPE(t), INTENT(IN) :: rhs
    !*****
    ! Allocation status of lhs and rhs on entry.
    PRINT "(*(L1,:,1X))", ALLOCATED(lhs%array), ALLOCATED(rhs%array)
    ! Change allocation status of lhs
    IF (ALLOCATED(lhs%array)) DEALLOCATE(lhs%array)
    ALLOCATE(lhs%array(5))
    ! Resulting allocation status of lhs and rhs.
    PRINT "(1X,*(L1,:,1X))", ALLOCATED(lhs%array), ALLOCATED(rhs%array)
  END SUBROUTINE def_assign
  SUBROUTINE reset(obj)
    TYPE(t), INTENT(OUT) :: obj
  END SUBROUTINE reset
END MODULE DefinedAssignmentModule

PROGRAM DefinedAssignmentTest
  USE DefinedAssignmentModule
  IMPLICIT NONE
  TYPE(t) :: a

  ! This...
  a = a

  CALL reset(a)
  ! ...should be equivalent to this...
  CALL def_assign(a, (a))

  CALL reset(a)
  ALLOCATE(a%array(2))
  a = a     ! rhs should be allocated on entry.

END PROGRAM DefinedAssignmentTest

results in:

F F
 T T
F F
 T F
F F
 T T

The first two lines indicate that changes to lhs inside the procedure result in
changes to rhs (even though rhs is equivalent to the the value of a
parenthesised expression per F2008 12.4.3.4.3 - hence the two arguments are not
aliased).  

The third and fourth lines indicate that the compiler is correctly handling
explicit passing of a parenthesised expression.  

The fifth and sixth lines indicate that application of INTENT(OUT) to lhs is
affecting rhs on entry to the procedure.

Reply via email to