111
|
1 ! { dg-do run }
|
|
2 !
|
|
3 ! Contributed by Vladimir Fuka
|
|
4 ! Check that pr61337 and pr78053, which was caused by this testcase, is fixed.
|
|
5
|
|
6 module array_list
|
|
7
|
|
8 type container
|
|
9 class(*), allocatable :: items(:)
|
|
10 end type
|
|
11
|
|
12 contains
|
|
13
|
|
14 subroutine add_item(a, e)
|
|
15 type(container),allocatable,intent(inout) :: a(:)
|
|
16 class(*),intent(in) :: e(:)
|
|
17 type(container),allocatable :: tmp(:)
|
|
18
|
|
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
|
|
29
|
|
30 end module
|
|
31
|
|
32 program test_pr61337
|
|
33
|
|
34 use array_list
|
|
35
|
|
36 type(container), allocatable :: a_list(:)
|
|
37 integer(kind = 8) :: i
|
|
38
|
|
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"])
|
|
43
|
131
|
44 if (size(a_list) /= 4) STOP 1
|
111
|
45 do i = 1, size(a_list)
|
|
46 call checkarr(a_list(i))
|
|
47 end do
|
|
48
|
|
49 deallocate(a_list)
|
|
50
|
|
51 contains
|
|
52
|
|
53 subroutine checkarr(c)
|
|
54 type(container) :: c
|
|
55
|
|
56 if (allocated(c%items)) then
|
|
57 select type (x=>c%items)
|
|
58 type is (integer)
|
131
|
59 if (any(x /= [1, 2])) STOP 2
|
111
|
60 type is (real(kind=8))
|
131
|
61 if (any(x /= [3.0_8, 4.0_8])) STOP 3
|
111
|
62 type is (logical)
|
131
|
63 if (any(x .neqv. [.true., .false.])) STOP 4
|
111
|
64 type is (character(len=*))
|
131
|
65 if (len(x) /= 3) STOP 5
|
|
66 if (any(x /= ["foo", "bar", "baz"])) STOP 6
|
111
|
67 class default
|
131
|
68 STOP 7
|
111
|
69 end select
|
|
70 else
|
131
|
71 STOP 8
|
111
|
72 end if
|
|
73 end subroutine
|
|
74 end
|