Ignore:
Timestamp:
Apr 30, 2020 12:20:40 PM (4 years ago)
Author:
raasch
Message:

chemistry decycling replaced by explicit setting of lateral boundary conditions

File:
1 edited

Legend:

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

    r4508 r4511  
    2525! -----------------
    2626! $Id$
     27! chemistry decycling replaced by explicit setting of lateral boundary conditions
     28!
     29! 4508 2020-04-24 13:32:20Z raasch
    2730! salsa decycling replaced by explicit setting of lateral boundary conditions
    2831!
     
    242245
    243246    USE chem_modules,                                                                              &
    244         ONLY:  bc_cs_t_val, chem_species, emissions_anthropogenic, emiss_read_legacy_mode,         &
    245                n_matched_vars
    246 
    247 #if defined( __parallel )
    248     USE chem_modules,                                                                              &
    249         ONLY:  cs_name
    250 #endif
    251 
    252     USE chemistry_model_mod,                                                                       &
    253         ONLY:  chem_boundary_conds
     247        ONLY:  bc_cs_t_val, chem_species, communicator_chem, emissions_anthropogenic,              &
     248               emiss_read_legacy_mode, n_matched_vars
    254249
    255250    USE control_parameters,                                                                        &
     
    469464    INTEGER(iwp) ::  icc                 !< additional index for aerosol mass bins
    470465    INTEGER(iwp) ::  ig                  !< index for salsa gases
    471     INTEGER(iwp) ::  lsp                 !<
    472466    INTEGER(iwp) ::  mid                 !< masked output running index
    473 #if defined( __parallel )
    474     INTEGER(iwp) ::  lsp_usr             !<
    475467    INTEGER(iwp) ::  n                   !< loop counter for chemistry species
    476 #endif
    477468
    478469    REAL(wp) ::  dt_3d_old  !< temporary storage of timestep to be used for
     
    675666           bc_q_t_val  = ( q_init(nzt+1) - q_init(nzt) ) / dzu(nzt+1)
    676667           IF ( air_chemistry )  THEN
    677               DO  lsp = 1, nvar
    678                  bc_cs_t_val = (  chem_species(lsp)%conc_pr_init(nzt+1)                            &
    679                                 - chem_species(lsp)%conc_pr_init(nzt) )                            &
     668              DO  n = 1, nvar
     669                 bc_cs_t_val = (  chem_species(n)%conc_pr_init(nzt+1)                              &
     670                                - chem_species(n)%conc_pr_init(nzt) )                              &
    680671                               / dzu(nzt+1)
    681672              ENDDO
     
    824815          IF ( passive_scalar )  CALL exchange_horiz( s_p, nbgp )
    825816          IF ( air_chemistry )  THEN
    826              DO  lsp = 1, nvar
    827                 CALL exchange_horiz( chem_species(lsp)%conc_p, nbgp )
     817             DO  n = 1, nvar
     818                CALL exchange_horiz( chem_species(n)%conc_p, nbgp,                                 &
     819                                     alternative_communicator = communicator_chem )
    828820             ENDDO
    829821          ENDIF
     
    932924                IF ( air_chemistry )  THEN
    933925                   DO  n = 1, nvar
    934                       CALL exchange_horiz( chem_species(n)%conc, nbgp )
     926                      CALL exchange_horiz( chem_species(n)%conc, nbgp,                             &
     927                                           alternative_communicator = communicator_chem )
    935928                   ENDDO
    936929                ENDIF
     
    960953!--          Set boundary conditions again after interpolation and anterpolation.
    961954             CALL pmci_boundary_conds
    962 
    963 !
    964 !--          Set chemistry boundary conditions (decycling)
    965              IF ( air_chemistry )  THEN
    966                 DO  lsp = 1, nvar
    967                    lsp_usr = 1
    968                    DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
    969                       IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) )  THEN
    970                          CALL chem_boundary_conds( chem_species(lsp)%conc,                         &
    971                                                    chem_species(lsp)%conc_pr_init )
    972                       ENDIF
    973                       lsp_usr = lsp_usr + 1
    974                    ENDDO
    975                 ENDDO
    976              ENDIF
    977955
    978956             CALL cpu_log( log_point(60), 'nesting', 'stop' )
Note: See TracChangeset for help on using the changeset viewer.