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

    r4360 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives added for serial mode
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Corrected "Former revisions" section
    2831!
     
    4649
    4750    USE control_parameters,                                                    &
    48         ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level, mg_switch_to_pe0, synchronous_exchange
     51        ONLY:  bc_lr_cyc, bc_ns_cyc
     52
     53#if defined( __parallel )
     54    USE control_parameters,                                                    &
     55        ONLY:  grid_level, mg_switch_to_pe0, synchronous_exchange
     56#endif
    4957               
    5058    USE cpulog,                                                                &
     
    272280!> @todo Missing subroutine description.
    273281!------------------------------------------------------------------------------!
    274  SUBROUTINE exchange_horiz_int( ar, nys_l, nyn_l, nxl_l, nxr_l, nzt_l, nbgp_local)
     282 SUBROUTINE exchange_horiz_int( ar, nys_l, nyn_l, nxl_l, nxr_l, nzt_l, nbgp_local )
     283
    275284
    276285    USE control_parameters,                                                    &
    277         ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level
     286        ONLY:  bc_lr_cyc, bc_ns_cyc
     287
     288#if defined( __parallel )
     289    USE control_parameters,                                                    &
     290        ONLY:  grid_level
     291#endif
    278292                       
    279293    USE indices,                                                               &
Note: See TracChangeset for help on using the changeset viewer.