Ignore:
Timestamp:
Apr 24, 2019 12:52:08 PM (5 years ago)
Author:
banzhafs
Message:

Correct/complete module_interface introduction for chemistry model and bug fix in chem_depo subroutine

File:
1 edited

Legend:

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

    r3885 r3929  
    2525! -----------------
    2626! $Id$
     27! Reverse changes back from revision 3878: use chem_boundary_conds instead of
     28! chem_boundary_conds_decycle
     29!
     30!
     31! 3885 2019-04-11 11:29:34Z kanani
    2732! Changes related to global restructuring of location messages and introduction
    2833! of additional debug messages
    29 ! 
     34!
    3035! 3879 2019-04-08 20:25:23Z knoop
    3136! Moved wtm_forces to module_interface_actions
     
    510515
    511516    USE chem_gasphase_mod,                                                                         &
    512         ONLY:  nspec
     517        ONLY:  nvar
    513518
    514519    USE chem_modules,                                                                              &
    515         ONLY:  bc_cs_t_val, emissions_anthropogenic, nspec_out, chem_species
     520        ONLY:  bc_cs_t_val, chem_species, cs_name, emissions_anthropogenic, nspec_out
    516521
    517522    USE chemistry_model_mod,                                                                       &
    518         ONLY:  chem_boundary_conds_decycle
     523        ONLY:  chem_boundary_conds
    519524
    520525    USE control_parameters,                                                                        &
     
    684689    INTEGER(iwp)      ::  icc       !< additional index for aerosol mass bins
    685690    INTEGER(iwp)      ::  ig        !< index for salsa gases
     691    INTEGER(iwp)      ::  lsp
     692    INTEGER(iwp)      ::  lsp_usr   !<
    686693    INTEGER(iwp)      ::  n         !< loop counter for chemistry species
    687694
     
    861868           bc_q_t_val  = ( q_init(nzt+1) - q_init(nzt) ) / dzu(nzt+1)
    862869           IF ( air_chemistry )  THEN
    863               DO  n = 1, nspec
    864                  bc_cs_t_val = (  chem_species(n)%conc_pr_init(nzt+1)                            &
    865                                 - chem_species(n)%conc_pr_init(nzt) )                            &
     870              DO  lsp = 1, nvar
     871                 bc_cs_t_val = (  chem_species(lsp)%conc_pr_init(nzt+1)                            &
     872                                - chem_species(lsp)%conc_pr_init(nzt) )                            &
    866873                               / dzu(nzt+1)
    867874              ENDDO
     
    10381045          ENDIF
    10391046          IF ( passive_scalar )  CALL exchange_horiz( s_p, nbgp )
    1040           IF ( air_chemistry  )  CALL chem_boundary_conds_decycle
     1047          IF ( air_chemistry )  THEN
     1048             DO  lsp = 1, nvar
     1049                CALL exchange_horiz( chem_species(lsp)%conc_p, nbgp )
     1050!
     1051!--             kanani: Push chem_boundary_conds after CALL boundary_conds
     1052                lsp_usr = 1
     1053                DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
     1054                   IF ( TRIM(chem_species(lsp)%name) == TRIM(cs_name(lsp_usr)) )  THEN
     1055                      CALL chem_boundary_conds( chem_species(lsp)%conc_p,                          &
     1056                                                chem_species(lsp)%conc_pr_init )
     1057                   ENDIF
     1058                   lsp_usr = lsp_usr + 1
     1059                ENDDO
     1060             ENDDO
     1061          ENDIF
    10411062
    10421063          IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
     
    11211142
    11221143                IF ( air_chemistry )  THEN
    1123                    DO  n = 1, nspec
     1144                   DO  n = 1, nvar
    11241145                      CALL exchange_horiz( chem_species(n)%conc, nbgp )
    11251146                   ENDDO
Note: See TracChangeset for help on using the changeset viewer.