Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/transpose.f90

    r1319 r1320  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! old module precision_kind is removed,
     26! revision history before 2012 removed,
     27! comment fields (!:) to be used for variable explanations added to
     28! all variable declaration statements
    2329!
    2430! Former revisions:
     
    5561! indices nxa, nya, etc. replaced by nx, ny, etc.
    5662!
    57 ! 683 2011-02-09 14:25:15Z raasch
    58 ! openMP parallelization of transpositions for 2d-domain-decomposition
    59 !
    60 ! 622 2010-12-10 08:08:13Z raasch
    61 ! optional barriers included in order to speed up collective operations
    62 !
    63 ! 164 2008-05-15 08:46:15Z raasch
    64 ! f_inv changed from subroutine argument to automatic array in order to do
    65 ! re-ordering from f_in to f_inv in one step, one array work is needed instead
    66 ! of work1 and work2
    67 !
    68 ! February 2007
    69 ! RCS Log replace by Id keyword, revision history cleaned up
    70 !
    71 ! Revision 1.2  2004/04/30 13:12:17  raasch
    72 ! Switched from mpi_alltoallv to the simpler mpi_alltoall,
    73 ! all former transpose-routine files collected in this file, enlarged
    74 ! transposition arrays introduced
    75 !
    76 ! Revision 1.1  2004/04/30 13:08:16  raasch
    77 ! Initial revision (collection of former routines transpose_xy, transpose_xz,
    78 !                   transpose_yx, transpose_yz, transpose_zx, transpose_zy)
    79 !
    8063! Revision 1.1  1997/07/24 11:25:18  raasch
    8164! Initial revision
     
    8871!------------------------------------------------------------------------------!
    8972
    90      USE indices
    91      USE transpose_indices
     73     USE indices,                                                              &
     74         ONLY:  nx
     75
     76     USE kinds
     77
     78     USE transpose_indices,                                                    &
     79         ONLY:  nxl_z, nxr_z, nyn_x, nyn_z, nys_x, nys_z, nzb_x, nzt_x
    9280
    9381     IMPLICIT NONE
    9482
    95      REAL ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x)
    96      REAL ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx)
    97 
    98 
    99      INTEGER ::  i, j, k
    100 
     83     REAL(wp) ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x)  !:
     84     REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !:
     85
     86
     87     INTEGER(iwp) ::  i !:
     88     INTEGER(iwp) ::  j !:
     89     INTEGER(iwp) ::  k !:
    10190!
    10291!-- Rearrange indices of input array in order to make data to be send
     
    128117!------------------------------------------------------------------------------!
    129118
    130     USE cpulog
    131     USE indices
     119    USE cpulog,                                                                &
     120        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     121
     122    USE indices,                                                               &
     123        ONLY:  nx, ny
     124       
     125    USE kinds
     126
    132127    USE pegrid
    133     USE transpose_indices
     128
     129    USE transpose_indices,                                                     &
     130        ONLY:  nxl_y, nxr_y, nyn_x, nys_x, nzb_x, nzb_y, nzt_x, nzt_y
    134131
    135132    IMPLICIT NONE
    136133
    137     INTEGER ::  i, j, k, l, ys
    138    
    139     REAL ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx), f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y)
    140 
    141     REAL, DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work
     134    INTEGER(iwp) ::  i  !:
     135    INTEGER(iwp) ::  j  !:
     136    INTEGER(iwp) ::  k  !:
     137    INTEGER(iwp) ::  l  !:
     138    INTEGER(iwp) ::  ys !:
     139 
     140    REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !:
     141    REAL(wp) ::  f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y) !:
     142
     143    REAL(wp), DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work !:
    142144
    143145
     
    207209!------------------------------------------------------------------------------!
    208210
    209      USE indices
    210      USE transpose_indices
     211     USE indices,                                                              &
     212         ONLY:  nxl, nxr, nyn, nys, nz
     213
     214     USE kinds
    211215
    212216     IMPLICIT NONE
    213217
    214      REAL ::  f_inv(nys:nyn,nxl:nxr,1:nz)
    215      REAL ::  f_out(1:nz,nys:nyn,nxl:nxr)
    216 
    217 
    218      INTEGER ::  i, j, k
    219 
     218     REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz) !:
     219     REAL(wp) ::  f_out(1:nz,nys:nyn,nxl:nxr) !:
     220
     221     INTEGER(iwp) ::  i !:
     222     INTEGER(iwp) ::  j !:
     223     INTEGER(iwp) ::  k !:
    220224!
    221225!-- Rearrange indices of input array in order to make data to be send
     
    249253!------------------------------------------------------------------------------!
    250254
    251     USE cpulog
    252     USE indices
    253     USE pegrid
    254     USE transpose_indices
     255    USE cpulog,                                                                &
     256        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     257
     258    USE indices,                                                               &
     259        ONLY:  nnx, nx, nxl, nxr, ny, nyn, nys, nz
     260
     261    USE kinds
     262
     263    USE pegrid,                                                                &
     264        ONLY:  collective_wait, comm1dx, comm2d, ierr, MPI_DOUBLE_PRECISION,   &
     265               pdims, sendrecvcount_zx
     266
     267    USE transpose_indices,                                                     &
     268        ONLY:  nyn_x, nys_x, nzb_x, nzt_x
    255269
    256270    IMPLICIT NONE
    257271
    258     INTEGER ::  i, j, k, l, xs
    259    
    260     REAL ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x), f_inv(nys:nyn,nxl:nxr,1:nz)
    261 
    262     REAL, DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work
     272    INTEGER(iwp) ::  i  !:
     273    INTEGER(iwp) ::  j  !:
     274    INTEGER(iwp) ::  k  !:
     275    INTEGER(iwp) ::  l  !:
     276    INTEGER(iwp) ::  xs !:
     277
     278    REAL(wp) ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !:
     279    REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz) !:
     280
     281    REAL(wp), DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work !:
    263282
    264283
     
    331350!------------------------------------------------------------------------------!
    332351
    333      USE indices
    334      USE transpose_indices
     352     USE indices,                                                              &
     353         ONLY:  nx
     354
     355     USE kinds
     356
     357     USE transpose_indices,                                                    &
     358         ONLY:  nyn_x, nys_x, nzb_x, nzt_x
    335359
    336360     IMPLICIT NONE
    337361
    338      REAL ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx)
    339      REAL ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x)
    340 
    341 
    342      INTEGER ::  i, j, k
    343 
     362     REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !:
     363     REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !:
     364
     365
     366     INTEGER(iwp) ::  i !:
     367     INTEGER(iwp) ::  j !:
     368     INTEGER(iwp) ::  k !:
    344369!
    345370!-- Rearrange indices of input array in order to make data to be send
     
    371396!------------------------------------------------------------------------------!
    372397
    373     USE cpulog
    374     USE indices
    375     USE pegrid
    376     USE transpose_indices
     398    USE cpulog,                                                                &
     399        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     400
     401    USE indices,                                                               &
     402        ONLY:  nx, ny
     403
     404    USE kinds
     405
     406    USE pegrid,                                                                &
     407        ONLY:  collective_wait, comm1dy, comm2d, ierr, MPI_DOUBLE_PRECISION,   &
     408               numprocs, pdims, sendrecvcount_xy
     409
     410    USE transpose_indices,                                                     &
     411        ONLY:  nxl_y, nxr_y, nyn_x, nys_x, nzb_x, nzb_y, nzt_x, nzt_y
    377412
    378413    IMPLICIT NONE
    379414
    380     INTEGER ::  i, j, k, l, ys
    381    
    382     REAL ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y), f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx)
    383 
    384     REAL, DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work
     415    INTEGER(iwp) ::  i  !:
     416    INTEGER(iwp) ::  j  !:
     417    INTEGER(iwp) ::  k  !:
     418    INTEGER(iwp) ::  l  !:
     419    INTEGER(iwp) ::  ys !:
     420
     421    REAL(wp) ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y)  !:
     422    REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !:
     423
     424    REAL(wp), DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work !:
    385425
    386426
     
    453493!------------------------------------------------------------------------------!
    454494
    455     USE cpulog
    456     USE indices
    457     USE pegrid
    458     USE transpose_indices
     495    USE cpulog,                                                                &
     496        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     497
     498    USE indices,                                                               &
     499        ONLY:  nnx, nny, nnz, nx, nxl, nxr, nyn, nys, nz
     500
     501    USE kinds
     502
     503    USE pegrid,                                                                &
     504        ONLY:  collective_wait, comm1dx, comm2d, ierr, MPI_DOUBLE_PRECISION,   &
     505               pdims, sendrecvcount_xy
     506
     507    USE transpose_indices,                                                     &
     508        ONLY:  nyn_x, nys_x, nzb_x, nzt_x
    459509
    460510    IMPLICIT NONE
    461511
    462     INTEGER ::  i, j, k, l, m, xs
    463 
    464     REAL ::  f_in(1:nz,nys:nyn,nxl:nxr), f_inv(nxl:nxr,1:nz,nys:nyn), &
    465              f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x),                     &
    466              work(nnx*nny*nnz)
    467 
     512    INTEGER(iwp) ::  i  !:
     513    INTEGER(iwp) ::  j  !:
     514    INTEGER(iwp) ::  k  !:
     515    INTEGER(iwp) ::  l  !:
     516    INTEGER(iwp) ::  m  !:
     517    INTEGER(iwp) ::  xs !:
     518
     519    REAL(wp) ::  f_in(1:nz,nys:nyn,nxl:nxr)          !:
     520    REAL(wp) ::  f_inv(nxl:nxr,1:nz,nys:nyn)         !:
     521    REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !:
     522    REAL(wp) ::  work(nnx*nny*nnz)                   !:
    468523#if defined( __parallel )
    469524
     
    517572!------------------------------------------------------------------------------!
    518573
    519      USE indices
    520      USE transpose_indices
     574     USE indices,                                                              &
     575         ONLY:  ny
     576
     577     USE kinds
     578
     579     USE transpose_indices,                                                    &
     580         ONLY:  nxl_y, nxr_y, nzb_y, nzt_y
    521581
    522582     IMPLICIT NONE
    523583
    524      REAL ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y)
    525      REAL ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny)
    526 
    527 
    528      INTEGER ::  i, j, k
     584     REAL(wp) ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y)  !:
     585     REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !:
     586
     587     INTEGER(iwp) ::  i !:
     588     INTEGER(iwp) ::  j !:
     589     INTEGER(iwp) ::  k !:
    529590
    530591!
     
    557618!------------------------------------------------------------------------------!
    558619
    559     USE cpulog
    560     USE indices
    561     USE pegrid
    562     USE transpose_indices
     620    USE cpulog,                                                                &
     621        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     622
     623    USE indices,                                                               &
     624        ONLY:  ny, nz
     625
     626    USE kinds
     627
     628    USE pegrid,                                                                &
     629        ONLY:  collective_wait, comm1dx, comm2d, ierr, MPI_DOUBLE_PRECISION,   &
     630               pdims, sendrecvcount_yz
     631
     632    USE transpose_indices,                                                     &
     633        ONLY:  nxl_y, nxl_z, nxr_y, nxr_z, nyn_z, nys_z, nzb_y, nzt_y
    563634
    564635    IMPLICIT NONE
    565636
    566     INTEGER ::  i, j, k, l, zs
    567    
    568     REAL ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny), f_out(nxl_z:nxr_z,nys_z:nyn_z,1:nz)
    569 
    570     REAL, DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work
     637    INTEGER(iwp) ::  i  !:
     638    INTEGER(iwp) ::  j  !:
     639    INTEGER(iwp) ::  k  !:
     640    INTEGER(iwp) ::  l  !:
     641    INTEGER(iwp) ::  zs !:
     642
     643    REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !:
     644    REAL(wp) ::  f_out(nxl_z:nxr_z,nys_z:nyn_z,1:nz) !:
     645
     646    REAL(wp), DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work !:
    571647
    572648
     
    637713!------------------------------------------------------------------------------!
    638714
    639      USE indices
    640      USE transpose_indices
     715     USE indices,                                                              &
     716         ONLY:  nxl, nxr, nyn, nys, nz
     717
     718     USE kinds
    641719
    642720     IMPLICIT NONE
    643721
    644      REAL ::  f_in(1:nz,nys:nyn,nxl:nxr)
    645      REAL ::  f_inv(nys:nyn,nxl:nxr,1:nz)
    646 
    647 
    648      INTEGER ::  i, j, k
     722     REAL(wp) ::  f_in(1:nz,nys:nyn,nxl:nxr)  !:
     723     REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz) !:
     724
     725     INTEGER(iwp) ::  i !:
     726     INTEGER(iwp) ::  j !:
     727     INTEGER(iwp) ::  k !:
    649728
    650729!
     
    677756!------------------------------------------------------------------------------!
    678757
    679     USE cpulog
    680     USE indices
    681     USE pegrid
    682     USE transpose_indices
     758    USE cpulog,                                                                &
     759        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     760
     761    USE indices,                                                               &
     762        ONLY:  nnx, nx, nxl, nxr, nyn, nys, nz
     763
     764    USE kinds
     765
     766    USE pegrid,                                                                &
     767        ONLY:  collective_wait, comm1dx, comm2d, ierr, MPI_DOUBLE_PRECISION,   &
     768               pdims, sendrecvcount_zx
     769
     770    USE transpose_indices,                                                     &
     771        ONLY:  nyn_x, nys_x, nzb_x, nzt_x
    683772
    684773    IMPLICIT NONE
    685774
    686     INTEGER ::  i, j, k, l, xs
    687    
    688     REAL ::  f_inv(nys:nyn,nxl:nxr,1:nz), f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x)
    689 
    690     REAL, DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work
     775    INTEGER(iwp) ::  i  !:
     776    INTEGER(iwp) ::  j  !:
     777    INTEGER(iwp) ::  k  !:
     778    INTEGER(iwp) ::  l  !:
     779    INTEGER(iwp) ::  xs !:
     780
     781    REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz)         !:
     782    REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !:
     783
     784    REAL(wp), DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work !:
    691785
    692786
     
    757851!------------------------------------------------------------------------------!
    758852
    759      USE indices
    760      USE transpose_indices
     853     USE indices,                                                              &
     854         ONLY:  ny
     855
     856     USE kinds
     857
     858     USE transpose_indices,                                                    &
     859         ONLY:  nxl_y, nxr_y, nzb_y, nzt_y
    761860
    762861     IMPLICIT NONE
    763862
    764      REAL ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny)
    765      REAL ::  f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y)
    766 
    767 
    768      INTEGER ::  i, j, k
     863     REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !:
     864     REAL(wp) ::  f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y) !:
     865
     866
     867     INTEGER(iwp) ::  i !:
     868     INTEGER(iwp) ::  j !:
     869     INTEGER(iwp) ::  k !:
    769870
    770871!
     
    797898!------------------------------------------------------------------------------!
    798899
    799     USE cpulog
    800     USE indices
    801     USE pegrid
    802     USE transpose_indices
     900    USE cpulog,                                                                &
     901        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     902
     903    USE indices,                                                               &
     904        ONLY:  ny, nz
     905
     906    USE kinds
     907
     908    USE pegrid,                                                                &
     909        ONLY:  collective_wait, comm1dx, comm2d, ierr, MPI_DOUBLE_PRECISION,   &
     910               pdims, sendrecvcount_yz
     911
     912    USE transpose_indices,                                                     &
     913        ONLY:  nxl_y, nxl_z, nxr_y, nxr_z, nyn_z, nys_z, nzb_y, nzt_y
    803914
    804915    IMPLICIT NONE
    805916
    806     INTEGER ::  i, j, k, l, zs
    807    
    808     REAL ::  f_in(nxl_z:nxr_z,nys_z:nyn_z,1:nz), f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny)
    809 
    810     REAL, DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work
    811 
     917    INTEGER(iwp) ::  i  !:
     918    INTEGER(iwp) ::  j  !:
     919    INTEGER(iwp) ::  k  !:
     920    INTEGER(iwp) ::  l  !:
     921    INTEGER(iwp) ::  zs !:
     922
     923    REAL(wp) ::  f_in(nxl_z:nxr_z,nys_z:nyn_z,1:nz)  !:
     924    REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !:
     925
     926    REAL(wp), DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work !:
    812927
    813928!
     
    881996!------------------------------------------------------------------------------!
    882997
    883     USE cpulog
    884     USE indices
    885     USE pegrid
    886     USE transpose_indices
     998    USE cpulog,                                                                &
     999        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     1000
     1001    USE indices,                                                               &
     1002        ONLY:  nnx, nny, nnz, nxl, nxr, nyn, nys, ny, nz
     1003
     1004    USE kinds
     1005
     1006    USE pegrid,                                                                &
     1007        ONLY:  collective_wait, comm1dy, comm2d, ierr, MPI_DOUBLE_PRECISION,   &
     1008               pdims, sendrecvcount_zyd
     1009
     1010    USE transpose_indices,                                                     &
     1011        ONLY:  nxl_y, nxl_yd, nxr_y, nxr_yd, nzb_y, nzb_yd, nzt_y, nzt_yd
    8871012
    8881013    IMPLICIT NONE
    8891014
    890     INTEGER ::  i, j, k, l, m, ys
    891    
    892     REAL ::  f_in(1:nz,nys:nyn,nxl:nxr), f_inv(nys:nyn,nxl:nxr,1:nz), &
    893              f_out(0:ny,nxl_yd:nxr_yd,nzb_yd:nzt_yd),                 &
    894              work(nnx*nny*nnz)
     1015    INTEGER(iwp) ::  i  !:
     1016    INTEGER(iwp) ::  j  !:
     1017    INTEGER(iwp) ::  k  !:
     1018    INTEGER(iwp) ::  l  !:
     1019    INTEGER(iwp) ::  m  !:
     1020    INTEGER(iwp) ::  ys !:
     1021
     1022    REAL(wp) ::  f_in(1:nz,nys:nyn,nxl:nxr)              !:
     1023    REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz)             !:
     1024    REAL(wp) ::  f_out(0:ny,nxl_yd:nxr_yd,nzb_yd:nzt_yd) !:
     1025    REAL(wp) ::  work(nnx*nny*nnz)                       !:
    8951026
    8961027#if defined( __parallel )
Note: See TracChangeset for help on using the changeset viewer.