Ignore:
Timestamp:
Oct 7, 2015 11:56:08 PM (9 years ago)
Author:
knoop
Message:

Code annotations made doxygen readable

File:
1 edited

Legend:

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

    r1325 r1682  
    1  SUBROUTINE resort_for_xy( f_in, f_inv )
    2 
     1!> @file transpose.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
     21! Code annotations made doxygen readable
    2222!
    2323! Former revisions:
     
    7272! Description:
    7373! ------------
    74 ! Resorting data for the transposition from x to y. The transposition itself
    75 ! is carried out in transpose_xy
    76 !------------------------------------------------------------------------------!
     74!> Resorting data for the transposition from x to y. The transposition itself
     75!> is carried out in transpose_xy
     76!------------------------------------------------------------------------------!
     77 SUBROUTINE resort_for_xy( f_in, f_inv )
     78 
    7779
    7880     USE indices,                                                              &
     
    8688     IMPLICIT NONE
    8789
    88      REAL(wp) ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x)  !:
    89      REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !:
    90 
    91 
    92      INTEGER(iwp) ::  i !:
    93      INTEGER(iwp) ::  j !:
    94      INTEGER(iwp) ::  k !:
     90     REAL(wp) ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x)  !<
     91     REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !<
     92
     93
     94     INTEGER(iwp) ::  i !<
     95     INTEGER(iwp) ::  j !<
     96     INTEGER(iwp) ::  k !<
    9597!
    9698!-- Rearrange indices of input array in order to make data to be send
     
    112114
    113115
     116!------------------------------------------------------------------------------!
     117! Description:
     118! ------------
     119!> Transposition of input array (f_in) from x to y. For the input array, all
     120!> elements along x reside on the same PE, while after transposition, all
     121!> elements along y reside on the same PE.
     122!------------------------------------------------------------------------------!
    114123 SUBROUTINE transpose_xy( f_inv, f_out )
    115124
    116 !------------------------------------------------------------------------------!
    117 ! Description:
    118 ! ------------
    119 ! Transposition of input array (f_in) from x to y. For the input array, all
    120 ! elements along x reside on the same PE, while after transposition, all
    121 ! elements along y reside on the same PE.
    122 !------------------------------------------------------------------------------!
    123125
    124126    USE cpulog,                                                                &
     
    137139    IMPLICIT NONE
    138140
    139     INTEGER(iwp) ::  i  !:
    140     INTEGER(iwp) ::  j  !:
    141     INTEGER(iwp) ::  k  !:
    142     INTEGER(iwp) ::  l  !:
    143     INTEGER(iwp) ::  ys !:
     141    INTEGER(iwp) ::  i  !<
     142    INTEGER(iwp) ::  j  !<
     143    INTEGER(iwp) ::  k  !<
     144    INTEGER(iwp) ::  l  !<
     145    INTEGER(iwp) ::  ys !<
    144146 
    145     REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !:
    146     REAL(wp) ::  f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y) !:
    147 
    148     REAL(wp), DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work !:
     147    REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !<
     148    REAL(wp) ::  f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y) !<
     149
     150    REAL(wp), DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work !<
    149151
    150152
     
    205207
    206208
     209!------------------------------------------------------------------------------!
     210! Description:
     211! ------------
     212!> Resorting data after the transposition from x to z. The transposition itself
     213!> is carried out in transpose_xz
     214!------------------------------------------------------------------------------!
    207215 SUBROUTINE resort_for_xz( f_inv, f_out )
    208216
    209 !------------------------------------------------------------------------------!
    210 ! Description:
    211 ! ------------
    212 ! Resorting data after the transposition from x to z. The transposition itself
    213 ! is carried out in transpose_xz
    214 !------------------------------------------------------------------------------!
    215217
    216218     USE indices,                                                              &
     
    221223     IMPLICIT NONE
    222224
    223      REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz) !:
    224      REAL(wp) ::  f_out(1:nz,nys:nyn,nxl:nxr) !:
    225 
    226      INTEGER(iwp) ::  i !:
    227      INTEGER(iwp) ::  j !:
    228      INTEGER(iwp) ::  k !:
     225     REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz) !<
     226     REAL(wp) ::  f_out(1:nz,nys:nyn,nxl:nxr) !<
     227
     228     INTEGER(iwp) ::  i !<
     229     INTEGER(iwp) ::  j !<
     230     INTEGER(iwp) ::  k !<
    229231!
    230232!-- Rearrange indices of input array in order to make data to be send
     
    248250
    249251
     252!------------------------------------------------------------------------------!
     253! Description:
     254! ------------
     255!> Transposition of input array (f_in) from x to z. For the input array, all
     256!> elements along x reside on the same PE, while after transposition, all
     257!> elements along z reside on the same PE.
     258!------------------------------------------------------------------------------!
    250259 SUBROUTINE transpose_xz( f_in, f_inv )
    251260
    252 !------------------------------------------------------------------------------!
    253 ! Description:
    254 ! ------------
    255 ! Transposition of input array (f_in) from x to z. For the input array, all
    256 ! elements along x reside on the same PE, while after transposition, all
    257 ! elements along z reside on the same PE.
    258 !------------------------------------------------------------------------------!
    259261
    260262    USE cpulog,                                                                &
     
    273275    IMPLICIT NONE
    274276
    275     INTEGER(iwp) ::  i  !:
    276     INTEGER(iwp) ::  j  !:
    277     INTEGER(iwp) ::  k  !:
    278     INTEGER(iwp) ::  l  !:
    279     INTEGER(iwp) ::  xs !:
    280 
    281     REAL(wp) ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !:
    282     REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz) !:
    283 
    284     REAL(wp), DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work !:
     277    INTEGER(iwp) ::  i  !<
     278    INTEGER(iwp) ::  j  !<
     279    INTEGER(iwp) ::  k  !<
     280    INTEGER(iwp) ::  l  !<
     281    INTEGER(iwp) ::  xs !<
     282
     283    REAL(wp) ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !<
     284    REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz) !<
     285
     286    REAL(wp), DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work !<
    285287
    286288
     
    344346
    345347
     348!------------------------------------------------------------------------------!
     349! Description:
     350! ------------
     351!> Resorting data after the transposition from y to x. The transposition itself
     352!> is carried out in transpose_yx
     353!------------------------------------------------------------------------------!
    346354 SUBROUTINE resort_for_yx( f_inv, f_out )
    347355
    348 !------------------------------------------------------------------------------!
    349 ! Description:
    350 ! ------------
    351 ! Resorting data after the transposition from y to x. The transposition itself
    352 ! is carried out in transpose_yx
    353 !------------------------------------------------------------------------------!
    354356
    355357     USE indices,                                                              &
     
    363365     IMPLICIT NONE
    364366
    365      REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !:
    366      REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !:
    367 
    368 
    369      INTEGER(iwp) ::  i !:
    370      INTEGER(iwp) ::  j !:
    371      INTEGER(iwp) ::  k !:
     367     REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !<
     368     REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !<
     369
     370
     371     INTEGER(iwp) ::  i !<
     372     INTEGER(iwp) ::  j !<
     373     INTEGER(iwp) ::  k !<
    372374!
    373375!-- Rearrange indices of input array in order to make data to be send
     
    389391
    390392
     393!------------------------------------------------------------------------------!
     394! Description:
     395! ------------
     396!> Transposition of input array (f_in) from y to x. For the input array, all
     397!> elements along y reside on the same PE, while after transposition, all
     398!> elements along x reside on the same PE.
     399!------------------------------------------------------------------------------!
    391400 SUBROUTINE transpose_yx( f_in, f_inv )
    392401
    393 !------------------------------------------------------------------------------!
    394 ! Description:
    395 ! ------------
    396 ! Transposition of input array (f_in) from y to x. For the input array, all
    397 ! elements along y reside on the same PE, while after transposition, all
    398 ! elements along x reside on the same PE.
    399 !------------------------------------------------------------------------------!
    400402
    401403    USE cpulog,                                                                &
     
    414416    IMPLICIT NONE
    415417
    416     INTEGER(iwp) ::  i  !:
    417     INTEGER(iwp) ::  j  !:
    418     INTEGER(iwp) ::  k  !:
    419     INTEGER(iwp) ::  l  !:
    420     INTEGER(iwp) ::  ys !:
    421 
    422     REAL(wp) ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y)  !:
    423     REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !:
    424 
    425     REAL(wp), DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work !:
     418    INTEGER(iwp) ::  i  !<
     419    INTEGER(iwp) ::  j  !<
     420    INTEGER(iwp) ::  k  !<
     421    INTEGER(iwp) ::  l  !<
     422    INTEGER(iwp) ::  ys !<
     423
     424    REAL(wp) ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y)  !<
     425    REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !<
     426
     427    REAL(wp), DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work !<
    426428
    427429
     
    482484
    483485
     486!------------------------------------------------------------------------------!
     487! Description:
     488! ------------
     489!> Transposition of input array (f_in) from y to x. For the input array, all
     490!> elements along y reside on the same PE, while after transposition, all
     491!> elements along x reside on the same PE.
     492!> This is a direct transposition for arrays with indices in regular order
     493!> (k,j,i) (cf. transpose_yx).
     494!------------------------------------------------------------------------------!
    484495 SUBROUTINE transpose_yxd( f_in, f_out )
    485496
    486 !------------------------------------------------------------------------------!
    487 ! Description:
    488 ! ------------
    489 ! Transposition of input array (f_in) from y to x. For the input array, all
    490 ! elements along y reside on the same PE, while after transposition, all
    491 ! elements along x reside on the same PE.
    492 ! This is a direct transposition for arrays with indices in regular order
    493 ! (k,j,i) (cf. transpose_yx).
    494 !------------------------------------------------------------------------------!
    495497
    496498    USE cpulog,                                                                &
     
    509511    IMPLICIT NONE
    510512
    511     INTEGER(iwp) ::  i  !:
    512     INTEGER(iwp) ::  j  !:
    513     INTEGER(iwp) ::  k  !:
    514     INTEGER(iwp) ::  l  !:
    515     INTEGER(iwp) ::  m  !:
    516     INTEGER(iwp) ::  xs !:
    517 
    518     REAL(wp) ::  f_in(1:nz,nys:nyn,nxl:nxr)          !:
    519     REAL(wp) ::  f_inv(nxl:nxr,1:nz,nys:nyn)         !:
    520     REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !:
    521     REAL(wp) ::  work(nnx*nny*nnz)                   !:
     513    INTEGER(iwp) ::  i  !<
     514    INTEGER(iwp) ::  j  !<
     515    INTEGER(iwp) ::  k  !<
     516    INTEGER(iwp) ::  l  !<
     517    INTEGER(iwp) ::  m  !<
     518    INTEGER(iwp) ::  xs !<
     519
     520    REAL(wp) ::  f_in(1:nz,nys:nyn,nxl:nxr)          !<
     521    REAL(wp) ::  f_inv(nxl:nxr,1:nz,nys:nyn)         !<
     522    REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !<
     523    REAL(wp) ::  work(nnx*nny*nnz)                   !<
    522524#if defined( __parallel )
    523525
     
    562564
    563565
     566!------------------------------------------------------------------------------!
     567! Description:
     568! ------------
     569!> Resorting data for the transposition from y to z. The transposition itself
     570!> is carried out in transpose_yz
     571!------------------------------------------------------------------------------!
    564572 SUBROUTINE resort_for_yz( f_in, f_inv )
    565573
    566 !------------------------------------------------------------------------------!
    567 ! Description:
    568 ! ------------
    569 ! Resorting data for the transposition from y to z. The transposition itself
    570 ! is carried out in transpose_yz
    571 !------------------------------------------------------------------------------!
    572574
    573575     USE indices,                                                              &
     
    581583     IMPLICIT NONE
    582584
    583      REAL(wp) ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y)  !:
    584      REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !:
    585 
    586      INTEGER(iwp) ::  i !:
    587      INTEGER(iwp) ::  j !:
    588      INTEGER(iwp) ::  k !:
     585     REAL(wp) ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y)  !<
     586     REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !<
     587
     588     INTEGER(iwp) ::  i !<
     589     INTEGER(iwp) ::  j !<
     590     INTEGER(iwp) ::  k !<
    589591
    590592!
     
    607609
    608610
     611!------------------------------------------------------------------------------!
     612! Description:
     613! ------------
     614!> Transposition of input array (f_in) from y to z. For the input array, all
     615!> elements along y reside on the same PE, while after transposition, all
     616!> elements along z reside on the same PE.
     617!------------------------------------------------------------------------------!
    609618 SUBROUTINE transpose_yz( f_inv, f_out )
    610619
    611 !------------------------------------------------------------------------------!
    612 ! Description:
    613 ! ------------
    614 ! Transposition of input array (f_in) from y to z. For the input array, all
    615 ! elements along y reside on the same PE, while after transposition, all
    616 ! elements along z reside on the same PE.
    617 !------------------------------------------------------------------------------!
    618620
    619621    USE cpulog,                                                                &
     
    632634    IMPLICIT NONE
    633635
    634     INTEGER(iwp) ::  i  !:
    635     INTEGER(iwp) ::  j  !:
    636     INTEGER(iwp) ::  k  !:
    637     INTEGER(iwp) ::  l  !:
    638     INTEGER(iwp) ::  zs !:
    639 
    640     REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !:
    641     REAL(wp) ::  f_out(nxl_z:nxr_z,nys_z:nyn_z,1:nz) !:
    642 
    643     REAL(wp), DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work !:
     636    INTEGER(iwp) ::  i  !<
     637    INTEGER(iwp) ::  j  !<
     638    INTEGER(iwp) ::  k  !<
     639    INTEGER(iwp) ::  l  !<
     640    INTEGER(iwp) ::  zs !<
     641
     642    REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !<
     643    REAL(wp) ::  f_out(nxl_z:nxr_z,nys_z:nyn_z,1:nz) !<
     644
     645    REAL(wp), DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work !<
    644646
    645647
     
    701703
    702704
     705!------------------------------------------------------------------------------!
     706! Description:
     707! ------------
     708!> Resorting data for the transposition from z to x. The transposition itself
     709!> is carried out in transpose_zx
     710!------------------------------------------------------------------------------!
    703711 SUBROUTINE resort_for_zx( f_in, f_inv )
    704712
    705 !------------------------------------------------------------------------------!
    706 ! Description:
    707 ! ------------
    708 ! Resorting data for the transposition from z to x. The transposition itself
    709 ! is carried out in transpose_zx
    710 !------------------------------------------------------------------------------!
    711713
    712714     USE indices,                                                              &
     
    717719     IMPLICIT NONE
    718720
    719      REAL(wp) ::  f_in(1:nz,nys:nyn,nxl:nxr)  !:
    720      REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz) !:
    721 
    722      INTEGER(iwp) ::  i !:
    723      INTEGER(iwp) ::  j !:
    724      INTEGER(iwp) ::  k !:
     721     REAL(wp) ::  f_in(1:nz,nys:nyn,nxl:nxr)  !<
     722     REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz) !<
     723
     724     INTEGER(iwp) ::  i !<
     725     INTEGER(iwp) ::  j !<
     726     INTEGER(iwp) ::  k !<
    725727
    726728!
     
    743745
    744746
     747!------------------------------------------------------------------------------!
     748! Description:
     749! ------------
     750!> Transposition of input array (f_in) from z to x. For the input array, all
     751!> elements along z reside on the same PE, while after transposition, all
     752!> elements along x reside on the same PE.
     753!------------------------------------------------------------------------------!
    745754 SUBROUTINE transpose_zx( f_inv, f_out )
    746755
    747 !------------------------------------------------------------------------------!
    748 ! Description:
    749 ! ------------
    750 ! Transposition of input array (f_in) from z to x. For the input array, all
    751 ! elements along z reside on the same PE, while after transposition, all
    752 ! elements along x reside on the same PE.
    753 !------------------------------------------------------------------------------!
    754756
    755757    USE cpulog,                                                                &
     
    768770    IMPLICIT NONE
    769771
    770     INTEGER(iwp) ::  i  !:
    771     INTEGER(iwp) ::  j  !:
    772     INTEGER(iwp) ::  k  !:
    773     INTEGER(iwp) ::  l  !:
    774     INTEGER(iwp) ::  xs !:
    775 
    776     REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz)         !:
    777     REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !:
    778 
    779     REAL(wp), DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work !:
     772    INTEGER(iwp) ::  i  !<
     773    INTEGER(iwp) ::  j  !<
     774    INTEGER(iwp) ::  k  !<
     775    INTEGER(iwp) ::  l  !<
     776    INTEGER(iwp) ::  xs !<
     777
     778    REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz)         !<
     779    REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !<
     780
     781    REAL(wp), DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work !<
    780782
    781783
     
    837839
    838840
     841!------------------------------------------------------------------------------!
     842! Description:
     843! ------------
     844!> Resorting data after the transposition from z to y. The transposition itself
     845!> is carried out in transpose_zy
     846!------------------------------------------------------------------------------!
    839847 SUBROUTINE resort_for_zy( f_inv, f_out )
    840848
    841 !------------------------------------------------------------------------------!
    842 ! Description:
    843 ! ------------
    844 ! Resorting data after the transposition from z to y. The transposition itself
    845 ! is carried out in transpose_zy
    846 !------------------------------------------------------------------------------!
    847849
    848850     USE indices,                                                              &
     
    856858     IMPLICIT NONE
    857859
    858      REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !:
    859      REAL(wp) ::  f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y) !:
    860 
    861 
    862      INTEGER(iwp) ::  i !:
    863      INTEGER(iwp) ::  j !:
    864      INTEGER(iwp) ::  k !:
     860     REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !<
     861     REAL(wp) ::  f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y) !<
     862
     863
     864     INTEGER(iwp) ::  i !<
     865     INTEGER(iwp) ::  j !<
     866     INTEGER(iwp) ::  k !<
    865867
    866868!
     
    883885
    884886
     887!------------------------------------------------------------------------------!
     888! Description:
     889! ------------
     890!> Transposition of input array (f_in) from z to y. For the input array, all
     891!> elements along z reside on the same PE, while after transposition, all
     892!> elements along y reside on the same PE.
     893!------------------------------------------------------------------------------!
    885894 SUBROUTINE transpose_zy( f_in, f_inv )
    886895
    887 !------------------------------------------------------------------------------!
    888 ! Description:
    889 ! ------------
    890 ! Transposition of input array (f_in) from z to y. For the input array, all
    891 ! elements along z reside on the same PE, while after transposition, all
    892 ! elements along y reside on the same PE.
    893 !------------------------------------------------------------------------------!
    894896
    895897    USE cpulog,                                                                &
     
    908910    IMPLICIT NONE
    909911
    910     INTEGER(iwp) ::  i  !:
    911     INTEGER(iwp) ::  j  !:
    912     INTEGER(iwp) ::  k  !:
    913     INTEGER(iwp) ::  l  !:
    914     INTEGER(iwp) ::  zs !:
    915 
    916     REAL(wp) ::  f_in(nxl_z:nxr_z,nys_z:nyn_z,1:nz)  !:
    917     REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !:
    918 
    919     REAL(wp), DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work !:
     912    INTEGER(iwp) ::  i  !<
     913    INTEGER(iwp) ::  j  !<
     914    INTEGER(iwp) ::  k  !<
     915    INTEGER(iwp) ::  l  !<
     916    INTEGER(iwp) ::  zs !<
     917
     918    REAL(wp) ::  f_in(nxl_z:nxr_z,nys_z:nyn_z,1:nz)  !<
     919    REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !<
     920
     921    REAL(wp), DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work !<
    920922
    921923!
     
    977979
    978980
     981!------------------------------------------------------------------------------!
     982! Description:
     983! ------------
     984!> Transposition of input array (f_in) from z to y. For the input array, all
     985!> elements along z reside on the same PE, while after transposition, all
     986!> elements along y reside on the same PE.
     987!> This is a direct transposition for arrays with indices in regular order
     988!> (k,j,i) (cf. transpose_zy).
     989!------------------------------------------------------------------------------!
    979990 SUBROUTINE transpose_zyd( f_in, f_out )
    980991
    981 !------------------------------------------------------------------------------!
    982 ! Description:
    983 ! ------------
    984 ! Transposition of input array (f_in) from z to y. For the input array, all
    985 ! elements along z reside on the same PE, while after transposition, all
    986 ! elements along y reside on the same PE.
    987 ! This is a direct transposition for arrays with indices in regular order
    988 ! (k,j,i) (cf. transpose_zy).
    989 !------------------------------------------------------------------------------!
    990992
    991993    USE cpulog,                                                                &
     
    10041006    IMPLICIT NONE
    10051007
    1006     INTEGER(iwp) ::  i  !:
    1007     INTEGER(iwp) ::  j  !:
    1008     INTEGER(iwp) ::  k  !:
    1009     INTEGER(iwp) ::  l  !:
    1010     INTEGER(iwp) ::  m  !:
    1011     INTEGER(iwp) ::  ys !:
    1012 
    1013     REAL(wp) ::  f_in(1:nz,nys:nyn,nxl:nxr)              !:
    1014     REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz)             !:
    1015     REAL(wp) ::  f_out(0:ny,nxl_yd:nxr_yd,nzb_yd:nzt_yd) !:
    1016     REAL(wp) ::  work(nnx*nny*nnz)                       !:
     1008    INTEGER(iwp) ::  i  !<
     1009    INTEGER(iwp) ::  j  !<
     1010    INTEGER(iwp) ::  k  !<
     1011    INTEGER(iwp) ::  l  !<
     1012    INTEGER(iwp) ::  m  !<
     1013    INTEGER(iwp) ::  ys !<
     1014
     1015    REAL(wp) ::  f_in(1:nz,nys:nyn,nxl:nxr)              !<
     1016    REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz)             !<
     1017    REAL(wp) ::  f_out(0:ny,nxl_yd:nxr_yd,nzb_yd:nzt_yd) !<
     1018    REAL(wp) ::  work(nnx*nny*nnz)                       !<
    10171019
    10181020#if defined( __parallel )
Note: See TracChangeset for help on using the changeset viewer.