Ignore:
Timestamp:
Mar 5, 2020 3:59:50 PM (4 years ago)
Author:
raasch
Message:

bugfix: cpp-directives for serial mode added

File:
1 edited

Legend:

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

    r4442 r4444  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives for serial mode added, dummy statements to prevent compile errors added
     28!
     29! 4442 2020-03-04 19:21:13Z suehring
    2730! Set back turbulent length scale to 8 x grid spacing in the parametrized mode
    2831! (was accidantly changed).
     
    286289    INTEGER(iwp) ::  nzb_y_stg          !< lower bound of z coordinate (required for transposing z on PEs along y)
    287290    INTEGER(iwp) ::  nzt_y_stg          !< upper bound of z coordinate (required for transposing z on PEs along y)
     291#if defined( __parallel )
    288292    INTEGER(iwp) ::  stg_type_xz        !< MPI type for full z range
    289293    INTEGER(iwp) ::  stg_type_xz_small  !< MPI type for small z range
    290294    INTEGER(iwp) ::  stg_type_yz        !< MPI type for full z range
    291295    INTEGER(iwp) ::  stg_type_yz_small  !< MPI type for small z range
     296#endif
    292297
    293298    INTEGER(iwp), DIMENSION(3) ::  nr_non_topo_xz = 0 !< number of non-topography grid points at xz cross-sections,
     
    296301                                                      !< required for bias correction of imposed perturbations
    297302   
     303#if defined( __parallel )
    298304    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  displs_xz      !< displacement for MPI_GATHERV
    299305    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  recv_count_xz  !< receive count for MPI_GATHERV
    300306    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  displs_yz      !< displacement for MPI_GATHERV
    301307    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  recv_count_yz  !< receive count for MPI_GATHERV
     308#endif
    302309    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nux            !< length scale of u in x direction (in gp)
    303310    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nuy            !< length scale of u in y direction (in gp)
     
    595602    INTEGER(iwp) :: j                        !> loop index
    596603    INTEGER(iwp) :: k                        !< index
     604#if defined( __parallel )
    597605    INTEGER(iwp) :: newtype                  !< dummy MPI type
    598606    INTEGER(iwp) :: realsize                 !< size of REAL variables
     607#endif
    599608
    600609    INTEGER(iwp), DIMENSION(3) ::  nr_non_topo_xz_l = 0 !< number of non-topography grid points at xz-cross-section on subdomain
     
    612621    REAL(wp) :: lwy     !< length scale for w in y direction
    613622    REAL(wp) :: lwz     !< length scale for w in z direction
     623#if defined( __parallel )
    614624    REAL(wp) :: nnz     !< increment used to determine processor decomposition of z-axis along x and y direction
     625#endif
    615626    REAL(wp) :: zz      !< height
    616627
     
    622633!-- Create mpi-datatypes for exchange in case of non-local but distributed
    623634!-- computation of the velocity seeds. This option is useful in
    624 !-- case large turbulent length scales are presentm, where the computational
    625 !-- effort becomes large and need to be parallelized. For parametrized
     635!-- case large turbulent length scales are present, where the computational
     636!-- effort becomes large and need to be parallelized. For parameterized
    626637!-- turbulence the length scales are small and computing the velocity seeds
    627638!-- locally is faster (no overhead by communication).
     
    18921903#else
    18931904       f_n(nzb+1:nzt+1,nys:nyn) = f_n_l(nzb_x_stg:nzt_x_stg+1,nys:nyn)
     1905!
     1906!--    Next line required to avoid compile errors because of unused dummy arguments
     1907       IF ( id_left == 0 )  id_right = 0
    18941908#endif
    18951909
     
    20732087#else
    20742088       f_n(nzb+1:nzt+1,nxl:nxr) = f_n_l(nzb_y_stg:nzt_y_stg+1,nxl:nxr)
     2089!
     2090!--    Next line required to avoid compile errors because of unused dummy arguments
     2091       IF ( id_north == 0 )  id_south = 0
    20752092#endif
    20762093
Note: See TracChangeset for help on using the changeset viewer.