annotate gcc/testsuite/gfortran.dg/alloc_comp_class_5.f03 @ 158:494b0b89df80 default tip

...
author Shinji KONO <kono@ie.u-ryukyu.ac.jp>
date Mon, 25 May 2020 18:13:55 +0900
parents 84e7813d76e9
children
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
rev   line source
111
kono
parents:
diff changeset
1 ! { dg-do run }
kono
parents:
diff changeset
2 !
kono
parents:
diff changeset
3 ! Contributed by Vladimir Fuka
kono
parents:
diff changeset
4 ! Check that pr61337 and pr78053, which was caused by this testcase, is fixed.
kono
parents:
diff changeset
5
kono
parents:
diff changeset
6 module array_list
kono
parents:
diff changeset
7
kono
parents:
diff changeset
8 type container
kono
parents:
diff changeset
9 class(*), allocatable :: items(:)
kono
parents:
diff changeset
10 end type
kono
parents:
diff changeset
11
kono
parents:
diff changeset
12 contains
kono
parents:
diff changeset
13
kono
parents:
diff changeset
14 subroutine add_item(a, e)
kono
parents:
diff changeset
15 type(container),allocatable,intent(inout) :: a(:)
kono
parents:
diff changeset
16 class(*),intent(in) :: e(:)
kono
parents:
diff changeset
17 type(container),allocatable :: tmp(:)
kono
parents:
diff changeset
18
kono
parents:
diff changeset
19 if (.not.allocated(a)) then
kono
parents:
diff changeset
20 allocate(a(1))
kono
parents:
diff changeset
21 allocate(a(1)%items(size(e)), source = e)
kono
parents:
diff changeset
22 else
kono
parents:
diff changeset
23 call move_alloc(a,tmp)
kono
parents:
diff changeset
24 allocate(a(size(tmp)+1))
kono
parents:
diff changeset
25 a(1:size(tmp)) = tmp
kono
parents:
diff changeset
26 allocate(a(size(tmp)+1)%items(size(e)), source=e)
kono
parents:
diff changeset
27 end if
kono
parents:
diff changeset
28 end subroutine
kono
parents:
diff changeset
29
kono
parents:
diff changeset
30 end module
kono
parents:
diff changeset
31
kono
parents:
diff changeset
32 program test_pr61337
kono
parents:
diff changeset
33
kono
parents:
diff changeset
34 use array_list
kono
parents:
diff changeset
35
kono
parents:
diff changeset
36 type(container), allocatable :: a_list(:)
kono
parents:
diff changeset
37 integer(kind = 8) :: i
kono
parents:
diff changeset
38
kono
parents:
diff changeset
39 call add_item(a_list, [1, 2])
kono
parents:
diff changeset
40 call add_item(a_list, [3.0_8, 4.0_8])
kono
parents:
diff changeset
41 call add_item(a_list, [.true., .false.])
kono
parents:
diff changeset
42 call add_item(a_list, ["foo", "bar", "baz"])
kono
parents:
diff changeset
43
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
44 if (size(a_list) /= 4) STOP 1
111
kono
parents:
diff changeset
45 do i = 1, size(a_list)
kono
parents:
diff changeset
46 call checkarr(a_list(i))
kono
parents:
diff changeset
47 end do
kono
parents:
diff changeset
48
kono
parents:
diff changeset
49 deallocate(a_list)
kono
parents:
diff changeset
50
kono
parents:
diff changeset
51 contains
kono
parents:
diff changeset
52
kono
parents:
diff changeset
53 subroutine checkarr(c)
kono
parents:
diff changeset
54 type(container) :: c
kono
parents:
diff changeset
55
kono
parents:
diff changeset
56 if (allocated(c%items)) then
kono
parents:
diff changeset
57 select type (x=>c%items)
kono
parents:
diff changeset
58 type is (integer)
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
59 if (any(x /= [1, 2])) STOP 2
111
kono
parents:
diff changeset
60 type is (real(kind=8))
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
61 if (any(x /= [3.0_8, 4.0_8])) STOP 3
111
kono
parents:
diff changeset
62 type is (logical)
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
63 if (any(x .neqv. [.true., .false.])) STOP 4
111
kono
parents:
diff changeset
64 type is (character(len=*))
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
65 if (len(x) /= 3) STOP 5
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
66 if (any(x /= ["foo", "bar", "baz"])) STOP 6
111
kono
parents:
diff changeset
67 class default
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
68 STOP 7
111
kono
parents:
diff changeset
69 end select
kono
parents:
diff changeset
70 else
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
71 STOP 8
111
kono
parents:
diff changeset
72 end if
kono
parents:
diff changeset
73 end subroutine
kono
parents:
diff changeset
74 end