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/time_integration.f90

    r3294 r3298  
    2525! -----------------
    2626! $Id$
     27! - Formatting, clean-up, comments (kanani)
     28! - Added CALL to chem_emissions_setup (Russo)
     29! - Code added for decycling chemistry (basit)
     30!
     31! 3294 2018-10-01 02:37:10Z raasch
    2732! changes concerning modularization of ocean option
    2833!
     
    380385        ONLY:  calc_mean_profile
    381386
     387    USE chem_emissions_mod,                                                    &
     388        ONLY:  chem_emissions_setup
     389
     390    USE chem_modules,                                                          &
     391        ONLY:  bc_cs_t_val, call_chem_at_all_substeps, cs_name,                &
     392               constant_csflux, do_emis, nspec, nspec_out
     393
    382394    USE chemistry_model_mod,                                                   &
    383         ONLY:  chem_emissions, chem_species
    384 
    385     USE chem_modules,                                                          &
    386         ONLY:  nspec
     395        ONLY:  chem_boundary_conds, chem_species
    387396
    388397    USE control_parameters,                                                    &
     
    426435        ONLY:  cpu_log, log_point, log_point_s
    427436
     437    USE date_and_time_mod,                                                     &
     438        ONLY:  calc_date_and_time, hour_call_emis, hour_of_year
     439
    428440    USE flight_mod,                                                            &
    429441        ONLY:  flight_measurement
     
    450462               lsf_nesting_offline, lsf_nesting_offline_mass_conservation
    451463
    452     USE netcdf_data_input_mod,                                                 &
    453         ONLY:  nest_offl, netcdf_data_input_lsf
    454 
    455464    USE multi_agent_system_mod,                                                &
    456465        ONLY:  agents_active, multi_agent_system
     466
     467    USE netcdf_data_input_mod,                                                 &
     468        ONLY:  chem_emis, chem_emis_att, nest_offl, netcdf_data_input_lsf
    457469
    458470    USE ocean_mod,                                                             &
     
    525537    IMPLICIT NONE
    526538
    527     CHARACTER (LEN=9) ::  time_to_string          !<
    528 
    529     INTEGER(iwp)      ::  n  !< loop counter for chemistry species
     539    CHARACTER (LEN=9) ::  time_to_string   !<
     540
     541    INTEGER(iwp)      ::  lsp       !<
     542    INTEGER(iwp)      ::  lsp_usr   !<
     543    INTEGER(iwp)      ::  n         !< loop counter for chemistry species
    530544
    531545    REAL(wp) ::  dt_3d_old  !< temporary storage of timestep to be used for
     
    611625           bc_pt_t_val = ( pt_init(nzt+1) - pt_init(nzt) ) / dzu(nzt+1)
    612626           bc_q_t_val  = ( q_init(nzt+1) - q_init(nzt) ) / dzu(nzt+1)
     627           IF ( air_chemistry )  THEN
     628              DO  lsp = 1, nspec
     629                 bc_cs_t_val = (  chem_species(lsp)%conc_pr_init(nzt+1)       &
     630                                - chem_species(lsp)%conc_pr_init(nzt) )       &
     631                               / dzu(nzt+1)
     632              ENDDO
     633           ENDIF
    613634       ENDIF
    614635!
     
    783804          IF ( passive_scalar )  CALL exchange_horiz( s_p, nbgp )
    784805          IF ( air_chemistry )  THEN
    785              DO  n = 1, nspec     
    786                 CALL exchange_horiz( chem_species(n)%conc_p, nbgp )
     806             DO  lsp = 1, nspec
     807                CALL exchange_horiz( chem_species(lsp)%conc_p, nbgp )
     808!
     809!--             kanani: Push chem_boundary_conds after CALL boundary_conds
     810                lsp_usr = 1
     811                DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
     812                   IF ( TRIM(chem_species(lsp)%name) == TRIM(cs_name(lsp_usr)) )  THEN
     813                      CALL chem_boundary_conds( chem_species(lsp)%conc_p,              &
     814                                                chem_species(lsp)%conc_pr_init )
     815                   ENDIF
     816                   lsp_usr = lsp_usr + 1
     817                ENDDO
    787818             ENDDO
    788819          ENDIF
     
    11221153!
    11231154!--    If required, consider chemical emissions
    1124 !--    (todo (FK): Implement hourly call of emissions, using time_utc from
    1125 !--                data_and_time_mod.f90;
    1126 !--                move the CALL to appropriate location)
    1127        IF ( air_chemistry ) THEN
    1128           CALL chem_emissions
     1155       IF ( air_chemistry  .AND.  do_emis )  THEN
     1156!
     1157!--       Update the time --> kanani: revise location of this CALL
     1158          CALL calc_date_and_time
     1159!
     1160!--       Call emission routine only once an hour
     1161          IF (hour_of_year  .GT.  hour_call_emis )  THEN
     1162             CALL chem_emissions_setup( chem_emis_att, chem_emis, nspec_out )
     1163             hour_call_emis = hour_of_year
     1164          ENDIF
    11291165       ENDIF
    11301166!
Note: See TracChangeset for help on using the changeset viewer.