Ignore:
Timestamp:
Apr 24, 2020 1:32:20 PM (4 years ago)
Author:
raasch
Message:

salsa decycling replaced by explicit setting of lateral boundary conditions

File:
1 edited

Legend:

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

    r4502 r4508  
    2525! -----------------
    2626! $Id$
     27! salsa decycling replaced by explicit setting of lateral boundary conditions
     28!
     29! 4502 2020-04-17 16:14:16Z schwenkel
    2730! Implementation of ice microphysics
    2831!
     
    213216
    214217    USE arrays_3d,                                                                                 &
    215         ONLY:  diss, diss_p, dzu, e_p, nc_p, nr_p, prho, pt, pt_p, pt_init, q, qc_p, qr_p, q_init, &
    216                q_p, ref_state, rho_ocean, sa_p, s_p, tend, u, u_p, v, vpt, v_p, w_p,               &
    217                qi_p, ni_p
     218        ONLY:  diss, diss_p, dzu, e_p, nc_p, ni_p, nr_p, prho, pt, pt_p, pt_init, q, qc_p, qr_p,   &
     219               q_init, q_p, qi_p, ref_state, rho_ocean, sa_p, s_p, tend, u, u_p, v, vpt, v_p, w_p
    218220
    219221#if defined( __parallel )  &&  ! defined( _OPENACC )
    220222    USE arrays_3d,                                                                                 &
    221         ONLY:  e, nc, nr, qc, qr, s, w, qi, ni
     223        ONLY:  e, nc, ni, nr, qc, qi, qr, s, w
    222224#endif
    223225
     
    228230    USE bulk_cloud_model_mod,                                                                      &
    229231        ONLY: bulk_cloud_model, calc_liquid_water_content, collision_turbulence,                   &
    230               microphysics_morrison, microphysics_seifert, microphysics_ice_extension
     232              microphysics_ice_extension, microphysics_morrison, microphysics_seifert
    231233
    232234    USE calc_mean_profile_mod,                                                                     &
     
    274276               time_dopr_listing, time_dopts, time_dosp, time_dosp_av, time_dots, time_do_av,      &
    275277               time_do_sla, time_disturb, time_run_control, time_since_reference_point,            &
    276                turbulent_inflow, turbulent_outflow, urban_surface,                                 &
     278               timestep_count, turbulent_inflow, turbulent_outflow, urban_surface,                 &
    277279               use_initial_profile_as_reference, use_single_reference_value, u_gtrans, v_gtrans,   &
    278                virtual_flight, virtual_measurement, ws_scheme_mom, ws_scheme_sca, timestep_count
     280               virtual_flight, virtual_measurement, ws_scheme_mom, ws_scheme_sca
    279281
    280282#if defined( __parallel )
     
    365367    USE salsa_mod,                                                                                 &
    366368        ONLY: aerosol_number, aerosol_mass, bc_am_t_val, bc_an_t_val, bc_gt_t_val,                 &
    367               nbins_aerosol, ncomponents_mass, ngases_salsa, salsa_boundary_conds,                 &
    368               salsa_emission_update, salsa_gas, salsa_gases_from_chem, skip_time_do_salsa
     369              communicator_salsa, nbins_aerosol, ncomponents_mass, ngases_salsa,                   &
     370              salsa_boundary_conditions, salsa_emission_update, salsa_gas, salsa_gases_from_chem,  &
     371              skip_time_do_salsa
    369372
    370373    USE spectra_mod,                                                                               &
     
    434437               flux_s_w,                                                                           &
    435438               heatflux_output_conversion,                                                         &
    436                kh, km, momentumflux_output_conversion, nc, nr, p, ptdf_x, ptdf_y, qc, qr, rdf,     &
     439               kh, km, momentumflux_output_conversion, nc, ni, nr, p, ptdf_x, ptdf_y, qc, qi, qr, rdf,     &
    437440               rdf_sc, rho_air, rho_air_zw, s, tdiss_m, te_m, tpt_m, tu_m, tv_m, tw_m, ug, u_init, &
    438                u_stokes_zu, vg, v_init, v_stokes_zu, w, zu, qi, ni
     441               u_stokes_zu, vg, v_init, v_stokes_zu, w, zu
    439442
    440443    USE control_parameters,                                                                        &
     
    448451               sums_wsus_ws_l, sums_vs2_ws_l, sums_wsvs_ws_l, sums_ws2_ws_l, sums_wspts_ws_l,      &
    449452               sums_wsqs_ws_l, sums_wssas_ws_l, sums_wsqcs_ws_l, sums_wsqrs_ws_l, sums_wsncs_ws_l, &
    450                sums_wsnrs_ws_l, sums_wsss_ws_l, weight_substep, sums_salsa_ws_l,                   &
    451                sums_wsqis_ws_l, sums_wsnis_ws_l
     453               sums_wsnrs_ws_l, sums_wsss_ws_l, weight_substep, sums_salsa_ws_l, sums_wsqis_ws_l,  &
     454               sums_wsnis_ws_l
    452455
    453456    USE surface_mod,                                                                               &
     
    703706       CALL module_interface_actions( 'before_timestep' )
    704707
     708!
    705709!--    Start of intermediate step loop
    706710       intermediate_timestep_count = 0
     
    770774             CALL prognostic_equations_vector
    771775          ENDIF
     776
    772777!
    773778!--       Movement of agents in multi agent system
     
    826831          IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
    827832             DO  ib = 1, nbins_aerosol
    828                 CALL exchange_horiz( aerosol_number(ib)%conc_p, nbgp )
     833                CALL exchange_horiz( aerosol_number(ib)%conc_p, nbgp,                              &
     834                                     alternative_communicator = communicator_salsa )
    829835                DO  ic = 1, ncomponents_mass
    830836                   icc = ( ic - 1 ) * nbins_aerosol + ib
    831                    CALL exchange_horiz( aerosol_mass(icc)%conc_p, nbgp )
     837                   CALL exchange_horiz( aerosol_mass(icc)%conc_p, nbgp,                            &
     838                                        alternative_communicator = communicator_salsa )
    832839                ENDDO
    833840             ENDDO
    834841             IF ( .NOT. salsa_gases_from_chem )  THEN
    835842                DO  ig = 1, ngases_salsa
    836                    CALL exchange_horiz( salsa_gas(ig)%conc_p, nbgp )
     843                   CALL exchange_horiz( salsa_gas(ig)%conc_p, nbgp,                                &
     844                                        alternative_communicator = communicator_salsa )
    837845                ENDDO
    838846             ENDIF
    839847          ENDIF
     848
    840849          CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
    841850
     
    845854!--       boundary conditions for module-specific variables
    846855          CALL module_interface_boundary_conditions
     856
    847857!
    848858!--       Incrementing timestep counter
     
    906916                   ENDIF
    907917                   IF ( bulk_cloud_model  .AND.  microphysics_ice_extension )  THEN
    908                        CALL exchange_horiz( qi, nbgp )
    909                        CALL exchange_horiz( ni, nbgp )
     918                      CALL exchange_horiz( qi, nbgp )
     919                      CALL exchange_horiz( ni, nbgp )
    910920                   ENDIF
     921
    911922                ENDIF
    912923
     
    927938                IF ( salsa  .AND. time_since_reference_point >= skip_time_do_salsa )  THEN
    928939                   DO  ib = 1, nbins_aerosol
    929                       CALL exchange_horiz( aerosol_number(ib)%conc, nbgp )
     940                      CALL exchange_horiz( aerosol_number(ib)%conc, nbgp,                          &
     941                                           alternative_communicator = communicator_salsa )
    930942                      DO  ic = 1, ncomponents_mass
    931943                         icc = ( ic - 1 ) * nbins_aerosol + ib
    932                          CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp )
     944                         CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp,                        &
     945                                              alternative_communicator = communicator_salsa )
    933946                      ENDDO
    934947                   ENDDO
    935948                   IF ( .NOT. salsa_gases_from_chem )  THEN
    936949                      DO  ig = 1, ngases_salsa
    937                          CALL exchange_horiz( salsa_gas(ig)%conc, nbgp )
     950                         CALL exchange_horiz( salsa_gas(ig)%conc, nbgp,                            &
     951                                              alternative_communicator = communicator_salsa )
    938952                      ENDDO
    939953                   ENDIF
     
    960974                   ENDDO
    961975                ENDDO
    962              ENDIF
    963 
    964 !
    965 !--          Set SALSA boundary conditions (decycling)
    966              IF ( salsa  .AND. time_since_reference_point >= skip_time_do_salsa )  THEN
    967                 DO  ib = 1, nbins_aerosol
    968                    CALL salsa_boundary_conds( aerosol_number(ib)%conc, aerosol_number(ib)%init )
    969                    DO  ic = 1, ncomponents_mass
    970                       icc = ( ic - 1 ) * nbins_aerosol + ib
    971                       CALL salsa_boundary_conds( aerosol_mass(icc)%conc, aerosol_mass(icc)%init )
    972                    ENDDO
    973                 ENDDO
    974                 IF ( .NOT. salsa_gases_from_chem )  THEN
    975                    DO  ig = 1, ngases_salsa
    976                       CALL salsa_boundary_conds( salsa_gas(ig)%conc, salsa_gas(ig)%init )
    977                    ENDDO
    978                 ENDIF
    979976             ENDIF
    980977
Note: See TracChangeset for help on using the changeset viewer.