Ignore:
Timestamp:
Apr 8, 2019 8:25:23 PM (5 years ago)
Author:
knoop
Message:

Moved loop over chem_species into chem_boundary_conds_decycle

File:
1 edited

Legend:

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

    r3876 r3879  
    3838!
    3939! 3833 2019-03-28 15:04:04Z forkel
    40 ! added USE chem_gasphase_mod, replaced nspec by nvar since fixed compounds are not integrated
     40! added USE chem_gasphase_mod, replaced nspec by nspec since fixed compounds are not integrated
    4141!
    4242! 3820 2019-03-27 11:53:41Z forkel
     
    506506
    507507    USE chem_gasphase_mod,                                                                         &
    508         ONLY:  nvar
     508        ONLY:  nspec
    509509
    510510    USE chem_modules,                                                                              &
    511         ONLY:  bc_cs_t_val, cs_name, emissions_anthropogenic, nspec_out, chem_species
     511        ONLY:  bc_cs_t_val, emissions_anthropogenic, nspec_out, chem_species
    512512
    513513    USE chemistry_model_mod,                                                                       &
    514         ONLY:  chem_boundary_conds
     514        ONLY:  chem_boundary_conds_decycle
    515515
    516516    USE control_parameters,                                                                        &
     
    680680    INTEGER(iwp)      ::  icc       !< additional index for aerosol mass bins
    681681    INTEGER(iwp)      ::  ig        !< index for salsa gases
    682     INTEGER(iwp)      ::  lsp
    683     INTEGER(iwp)      ::  lsp_usr   !<
    684682    INTEGER(iwp)      ::  n         !< loop counter for chemistry species
    685683
     
    859857           bc_q_t_val  = ( q_init(nzt+1) - q_init(nzt) ) / dzu(nzt+1)
    860858           IF ( air_chemistry )  THEN
    861               DO  lsp = 1, nvar
    862                  bc_cs_t_val = (  chem_species(lsp)%conc_pr_init(nzt+1)                            &
    863                                 - chem_species(lsp)%conc_pr_init(nzt) )                            &
     859              DO  n = 1, nspec
     860                 bc_cs_t_val = (  chem_species(n)%conc_pr_init(nzt+1)                            &
     861                                - chem_species(n)%conc_pr_init(nzt) )                            &
    864862                               / dzu(nzt+1)
    865863              ENDDO
     
    10361034          ENDIF
    10371035          IF ( passive_scalar )  CALL exchange_horiz( s_p, nbgp )
    1038           IF ( air_chemistry )  THEN
    1039              DO  lsp = 1, nvar
    1040                 CALL exchange_horiz( chem_species(lsp)%conc_p, nbgp )
    1041 !
    1042 !--             kanani: Push chem_boundary_conds after CALL boundary_conds
    1043                 lsp_usr = 1
    1044                 DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
    1045                    IF ( TRIM(chem_species(lsp)%name) == TRIM(cs_name(lsp_usr)) )  THEN
    1046                       CALL chem_boundary_conds( chem_species(lsp)%conc_p,                          &
    1047                                                 chem_species(lsp)%conc_pr_init )
    1048                    ENDIF
    1049                    lsp_usr = lsp_usr + 1
    1050                 ENDDO
    1051              ENDDO
    1052           ENDIF
     1036          IF ( air_chemistry  )  CALL chem_boundary_conds_decycle
    10531037
    10541038          IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
     
    11331117
    11341118                IF ( air_chemistry )  THEN
    1135                    DO  n = 1, nvar     
     1119                   DO  n = 1, nspec
    11361120                      CALL exchange_horiz( chem_species(n)%conc, nbgp )
    11371121                   ENDDO
Note: See TracChangeset for help on using the changeset viewer.