Ignore:
Timestamp:
Oct 2, 2018 12:21:11 PM (6 years ago)
Author:
kanani
Message:

Merge chemistry branch at r3297 to trunk

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/prognostic_equations.f90

    r3294 r3298  
    2525! -----------------
    2626! $Id$
     27! Code added for decycling chemistry (basit)
     28!
     29! 3294 2018-10-01 02:37:10Z raasch
    2730! changes concerning modularization of ocean option
    2831!
     
    335338
    336339    USE chemistry_model_mod,                                                   &
    337         ONLY:  chem_integrate, chem_prognostic_equations,                      &
    338                chem_species, nspec, nvar, spc_names
     340        ONLY:  chem_integrate, chem_species,  chem_prognostic_equations,       &
     341               nspec, nvar, spc_names, chem_boundary_conds
    339342           
    340343    USE chem_modules,                                                          &
     
    343346    USE chem_photolysis_mod,                                                   &
    344347        ONLY:  photolysis_control
     348
     349    USE chem_modules,                                                          &
     350        ONLY:  call_chem_at_all_substeps, chem_gasphase_on, cs_name
    345351
    346352    USE control_parameters,                                                    &
     
    456462
    457463    LOGICAL      ::  loop_start          !<
    458     INTEGER      ::  n, lsp              !< lsp running index for chem spcs
     464    INTEGER(iwp) ::  n
     465    INTEGER(iwp) :: lsp
     466    INTEGER(iwp) :: lsp_usr              !< lsp running index for chem spcs
    459467
    460468
     
    468476!-- concentrations of chemical species                                   
    469477    IF ( air_chemistry )  THEN
     478       lsp_usr = 1
    470479!
    471480!--    If required, calculate photolysis frequencies -
     
    492501!--    Loop over chemical species       
    493502       CALL cpu_log( log_point_s(84), 'chemistry exch-horiz ', 'start' )
    494        DO  n = 1, nspec
    495           CALL exchange_horiz( chem_species(n)%conc, nbgp )     
     503       DO  lsp = 1, nspec
     504          CALL exchange_horiz( chem_species(lsp)%conc, nbgp )   
     505          lsp_usr = 1 
     506          DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
     507             IF ( TRIM(chem_species(lsp)%name) == TRIM(cs_name(lsp_usr)) )  THEN
     508
     509                CALL chem_boundary_conds( chem_species(lsp)%conc_p,                                 &
     510                                          chem_species(lsp)%conc_pr_init )
     511             
     512             ENDIF
     513             lsp_usr = lsp_usr +1
     514          ENDDO
     515         
    496516       ENDDO
    497517       CALL cpu_log( log_point_s(84), 'chemistry exch-horiz ', 'stop' )
Note: See TracChangeset for help on using the changeset viewer.