c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / class_array_23.f03
blobf4afe911be6cc9fb9b393def9f53669ab9bfa724
1 ! { dg-do run }
3 ! Test the fix for PR84538 in which the scalarizer was taking the size
4 ! of 't', rather than 'te', to generate array references.
6 ! Contributed by Andrew Benson  <abensonca@gmail.com>
8 module bugMod
9   public
10   type :: t
11      integer :: i
12   end type t
13   type, extends(t) :: te
14      integer :: j
15   end type te
16 contains
17   subroutine check(n)
18     implicit none
19     class(t), intent(inout), dimension(:) :: n
20     integer :: i(2)
21     i = n%i ! Original testcase had this in a write statement. However,
22             ! it is the scalarizer that is getting the span wrong and so
23             ! this assignment failed too.
24     if (any (i .ne. [8,3])) stop 1
25     return
26   end subroutine check
27 end module bugMod
29 program bug
30   use bugMod
31   class(t), allocatable, dimension(:) :: n
32   allocate(te :: n(2))
33   n(1:2)%i=[8,3]
34   if (any (n%i .ne. [8,3])) stop 2
35   call check(n)
36   deallocate (n)
37 end program bug