Ignore:
Timestamp:
Oct 24, 2019 1:40:54 PM (4 years ago)
Author:
monakurppa
Message:

Add logical switched nesting_chem and nesting_offline_chem

File:
1 edited

Legend:

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

    r4260 r4273  
    2525! -----------------
    2626! $Id$
     27! Add a logical switch nesting_chem and rename nest_salsa to nesting_salsa
     28!
     29! 4260 2019-10-09 14:04:03Z hellstea
    2730! Rest of the possibly round-off-error sensitive grid-line matching tests
    2831! changed to round-off-error tolerant forms throughout the module.
     
    189192
    190193    USE chem_modules,                                                          &
    191         ONLY:  chem_species
     194        ONLY:  chem_species, nesting_chem
    192195
    193196    USE chemistry_model_mod,                                                   &
     
    248251    USE salsa_mod,                                                             &
    249252        ONLY:  aerosol_mass, aerosol_number, gconc_2, mconc_2, nbins_aerosol,  &
    250                ncomponents_mass, nconc_2, nest_salsa, ngases_salsa, salsa_gas, &
    251                salsa_gases_from_chem
     253               ncomponents_mass, nconc_2, nesting_salsa, ngases_salsa,        &
     254               salsa_gas, salsa_gases_from_chem
    252255
    253256    USE surface_mod,                                                           &
     
    11661169       ENDIF
    11671170       
    1168        IF ( air_chemistry )  THEN
     1171       IF ( air_chemistry  .AND.  nesting_chem )  THEN
    11691172          DO n = 1, nspec
    11701173             CALL pmc_set_dataarray_name( 'parent', 'chem_' // TRIM( chem_species(n)%name ),        &
     
    11731176       ENDIF
    11741177
    1175        IF ( salsa  .AND.  nest_salsa )  THEN
     1178       IF ( salsa  .AND.  nesting_salsa )  THEN
    11761179          DO  lb = 1, nbins_aerosol
    11771180             WRITE(salsa_char,'(i0)') lb
     
    23102313!
    23112314!-- Chemistry, depends on number of species
    2312     IF ( air_chemistry )  pmc_max_array = pmc_max_array + nspec
     2315    IF ( air_chemistry  .AND.  nesting_chem )  pmc_max_array = pmc_max_array + nspec
    23132316!
    23142317!-- SALSA, depens on the number aerosol size bins and chemical components +
    23152318!-- the number of default gases
    2316     IF ( salsa  .AND.  nest_salsa )  pmc_max_array = pmc_max_array + nbins_aerosol +                &
    2317          nbins_aerosol * ncomponents_mass
     2319    IF ( salsa  .AND.  nesting_salsa )  pmc_max_array = pmc_max_array + nbins_aerosol +            &
     2320                                                        nbins_aerosol * ncomponents_mass
    23182321    IF ( .NOT. salsa_gases_from_chem )  pmc_max_array = pmc_max_array + ngases_salsa
    23192322
     
    27172720       ENDIF
    27182721
    2719        IF ( air_chemistry )  THEN
     2722       IF ( air_chemistry  .AND.  nesting_chem )  THEN
    27202723          DO  n = 1, nspec
    27212724             CALL pmci_interp_1sto_all ( chem_species(n)%conc, chem_spec_c(:,:,:,n),                &
     
    27242727       ENDIF
    27252728
    2726        IF ( salsa  .AND.  nest_salsa )  THEN
     2729       IF ( salsa  .AND.  nesting_salsa )  THEN
    27272730          DO  lb = 1, nbins_aerosol
    27282731             CALL pmci_interp_1sto_all ( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),       &
     
    33943397             ENDIF
    33953398
    3396              IF ( air_chemistry )  THEN
     3399             IF ( air_chemistry  .AND.  nesting_chem )  THEN
    33973400                DO  n = 1, nspec
    33983401                   CALL pmci_interp_1sto_lr( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    34013404             ENDIF
    34023405
    3403              IF ( salsa  .AND.  nest_salsa )  THEN
     3406             IF ( salsa  .AND.  nesting_salsa )  THEN
    34043407                DO  lb = 1, nbins_aerosol
    34053408                   CALL pmci_interp_1sto_lr( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),   &
     
    34653468             ENDIF
    34663469
    3467              IF ( air_chemistry )  THEN
     3470             IF ( air_chemistry  .AND.  nesting_chem )  THEN
    34683471                DO  n = 1, nspec
    34693472                   CALL pmci_interp_1sto_lr( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    34723475             ENDIF
    34733476
    3474              IF ( salsa  .AND.  nest_salsa )  THEN
     3477             IF ( salsa  .AND.  nesting_salsa )  THEN
    34753478                DO  lb = 1, nbins_aerosol
    34763479                   CALL pmci_interp_1sto_lr( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),   &
     
    35363539             ENDIF
    35373540
    3538              IF ( air_chemistry )  THEN
     3541             IF ( air_chemistry  .AND.  nesting_chem )  THEN
    35393542                DO  n = 1, nspec
    35403543                   CALL pmci_interp_1sto_sn( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    35433546             ENDIF
    35443547             
    3545              IF ( salsa  .AND.  nest_salsa )  THEN
     3548             IF ( salsa  .AND.  nesting_salsa )  THEN
    35463549                DO  lb = 1, nbins_aerosol
    35473550                   CALL pmci_interp_1sto_sn( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),   &
     
    36073610             ENDIF
    36083611
    3609              IF ( air_chemistry )  THEN
     3612             IF ( air_chemistry  .AND.  nesting_chem )  THEN
    36103613                DO  n = 1, nspec
    36113614                   CALL pmci_interp_1sto_sn( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    36143617             ENDIF
    36153618             
    3616              IF ( salsa  .AND.  nest_salsa )  THEN
     3619             IF ( salsa  .AND.  nesting_salsa )  THEN
    36173620                DO  lb = 1, nbins_aerosol
    36183621                   CALL pmci_interp_1sto_sn( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),   &
     
    36733676       ENDIF
    36743677
    3675        IF ( air_chemistry )  THEN
     3678       IF ( air_chemistry  .AND.  nesting_chem )  THEN
    36763679          DO  n = 1, nspec
    36773680             CALL pmci_interp_1sto_t( chem_species(n)%conc, chem_spec_c(:,:,:,n),                   &
     
    36803683       ENDIF
    36813684       
    3682        IF ( salsa  .AND.  nest_salsa )  THEN
     3685       IF ( salsa  .AND.  nesting_salsa )  THEN
    36833686          DO  lb = 1, nbins_aerosol
    36843687             CALL pmci_interp_1sto_t( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),          &
     
    37643767      ENDIF
    37653768
    3766       IF ( air_chemistry )  THEN
     3769      IF ( air_chemistry  .AND.  nesting_chem )  THEN
    37673770         DO  n = 1, nspec
    37683771            CALL pmci_anterp_tophat( chem_species(n)%conc, chem_spec_c(:,:,:,n),                    &
     
    37703773         ENDDO
    37713774      ENDIF
    3772      
    3773       IF ( salsa  .AND.  nest_salsa )  THEN
     3775
     3776      IF ( salsa  .AND.  nesting_salsa )  THEN
    37743777         DO  lb = 1, nbins_aerosol
    37753778            CALL pmci_anterp_tophat( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),           &
     
    48164819!
    48174820!-- Set Neumann boundary conditions for chemical species
    4818     IF ( air_chemistry )  THEN
     4821    IF ( air_chemistry  .AND.  nesting_chem )  THEN
    48194822       IF ( ibc_cs_b == 1 )  THEN
    48204823          DO  n = 1, nspec
     
    48364839!
    48374840!-- Set Neumann boundary conditions for aerosols and salsa gases
    4838     IF ( salsa  .AND.  nest_salsa )  THEN
     4841    IF ( salsa  .AND.  nesting_salsa )  THEN
    48394842       IF ( ibc_salsa_b == 1 )  THEN
    48404843          DO  m = 1, bc_h(0)%ns
Note: See TracChangeset for help on using the changeset viewer.