PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / alloc_comp_class_5.f03
blob913ff0c3d99bdc08e7bddc30c47623f7735927f9
1 ! { dg-do run }
3 ! Contributed by Vladimir Fuka
4 ! Check that pr61337 and pr78053, which was caused by this testcase, is fixed.
6 module array_list
8   type container
9     class(*), allocatable :: items(:)
10   end type
12 contains
14   subroutine add_item(a, e)
15     type(container),allocatable,intent(inout) :: a(:)
16     class(*),intent(in) :: e(:)
17     type(container),allocatable :: tmp(:)
19       if (.not.allocated(a)) then
20         allocate(a(1))
21         allocate(a(1)%items(size(e)), source = e)
22       else
23         call move_alloc(a,tmp)
24         allocate(a(size(tmp)+1))
25         a(1:size(tmp)) = tmp
26         allocate(a(size(tmp)+1)%items(size(e)), source=e)
27       end if
28    end subroutine
30 end module
32 program test_pr61337
34   use array_list
36   type(container), allocatable :: a_list(:)
37   integer(kind = 8) :: i
39   call add_item(a_list, [1, 2])
40   call add_item(a_list, [3.0_8, 4.0_8])
41   call add_item(a_list, [.true., .false.])
42   call add_item(a_list, ["foo", "bar", "baz"])
44   if (size(a_list) /= 4) STOP 1
45   do i = 1, size(a_list)
46           call checkarr(a_list(i))
47   end do
49   deallocate(a_list)
51 contains
53   subroutine checkarr(c)
54     type(container) :: c
56     if (allocated(c%items)) then
57       select type (x=>c%items)
58         type is (integer)
59           if (any(x /= [1, 2])) STOP 2
60         type is (real(kind=8))
61           if (any(x /= [3.0_8, 4.0_8])) STOP 3
62         type is (logical)
63           if (any(x .neqv. [.true., .false.])) STOP 4
64         type is (character(len=*))
65           if (len(x) /= 3) STOP 5
66           if (any(x /= ["foo", "bar", "baz"])) STOP 6
67         class default
68           STOP 7
69       end select
70     else
71         STOP 8
72     end if
73   end subroutine
74 end