Ignore:
Timestamp:
Feb 12, 2020 1:08:46 PM (4 years ago)
Author:
banzhafs
Message:

chemistry model: implemented on-demand emission read mode for LOD 2

File:
1 edited

Legend:

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

    r4372 r4403  
    2222! Current revisions:
    2323! -----------------
    24 !
     24! 
    2525!
    2626! Former revisions:
    2727! -----------------
    2828! $Id$
     29! in subroutine chem_init (ECC)
     30! - allows different init paths emission data for legacy
     31!   mode emission and on-demand mode
     32! in subroutine chem_init_internal (ECC)
     33! - reads netcdf file only when legacy mode is activated
     34!   (i.e., emiss_read_legacy_mode = .TRUE.)
     35!   otherwise file is read once at the beginning to obtain
     36!   header information, and emission data are extracted on
     37!   an on-demand basis
     38!
     39! 4372 2020-01-14 10:20:35Z banzhafs
    2940! chem_parin : added handler for new namelist item emiss_legacy_read_mode (ECC)
    3041! added messages
     
    17731784 SUBROUTINE chem_init
    17741785
     1786!
     1787!-- 20200203 (ECC)
     1788!-- introduced additional interfaces for on-demand emission update
     1789
     1790!    USE chem_emissions_mod,                                                    &
     1791!        ONLY:  chem_emissions_init
     1792       
    17751793    USE chem_emissions_mod,                                                    &
    1776         ONLY:  chem_emissions_init
     1794        ONLY:  chem_emissions_init, chem_emissions_header_init
    17771795       
    17781796    USE netcdf_data_input_mod,                                                 &
     
    17911809           ilu_permanent_crops + ilu_savanna + ilu_semi_natural_veg + ilu_tropical_forest +    &
    17921810           ilu_urban ) == 0 )  CONTINUE
    1793          
    1794     IF ( emissions_anthropogenic )  CALL chem_emissions_init
     1811
     1812!
     1813!-- 20200203 (ECC)
     1814!-- calls specific emisisons initialization subroutines
     1815!-- for legacy mode and on-demand mode         
     1816
     1817!    IF ( emissions_anthropogenic )  CALL chem_emissions_init
     1818
     1819    IF  ( emissions_anthropogenic )  THEN
     1820
     1821       IF  ( emiss_read_legacy_mode )  THEN
     1822          CALL chem_emissions_init
     1823       ELSE
     1824          CALL chem_emissions_header_init
     1825       ENDIF
     1826
     1827    ENDIF
     1828
     1829
    17951830!
    17961831!-- Chemistry variables will be initialized if availabe from dynamic
     
    18351870    INTEGER(iwp) ::  lpr_lev           !< running index for chem spcs profile level
    18361871
     1872!
     1873!-- 20200203 ECC
     1874!-- reads netcdf data only under legacy mode
     1875
     1876!    IF ( emissions_anthropogenic )  THEN
     1877!       CALL netcdf_data_input_chemistry_data( chem_emis_att, chem_emis )
     1878!    ENDIF
     1879
    18371880    IF ( emissions_anthropogenic )  THEN
    1838        CALL netcdf_data_input_chemistry_data( chem_emis_att, chem_emis )
     1881       IF ( emiss_read_legacy_mode )  THEN
     1882          CALL netcdf_data_input_chemistry_data( chem_emis_att, chem_emis )
     1883       ENDIF
    18391884    ENDIF
     1885
    18401886!
    18411887!-- Allocate memory for chemical species
     
    24762522                              'Reverting to legacy emission read mode'
    24772523             CALL message ( 'parin_chem', 'CM0466', 0, 0, 0, 6, 0 )
     2524
    24782525             emiss_read_legacy_mode = .TRUE.
    24792526
     
    24822529             message_string = 'New emission read mode activated'           // &
    24832530                              CHAR(10)  //  '                    '         // &
    2484                               'LOD 2 emissions will be read on an '        // &           
    2485                               'hourly basis according to'                  // &             
    2486                               CHAR(10)  //  '                    '         // &
    2487                               'indicated timestamps'
     2531                              'LOD 2 emissions will be updated on-demand ' // &           
     2532                              'according to indicated timestamps'
    24882533             CALL message ( 'parin_chem', 'CM0467', 0, 0, 0, 6, 0 )
    24892534
Note: See TracChangeset for help on using the changeset viewer.