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

    r4420 r4444  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives for serial mode added
     28!
     29! 4420 2020-02-24 14:13:56Z maronga
    2730! Added output control for wind turbine model
    2831!
     
    198201
    199202    USE arrays_3d,                                                                                 &
    200         ONLY:  diss, diss_p, dzu, e, e_p, nc, nc_p, nr, nr_p, prho, pt, pt_p, pt_init, q_init, q,  &
    201                qc, qc_p, qr, qr_p, q_p, ref_state, rho_ocean, s, s_p, sa_p, &
    202                tend, u, u_p, v, vpt, v_p, w, w_p
     203        ONLY:  diss, diss_p, dzu, e_p, nc_p, nr_p, prho, pt, pt_p, pt_init, q, qc_p, qr_p, q_init, &
     204               q_p, ref_state, rho_ocean, sa_p, s_p, tend, u, u_p, v, vpt, v_p, w_p
     205
     206#if defined( __parallel )  &&  ! defined( _OPENACC )
     207    USE arrays_3d,                                                                                 &
     208        ONLY:  e, nc, nr, qc, qr, s, w
     209#endif
    203210
    204211    USE biometeorology_mod,                                                                        &
     
    220227
    221228    USE chem_modules,                                                                              &
    222         ONLY:  bc_cs_t_val, chem_species, cs_name,                                                 &
    223                emissions_anthropogenic, emiss_read_legacy_mode,                                    &
     229        ONLY:  bc_cs_t_val, chem_species, emissions_anthropogenic, emiss_read_legacy_mode,         &
    224230               n_matched_vars
     231
     232#if defined( __parallel )
     233    USE chem_modules,                                                                              &
     234        ONLY:  cs_name
     235#endif
    225236
    226237    USE chemistry_model_mod,                                                                       &
     
    242253               multi_agent_system_end, multi_agent_system_start, nesting_offline, neutral,         &
    243254               nr_timesteps_this_run, nudging, ocean_mode, passive_scalar, pt_reference,           &
    244                pt_slope_offset, random_heatflux, rans_mode, rans_tke_e, run_coupled, salsa,        &
     255               pt_slope_offset, random_heatflux, rans_tke_e, run_coupled, salsa,                   &
    245256               simulated_time, simulated_time_chr, skip_time_do2d_xy, skip_time_do2d_xz,           &
    246257               skip_time_do2d_yz, skip_time_do3d, skip_time_domask, skip_time_dopr,                &
     
    254265               virtual_flight, virtual_measurement, ws_scheme_mom, ws_scheme_sca, timestep_count
    255266
     267#if defined( __parallel )
     268    USE control_parameters,                                                                        &
     269        ONLY:  rans_mode
     270#endif
     271
    256272    USE cpulog,                                                                                    &
    257273        ONLY:  cpu_log, log_point, log_point_s
     
    311327    USE pegrid
    312328
     329#if defined( __parallel )
    313330    USE pmc_interface,                                                                             &
    314331        ONLY:  nested_run, nesting_mode, pmci_boundary_conds, pmci_datatrans, pmci_synchronize,    &
    315332        pmci_ensure_nest_mass_conservation, pmci_ensure_nest_mass_conservation_vertical,           &
    316333        pmci_set_swaplevel
     334#endif
    317335
    318336    USE progress_bar,                                                                              &
     
    361379
    362380    USE vertical_nesting_mod,                                                                      &
    363         ONLY:  vnested, vnest_anterpolate, vnest_anterpolate_e, vnest_boundary_conds,              &
    364                vnest_boundary_conds_khkm, vnest_deallocate, vnest_init, vnest_init_fine,           &
    365                vnest_start_time
     381        ONLY:  vnested, vnest_init
     382
     383#if defined( __parallel )
     384    USE vertical_nesting_mod,                                                                      &
     385        ONLY:  vnest_anterpolate, vnest_anterpolate_e, vnest_boundary_conds,                       &
     386               vnest_boundary_conds_khkm, vnest_deallocate, vnest_init_fine, vnest_start_time
     387#endif
    366388
    367389    USE virtual_measurement_mod,                                                                   &
     
    377399
    378400#if defined( _OPENACC )
    379     USE arrays_3d,                                                             &
    380         ONLY:  d, dd2zu, ddzu, ddzw, drho_air, drho_air_zw, dzw, heatflux_output_conversion, kh,   &
    381                km, momentumflux_output_conversion, p, ptdf_x, ptdf_y, rdf, rdf_sc, rho_air,        &
    382                rho_air_zw, tdiss_m, te_m, tpt_m, tu_m, tv_m, tw_m, ug, u_init, u_stokes_zu, vg,    &
    383                v_init, v_stokes_zu, zu
     401    USE arrays_3d,                                                                                 &
     402        ONLY:  d, dd2zu, ddzu, ddzw, drho_air, drho_air_zw, dzw, e, heatflux_output_conversion,    &
     403               kh, km, momentumflux_output_conversion, nc, nr, p, ptdf_x, ptdf_y, qc, qr, rdf,     &
     404               rdf_sc, rho_air, rho_air_zw, s, tdiss_m, te_m, tpt_m, tu_m, tv_m, tw_m, ug, u_init, &
     405               u_stokes_zu, vg, v_init, v_stokes_zu, w, zu
    384406
    385407    USE control_parameters,                                                                        &
     
    411433    INTEGER(iwp) ::  ig                  !< index for salsa gases
    412434    INTEGER(iwp) ::  lsp                 !<
     435    INTEGER(iwp) ::  mid                 !< masked output running index
     436#if defined( __parallel )
    413437    INTEGER(iwp) ::  lsp_usr             !<
    414     INTEGER(iwp) ::  mid                 !< masked output running index
    415438    INTEGER(iwp) ::  n                   !< loop counter for chemistry species
     439#endif
    416440
    417441    REAL(wp) ::  dt_3d_old  !< temporary storage of timestep to be used for
     
    520544!-- At beginning determine the first time step
    521545    CALL timestep
     546
     547#if defined( __parallel )
    522548!
    523549!-- Synchronize the timestep in case of nested run.
     
    528554       CALL pmci_synchronize
    529555    ENDIF
     556#endif
    530557
    531558!
     
    558585
    559586       CALL cpu_log( log_point_s(10), 'timesteps', 'start' )
     587
     588#if defined( __parallel )
    560589!
    561590!--    Vertical nesting: initialize fine grid
     
    568597          ENDIF
    569598       ENDIF
     599#endif
     600
    570601!
    571602!--    Determine ug, vg and w_subs in dependence on data from external file
     
    764795!--       Set the swap level for all modules
    765796          CALL module_interface_swap_timelevel( MOD( timestep_count, 2) )
     797
     798#if defined( __parallel )
    766799!
    767800!--       Set the swap level for steering the pmc data transfer
    768801          IF ( nested_run )  CALL pmci_set_swaplevel( MOD( timestep_count, 2) + 1 )  !> @todo: why the +1 ?
     802#endif
    769803
    770804          CALL cpu_log( log_point(28), 'swap_timelevel', 'stop' )
    771805
     806#if defined( __parallel )
    772807!
    773808!--       Vertical nesting: Interpolate fine grid data to the coarse grid
     
    886921
    887922          ENDIF
     923#endif
    888924
    889925!
     
    962998
    963999             IF (  vnest_init ) THEN
     1000#if defined( __parallel )
    9641001!
    9651002!--             Compute pressure in the CG, interpolate top boundary conditions
     
    9771014                CALL vnest_anterpolate_e
    9781015                CALL cpu_log( log_point_s(28), 'vnest_anter_e', 'stop' )
     1016#else
     1017                CONTINUE
     1018#endif
    9791019
    9801020             ELSE
     1021#if defined( __parallel )
    9811022!
    9821023!--             Mass (volume) flux correction to ensure global mass conservation for child domains.
     
    9881029                   ENDIF
    9891030                ENDIF
    990 
     1031#endif
    9911032                CALL pres
    9921033
     
    11071148             ENDIF
    11081149             CALL cpu_log( log_point(17), 'diffusivities', 'stop' )
     1150
     1151#if defined( __parallel )
    11091152!
    11101153!--          Vertical nesting: set fine grid eddy viscosity top boundary condition
    11111154             IF ( vnest_init )  CALL vnest_boundary_conds_khkm
     1155#endif
    11121156
    11131157          ENDIF
     
    16121656       CALL timestep
    16131657
     1658#if defined( __parallel )
    16141659!
    16151660!--    Synchronize the timestep in case of nested run.
     
    16201665          CALL pmci_synchronize
    16211666       ENDIF
     1667#endif
    16221668
    16231669!
     
    16531699!$ACC END DATA
    16541700
     1701#if defined( __parallel )
    16551702!
    16561703!-- Vertical nesting: Deallocate variables initialized for vertical nesting   
    16571704    IF ( vnest_init )  CALL vnest_deallocate
     1705#endif
    16581706
    16591707    IF ( myid == 0 )  CALL finish_progress_bar
Note: See TracChangeset for help on using the changeset viewer.