PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / class_48.f90
blob8e7413ba528c871086cd471957103fddd8fc712e
1 ! { dg-do run }
3 ! PR fortran/51972
4 ! Also tests fixes for PR52102
6 ! Check whether DT assignment with polymorphic components works.
9 subroutine test1 ()
10 type t
11 integer :: x
12 end type t
14 type t2
15 class(t), allocatable :: a
16 end type t2
18 type(t2) :: one, two
20 one = two
21 if (allocated (one%a)) STOP 1
23 allocate (two%a)
24 two%a%x = 7890
25 one = two
26 if (one%a%x /= 7890) STOP 2
28 deallocate (two%a)
29 one = two
30 if (allocated (one%a)) STOP 3
31 end subroutine test1
33 subroutine test2 ()
34 type t
35 integer, allocatable :: x(:)
36 end type t
38 type t2
39 class(t), allocatable :: a
40 end type t2
42 type(t2) :: one, two
44 one = two
45 if (allocated (one%a)) STOP 4
47 allocate (two%a)
48 one = two
49 if (.not.allocated (one%a)) STOP 5
50 if (allocated (one%a%x)) STOP 6
52 allocate (two%a%x(2))
53 two%a%x(:) = 7890
54 one = two
55 if (any (one%a%x /= 7890)) STOP 7
57 deallocate (two%a)
58 one = two
59 if (allocated (one%a)) STOP 8
60 end subroutine test2
63 subroutine test3 ()
64 type t
65 integer :: x
66 end type t
68 type t2
69 class(t), allocatable :: a(:)
70 end type t2
72 type(t2) :: one, two
74 ! Test allocate with array source - PR52102
75 allocate (two%a(2), source = [t(4), t(6)])
77 if (allocated (one%a)) STOP 9
79 one = two
80 if (.not.allocated (one%a)) STOP 10
82 if ((one%a(1)%x /= 4)) STOP 11
83 if ((one%a(2)%x /= 6)) STOP 12
85 deallocate (two%a)
86 one = two
88 if (allocated (one%a)) STOP 13
90 ! Test allocate with no source followed by assignments.
91 allocate (two%a(2))
92 two%a(1)%x = 5
93 two%a(2)%x = 7
95 if (allocated (one%a)) STOP 14
97 one = two
98 if (.not.allocated (one%a)) STOP 15
100 if ((one%a(1)%x /= 5)) STOP 16
101 if ((one%a(2)%x /= 7)) STOP 17
103 deallocate (two%a)
104 one = two
105 if (allocated (one%a)) STOP 18
106 end subroutine test3
108 subroutine test4 ()
109 type t
110 integer, allocatable :: x(:)
111 end type t
113 type t2
114 class(t), allocatable :: a(:)
115 end type t2
117 type(t2) :: one, two
119 if (allocated (one%a)) STOP 19
120 if (allocated (two%a)) STOP 20
122 allocate (two%a(2))
124 if (allocated (two%a(1)%x)) STOP 21
125 if (allocated (two%a(2)%x)) STOP 22
126 allocate (two%a(1)%x(3), source=[1,2,3])
127 allocate (two%a(2)%x(5), source=[5,6,7,8,9])
128 one = two
129 if (.not. allocated (one%a)) STOP 23
130 if (.not. allocated (one%a(1)%x)) STOP 24
131 if (.not. allocated (one%a(2)%x)) STOP 25
133 if (size(one%a) /= 2) STOP 26
134 if (size(one%a(1)%x) /= 3) STOP 27
135 if (size(one%a(2)%x) /= 5) STOP 28
136 if (any (one%a(1)%x /= [1,2,3])) STOP 29
137 if (any (one%a(2)%x /= [5,6,7,8,9])) STOP 30
139 deallocate (two%a(1)%x)
140 one = two
141 if (.not. allocated (one%a)) STOP 31
142 if (allocated (one%a(1)%x)) STOP 32
143 if (.not. allocated (one%a(2)%x)) STOP 33
145 if (size(one%a) /= 2) STOP 34
146 if (size(one%a(2)%x) /= 5) STOP 35
147 if (any (one%a(2)%x /= [5,6,7,8,9])) STOP 36
149 deallocate (two%a)
150 one = two
151 if (allocated (one%a)) STOP 37
152 if (allocated (two%a)) STOP 38
153 end subroutine test4
156 call test1 ()
157 call test2 ()
158 call test3 ()
159 call test4 ()