https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88143

Paul Thomas <pault at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Assignee|unassigned at gcc dot gnu.org      |pault at gcc dot gnu.org

--- Comment #4 from Paul Thomas <pault at gcc dot gnu.org> ---
Fortunately, this has a completely trivial fix.

In the condition, where the seg fault occurs, sym->assoc->target is NULL for
this case. The condition should be:

  if (sym->assoc && e->rank == 0 && e->ref && sym->ts.type == BT_CLASS
      && sym->assoc->target && sym->assoc->target->ts.type == BT_CLASS
      && CLASS_DATA (sym->assoc->target)->as)

This then works correctly:
MODULE m
   IMPLICIT NONE
   TYPE t
      INTEGER, DIMENSION(:), ALLOCATABLE :: i
   END TYPE
   CONTAINS
      SUBROUTINE s(x, idx1, idx2, k)
         CLASS(*), DIMENSION(:), INTENT(IN), OPTIONAL :: x
         INTEGER :: idx1, idx2, k
         SELECT TYPE ( x )
         CLASS IS ( t )
            ASSOCIATE ( j => x(idx1)%i )
               k = j(idx2)
            END ASSOCIATE
         END SELECT
      END
END

  use m
  class (t), allocatable :: c(:)
  integer :: k
  allocate (c(2))
  allocate (c(1)%i, source = [3,2,1])
  allocate (c(2)%i, source = [6,5,4])
  call s(c, 1, 3, k)
  if (k .ne. 1) stop 1
  call s(c, 2, 1, k)
  if (k .ne. 6) stop 2
end

Paul

Reply via email to