source: palm/trunk/SOURCE/transpose.f90 @ 1032

Last change on this file since 1032 was 1004, checked in by raasch, 12 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 19.9 KB
Line 
1 SUBROUTINE transpose_xy( f_in, work, f_out )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: transpose.f90 1004 2012-09-14 14:56:50Z letzel $
11!
12! 1003 2012-09-14 14:35:53Z raasch
13! indices nxa, nya, etc. replaced by nx, ny, etc.
14!
15! 683 2011-02-09 14:25:15Z raasch
16! openMP parallelization of transpositions for 2d-domain-decomposition
17!
18! 622 2010-12-10 08:08:13Z raasch
19! optional barriers included in order to speed up collective operations
20!
21! 164 2008-05-15 08:46:15Z raasch
22! f_inv changed from subroutine argument to automatic array in order to do
23! re-ordering from f_in to f_inv in one step, one array work is needed instead
24! of work1 and work2
25!
26! February 2007
27! RCS Log replace by Id keyword, revision history cleaned up
28!
29! Revision 1.2  2004/04/30 13:12:17  raasch
30! Switched from mpi_alltoallv to the simpler mpi_alltoall,
31! all former transpose-routine files collected in this file, enlarged
32! transposition arrays introduced
33!
34! Revision 1.1  2004/04/30 13:08:16  raasch
35! Initial revision (collection of former routines transpose_xy, transpose_xz,
36!                   transpose_yx, transpose_yz, transpose_zx, transpose_zy)
37!
38! Revision 1.1  1997/07/24 11:25:18  raasch
39! Initial revision
40!
41!
42! Description:
43! ------------
44! Transposition of input array (f_in) from x to y. For the input array, all
45! elements along x reside on the same PE, while after transposition, all
46! elements along y reside on the same PE.
47!------------------------------------------------------------------------------!
48
49    USE cpulog
50    USE indices
51    USE interfaces
52    USE pegrid
53    USE transpose_indices
54
55    IMPLICIT NONE
56
57    INTEGER ::  i, j, k, l, m, ys
58   
59    REAL ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x),   &
60             f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx),  &
61             f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y),  &
62             work(nnx*nny*nnz)
63
64#if defined( __parallel )
65
66!
67!-- Rearrange indices of input array in order to make data to be send
68!-- by MPI contiguous
69!$OMP  PARALLEL PRIVATE ( i, j, k )
70!$OMP  DO
71    DO  i = 0, nx
72       DO  k = nzb_x, nzt_x
73          DO  j = nys_x, nyn_x
74             f_inv(j,k,i) = f_in(i,j,k)
75          ENDDO
76       ENDDO
77    ENDDO
78!$OMP  END PARALLEL
79
80!
81!-- Transpose array
82    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'start' )
83    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
84    CALL MPI_ALLTOALL( f_inv(nys_x,nzb_x,0), sendrecvcount_xy, MPI_REAL, &
85                       work(1),              sendrecvcount_xy, MPI_REAL, &
86                       comm1dy, ierr )
87    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
88
89!
90!-- Reorder transposed array
91!$OMP  PARALLEL PRIVATE ( i, j, k, l, m, ys )
92!$OMP  DO
93    DO  l = 0, pdims(2) - 1
94       m  = l * ( nxr_y - nxl_y + 1 ) * ( nzt_y - nzb_y + 1 ) * &
95                ( nyn_x - nys_x + 1 )
96       ys = 0 + l * ( nyn_x - nys_x + 1 )
97       DO  i = nxl_y, nxr_y
98          DO  k = nzb_y, nzt_y
99             DO  j = ys, ys + nyn_x - nys_x
100                m = m + 1
101                f_out(j,i,k) = work(m)
102             ENDDO
103          ENDDO
104       ENDDO
105    ENDDO
106!$OMP  END PARALLEL
107
108#endif
109
110 END SUBROUTINE transpose_xy
111
112
113 SUBROUTINE transpose_xz( f_in, work, f_out )
114
115!------------------------------------------------------------------------------!
116! Description:
117! ------------
118! Transposition of input array (f_in) from x to z. For the input array, all
119! elements along x reside on the same PE, while after transposition, all
120! elements along z reside on the same PE.
121!------------------------------------------------------------------------------!
122
123    USE cpulog
124    USE indices
125    USE interfaces
126    USE pegrid
127    USE transpose_indices
128
129    IMPLICIT NONE
130
131    INTEGER ::  i, j, k, l, m, xs
132   
133    REAL ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x),  &
134             f_inv(nys:nyn,nxl:nxr,1:nz),         &
135             f_out(1:nz,nys:nyn,nxl:nxr),         &
136             work(nnx*nny*nnz)
137
138#if defined( __parallel )
139
140!
141!-- If the PE grid is one-dimensional along y, the array has only to be
142!-- reordered locally and therefore no transposition has to be done.
143    IF ( pdims(1) /= 1 )  THEN
144!
145!--    Reorder input array for transposition
146!$OMP  PARALLEL PRIVATE ( i, j, k, l, m, xs )
147!$OMP  DO
148       DO  l = 0, pdims(1) - 1
149          m  = l * ( nzt_x - nzb_x + 1 ) * nnx * ( nyn_x - nys_x + 1 )
150          xs = 0 + l * nnx
151          DO  k = nzb_x, nzt_x
152             DO  i = xs, xs + nnx - 1
153                DO  j = nys_x, nyn_x
154                   m = m + 1
155                   work(m) = f_in(i,j,k)
156                ENDDO
157             ENDDO
158          ENDDO
159       ENDDO
160!$OMP  END PARALLEL
161
162!
163!--    Transpose array
164       CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'start' )
165       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
166       CALL MPI_ALLTOALL( work(1),          sendrecvcount_zx, MPI_REAL, &
167                          f_inv(nys,nxl,1), sendrecvcount_zx, MPI_REAL, &
168                          comm1dx, ierr )
169       CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
170
171!
172!--    Reorder transposed array in a way that the z index is in first position
173!$OMP  PARALLEL PRIVATE ( i, j, k )
174!$OMP  DO
175       DO  k = 1, nz
176          DO  i = nxl, nxr
177             DO  j = nys, nyn
178                f_out(k,j,i) = f_inv(j,i,k)
179             ENDDO
180          ENDDO
181       ENDDO
182!$OMP  END PARALLEL
183    ELSE
184!
185!--    Reorder the array in a way that the z index is in first position
186!$OMP  PARALLEL PRIVATE ( i, j, k )
187!$OMP  DO
188       DO  i = nxl, nxr
189          DO  j = nys, nyn
190             DO  k = 1, nz
191                f_inv(j,i,k) = f_in(i,j,k)
192             ENDDO
193          ENDDO
194       ENDDO
195!$OMP  END PARALLEL
196
197!$OMP  PARALLEL PRIVATE ( i, j, k )
198!$OMP  DO
199       DO  k = 1, nz
200          DO  i = nxl, nxr
201             DO  j = nys, nyn
202                f_out(k,j,i) = f_inv(j,i,k)
203             ENDDO
204          ENDDO
205       ENDDO
206!$OMP  END PARALLEL
207
208    ENDIF
209
210
211#endif
212
213 END SUBROUTINE transpose_xz
214
215
216 SUBROUTINE transpose_yx( f_in, work, f_out )
217
218!------------------------------------------------------------------------------!
219! Description:
220! ------------
221! Transposition of input array (f_in) from y to x. For the input array, all
222! elements along y reside on the same PE, while after transposition, all
223! elements along x reside on the same PE.
224!------------------------------------------------------------------------------!
225
226    USE cpulog
227    USE indices
228    USE interfaces
229    USE pegrid
230    USE transpose_indices
231
232    IMPLICIT NONE
233
234    INTEGER ::  i, j, k, l, m, ys
235   
236    REAL ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y),  &
237             f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx), &
238             f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x), &
239             work(nnx*nny*nnz)
240
241#if defined( __parallel )
242
243!
244!-- Reorder input array for transposition
245!$OMP  PARALLEL PRIVATE ( i, j, k, l, m, ys )
246!$OMP  DO
247    DO  l = 0, pdims(2) - 1
248       m  = l * ( nxr_y - nxl_y + 1 ) * ( nzt_y - nzb_y + 1 ) * &
249                ( nyn_x - nys_x + 1 )
250       ys = 0 + l * ( nyn_x - nys_x + 1 )
251       DO  i = nxl_y, nxr_y
252          DO  k = nzb_y, nzt_y
253             DO  j = ys, ys + nyn_x - nys_x
254                m = m + 1
255                work(m) = f_in(j,i,k)
256             ENDDO
257          ENDDO
258       ENDDO
259    ENDDO
260!$OMP  END PARALLEL
261
262!
263!-- Transpose array
264    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'start' )
265    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
266    CALL MPI_ALLTOALL( work(1),              sendrecvcount_xy, MPI_REAL, &
267                       f_inv(nys_x,nzb_x,0), sendrecvcount_xy, MPI_REAL, &
268                       comm1dy, ierr )
269    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
270
271!
272!-- Reorder transposed array in a way that the x index is in first position
273!$OMP  PARALLEL PRIVATE ( i, j, k )
274!$OMP  DO
275    DO  i = 0, nx
276       DO  k = nzb_x, nzt_x
277          DO  j = nys_x, nyn_x
278             f_out(i,j,k) = f_inv(j,k,i)
279          ENDDO
280       ENDDO
281    ENDDO
282!$OMP  END PARALLEL
283
284#endif
285
286 END SUBROUTINE transpose_yx
287
288
289 SUBROUTINE transpose_yxd( f_in, work, f_out )
290
291!------------------------------------------------------------------------------!
292! Description:
293! ------------
294! Transposition of input array (f_in) from y to x. For the input array, all
295! elements along y reside on the same PE, while after transposition, all
296! elements along x reside on the same PE.
297! This is a direct transposition for arrays with indices in regular order
298! (k,j,i) (cf. transpose_yx).
299!------------------------------------------------------------------------------!
300
301    USE cpulog
302    USE indices
303    USE interfaces
304    USE pegrid
305    USE transpose_indices
306
307    IMPLICIT NONE
308
309    INTEGER ::  i, j, k, l, m, recvcount_yx, sendcount_yx, xs
310
311    REAL ::  f_in(1:nz,nys:nyn,nxl:nxr), f_inv(nxl:nxr,1:nz,nys:nyn), &
312             f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x),                     &
313             work(nnx*nny*nnz)
314
315#if defined( __parallel )
316
317!
318!-- Rearrange indices of input array in order to make data to be send
319!-- by MPI contiguous
320    DO  k = 1, nz
321       DO  j = nys, nyn
322          DO  i = nxl, nxr
323             f_inv(i,k,j) = f_in(k,j,i)
324          ENDDO
325       ENDDO
326    ENDDO
327
328!
329!-- Transpose array
330    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'start' )
331    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
332    CALL MPI_ALLTOALL( f_inv(nxl,1,nys), sendrecvcount_xy, MPI_REAL, &
333                       work(1),          sendrecvcount_xy, MPI_REAL, &
334                       comm1dx, ierr )
335    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
336
337!
338!-- Reorder transposed array
339    m = 0
340    DO  l = 0, pdims(1) - 1
341       xs = 0 + l * nnx
342       DO  j = nys_x, nyn_x
343          DO  k = 1, nz
344             DO  i = xs, xs + nnx - 1
345                m = m + 1
346                f_out(i,j,k) = work(m)
347             ENDDO
348          ENDDO
349       ENDDO
350    ENDDO
351
352#endif
353
354 END SUBROUTINE transpose_yxd
355
356
357 SUBROUTINE transpose_yz( f_in, work, f_out )
358
359!------------------------------------------------------------------------------!
360! Description:
361! ------------
362! Transposition of input array (f_in) from y to z. For the input array, all
363! elements along y reside on the same PE, while after transposition, all
364! elements along z reside on the same PE.
365!------------------------------------------------------------------------------!
366
367    USE cpulog
368    USE indices
369    USE interfaces
370    USE pegrid
371    USE transpose_indices
372
373    IMPLICIT NONE
374
375    INTEGER ::  i, j, k, l, m, zs
376   
377    REAL ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y),  &
378             f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny), &
379             f_out(nxl_z:nxr_z,nys_z:nyn_z,1:nz), &
380             work(nnx*nny*nnz)
381
382#if defined( __parallel )
383
384!
385!-- Rearrange indices of input array in order to make data to be send
386!-- by MPI contiguous
387!$OMP  PARALLEL PRIVATE ( i, j, k )
388!$OMP  DO
389    DO  j = 0, ny
390       DO  k = nzb_y, nzt_y
391          DO  i = nxl_y, nxr_y
392             f_inv(i,k,j) = f_in(j,i,k)
393          ENDDO
394       ENDDO
395    ENDDO
396!$OMP  END PARALLEL
397
398!
399!-- Move data to different array, because memory location of work1 is
400!-- needed further below (work1 = work2).
401!-- If the PE grid is one-dimensional along y, only local reordering
402!-- of the data is necessary and no transposition has to be done.
403    IF ( pdims(1) == 1 )  THEN
404!$OMP  PARALLEL PRIVATE ( i, j, k )
405!$OMP  DO
406       DO  j = 0, ny
407          DO  k = nzb_y, nzt_y
408             DO  i = nxl_y, nxr_y
409                f_out(i,j,k) = f_inv(i,k,j)
410             ENDDO
411          ENDDO
412       ENDDO
413!$OMP  END PARALLEL
414       RETURN
415    ENDIF
416
417!
418!-- Transpose array
419    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'start' )
420    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
421    CALL MPI_ALLTOALL( f_inv(nxl_y,nzb_y,0), sendrecvcount_yz, MPI_REAL, &
422                       work(1),              sendrecvcount_yz, MPI_REAL, &
423                       comm1dx, ierr )
424    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
425
426!
427!-- Reorder transposed array
428!$OMP  PARALLEL PRIVATE ( i, j, k, l, m, zs )
429!$OMP  DO
430    DO  l = 0, pdims(1) - 1
431       m  = l * ( nyn_z - nys_z + 1 ) * ( nzt_y - nzb_y + 1 ) * &
432                ( nxr_z - nxl_z + 1 )
433       zs = 1 + l * ( nzt_y - nzb_y + 1 )
434       DO  j = nys_z, nyn_z
435          DO  k = zs, zs + nzt_y - nzb_y
436             DO  i = nxl_z, nxr_z
437                m = m + 1
438                f_out(i,j,k) = work(m)
439             ENDDO
440          ENDDO
441       ENDDO
442    ENDDO
443!$OMP  END PARALLEL
444
445#endif
446
447 END SUBROUTINE transpose_yz
448
449
450 SUBROUTINE transpose_zx( f_in, work, f_out )
451
452!------------------------------------------------------------------------------!
453! Description:
454! ------------
455! Transposition of input array (f_in) from z to x. For the input array, all
456! elements along z reside on the same PE, while after transposition, all
457! elements along x reside on the same PE.
458!------------------------------------------------------------------------------!
459
460    USE cpulog
461    USE indices
462    USE interfaces
463    USE pegrid
464    USE transpose_indices
465
466    IMPLICIT NONE
467
468    INTEGER ::  i, j, k, l, m, xs
469   
470    REAL ::  f_in(1:nz,nys:nyn,nxl:nxr), f_inv(nys:nyn,nxl:nxr,1:nz), &
471             f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x),                     &
472             work(nnx*nny*nnz)
473
474#if defined( __parallel )
475
476!
477!-- Rearrange indices of input array in order to make data to be send
478!-- by MPI contiguous
479!$OMP  PARALLEL PRIVATE ( i, j, k )
480!$OMP  DO
481    DO  k = 1,nz
482       DO  i = nxl, nxr
483          DO  j = nys, nyn
484             f_inv(j,i,k) = f_in(k,j,i)
485          ENDDO
486       ENDDO
487    ENDDO
488!$OMP  END PARALLEL
489
490!
491!-- Move data to different array, because memory location of work1 is
492!-- needed further below (work1 = work2).
493!-- If the PE grid is one-dimensional along y, only local reordering
494!-- of the data is necessary and no transposition has to be done.
495    IF ( pdims(1) == 1 )  THEN
496!$OMP  PARALLEL PRIVATE ( i, j, k )
497!$OMP  DO
498       DO  k = 1, nz
499          DO  i = nxl, nxr
500             DO  j = nys, nyn
501                f_out(i,j,k) = f_inv(j,i,k)
502             ENDDO
503          ENDDO
504       ENDDO
505!$OMP  END PARALLEL
506       RETURN
507    ENDIF
508
509!
510!-- Transpose array
511    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'start' )
512    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
513    CALL MPI_ALLTOALL( f_inv(nys,nxl,1), sendrecvcount_zx, MPI_REAL, &
514                       work(1),          sendrecvcount_zx, MPI_REAL, &
515                       comm1dx, ierr )
516    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
517
518!
519!-- Reorder transposed array
520!$OMP  PARALLEL PRIVATE ( i, j, k, l, m, xs )
521!$OMP  DO
522    DO  l = 0, pdims(1) - 1
523       m  = l * ( nzt_x - nzb_x + 1 ) * nnx * ( nyn_x - nys_x + 1 )
524       xs = 0 + l * nnx
525       DO  k = nzb_x, nzt_x
526          DO  i = xs, xs + nnx - 1
527             DO  j = nys_x, nyn_x
528                m = m + 1
529                f_out(i,j,k) = work(m)
530             ENDDO
531          ENDDO
532       ENDDO
533    ENDDO
534!$OMP  END PARALLEL
535
536#endif
537
538 END SUBROUTINE transpose_zx
539
540
541 SUBROUTINE transpose_zy( f_in, work, f_out )
542
543!------------------------------------------------------------------------------!
544! Description:
545! ------------
546! Transposition of input array (f_in) from z to y. For the input array, all
547! elements along z reside on the same PE, while after transposition, all
548! elements along y reside on the same PE.
549!------------------------------------------------------------------------------!
550
551    USE cpulog
552    USE indices
553    USE interfaces
554    USE pegrid
555    USE transpose_indices
556
557    IMPLICIT NONE
558
559    INTEGER ::  i, j, k, l, m, zs
560   
561    REAL ::  f_in(nxl_z:nxr_z,nys_z:nyn_z,1:nz),  &
562             f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny), &
563             f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y), &
564             work(nnx*nny*nnz)
565
566#if defined( __parallel )
567
568!
569!-- If the PE grid is one-dimensional along y, the array has only to be
570!-- reordered locally and therefore no transposition has to be done.
571    IF ( pdims(1) /= 1 )  THEN
572!
573!--    Reorder input array for transposition
574!$OMP  PARALLEL PRIVATE ( i, j, k, l, m, zs )
575!$OMP  DO
576       DO  l = 0, pdims(1) - 1
577          m  = l * ( nyn_z - nys_z + 1 ) * ( nzt_y - nzb_y + 1 ) * &
578                   ( nxr_z - nxl_z + 1 )
579          zs = 1 + l * ( nzt_y - nzb_y + 1 )
580          DO  j = nys_z, nyn_z
581             DO  k = zs, zs + nzt_y - nzb_y
582                DO  i = nxl_z, nxr_z
583                   m = m + 1
584                   work(m) = f_in(i,j,k)
585                ENDDO
586             ENDDO
587          ENDDO
588       ENDDO
589!$OMP  END PARALLEL
590
591!
592!--    Transpose array
593       CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'start' )
594       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
595       CALL MPI_ALLTOALL( work(1),              sendrecvcount_yz, MPI_REAL, &
596                          f_inv(nxl_y,nzb_y,0), sendrecvcount_yz, MPI_REAL, &
597                          comm1dx, ierr )
598       CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
599
600!
601!--    Reorder transposed array in a way that the y index is in first position
602!$OMP  PARALLEL PRIVATE ( i, j, k )
603!$OMP  DO
604       DO  j = 0, ny
605          DO  k = nzb_y, nzt_y
606             DO  i = nxl_y, nxr_y
607                f_out(j,i,k) = f_inv(i,k,j)
608             ENDDO
609          ENDDO
610       ENDDO
611!$OMP  END PARALLEL
612    ELSE
613!
614!--    Reorder the array in a way that the y index is in first position
615!$OMP  PARALLEL PRIVATE ( i, j, k )
616!$OMP  DO
617       DO  k = nzb_y, nzt_y
618          DO  j = 0, ny
619             DO  i = nxl_y, nxr_y
620                f_inv(i,k,j) = f_in(i,j,k)
621             ENDDO
622          ENDDO
623       ENDDO
624!$OMP  END PARALLEL
625!
626!--    Move data to output array
627!$OMP  PARALLEL PRIVATE ( i, j, k )
628!$OMP  DO
629       DO  k = nzb_y, nzt_y
630          DO  i = nxl_y, nxr_y
631             DO  j = 0, ny
632                f_out(j,i,k) = f_inv(i,k,j)
633             ENDDO
634          ENDDO
635       ENDDO
636!$OMP  END PARALLEL
637
638    ENDIF
639
640#endif
641
642 END SUBROUTINE transpose_zy
643
644
645 SUBROUTINE transpose_zyd( f_in, work, f_out )
646
647!------------------------------------------------------------------------------!
648! Description:
649! ------------
650! Transposition of input array (f_in) from z to y. For the input array, all
651! elements along z reside on the same PE, while after transposition, all
652! elements along y reside on the same PE.
653! This is a direct transposition for arrays with indices in regular order
654! (k,j,i) (cf. transpose_zy).
655!------------------------------------------------------------------------------!
656
657    USE cpulog
658    USE indices
659    USE interfaces
660    USE pegrid
661    USE transpose_indices
662
663    IMPLICIT NONE
664
665    INTEGER ::  i, j, k, l, m, ys
666   
667    REAL ::  f_in(1:nz,nys:nyn,nxl:nxr), f_inv(nys:nyn,nxl:nxr,1:nz), &
668             f_out(0:ny,nxl_yd:nxr_yd,nzb_yd:nzt_yd),                 &
669             work(nnx*nny*nnz)
670
671#if defined( __parallel )
672
673!
674!-- Rearrange indices of input array in order to make data to be send
675!-- by MPI contiguous
676    DO  i = nxl, nxr
677       DO  j = nys, nyn
678          DO  k = 1, nz
679             f_inv(j,i,k) = f_in(k,j,i)
680          ENDDO
681       ENDDO
682    ENDDO
683
684!
685!-- Move data to different array, because memory location of work1 is
686!-- needed further below (work1 = work2).
687!-- If the PE grid is one-dimensional along x, only local reordering
688!-- of the data is necessary and no transposition has to be done.
689    IF ( pdims(2) == 1 )  THEN
690       DO  k = 1, nz
691          DO  i = nxl, nxr
692             DO  j = nys, nyn
693                f_out(j,i,k) = f_inv(j,i,k)
694             ENDDO
695          ENDDO
696       ENDDO
697       RETURN
698    ENDIF
699
700!
701!-- Transpose array
702    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'start' )
703    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
704    CALL MPI_ALLTOALL( f_inv(nys,nxl,1), sendrecvcount_zyd, MPI_REAL, &
705                       work(1),          sendrecvcount_zyd, MPI_REAL, &
706                       comm1dy, ierr )
707    CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
708
709!
710!-- Reorder transposed array
711    m = 0
712    DO  l = 0, pdims(2) - 1
713       ys = 0 + l * nny
714       DO  k = nzb_yd, nzt_yd
715          DO  i = nxl_yd, nxr_yd
716             DO  j = ys, ys + nny - 1
717                m = m + 1
718                f_out(j,i,k) = work(m)
719             ENDDO
720          ENDDO
721       ENDDO
722    ENDDO
723
724#endif
725
726 END SUBROUTINE transpose_zyd
Note: See TracBrowser for help on using the repository browser.