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

    r4360 r4444  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives for serial mode added
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Added missing OpenMP directives
    2831!
     
    5861
    5962    USE control_parameters,                                                    &
    60         ONLY:  cfl_factor, coupling_mode, dt_3d, dt_fixed, dt_max,             &
    61                galilei_transformation, message_string, rans_mode,              &
    62                stop_dt, terminate_coupled, terminate_coupled_remote,           &
    63                timestep_reason, u_gtrans, use_ug_for_galilei_tr, v_gtrans
     63        ONLY:  cfl_factor, dt_3d, dt_fixed, dt_max, galilei_transformation,    &
     64               message_string, rans_mode, stop_dt, timestep_reason, u_gtrans,  &
     65               use_ug_for_galilei_tr, v_gtrans
     66
     67#if defined( __parallel )
     68    USE control_parameters,                                                    &
     69        ONLY:  coupling_mode, terminate_coupled, terminate_coupled_remote
     70#endif
    6471
    6572    USE cpulog,                                                                &
     
    8895               w_max, w_max_ijk
    8996
     97#if defined( __parallel )
    9098    USE vertical_nesting_mod,                                                  &
    9199        ONLY:  vnested, vnest_timestep_sync
     100#endif
    92101
    93102    IMPLICIT NONE
     
    115124    REAL(wp) ::  v_gtrans_l        !<
    116125 
     126    REAL(wp), DIMENSION(2)         ::  uv_gtrans_l !<
     127#if defined( __parallel )
    117128    REAL(wp), DIMENSION(2)         ::  uv_gtrans   !<
    118     REAL(wp), DIMENSION(2)         ::  uv_gtrans_l !<
    119129    REAL(wp), DIMENSION(3)         ::  reduce      !<
    120     REAL(wp), DIMENSION(3)         ::  reduce_l    !<
     130    REAL(wp), DIMENSION(3)         ::  reduce_l    !<
     131#endif
    121132    REAL(wp), DIMENSION(nzb+1:nzt) ::  dxyz2_min   !< 
    122133    !$ACC DECLARE CREATE(dxyz2_min)
     
    382393    ENDIF
    383394
     395#if defined( __parallel )
    384396!
    385397!-- Vertical nesting: coarse and fine grid timestep has to be identical   
    386398    IF ( vnested )  CALL vnest_timestep_sync
     399#endif
    387400
    388401    CALL cpu_log( log_point(12), 'calculate_timestep', 'stop' )
Note: See TracChangeset for help on using the changeset viewer.