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/init_grid.f90

    r4414 r4444  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives for serial mode added
     28!
     29! 4414 2020-02-19 20:16:04Z suehring
    2730! - Remove deprecated topography arrays nzb_s_inner, nzb_u_inner, etc.
    2831! - Move initialization of boundary conditions and multigrid into an extra
     
    172175    USE pegrid
    173176
     177#if defined( __parallel )
    174178    USE vertical_nesting_mod,                                                  &
    175179        ONLY:  vnested, vnest_init_grid
     180#endif
    176181
    177182    IMPLICIT NONE
     
    751756       ENDDO
    752757    ENDIF
     758
     759#if defined( __parallel )
    753760!
    754761!-- Vertical nesting: communicate vertical grid level arrays between fine and
    755762!-- coarse grid
    756763    IF ( vnested )  CALL vnest_init_grid
     764#endif
    757765
    758766 END SUBROUTINE init_grid
     
    948956    INTEGER(iwp) ::  topo_top_index   !< orography top index, used to map 3D buildings onto terrain
    949957
     958#if defined( __parallel )
    950959    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  displace_dum        !< displacements of start addresses, used for MPI_ALLGATHERV
     960#endif
    951961    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids           !< building IDs on entire model domain
    952962    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final     !< building IDs on entire model domain, multiple occurences are sorted out
Note: See TracChangeset for help on using the changeset viewer.