summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/intent_out_11.f90
blob: c266385b49f146e077fabc263b5e60c9c9f709b7 (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
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
! { dg-do compile }
! { dg-options "-cpp -fcoarray=lib" }
! PR 87397 - this used to generate an ICE.

! Coarray Distributed Transpose Test
!
! Copyright (c) 2012-2014, Sourcery, Inc.
! All rights reserved.
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions are met:
!     * Redistributions of source code must retain the above copyright
!       notice, this list of conditions and the following disclaimer.
!     * Redistributions in binary form must reproduce the above copyright
!       notice, this list of conditions and the following disclaimer in the
!       documentation and/or other materials provided with the distribution.
!     * Neither the name of the Sourcery, Inc., nor the
!       names of its contributors may be used to endorse or promote products
!       derived from this software without specific prior written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND
! ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
! WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
! DISCLAIMED. IN NO EVENT SHALL SOURCERY, INC., BE LIABLE FOR ANY
! DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
! (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
! LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND
! ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
! (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
!
! Robodoc header:
!****m* dist_transpose/run_size
! NAME
!   run_size
!  SYNOPSIS
!   Encapsulate problem state, wall-clock timer interface, integer broadcasts, and a data copy.
!******
!==================  test transposes with integer x,y,z values  ===============================
module run_size
    use iso_fortran_env
    implicit none

    integer(int64), codimension[*] :: nx, ny, nz
    integer(int64), codimension[*] :: my, mx, first_y, last_y, first_x, last_x
    integer(int64) :: my_node, num_nodes
    real(real64), codimension[*] :: tran_time


contains

!****s* run_size/broadcast_int
! NAME
!   broadcast_int
!  SYNOPSIS
!   Broadcast a scalar coarray integer from image 1 to all other images.
!******
    subroutine broadcast_int( variable )
        integer(int64), codimension[*] :: variable
        integer(int64) :: i
        if( my_node == 1 ) then
            do i = 2, num_nodes;    variable[i] = variable;      end do
        end if
    end subroutine broadcast_int

subroutine copy3( A,B, n1, sA1, sB1, n2, sA2, sB2, n3, sA3, sB3 )
  implicit none
  complex, intent(in)  :: A(0:*)
  complex, intent(out) :: B(0:*)
  integer(int64), intent(in) :: n1, sA1, sB1
  integer(int64), intent(in) :: n2, sA2, sB2
  integer(int64), intent(in) :: n3, sA3, sB3
  integer(int64) i,j,k

  do k=0,n3-1
     do j=0,n2-1
        do i=0,n1-1
           B(i*sB1+j*sB2+k*sB3) = A(i*sA1+j*sA2+k*sA3)
        end do
     end do
  end do
end subroutine copy3

end module run_size

!****e* dist_transpose/coarray_distributed_transpose
! NAME
!   coarray_distributed_transpose
! SYNOPSIS
!   This program tests the transpose routines used in Fourier-spectral simulations of homogeneous turbulence.
!   The data is presented to the physics routines as groups of y-z or x-z planes distributed among the images.
!   The (out-of-place) transpose routines do the x <--> y transposes required and consist of transposes within
!   data blocks (intra-image) and a transpose of the distribution of these blocks among the images (inter-image).
!
!   Two methods are tested here:
!   RECEIVE: receive block from other image and transpose it
!   SEND:    transpose block and send it to other image
!
!   This code is the coarray analog of mpi_distributed_transpose.
!******

program coarray_distributed_transpose
  !(***********************************************************************************************************
  !                   m a i n   p r o g r a m
  !***********************************************************************************************************)
      use run_size
      implicit none

      complex, allocatable ::  u(:,:,:,:)[:]    ! u(nz,4,first_x:last_x,ny)[*]    !(*-- ny = my * num_nodes --*)
      complex, allocatable ::  ur(:,:,:,:)[:]   !ur(nz,4,first_y:last_y,nx/2)[*]  !(*-- nx/2 = mx * num_nodes --*)
      complex, allocatable :: bufr_X_Y(:,:,:,:)
      complex, allocatable :: bufr_Y_X(:,:,:,:)
      integer(int64) :: x, y, z, msg_size, iter

      num_nodes = num_images()
      my_node = this_image()

      if( my_node == 1 ) then
           !write(6,*) "nx,ny,nz : ";      read(5,*) nx, ny, nz
            nx=32; ny=32; nz=32
            call broadcast_int( nx );        call broadcast_int( ny );        call broadcast_int( nz );
       end if
      sync all  !-- other nodes wait for broadcast!


      if ( mod(ny,num_nodes) == 0)  then;   my = ny / num_nodes
                                    else;   write(6,*) "node ", my_node, " ny not multiple of num_nodes";     error stop
      end if

      if ( mod(nx/2,num_nodes) == 0)  then;   mx = nx/2 / num_nodes
                                    else;   write(6,*) "node ", my_node, "nx/2 not multiple of num_nodes";     error stop
      end if

      first_y = (my_node-1)*my + 1;   last_y  = (my_node-1)*my + my
      first_x = (my_node-1)*mx + 1;   last_x  = (my_node-1)*mx + mx

      allocate (  u(nz , 4 , first_x:last_x , ny)  [*] )   !(*-- y-z planes --*)
      allocate ( ur(nz , 4 , first_y:last_y , nx/2)[*] )   !(*-- x-z planes --*)
      allocate ( bufr_X_Y(nz,4,mx,my) )
      allocate ( bufr_Y_X(nz,4,my,mx) )

      msg_size = nz*4*mx*my     !-- message size (complex data items)

!---------  initialize data u (mx y-z planes per image) ----------

        do x = first_x, last_x
            do y = 1, ny
                do z = 1, nz
                    u(z,1,x,y) = x
                    u(z,2,x,y) = y
                    u(z,3,x,y) = z
                end do
            end do
        end do

    tran_time = 0
    do iter = 1, 2  !--- 2 transform pairs per second-order time step

!---------  transpose data u -> ur (mx y-z planes to my x-z planes per image)  --------

      ur = 0

      call transpose_X_Y

!--------- test data ur (my x-z planes per image) ----------

        do x = 1, nx/2
            do y = first_y, last_y
                do z = 1, nz
                    if ( real(ur(z,1,y,x)) /= x .or. real(ur(z,2,y,x)) /= y .or. real(ur(z,3,y,x)) /= z )then
                        write(6,fmt="(A,i3,3(6X,A,f7.3,i4))") "transpose_X_Y failed:  image ", my_node &
                            , " X ",real(ur(z,1,y,x)),x, "  Y ",real(ur(z,2,y,x)),y, "  Z ", real(ur(z,3,y,x)),z
                        stop
                    end if
                end do
            end do
        end do

!---------  transpose data ur -> u (my x-z planes to mx y-z planes per image)  --------

      u = 0
      call transpose_Y_X

!--------- test data u (mx y-z planes per image) ----------

        do x = first_x, last_x
            do y = 1, ny
                do z = 1, nz
                    if ( real(u(z,1,x,y)) /= x .or. real(u(z,2,x,y)) /= y .or. real(u(z,3,x,y)) /= z )then
                        write(6,fmt="(A,i3,3(6X,A,f7.3,i4))") "transpose_Y_X failed:  image ", my_node &
                            , " X ",real(u(z,1,x,y)),x, "  Y ",real(u(z,2,x,y)),y, "  Z ", real(u(z,3,x,y)),z
                        stop
                    end if
                end do
            end do
        end do
    end do

        sync all
        if( my_node == 1 )  write(6,fmt="(A,f8.3)")  "test passed:  tran_time ", tran_time

    deallocate ( bufr_X_Y );    deallocate ( bufr_Y_X )

!=========================   end of main executable  =============================

contains

!-------------   out-of-place transpose data_s --> data_r  ----------------------------

 subroutine transpose_X_Y

    use run_size
    implicit none

    integer(int64) :: i,stage
    real(real64) :: tmp

    sync all   !--  wait for other nodes to finish compute
    call cpu_time(tmp)
    tran_time = tran_time - tmp

    call copy3 (    u(1,1,first_x,1+(my_node-1)*my) &                   !-- intra-node transpose
                ,  ur(1,1,first_y,1+(my_node-1)*mx) &                   !-- no inter-node transpose needed
                ,   nz*3, 1_8, 1_8        &                                 !-- note: only 3 of 4 words needed
                ,   mx, nz*4, nz*4*my &
                ,   my, nz*4*mx, nz*4 )

#define RECEIVE
#ifdef RECEIVE

    do stage = 1, num_nodes-1
        i = 1 + mod( my_node-1+stage, num_nodes )
        bufr_X_Y(:,:,:,:) = u(:,:,:,1+(my_node-1)*my:my_node*my)[i]         !-- inter-node transpose to buffer
        call copy3 ( bufr_X_Y, ur(1,1,first_y,1+(i-1)*mx)  &                !-- intra-node transpose from buffer
                        ,   nz*3, 1_8, 1_8        &                             !-- note: only 3 of 4 words needed
                        ,   mx, nz*4, nz*4*my &
                        ,   my, nz*4*mx, nz*4 )
    end do

#else

    do stage = 1, num_nodes-1
        i = 1 + mod( my_node-1+stage, num_nodes )
        call  copy3 ( u(1,1,first_x,1+(i-1)*my), bufr_Y_X   &        !-- intra-node transpose to buffer
                    ,   nz*3, 1_8, 1_8        &
                    ,   mx, nz*4, nz*4*my &
                    ,   my, nz*4*mx, nz*4 )
        ur(:,:,:,1+(my_node-1)*mx:my_node*mx)[i] = bufr_Y_X(:,:,:,:)        !-- inter-node transpose from buffer
    end do

#endif

    sync all     !--  wait for other nodes to finish transpose
    call cpu_time(tmp)
    tran_time = tran_time + tmp

 end  subroutine transpose_X_Y

!-------------   out-of-place transpose data_r --> data_s  ----------------------------

subroutine transpose_Y_X
    use run_size
    implicit none

    integer(int64) :: i, stage
    real(real64) :: tmp

    sync all   !--  wait for other nodes to finish compute
    call cpu_time(tmp)
    tran_time = tran_time - tmp

    call copy3 (   ur(1,1,first_y,1+(my_node-1)*mx) &                   !-- intra-node transpose
                ,   u(1,1,first_x,1+(my_node-1)*my) &                   !-- no inter-node transpose needed
                ,   nz*4, 1_8, 1_8        &                                 !-- note: all 4 words needed
                ,   my, nz*4, nz*4*mx &
                ,   mx, nz*4*my, nz*4 )

#define RECEIVE
#ifdef RECEIVE

    do stage = 1, num_nodes-1
        i = 1 + mod( my_node-1+stage, num_nodes )
        bufr_Y_X(:,:,:,:) = ur(:,:,:,1+(my_node-1)*mx:my_node*mx)[i]        !-- inter-node transpose to buffer
        call copy3 ( bufr_Y_X, u(1,1,first_x,1+(i-1)*my)  &                 !-- intra-node transpose from buffer
                    ,   nz*4, 1_8, 1_8        &
                    ,   my, nz*4, nz*4*mx &
                    ,   mx, nz*4*my, nz*4 )
    end do

#else

    do stage = 1, num_nodes-1
        i = 1 + mod( my_node-1+stage, num_nodes )
        call copy3 ( ur(1,1,first_y,1+(i-1)*mx), bufr_X_Y  &                 !-- intra-node transpose from buffer
                    ,   nz*4, 1_8, 1_8        &
                    ,   my, nz*4, nz*4*mx &
                    ,   mx, nz*4*my, nz*4 )
        u(:,:,:,1+(my_node-1)*my:my_node*my)[i] = bufr_X_Y(:,:,:,:)        !-- inter-node transpose from buffer
    end do

#endif

    sync all     !--  wait for other nodes to finish transpose
    call cpu_time(tmp)
    tran_time = tran_time + tmp

 end  subroutine transpose_Y_X


end program coarray_distributed_transpose