3 ! Contributed by Vladimir Fuka
4 ! Check that pr61337 and pr78053, which was caused by this testcase, is fixed.
9 class(*), allocatable :: items(:)
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
21 allocate(a(1)%items(size(e)), source = e)
23 call move_alloc(a,tmp)
24 allocate(a(size(tmp)+1))
26 allocate(a(size(tmp)+1)%items(size(e)), source=e)
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))
53 subroutine checkarr(c)
56 if (allocated(c%items)) then
57 select type (x=>c%items)
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
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