Ignore:
Timestamp:
Feb 27, 2020 3:24:30 PM (5 years ago)
Author:
raasch
Message:

serial (non-MPI) test case added, several bugfixes for the serial mode

File:
1 edited

Legend:

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

    r4415 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives added for serial mode
     28!
     29! 4415 2020-02-20 10:30:33Z raasch
    2730! bugfix for misplaced preprocessor directive
    2831!
     
    111114
    112115
     116#if defined( __parallel )
    113117    USE cpulog,                                                                &
    114118        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     119#endif
    115120
    116121    USE indices,                                                               &
     
    129134    INTEGER(iwp) ::  j  !<
    130135    INTEGER(iwp) ::  k  !<
     136
     137#if defined( __parallel )
    131138    INTEGER(iwp) ::  l  !<
    132139    INTEGER(iwp) ::  ys !<
     140#endif
    133141
    134142    REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !<
    135143    REAL(wp) ::  f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y) !<
    136144
     145#if defined( __parallel )
    137146    REAL(wp), DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work !<
    138147#if __acc_fft_device
    139148    !$ACC DECLARE CREATE(work)
     149#endif
    140150#endif
    141151
     
    271281 SUBROUTINE transpose_xz( f_in, f_inv )
    272282
    273 
     283#if defined( __parallel )
    274284    USE cpulog,                                                                &
    275285        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     
    277287    USE fft_xy,                                                                &
    278288        ONLY:  f_vec_x, temperton_fft_vec
     289#endif
    279290
    280291    USE indices,                                                               &
    281         ONLY:  nnx, nx, nxl, nxr, nyn, nys, nz
     292        ONLY:  nx, nxl, nxr, nyn, nys, nz
     293#if defined( __parallel )
     294    USE indices,                                                               &
     295        ONLY:  nnx
     296#endif
    282297
    283298    USE kinds
     
    293308    INTEGER(iwp) ::  j  !<
    294309    INTEGER(iwp) ::  k  !<
     310#if defined( __parallel )
    295311    INTEGER(iwp) ::  l  !<
    296312    INTEGER(iwp) ::  mm !<
    297313    INTEGER(iwp) ::  xs !<
     314#endif
    298315
    299316    REAL(wp) ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !<
    300317    REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz) !<
    301318
     319#if defined( __parallel )
    302320    REAL(wp), DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work !<
    303321#if __acc_fft_device
    304322    !$ACC DECLARE CREATE(work)
     323#endif
    305324#endif
    306325
     
    460479
    461480
     481#if defined( __parallel )
    462482    USE cpulog,                                                                &
    463483        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     484#endif
    464485
    465486    USE indices,                                                               &
     
    478499    INTEGER(iwp) ::  j  !<
    479500    INTEGER(iwp) ::  k  !<
     501#if defined( __parallel )
    480502    INTEGER(iwp) ::  l  !<
    481503    INTEGER(iwp) ::  ys !<
     504#endif
    482505
    483506    REAL(wp) ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y)  !<
    484507    REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !<
    485508
     509#if defined( __parallel )
    486510    REAL(wp), DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work !<
    487511#if __acc_fft_device
    488512    !$ACC DECLARE CREATE(work)
     513#endif
    489514#endif
    490515
     
    575600!> (k,j,i) (cf. transpose_yx).
    576601!------------------------------------------------------------------------------!
     602#if defined( __parallel )
    577603 SUBROUTINE transpose_yxd( f_in, f_out )
    578604
     
    604630    REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !<
    605631    REAL(wp) ::  work(nnx*nny*nnz)                   !<
    606 #if defined( __parallel )
    607632
    608633!
     
    641666    ENDDO
    642667
    643 #endif
    644 
    645668 END SUBROUTINE transpose_yxd
     669#endif
    646670
    647671
     
    703727
    704728
     729#if defined( __parallel )
    705730    USE cpulog,                                                                &
    706731        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     732#endif
    707733
    708734    USE indices,                                                               &
     
    721747    INTEGER(iwp) ::  j  !<
    722748    INTEGER(iwp) ::  k  !<
     749#if defined( __parallel )
    723750    INTEGER(iwp) ::  l  !<
    724751    INTEGER(iwp) ::  zs !<
     752#endif
    725753
    726754    REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !<
    727755    REAL(wp) ::  f_out(nxl_z:nxr_z,nys_z:nyn_z,1:nz) !<
    728756
     757#if defined( __parallel )
    729758    REAL(wp), DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work !<
    730759#if __acc_fft_device
    731760    !$ACC DECLARE CREATE(work)
     761#endif
    732762#endif
    733763
     
    864894
    865895
     896#if defined( __parallel )
    866897    USE cpulog,                                                                &
    867898        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     
    869900    USE fft_xy,                                                                &
    870901        ONLY:  f_vec_x, temperton_fft_vec
     902#endif
    871903
    872904    USE indices,                                                               &
    873         ONLY:  nnx, nx, nxl, nxr, nyn, nys, nz
     905        ONLY:  nx, nxl, nxr, nyn, nys, nz
     906#if defined( __parallel )
     907    USE indices,                                                               &
     908        ONLY:  nnx
     909#endif
    874910
    875911    USE kinds
     
    885921    INTEGER(iwp) ::  j  !<
    886922    INTEGER(iwp) ::  k  !<
     923#if defined( __parallel )
    887924    INTEGER(iwp) ::  l  !<
    888925    INTEGER(iwp) ::  mm !<
    889926    INTEGER(iwp) ::  xs !<
     927#endif
    890928
    891929    REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz)         !<
    892930    REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !<
    893931
     932#if defined( __parallel )
    894933    REAL(wp), DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work !<
    895934#if __acc_fft_device
    896935    !$ACC DECLARE CREATE(work)
     936#endif
    897937#endif
    898938
     
    10541094
    10551095
     1096#if defined( __parallel )
    10561097    USE cpulog,                                                                &
    10571098        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     1099#endif
    10581100
    10591101    USE indices,                                                               &
     
    10721114    INTEGER(iwp) ::  j  !<
    10731115    INTEGER(iwp) ::  k  !<
     1116#if defined( __parallel )
    10741117    INTEGER(iwp) ::  l  !<
    10751118    INTEGER(iwp) ::  zs !<
     1119#endif
    10761120
    10771121    REAL(wp) ::  f_in(nxl_z:nxr_z,nys_z:nyn_z,1:nz)  !<
    10781122    REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !<
    10791123
     1124#if defined( __parallel )
    10801125    REAL(wp), DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work !<
    10811126#if __acc_fft_device
    10821127    !$ACC DECLARE CREATE(work)
     1128#endif
    10831129#endif
    10841130
     
    11701216!> (k,j,i) (cf. transpose_zy).
    11711217!------------------------------------------------------------------------------!
     1218#if defined( __parallel )
    11721219 SUBROUTINE transpose_zyd( f_in, f_out )
    11731220
     
    11991246    REAL(wp) ::  f_out(0:ny,nxl_yd:nxr_yd,nzb_yd:nzt_yd) !<
    12001247    REAL(wp) ::  work(nnx*nny*nnz)                       !<
    1201 
    1202 #if defined( __parallel )
    12031248
    12041249!
     
    12531298    ENDDO
    12541299
    1255 #endif
    1256 
    12571300 END SUBROUTINE transpose_zyd
     1301#endif
Note: See TracChangeset for help on using the changeset viewer.