aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/finalize_15.f90
blob: 3c18b2ae108d850cfd6ba18e607a2eb9d8ba0efd (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
! { dg-do run }
!
! PR fortran/37336
!
! Check the scalarizer/array packing with strides
! in the finalization wrapper
!
module m
  implicit none

  type t1
    integer :: i
  contains
    final :: fini_elem
  end type t1

  type, extends(t1) :: t1e
    integer :: j
  contains
    final :: fini_elem2
  end type t1e

  type t2
    integer :: i
  contains
    final :: fini_shape
  end type t2

  type, extends(t2) :: t2e
    integer :: j
  contains
    final :: fini_shape2
  end type t2e

  type t3
    integer :: i
  contains
    final :: fini_explicit
  end type t3

  type, extends(t3) :: t3e
    integer :: j
  contains
    final :: fini_explicit2
  end type t3e

  integer :: cnt1, cnt1e, cnt2, cnt2e, cnt3, cnt3e

contains

  impure elemental subroutine fini_elem(x)
    type(t1), intent(inout) :: x
    integer :: i, j, i2, j2

    if (cnt1e /= 5*4) call abort ()
    j = mod (cnt1,5)+1
    i = cnt1/5 + 1
    i2 = (i-1)*3 + 1
    j2 = (j-1)*2 + 1
    if (x%i /= j2 + 100*i2) call abort ()
    x%i = x%i * (-13)
    cnt1 = cnt1 + 1
  end subroutine fini_elem

  impure elemental subroutine fini_elem2(x)
    type(t1e), intent(inout) :: x
    integer :: i, j, i2, j2

    j = mod (cnt1e,5)+1
    i = cnt1e/5 + 1
    i2 = (i-1)*3 + 1
    j2 = (j-1)*2 + 1
    if (x%i /= j2 + 100*i2) call abort ()
    if (x%j /= (j2 + 100*i2)*100) call abort ()
    x%j = x%j * (-13)
    cnt1e = cnt1e + 1
  end subroutine fini_elem2

  subroutine fini_shape(x)
    type(t2) :: x(:,:)
    if (cnt2e /= 1 .or. cnt2 /= 0) call abort ()
    call check_var_sec(x%i, 1)
    x%i = x%i * (-13)
    cnt2 = cnt2 + 1
  end subroutine fini_shape

  subroutine fini_shape2(x)
    type(t2e) :: x(:,:)
    call check_var_sec(x%i, 1)
    call check_var_sec(x%j, 100)
    x%j = x%j * (-13)
    cnt2e = cnt2e + 1
  end subroutine fini_shape2

  subroutine fini_explicit(x)
    type(t3) :: x(5,4)
    if (cnt3e /= 1 .or. cnt3 /= 0) call abort ()
    call check_var_sec(x%i, 1)
    x%i = x%i * (-13)
    cnt3 = cnt3 + 1
  end subroutine fini_explicit

  subroutine fini_explicit2(x)
    type(t3e) :: x(5,4)
    call check_var_sec(x%i, 1)
    call check_var_sec(x%j, 100)
    x%j = x%j * (-13)
    cnt3e = cnt3e + 1
  end subroutine fini_explicit2

  subroutine fin_test_1(x)
    class(t1), intent(out) :: x(5,4)
  end subroutine fin_test_1

  subroutine fin_test_2(x)
    class(t2), intent(out) :: x(:,:)
  end subroutine fin_test_2

  subroutine fin_test_3(x)
    class(t3), intent(out) :: x(:,:)
    if (any (shape(x) /= [5,4])) call abort ()
  end subroutine fin_test_3

  subroutine check_var_sec(x, factor)
    integer :: x(:,:)
    integer, value :: factor
    integer :: i, j, i2, j2

    do i = 1, 4
      i2 = (i-1)*3 + 1
      do j = 1, 5
        j2 = (j-1)*2 + 1
        if (x(j,i) /= (j2 + 100*i2)*factor) call abort ()
      end do
    end do
  end subroutine check_var_sec
end module m


program test
  use m
  implicit none

  class(t1), allocatable :: x(:,:)
  class(t2), allocatable :: y(:,:)
  class(t3), allocatable :: z(:,:)
  integer :: i, j

  cnt1 = 0; cnt1e = 0; cnt2 = 0; cnt2e = 0;  cnt3 = 0; cnt3e = 0

  allocate (t1e :: x(10,10))
  allocate (t2e :: y(10,10))
  allocate (t3e :: z(10,10))

  select type(x)
    type is (t1e)
      do i = 1, 10
        do j = 1, 10
          x(j,i)%i = j + 100*i
          x(j,i)%j = (j + 100*i)*100
        end do
      end do
  end select

  select type(y)
    type is (t2e)
      do i = 1, 10
        do j = 1, 10
          y(j,i)%i = j + 100*i
          y(j,i)%j = (j + 100*i)*100
        end do
      end do
  end select

  select type(z)
    type is (t3e)
      do i = 1, 10
        do j = 1, 10
          z(j,i)%i = j + 100*i
          z(j,i)%j = (j + 100*i)*100
        end do
      end do
  end select

  if (cnt1 + cnt1e + cnt2 + cnt2e + cnt3 + cnt3e /= 0) call abort()

  call fin_test_1(x(::2,::3))
  if (cnt1 /= 5*4) call abort ()
  if (cnt1e /= 5*4) call abort ()
  cnt1 = 0; cnt1e = 0
  if (cnt2 + cnt2e + cnt3 + cnt3e /= 0) call abort()

  call fin_test_2(y(::2,::3))
  if (cnt2 /= 1) call abort ()
  if (cnt2e /= 1) call abort ()
  cnt2 = 0; cnt2e = 0
  if (cnt1 + cnt1e + cnt3 + cnt3e /= 0) call abort()

  call fin_test_3(z(::2,::3))
  if (cnt3 /= 1) call abort ()
  if (cnt3e /= 1) call abort ()
  cnt3 = 0; cnt3e = 0
  if (cnt1 + cnt1e + cnt2 + cnt2e /= 0) call abort()

  select type(x)
    type is (t1e)
      call check_val(x%i, 1)
      call check_val(x%j, 100)
  end select

  select type(y)
    type is (t2e)
      call check_val(y%i, 1)
      call check_val(y%j, 100)
  end select

  select type(z)
    type is (t3e)
      call check_val(z%i, 1)
      call check_val(z%j, 100)
  end select

contains
  subroutine check_val(x, factor)
    integer :: x(:,:)
    integer, value :: factor
    integer :: i, j
    do i = 1, 10
      do j = 1, 10
        if (mod (j-1, 2) == 0 .and. mod (i-1, 3) == 0) then
          if (x(j,i) /= (j + 100*i)*factor*(-13)) call abort ()
        else
          if (x(j,i) /= (j + 100*i)*factor) call abort ()
        end if
      end do
    end do
  end subroutine check_val
end program test