Ignore:
Timestamp:
May 13, 2019 11:04:01 AM (5 years ago)
Author:
suehring
Message:

Updates from chemistriy branched merged into trunk: code cleaning and formatting, code structure optimizations

File:
1 edited

Legend:

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

    r3961 r3968  
    2525! -----------------
    2626! $Id$
     27! - clean-up index notations for emission_values to eliminate magic numbers
     28! - introduce temporary variable dum_var_5d as well as subroutines
     29!   get_var_5d_real and get_var_5d_real_dynamic
     30! - remove emission-specific code in generic get_variable routines
     31! - in subroutine netcdf_data_input_chemistry_data change netCDF LOD 1
     32!   (default) emission_values to the following index order:
     33!   z, y, x, species, category
     34! - in subroutine netcdf_data_input_chemistry_data
     35!   changed netCDF LOD 2 pre-processed emission_values to the following index
     36!   order: time, z, y, x, species
     37! - in type chem_emis_att_type replace nspec with n_emiss_species
     38!   but retained nspec for backward compatibility with salsa_mod. (E.C. Chan)
     39!
     40! 3961 2019-05-08 16:12:31Z suehring
    2741! Revise checks for building IDs and types
    2842!
     
    289303! Initial revision (suehring)
    290304!
    291 !
    292 !
    293 !
    294305! Authors:
    295306! --------
    296307! @author Matthias Suehring
     308! @author Edward C. Chan
     309! @author Emanuele Russo
    297310!
    298311! Description:
     
    300313!> Modulue contains routines to input data according to Palm input data
    301314!> standart using dynamic and static input files.
    302 !> @todo - Chemistry: revise reading of netcdf file and ajdust formatting according to standard!!!
     315!> @todo - Chemistry: revise reading of netcdf file and ajdust formatting
     316!>         according to standard!!! (ecc/done)
    303317!> @todo - Order input alphabetically
    304318!> @todo - Revise error messages and error numbers
    305319!> @todo - Input of missing quantities (chemical species, emission rates)
    306320!> @todo - Defninition and input of still missing variable attributes
     321!>         (ecc/what are they?)
    307322!> @todo - Input of initial geostrophic wind profiles with cyclic conditions.
     323!> @todo - remove z dimension from default_emission_data nad preproc_emission_data
     324!          and correpsonding subroutines get_var_5d_real and get_var_5d_dynamic (ecc)
     325!> @todo - decpreciate chem_emis_att_type@nspec (ecc)
     326!> @todo - depreciate subroutines get_variable_4d_to_3d_real and
     327!>         get_variable_5d_to_4d_real (ecc)
    308328!------------------------------------------------------------------------------!
    309329 MODULE netcdf_data_input_mod
     
    348368       CHARACTER(LEN=17) ::  char_s = 'ls_forcing_south_' !< leading substring for variables at south boundary
    349369       CHARACTER(LEN=15) ::  char_t = 'ls_forcing_top_'   !< leading substring for variables at top boundary
    350    
     370
    351371       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names         !< list of variable in dynamic input file
    352372       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_l  !< names of mesoscale nested chemistry variables at left boundary
     
    363383
    364384       LOGICAL      ::  init         = .FALSE. !< flag indicating that offline nesting is already initialized
    365        
     385
    366386       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_l !< flags inidicating whether left boundary data for chemistry is in dynamic input file 
    367387       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_n !< flags inidicating whether north boundary data for chemistry is in dynamic input file
     
    491511
    492512       !-DIMENSIONS
    493        INTEGER(iwp)                                 :: nspec=0                   !< number of chem species for which emission values are provided
    494        INTEGER(iwp)                                 :: ncat=0                    !< number of emission categories
    495        INTEGER(iwp)                                 :: nvoc=0                    !< number of VOCs components
    496        INTEGER(iwp)                                 :: npm=0                     !< number of PMs components
    497        INTEGER(iwp)                                 :: nnox=2                    !< number of NOx components: NO and NO2
    498        INTEGER(iwp)                                 :: nsox=2                    !< number of SOx components: SO and SO4
    499        INTEGER(iwp)                                 :: nhoursyear                !< number of hours of a specific year in the HOURLY mode
    500                                                                                  !  of the default mode
    501        INTEGER(iwp)                                 :: nmonthdayhour             !< number of month days and hours in the MDH mode
    502                                                                                  !  of the default mode
    503        INTEGER(iwp)                                 :: dt_emission               !< Number of emissions timesteps for one year
    504                                                                                  !  in the pre-processed emissions case
     513       
     514       INTEGER(iwp)                                 :: nspec=0            !< no of chem species provided in emission_values
     515       INTEGER(iwp)                                 :: n_emiss_species=0  !< no of chem species provided in emission_values
     516                                                                          !< same function as nspec, which will be depreciated (ecc)
     517                                                                                 
     518       INTEGER(iwp)                                 :: ncat=0             !< number of emission categories
     519       INTEGER(iwp)                                 :: nvoc=0             !< number of VOC components
     520       INTEGER(iwp)                                 :: npm=0              !< number of PM components
     521       INTEGER(iwp)                                 :: nnox=2             !< number of NOx components: NO and NO2
     522       INTEGER(iwp)                                 :: nsox=2             !< number of SOX components: SO and SO4
     523       INTEGER(iwp)                                 :: nhoursyear         !< number of hours of a specific year in the HOURLY mode
     524                                                                          !< of the default mode
     525       INTEGER(iwp)                                 :: nmonthdayhour      !< number of month days and hours in the MDH mode
     526                                                                          !< of the default mode
     527       INTEGER(iwp)                                 :: dt_emission        !< Number of emissions timesteps for one year
     528                                                                          !< in the pre-processed emissions case
    505529       !-- 1d emission input variables
    506        CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: pm_name                   !< Names of PMs components
    507        CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: cat_name                  !< Emission categories names
    508        CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: species_name              !< Names of emission chemical species
    509        CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: voc_name                  !< Names of VOCs components
    510        CHARACTER (LEN=25)                           :: units                     !< Units
    511 
    512        INTEGER(iwp)                                 :: i_hour                    !< indices for assigning the emission values at different timesteps
    513        INTEGER(iwp),ALLOCATABLE, DIMENSION(:)       :: cat_index                 !< Index of emission categories
    514        INTEGER(iwp),ALLOCATABLE, DIMENSION(:)       :: species_index             !< Index of emission chem species
    515 
    516        REAL(wp),ALLOCATABLE, DIMENSION(:)           :: xm                        !< Molecular masses of emission chem species
     530       CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: pm_name       !< Names of PM components
     531       CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: cat_name      !< Emission category names
     532       CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: species_name  !< Names of emission chemical species
     533       CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: voc_name      !< Names of VOCs components
     534       CHARACTER (LEN=25)                           :: units         !< Units
     535
     536       INTEGER(iwp)                                 :: i_hour         !< indices for assigning emission values at different timesteps
     537       INTEGER(iwp),ALLOCATABLE, DIMENSION(:)       :: cat_index      !< Indices for emission categories
     538       INTEGER(iwp),ALLOCATABLE, DIMENSION(:)       :: species_index  !< Indices for emission chem species
     539
     540       REAL(wp),ALLOCATABLE, DIMENSION(:)           :: xm             !< Molecular masses of emission chem species
    517541
    518542       !-- 2d emission input variables
    519        REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: hourly_emis_time_factor   !< Time factors for HOURLY emissions (DEFAULT mode)
    520        REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: mdh_emis_time_factor      !< Time factors for MDH emissions (DEFAULT mode)
    521        REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: nox_comp                  !< Composition of NO and NO2
    522        REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: sox_comp                  !< Composition of SO2 and SO4
    523        REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: voc_comp                  !< Composition of different VOC components (number not fixed)
     543       REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: hourly_emis_time_factor  !< Time factors for HOURLY emissions (DEFAULT mode)
     544       REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: mdh_emis_time_factor     !< Time factors for MDH emissions (DEFAULT mode)
     545       REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: nox_comp                 !< Composition of NO and NO2
     546       REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: sox_comp                 !< Composition of SO2 and SO4
     547       REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: voc_comp                 !< Composition of VOC components (not fixed)
    524548
    525549       !-- 3d emission input variables
    526        REAL(wp),ALLOCATABLE, DIMENSION(:,:,:)       :: pm_comp                   !< Composition of different PMs components (number not fixed)
     550       REAL(wp),ALLOCATABLE, DIMENSION(:,:,:)       :: pm_comp                  !< Composition of PM components (not fixed)
    527551 
    528552    END TYPE chem_emis_att_type
    529553
    530554
    531 !-- Data type for the values of chemistry emissions ERUSSO
     555!-- Data type for the values of chemistry emissions
    532556    TYPE chem_emis_val_type
    533557
    534        !REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: stack_height              !< stack height
    535 
    536        !-- 3d emission input variables
    537        REAL(wp),ALLOCATABLE, DIMENSION(:,:,:)     :: default_emission_data     !< Input Values emissions DEFAULT mode
    538 
    539        !-- 4d emission input variables
    540        REAL(wp),ALLOCATABLE, DIMENSION(:,:,:,:)   :: preproc_emission_data      !< Input Values emissions PRE-PROCESSED mode
     558       !REAL(wp),ALLOCATABLE, DIMENSION(:,:)     :: stack_height           !< stack height (ecc / to be implemented)
     559       REAL(wp),ALLOCATABLE, DIMENSION(:,:,:)    :: default_emission_data  !< Emission input values for LOD1 (DEFAULT mode)
     560       REAL(wp),ALLOCATABLE, DIMENSION(:,:,:,:)  :: preproc_emission_data  !< Emission input values for LOD2 (PRE-PROCESSED mode)
    541561
    542562    END TYPE chem_emis_val_type
     
    890910       MODULE PROCEDURE get_variable_4d_real
    891911       MODULE PROCEDURE get_variable_5d_to_4d_real
    892        MODULE PROCEDURE get_variable_string       
     912       MODULE PROCEDURE get_variable_5d_real           ! (ecc) temp subroutine 4 reading 5D NC arrays
     913       MODULE PROCEDURE get_variable_5d_real_dynamic   ! 2B removed as z is out of emission_values
     914       MODULE PROCEDURE get_variable_string
    893915    END INTERFACE get_variable
    894916
     
    13801402! Description:
    13811403! ------------
    1382 !> Reads Chemistry NETCDF Input data, such as emission values, emission species, etc. .
    1383 !------------------------------------------------------------------------------!
     1404!> Reads Chemistry NETCDF Input data, such as emission values, emission species, etc.
     1405!------------------------------------------------------------------------------!
     1406
    13841407    SUBROUTINE netcdf_data_input_chemistry_data(emt_att,emt)
    13851408
    13861409       USE chem_modules,                                       &
    1387            ONLY:  mode_emis, time_fac_type, surface_csflux_name
     1410           ONLY:  emiss_lod, time_fac_type, surface_csflux_name
    13881411
    13891412       USE control_parameters,                                 &
     
    13951418       IMPLICIT NONE
    13961419
    1397        TYPE(chem_emis_att_type), INTENT(INOUT)                                        :: emt_att
    1398        TYPE(chem_emis_val_type), ALLOCATABLE, DIMENSION(:), INTENT(INOUT)             :: emt
     1420       TYPE(chem_emis_att_type), INTENT(INOUT)                             :: emt_att
     1421       TYPE(chem_emis_val_type), ALLOCATABLE, DIMENSION(:), INTENT(INOUT)  :: emt
    13991422   
    1400        INTEGER(iwp)                                     :: ispec                 !< index for number of emission species in input
    1401 
    1402        INTEGER(iwp)                                     :: num_vars              !< number of variables in netcdf input file
    1403        INTEGER(iwp)                                     :: len_dims              !< Length of dimension
    1404 
    1405        REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)          :: dum_var_3d            !< variable for storing temporary data of 3-dimensional
    1406                                                                                  !  variables read from netcdf for chemistry emissions
    1407 
    1408        REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:)        :: dum_var_4d            !< variable for storing temporary data of 5-dimensional
    1409                                                                                  !< variables read from netcdf for chemistry emissions
    1410 !--
    1411        !> Start the processing of the data
    1412 
    1413        !> Parameterized mode of the emissions
    1414        IF (TRIM(mode_emis)=="PARAMETERIZED" .OR. TRIM(mode_emis)=="parameterized") THEN
     1423       INTEGER(iwp)  ::  i, j, k      !< generic counters
     1424       INTEGER(iwp)  ::  ispec        !< index for number of emission species in input
     1425       INTEGER(iwp)  ::  len_dims     !< Length of dimension
     1426       INTEGER(iwp)  ::  num_vars     !< number of variables in netcdf input file
     1427
     1428!
     1429!-- dum_var_4d are designed to read in emission_values from the chemistry netCDF file.
     1430!-- Currently the vestigial "z" dimension in emission_values makes it a 5D array,
     1431!-- hence the corresponding dum_var_5d array.  When the "z" dimension is removed
     1432!-- completely, dum_var_4d will be used instead
     1433!-- (ecc 20190425)
     1434
     1435!       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:)    ::  dum_var_4d  !< temp array 4 4D chem emission data
     1436       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:,:)  ::  dum_var_5d  !< temp array 4 5D chem emission data
     1437
     1438!
     1439!-- Start processing data
     1440
     1441       CALL location_message( 'starting allocation of chemistry emissions arrays', .FALSE. )
     1442
     1443!
     1444!-- Emission LOD 0 (Parameterized mode)
     1445
     1446        IF  ( emiss_lod == 0 )  THEN
     1447
     1448! for reference (ecc)
     1449!       IF (TRIM(mode_emis) == "PARAMETERIZED" .OR. TRIM(mode_emis) == "parameterized") THEN
    14151450
    14161451           ispec=1
    1417            emt_att%nspec=0
    1418 
    1419           !number of species
     1452           emt_att%n_emiss_species = 0
     1453
     1454!
     1455!-- number of species
     1456
    14201457           DO  WHILE (TRIM( surface_csflux_name( ispec ) ) /= 'novalue' )
    14211458
    1422              emt_att%nspec=emt_att%nspec+1
     1459             emt_att%n_emiss_species = emt_att%n_emiss_species + 1
    14231460             ispec=ispec+1
     1461!
     1462!-- followling line retained for compatibility with salsa_mod
     1463!-- which still uses emt_att%nspec heavily (ecc)
     1464
     1465             emt_att%nspec = emt_att%nspec + 1
    14241466
    14251467           ENDDO
    14261468
    1427           !-- allocate emission values data type arrays
    1428           ALLOCATE(emt(emt_att%nspec))
    1429 
    1430           !-- Read EMISSION SPECIES NAMES
    1431 
    1432           !Assign values
    1433           ALLOCATE(emt_att%species_name(emt_att%nspec))
     1469!
     1470!-- allocate emission values data type arrays
     1471
     1472          ALLOCATE ( emt(emt_att%n_emiss_species) )
     1473
     1474!
     1475!-- Read EMISSION SPECIES NAMES
     1476
     1477!
     1478!-- allocate space for strings
     1479
     1480          ALLOCATE (emt_att%species_name(emt_att%n_emiss_species) )
    14341481 
    1435          DO ispec=1,emt_att%nspec
     1482         DO ispec = 1, emt_att%n_emiss_species
    14361483            emt_att%species_name(ispec) = TRIM(surface_csflux_name(ispec))
    14371484         ENDDO
    14381485
    1439 
    1440        !> DEFAULT AND PRE-PROCESSED MODE
     1486!
     1487!-- LOD 1 (default mode) and LOD 2 (pre-processed mode)
     1488
    14411489       ELSE
    14421490
    1443 #if defined ( __netcdf )       
     1491#if defined ( __netcdf )
     1492
    14441493          IF ( .NOT. input_pids_chem )  RETURN
    14451494
    1446           !-- Open file in read-only mode
    1447           CALL open_read_file( TRIM( input_file_chem ) //                       &
    1448                                TRIM( coupling_char ), id_emis )
    1449           !-- inquire number of variables
    1450           CALL inquire_num_variables( id_emis, num_vars )
    1451 
    1452           !-- Get General Dimension Lengths: only number of species and number of categories.
    1453           !                                  the other dimensions depend on the mode of the emissions or on the presence of specific components
    1454           !nspecies
    1455           CALL netcdf_data_input_get_dimension_length( id_emis, emt_att%nspec, 'nspecies' )
    1456 
     1495!
     1496!-- first we allocate memory space for the emission species and then
     1497!-- we differentiate between LOD 1 (default mode) and LOD 2 (pre-processed mode)
     1498
     1499!
     1500!-- open emission data file ( {palmcase}_chemistry )
     1501
     1502          CALL open_read_file ( TRIM(input_file_chem) // TRIM(coupling_char), id_emis )
     1503
     1504!
     1505!-- inquire number of variables
     1506
     1507          CALL inquire_num_variables ( id_emis, num_vars )
     1508
     1509!
     1510!-- Get General Dimension Lengths: only # species and # categories.
     1511!-- Tther dimensions depend on the emission mode or specific components
     1512
     1513          CALL netcdf_data_input_get_dimension_length (    &
     1514                                 id_emis, emt_att%n_emiss_species, 'nspecies' )
     1515
     1516!
     1517!-- backward compatibility for salsa_mod (ecc)
     1518
     1519          emt_att%nspec = emt_att%n_emiss_species
     1520
     1521!
     1522!-- Allocate emission values data type arrays
     1523
     1524          ALLOCATE ( emt(emt_att%n_emiss_species) )
     1525
     1526!
     1527!-- READING IN SPECIES NAMES
     1528
     1529!
     1530!-- Allocate memory for species names
     1531
     1532          ALLOCATE ( emt_att%species_name(emt_att%n_emiss_species) )
     1533
     1534!
     1535!-- Retrieve variable name (again, should use n_emiss_strlen)
     1536
     1537          CALL get_variable( id_emis, 'emission_name',    &
     1538                             string_values, emt_att%n_emiss_species )
     1539          emt_att%species_name=string_values
     1540
     1541!
     1542!-- dealocate string_values previously allocated in get_variable call
     1543
     1544          IF  ( ALLOCATED(string_values) )  DEALLOCATE (string_values)
     1545
     1546!
     1547!-- READING IN SPECIES INDICES
     1548
     1549!
     1550!-- Allocate memory for species indices
     1551
     1552          ALLOCATE ( emt_att%species_index(emt_att%n_emiss_species) )
     1553
     1554!
     1555!-- Retrieve variable data
     1556
     1557          CALL get_variable( id_emis, 'emission_index', emt_att%species_index )
     1558!
     1559!-- Now the routine has to distinguish between chemistry emission
     1560!-- LOD 1 (DEFAULT mode) and LOD 2 (PRE-PROCESSED mode)
     1561
     1562!
     1563!-- START OF EMISSION LOD 1 (DEFAULT MODE)
     1564
     1565
     1566          IF  ( emiss_lod == 1 )  THEN
     1567
     1568! for reference (ecc)
     1569!          IF (TRIM(mode_emis) == "DEFAULT" .OR. TRIM(mode_emis) == "default") THEN
     1570
     1571!
     1572!-- get number of emission categories
     1573
     1574             CALL netcdf_data_input_get_dimension_length (           &
     1575                                    id_emis, emt_att%ncat, 'ncat' )
     1576
     1577!-- READING IN EMISSION CATEGORIES INDICES
     1578
     1579             ALLOCATE ( emt_att%cat_index(emt_att%ncat) )
     1580
     1581!
     1582!-- Retrieve variable data
     1583
     1584             CALL get_variable( id_emis, 'emission_cat_index', emt_att%cat_index )
     1585
     1586
     1587!
     1588!-- Loop through individual species to get basic information on
     1589!-- VOC/PM/NOX/SOX
     1590
     1591!------------------------------------------------------------------------------
     1592!-- NOTE - CHECK ARRAY INDICES FOR READING IN NAMES AND SPECIES
     1593!--        IN LOD1 (DEFAULT MODE) FOR THE VARIOUS MODE SPLITS
     1594!--        AS ALL ID_EMIS CONDITIONALS HAVE BEEN REMOVED FROM GET_VAR
     1595!--        FUNCTIONS.  IN THEORY THIS WOULD MEAN ALL ARRAYS SHOULD BE
     1596!--        READ FROM 0 to N-1 (C CONVENTION) AS OPPOSED TO 1 to N
     1597!--        (FORTRAN CONVENTION).  KEEP THIS IN MIND !!
     1598!--        (ecc 20190424)
     1599!------------------------------------------------------------------------------
    14571600 
    1458           !-- Allocate emission values data type arrays
    1459           ALLOCATE(emt(1:emt_att%nspec))
    1460 
    1461 
    1462           !-- Read EMISSION SPECIES NAMES
    1463           !Allocate Arrays
    1464           ALLOCATE(emt_att%species_name(emt_att%nspec))
    1465 
    1466           !Call get Variable
    1467           CALL get_variable( id_emis, 'emission_name', string_values, emt_att%nspec )
    1468           emt_att%species_name=string_values
    1469           ! If allocated, Deallocate var_string, an array only used for reading-in strings
    1470           IF (ALLOCATED(string_values)) DEALLOCATE(string_values)
    1471 
    1472           !-- Read EMISSION SPECIES INDEX
    1473           !Allocate Arrays
    1474           ALLOCATE(emt_att%species_index(emt_att%nspec))
    1475           !Call get Variable
    1476           CALL get_variable( id_emis, 'emission_index', emt_att%species_index )
    1477 
    1478 
    1479           !-- Now the routine has to distinguish between DEFAULT and PRE-PROCESSED chemistry emission modes
    1480 
    1481           IF (TRIM(mode_emis)=="DEFAULT" .OR. TRIM(mode_emis)=="default") THEN
     1601             DO  ispec = 1, emt_att%n_emiss_species
     1602
     1603!
     1604!-- VOC DATA (name and composition)
     1605
     1606                IF  ( TRIM(emt_att%species_name(ispec)) == "VOC" .OR.                  &
     1607                      TRIM(emt_att%species_name(ispec)) == "voc" )  THEN
     1608
     1609!
     1610!-- VOC name
     1611                   CALL netcdf_data_input_get_dimension_length (     &
     1612                                          id_emis, emt_att%nvoc, 'nvoc' )
     1613                   ALLOCATE ( emt_att%voc_name(emt_att%nvoc) )
     1614                   CALL get_variable ( id_emis,"emission_voc_name",  &
     1615                                       string_values, emt_att%nvoc )
     1616                   emt_att%voc_name = string_values
     1617                   IF  ( ALLOCATED(string_values) )  DEALLOCATE (string_values)
     1618
     1619!
     1620!-- VOC composition
     1621
     1622                   ALLOCATE ( emt_att%voc_comp(emt_att%ncat,emt_att%nvoc) )
     1623                   CALL get_variable ( id_emis, "composition_voc", emt_att%voc_comp,     &
     1624                                       1, emt_att%ncat, 1, emt_att%nvoc )
     1625
     1626                ENDIF  ! VOC
     1627
     1628!
     1629!-- PM DATA (name and composition)
     1630
     1631                IF  ( TRIM(emt_att%species_name(ispec)) == "PM" .OR.                   &
     1632                      TRIM(emt_att%species_name(ispec)) == "pm")  THEN
     1633
     1634!
     1635!-- PM name
     1636
     1637                   CALL netcdf_data_input_get_dimension_length (     &
     1638                                          id_emis, emt_att%npm, 'npm' )
     1639                   ALLOCATE ( emt_att%pm_name(emt_att%npm) )
     1640                   CALL get_variable ( id_emis, "pm_name", string_values, emt_att%npm )
     1641                   emt_att%pm_name = string_values
     1642                   IF  ( ALLOCATED(string_values) )  DEALLOCATE (string_values)     
     1643
     1644!
     1645!-- PM composition (PM1, PM2.5 and PM10)
     1646
     1647                   len_dims = 3  ! PM1, PM2.5, PM10
     1648                   ALLOCATE(emt_att%pm_comp(emt_att%ncat,emt_att%npm,len_dims))
     1649                   CALL get_variable ( id_emis, "composition_pm", emt_att%pm_comp,       &
     1650                                       1, emt_att%ncat, 1, emt_att%npm, 1, len_dims )
     1651
     1652                ENDIF  ! PM
     1653
     1654!
     1655!-- NOX (NO and NO2)
     1656
     1657                IF  ( TRIM(emt_att%species_name(ispec)) == "NOX" .OR.                  &
     1658                      TRIM(emt_att%species_name(ispec)) == "nox" )  THEN
     1659
     1660                   ALLOCATE ( emt_att%nox_comp(emt_att%ncat,emt_att%nnox) )
     1661                   CALL get_variable ( id_emis, "composition_nox", emt_att%nox_comp,     &
     1662                                       1, emt_att%ncat, 1, emt_att%nnox )
     1663
     1664                ENDIF  ! NOX
     1665
     1666!
     1667!-- SOX (SO2 and SO4)
     1668
     1669                IF  ( TRIM(emt_att%species_name(ispec)) == "SOX" .OR.                  &
     1670                      TRIM(emt_att%species_name(ispec)) == "sox" )  THEN
     1671
     1672                   ALLOCATE ( emt_att%sox_comp(emt_att%ncat,emt_att%nsox) )
     1673                   CALL get_variable ( id_emis, "composition_sox", emt_att%sox_comp,     &
     1674                                       1, emt_att%ncat, 1, emt_att%nsox )
     1675
     1676                ENDIF  ! SOX
     1677
     1678             ENDDO  ! do ispec
     1679
     1680!
     1681!-- EMISSION TIME SCALING FACTORS (hourly and MDH data)
    14821682 
    1483              !number of categories
    1484              CALL netcdf_data_input_get_dimension_length( id_emis, emt_att%ncat, 'ncat' )
    1485 
    1486              !-- Read EMISSION CATEGORIES INDEX
    1487              !Allocate Arrays
    1488              ALLOCATE(emt_att%cat_index(emt_att%ncat))
    1489              !Call get Variable
    1490              CALL get_variable( id_emis, 'emission_cat_index', emt_att%cat_index )
    1491 
     1683!     
     1684!-- HOUR   
     1685             IF  ( TRIM(time_fac_type) == "HOUR" .OR.                        &
     1686                   TRIM(time_fac_type) == "hour" )  THEN
     1687
     1688                CALL netcdf_data_input_get_dimension_length (                  &
     1689                                       id_emis, emt_att%nhoursyear, 'nhoursyear' )
     1690                ALLOCATE ( emt_att%hourly_emis_time_factor(emt_att%ncat,emt_att%nhoursyear) )
     1691                CALL get_variable ( id_emis, "emission_time_factors",          &
     1692                                    emt_att%hourly_emis_time_factor,           &
     1693                                    1, emt_att%ncat, 1, emt_att%nhoursyear )
     1694
     1695!
     1696!-- MDH
     1697
     1698             ELSE IF  ( TRIM(time_fac_type)  ==  "MDH" .OR.                  &
     1699                        TRIM(time_fac_type)  ==  "mdh" )  THEN
     1700
     1701                CALL netcdf_data_input_get_dimension_length (                  &
     1702                                       id_emis, emt_att%nmonthdayhour, 'nmonthdayhour' )
     1703                ALLOCATE ( emt_att%mdh_emis_time_factor(emt_att%ncat,emt_att%nmonthdayhour) )
     1704                CALL get_variable ( id_emis, "emission_time_factors",          &
     1705                                    emt_att%mdh_emis_time_factor,              &
     1706                                    1, emt_att%ncat, 1, emt_att%nmonthdayhour )
     1707
     1708!
     1709!-- ERROR (time factor undefined)
     1710
     1711             ELSE
     1712
     1713                message_string = 'We are in the DEFAULT chemistry emissions mode: '  //  &
     1714                                 '     !no time-factor type specified!'              //  &
     1715                                 'Please specify the value of time_fac_type:'        //  &
     1716                                 '         either "MDH" or "HOUR"'                 
     1717                CALL message( 'netcdf_data_input_chemistry_data', 'CM0200', 2, 2, 0, 6, 0 )
    14921718 
    1493              DO ispec=1,emt_att%nspec
    1494                 !-- EMISSION_VOC_NAME (1-DIMENSIONAL)
    1495                 IF (TRIM(emt_att%species_name(ispec))=="VOC" .OR. TRIM(emt_att%species_name(ispec))=="voc") THEN
    1496                    !Allocate Array
    1497                    CALL netcdf_data_input_get_dimension_length( id_emis, emt_att%nvoc, 'nvoc' )
    1498                    ALLOCATE(emt_att%voc_name(1:emt_att%nvoc))
    1499                    !Read-in Variable
    1500                    CALL get_variable( id_emis,"emission_voc_name",string_values, emt_att%nvoc)
    1501                    emt_att%voc_name=string_values
    1502                    IF (ALLOCATED(string_values)) DEALLOCATE(string_values)
     1719
     1720             ENDIF  ! time_fac_type
     1721
     1722!
     1723!-- read in default (LOD1) emissions from chemisty netCDF file per species
     1724
     1725!
     1726!-- NOTE - at the moment the data is read in per species, but in the future it would
     1727!--        be much more sensible to read in per species per time step to reduce
     1728!--        memory consumption and, to a lesser degree, dimensionality of data exchange
     1729!--        (I expect this will be necessary when the problem size is large)
     1730
     1731             DO ispec = 1, emt_att%n_emiss_species
     1732
     1733!
     1734!-- allocate space for species specific emission values
     1735!-- NOTE - this array is extended by 1 cell in each horizontal direction
     1736!--        to compensate for an apparent linear offset.  The reason of this
     1737!--        offset is not known but it has been determined to take place beyond the
     1738!--        scope of this module, and has little to do with index conventions.
     1739!--        That is, setting the array horizontal limit from nx0:nx1 to 1:(nx1-nx0+1)
     1740!--        or nx0+1:nx1+1 did not result in correct or definite behavior
     1741!--        This must be looked at at some point by the Hannover team but for now
     1742!--        this workaround is deemed reasonable (ecc 20190417)
     1743
     1744                IF ( .NOT. ALLOCATED ( emt(ispec)%default_emission_data ) )  THEN
     1745                    ALLOCATE ( emt(ispec)%default_emission_data(emt_att%ncat,nys:nyn+1,nxl:nxr+1) )
     1746                ENDIF
     1747!
     1748!-- allocate dummy variable w/ index order identical to that shown in the netCDF header
     1749
     1750                ALLOCATE ( dum_var_5d(1,nys:nyn,nxl:nxr,1,emt_att%ncat) )
     1751!
     1752!-- get variable.  be very careful
     1753!-- I am using get_variable_5d_real_dynamic (note logical argument at the end)
     1754!-- 1) use Fortran index convention (i.e., 1 to N)
     1755!-- 2) index order must be in reverse order from above allocation order
    15031756 
    1504                 !-- COMPOSITION VOC (2-DIMENSIONAL)
    1505                    !Allocate Array
    1506                    ALLOCATE(emt_att%voc_comp(1:emt_att%ncat,1:emt_att%nvoc))
    1507                    !Read-in Variable
    1508 !               CALL get_variable(id_emis,"composition_voc",emt%voc_comp,1,1,emt%ncat,emt%nvoc)
    1509                    CALL get_variable(id_emis,"composition_voc",emt_att%voc_comp,1,emt_att%ncat,1,emt_att%nvoc)
     1757                CALL get_variable ( id_emis, "emission_values", dum_var_5d, &
     1758                                    1,            ispec, nxl+1,     nys+1,     1,                    &
     1759                                    emt_att%ncat, 1,     nxr-nxl+1, nyn-nys+1, emt_att%dt_emission,  &
     1760                                    .FALSE. )
     1761!
     1762!-- assign temp array to data structure then deallocate temp array
     1763!-- NOTE - indices are shifted from nx0:nx1 to nx0+1:nx1+1 to offset
     1764!--        the emission data array to counter said domain offset
     1765!--        (ecc 20190417)
     1766
     1767                DO k = 1, emt_att%ncat
     1768                   DO j = nys+1, nyn+1
     1769                      DO i = nxl+1, nxr+1
     1770                         emt(ispec)%default_emission_data(k,j,i) = dum_var_5d(1,j-1,i-1,1,k)
     1771                      ENDDO
     1772                   ENDDO
     1773                ENDDO
     1774
     1775                DEALLOCATE ( dum_var_5d )
     1776
     1777             ENDDO  ! ispec
     1778!
     1779!-- UNITS
     1780
     1781             CALL get_attribute(id_emis,"units",emt_att%units,.FALSE.,"emission_values")
     1782
     1783!
     1784!-- END DEFAULT MODE
     1785
     1786
     1787!
     1788!-- START LOD 2 (PRE-PROCESSED MODE)
     1789
     1790          ELSE IF  ( emiss_lod == 2 )  THEN
     1791
     1792! for reference (ecc)
     1793!          ELSE IF (TRIM(mode_emis) == "PRE-PROCESSED" .OR. TRIM(mode_emis) == "pre-processed") THEN
     1794
     1795!
     1796!-- For LOD 2 only VOC and emission data need be read
     1797
     1798!------------------------------------------------------------------------------
     1799!-- NOTE - CHECK ARRAY INDICES FOR READING IN NAMES AND SPECIES
     1800!--        IN LOD2 (PRE-PROCESSED MODE) FOR THE VARIOUS MODE SPLITS
     1801!--        AS ALL ID_EMIS CONDITIONALS HAVE BEEN REMOVED FROM GET_VAR
     1802!--        FUNCTIONS.  IN THEORY THIS WOULD MEAN ALL ARRAYS SHOULD BE
     1803!--        READ FROM 0 to N-1 (C CONVENTION) AS OPPOSED TO 1 to N
     1804!--        (FORTRAN CONVENTION).  KEEP THIS IN MIND !!
     1805!--        (ecc 20190424)
     1806!------------------------------------------------------------------------------
     1807
     1808             DO ispec = 1, emt_att%n_emiss_species
     1809
     1810!
     1811!-- VOC DATA (name and composition)
     1812
     1813                IF  ( TRIM(emt_att%species_name(ispec)) == "VOC" .OR.                  &
     1814                      TRIM(emt_att%species_name(ispec)) == "voc" )  THEN
     1815
     1816!
     1817!-- VOC name
     1818                   CALL netcdf_data_input_get_dimension_length (                         &
     1819                                          id_emis, emt_att%nvoc, 'nvoc' )
     1820                   ALLOCATE ( emt_att%voc_name(emt_att%nvoc) )
     1821                   CALL get_variable ( id_emis, "emission_voc_name",                     &
     1822                                       string_values, emt_att%nvoc)
     1823                   emt_att%voc_name = string_values
     1824                   IF  ( ALLOCATED(string_values) )  DEALLOCATE (string_values)
     1825
     1826!
     1827!-- VOC composition
     1828 
     1829                   ALLOCATE ( emt_att%voc_comp(emt_att%ncat,emt_att%nvoc) )
     1830                   CALL get_variable ( id_emis, "composition_voc", emt_att%voc_comp,     &
     1831                                       1, emt_att%ncat, 1, emt_att%nvoc )
     1832                ENDIF  ! VOC
     1833 
     1834             ENDDO  ! ispec
     1835
     1836!
     1837!-- EMISSION DATA
     1838
     1839             CALL netcdf_data_input_get_dimension_length (                               &
     1840                                    id_emis, emt_att%dt_emission, 'time' )   
     1841 
     1842!
     1843!-- read in pre-processed (LOD2) emissions from chemisty netCDF file per species
     1844
     1845!
     1846!-- NOTE - at the moment the data is read in per species, but in the future it would
     1847!--        be much more sensible to read in per species per time step to reduce
     1848!--        memory consumption and, to a lesser degree, dimensionality of data exchange
     1849!--        (I expect this will be necessary when the problem size is large)
     1850
     1851             DO ispec = 1, emt_att%n_emiss_species
     1852
     1853!
     1854!-- allocate space for species specific emission values
     1855!-- NOTE - this array is extended by 1 cell in each horizontal direction
     1856!--        to compensate for an apparent linear offset.  The reason of this
     1857!--        offset is not known but it has been determined to take place beyond the
     1858!--        scope of this module, and has little to do with index conventions.
     1859!--        That is, setting the array horizontal limit from nx0:nx1 to 1:(nx1-nx0+1)
     1860!--        or nx0+1:nx1+1 did not result in correct or definite behavior
     1861!--        This must be looked at at some point by the Hannover team but for now
     1862!--        this workaround is deemed reasonable (ecc 20190417)
     1863
     1864                IF ( .NOT. ALLOCATED( emt(ispec)%preproc_emission_data ) )  THEN
     1865                   ALLOCATE( emt(ispec)%preproc_emission_data(                           &
     1866                             emt_att%dt_emission, 1, nys:nyn+1, nxl:nxr+1) )
    15101867                ENDIF
    1511 
    1512                 !-- EMISSION_PM_NAME (1-DIMENSIONAL)
    1513                 IF (TRIM(emt_att%species_name(ispec))=="PM" .OR. TRIM(emt_att%species_name(ispec))=="pm") THEN
    1514                    CALL netcdf_data_input_get_dimension_length( id_emis, emt_att%npm, 'npm' )
    1515                    ALLOCATE(emt_att%pm_name(1:emt_att%npm))
    1516                    !Read-in Variable
    1517                    CALL get_variable( id_emis,"pm_name",string_values, emt_att%npm)
    1518                    emt_att%pm_name=string_values
    1519                    IF (ALLOCATED(string_values)) DEALLOCATE(string_values)     
    1520 
    1521                 !-- COMPOSITION PM (3-DIMENSIONAL)
    1522                    !Allocate
    1523                    len_dims=3  !> number of PMs: PM1, PM2.5 and PM10
    1524                    ALLOCATE(emt_att%pm_comp(1:emt_att%ncat,1:emt_att%npm,1:len_dims))
    1525                    !Read-in Variable
    1526                    CALL get_variable(id_emis,"composition_pm",emt_att%pm_comp,1,emt_att%ncat,1,emt_att%npm,1,len_dims)                   
    1527                 ENDIF
    1528 
    1529                 !-- COMPOSITION_NOX (2-DIMENSIONAL)
    1530                 IF (TRIM(emt_att%species_name(ispec))=="NOx" .OR. TRIM(emt_att%species_name(ispec))=="nox") THEN
    1531                    !Allocate array
    1532                    ALLOCATE(emt_att%nox_comp(1:emt_att%ncat,1:emt_att%nnox))
    1533                    !Read-in Variable
    1534                    CALL get_variable(id_emis,"composition_nox",emt_att%nox_comp,1,emt_att%ncat,1,emt_att%nnox)
    1535                 ENDIF
    1536 
    1537                 !-- COMPOSITION-SOX (2-DIMENSIONAL)
    1538                 IF (TRIM(emt_att%species_name(ispec))=="SOx" .OR. TRIM(emt_att%species_name(ispec))=="sox") THEN
    1539                    ALLOCATE(emt_att%sox_comp(1:emt_att%ncat,1:emt_att%nsox))
    1540                    !Read-in Variable
    1541                    CALL get_variable(id_emis,"composition_sox",emt_att%sox_comp,1,emt_att%ncat,1,emt_att%nsox)
    1542                 ENDIF
    1543              ENDDO !>ispec
    1544 
    1545 !-- For reading the emission time factors, the distinction between HOUR and MDH data is necessary
    1546      
    1547              !-- EMISSION_TIME_SCALING_FACTORS
    1548                 !-- HOUR   
    1549              IF (TRIM(time_fac_type)=="HOUR" .OR. TRIM(time_fac_type)=="hour") THEN
    1550                 !-- Allocate Array
    1551                 CALL netcdf_data_input_get_dimension_length( id_emis, emt_att%nhoursyear, 'nhoursyear' )
    1552                 ALLOCATE(emt_att%hourly_emis_time_factor(1:emt_att%ncat,1:emt_att%nhoursyear))
    1553                 !Read-in Variable
    1554                 CALL get_variable(id_emis,"emission_time_factors",emt_att%hourly_emis_time_factor,1,   &
    1555                                   emt_att%ncat,1,emt_att%nhoursyear)
    1556 
    1557                 !-- MDH
    1558              ELSE IF (TRIM(time_fac_type) == "MDH" .OR. TRIM(time_fac_type) == "mdh") THEN
    1559                 !-- Allocate Array
    1560                 CALL netcdf_data_input_get_dimension_length( id_emis, emt_att%nmonthdayhour, 'nmonthdayhour' )
    1561                 ALLOCATE(emt_att%mdh_emis_time_factor(1:emt_att%ncat,1:emt_att%nmonthdayhour))
    1562                 !-- Read-in Variable
    1563                 CALL get_variable(id_emis,"emission_time_factors",emt_att%mdh_emis_time_factor,1,       &
    1564                                   emt_att%ncat,1,emt_att%nmonthdayhour)
    1565 
    1566              ELSE
    1567 
    1568              message_string = 'We are in the DEFAULT chemistry emissions mode: '            //          &
    1569                               '     !no time-factor type specified!'                        //          &
    1570                               'Please, specify the value of time_fac_type:'                 //          &
    1571                               '         either "MDH" or "HOUR"'                 
    1572              CALL message( 'netcdf_data_input_chemistry_data', 'CM0200', 2, 2, 0, 6, 0 )
    1573  
    1574 
    1575              ENDIF
    1576 
    1577              !-- Finally read-in the emission values and their units (DEFAULT mode)
    1578 
    1579              DO ispec=1,emt_att%nspec
    1580 
    1581                 IF ( .NOT. ALLOCATED( emt(ispec)%default_emission_data ) )                              &
    1582                     ALLOCATE(emt(ispec)%default_emission_data(1:emt_att%ncat,1:ny+1,1:nx+1))
    1583 
    1584                 ALLOCATE(dum_var_3d(1:emt_att%ncat,nys+1:nyn+1,nxl+1:nxr+1))
    1585 
    1586                 CALL get_variable(id_emis,"emission_values",dum_var_3d,ispec,1,emt_att%ncat,nys,nyn,nxl,nxr)         
    1587 
    1588                 emt(ispec)%default_emission_data(:,nys+1:nyn+1,nxl+1:nxr+1) =                           &
    1589                     dum_var_3d(1:emt_att%ncat,nys+1:nyn+1,nxl+1:nxr+1)
    1590 
    1591                 DEALLOCATE (dum_var_3d)
    1592 
    1593              ENDDO
    1594 
    1595              !-- UNITS
    1596              CALL get_attribute(id_emis,"units",emt_att%units,.FALSE.,"emission_values")
    1597 
    1598 
    1599           !-- PRE-PROCESSED MODE --
    1600 
    1601           ELSE IF (TRIM(mode_emis)=="PRE-PROCESSED" .OR. TRIM(mode_emis)=="pre-processed") THEN
    1602           !-- In the PRE-PROCESSED mode, only the VOC names, the VOC_composition, the emission values and their units remain to be read at this point
    1603 
    1604              DO ispec=1,emt_att%nspec
    1605 
    1606              !-- EMISSION_VOC_NAME (1-DIMENSIONAL)
    1607                 IF (TRIM(emt_att%species_name(ispec))=="VOC" .OR. TRIM(emt_att%species_name(ispec))=="voc") THEN
    1608                    !Allocate Array
    1609                    CALL netcdf_data_input_get_dimension_length( id_emis, emt_att%nvoc, 'nvoc' )
    1610                    ALLOCATE(emt_att%voc_name(1:emt_att%nvoc))
    1611                    !Read-in Variable
    1612                    CALL get_variable( id_emis,"emission_voc_name",string_values, emt_att%nvoc)
    1613                    emt_att%voc_name=string_values
    1614                    IF (ALLOCATED(string_values)) DEALLOCATE(string_values)
    1615  
    1616              !-- COMPOSITION VOC (2-DIMENSIONAL)
    1617                    !Allocate Array
    1618                    ALLOCATE(emt_att%voc_comp(1:emt_att%ncat,1:emt_att%nvoc))
    1619                    !Read-in Variable
    1620                    CALL get_variable(id_emis,"composition_voc",emt_att%voc_comp,1,emt_att%ncat,1,emt_att%nvoc)
    1621                 ENDIF
    1622  
    1623              ENDDO !> ispec
    1624 
    1625              !-- EMISSION_VALUES (4-DIMENSIONAL)
    1626              !Calculate temporal dimension length
    1627              CALL netcdf_data_input_get_dimension_length( id_emis, emt_att%dt_emission, 'time' )   
    1628          
    1629 
    1630              DO ispec=1,emt_att%nspec
    1631 
    1632                 !Allocation for the entire domain has to be done only for the first processor between all the subdomains     
    1633                 IF ( .NOT. ALLOCATED( emt(ispec)%preproc_emission_data ) )                              &
    1634                     ALLOCATE(emt(ispec)%preproc_emission_data(emt_att%dt_emission,1,1:ny+1,1:nx+1))
    1635 
    1636                 !> allocate variable where to pass emission values read from netcdf
    1637                 ALLOCATE(dum_var_4d(1:emt_att%dt_emission,1,nys+1:nyn+1,nxl+1:nxr+1))
    1638 
    1639                 !Read-in Variable
    1640                 CALL get_variable(id_emis,"emission_values",dum_var_4d,ispec,1,emt_att%dt_emission,1,1,nys,nyn,nxl,nxr)         
    1641 
    1642      
    1643                 emt(ispec)%preproc_emission_data(:,1,nys+1:nyn+1,nxl+1:nxr+1) =                         &
    1644                       dum_var_4d(1:emt_att%dt_emission,1,nys+1:nyn+1,nxl+1:nxr+1)
    1645 
    1646                 DEALLOCATE ( dum_var_4d )
    1647 
    1648              ENDDO
    1649 
    1650              !-- UNITS
    1651              CALL get_attribute(id_emis,"units",emt_att%units,.FALSE.,"emission_values")
     1868!
     1869!-- allocate dummy variable w/ index order identical to that shown in the netCDF header
     1870
     1871                ALLOCATE ( dum_var_5d(emt_att%dt_emission,1,nys:nyn,nxl:nxr,1) )
     1872!
     1873!-- get variable.  be very careful
     1874!-- I am using get_variable_5d_real_dynamic (note logical argument at the end)
     1875!-- 1) use Fortran index convention (i.e., 1 to N)
     1876!-- 2) index order must be in reverse order from above allocation order
     1877
     1878                CALL get_variable ( id_emis, "emission_values", dum_var_5d, &
     1879                                    ispec, nxl+1,     nys+1,     1, 1,                   &
     1880                                    1,     nxr-nxl+1, nyn-nys+1, 1, emt_att%dt_emission, &
     1881                                    .FALSE. )
     1882!
     1883!-- assign temp array to data structure then deallocate temp array
     1884!-- NOTE - indices are shifted from nx0:nx1 to nx0+1:nx1+1 to offset
     1885!--        the emission data array to counter said unkonwn offset
     1886!--        (ecc 20190417)
     1887
     1888                DO k = 1, emt_att%dt_emission
     1889                   DO j = nys+1, nyn+1
     1890                      DO i = nxl+1, nxr+1
     1891                         emt(ispec)%preproc_emission_data(k,1,j,i) = dum_var_5d(k,1,j-1,i-1,1)
     1892                      ENDDO
     1893                   ENDDO
     1894                ENDDO
     1895
     1896                DEALLOCATE ( dum_var_5d )
     1897
     1898             ENDDO  ! ispec
     1899!
     1900!-- UNITS
     1901
     1902             CALL get_attribute ( id_emis, "units", emt_att%units, .FALSE. , "emission_values" )
    16521903       
    1653           ENDIF
    1654 
    1655        CALL close_input_file( id_emis )
     1904          ENDIF  ! LOD1 & LOD2 (default and pre-processed mode)
     1905
     1906          CALL close_input_file (id_emis)
    16561907
    16571908#endif
    1658        ENDIF
     1909
     1910       ENDIF ! LOD0 (parameterized mode)
    16591911
    16601912    END SUBROUTINE netcdf_data_input_chemistry_data
     1913
    16611914
    16621915!------------------------------------------------------------------------------!
     
    53585611       ENDIF
    53595612
    5360 
    5361        !Temporary solution for reading emission chemistry files: TBD: we should discuss whether remove it or not
    5362        IF ( id==id_emis ) THEN
    5363 
    5364           !--    Allocate temporary variable according to memory access on file.
    5365           ALLOCATE( tmp(is:ie,js:je) )
    5366 
    5367           !--    Get variable
    5368           nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
    5369                                   start = (/ is,      js /),                  &
    5370                                   count = (/ ie-is+1 , je-js+1 /) )
    5371 
    5372           var=tmp
    5373 
    5374           CALL handle_error( 'get_variable_2d_real', 530, variable_name ) !TBD: the error number shuld be changed, but since the solution is
    5375                                                                           ! provisory, we give the same as below
    5376  
    5377           DEALLOCATE( tmp )
    5378        
    5379        !>  Original Subroutine part
    5380        ELSE
    5381 !
    5382 !--       Allocate temporary variable according to memory access on file.
    5383           ALLOCATE( tmp(is:ie,js:je) )
    5384 !
    5385 !--       Get variable
    5386           nc_stat = NF90_GET_VAR( id, id_var, tmp,                             &
    5387                                   start = (/ is+1,      js+1 /),               &
    5388                                   count = (/ ie-is + 1, je-js+1 /) )   
     5613!
     5614!-- Allocate temporary variable according to memory access on file.
     5615       ALLOCATE( tmp(is:ie,js:je) )
     5616!
     5617!-- Get variable
     5618       nc_stat = NF90_GET_VAR( id, id_var, tmp,            &
     5619                      start = (/ is+1,      js+1 /),       &
     5620                      count = (/ ie-is + 1, je-js+1 /) )   
    53895621          CALL handle_error( 'get_variable_2d_real', 530, variable_name )
    53905622!
    5391 !--       Resort data. Please note, dimension subscripts of var all start at 1.
     5623!-- Resort data. Please note, dimension subscripts of var all start at 1.
    53925624          DO  i = is, ie
    53935625             DO  j = js, je
     
    53985630          DEALLOCATE( tmp )
    53995631
    5400        ENDIF
    54015632#endif
    54025633    END SUBROUTINE get_variable_2d_real
     
    57135944       ENDIF
    57145945
    5715       !Temporary solution for reading emission chemistry files:
    5716        IF ( id==id_emis ) THEN
    5717 
    5718           !--    Allocate temporary variable according to memory access on file.
    5719           ALLOCATE( tmp(is:ie,js:je,k1s:k1e,k2s:k2e) )
    5720 
    5721           !--    Get variable
    5722           nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
    5723                                   start = (/ is,   js,   k1s+1,   k2s+1 /),                  &
    5724                                   count = (/ ie-is+1 , je-js+1, k1e-k1s+1, k2e-k2s+1 /) )
    5725 
    5726           var=tmp
     5946!
     5947!-- Allocate temporary variable according to memory access on file.
     5948       ALLOCATE( tmp(is:ie,js:je,k1s:k1e,k2s:k2e) )
     5949!
     5950!-- Get variable
     5951       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
     5952                      start = (/ is+1,    js+1,    k1s+1,     k2s+1 /),        &
     5953                      count = (/ ie-is+1, je-js+1, k1e-k1s+1, k2e-k2s+1 /) )
    57275954
    57285955          CALL handle_error( 'get_variable_4d_real', 535, variable_name )
    5729  
    5730           DEALLOCATE( tmp )
    5731 
    5732        !> Original subroutine part
    5733        ELSE
    5734 !
    5735 !--       Allocate temporary variable according to memory access on file.
    5736           ALLOCATE( tmp(is:ie,js:je,k1s:k1e,k2s:k2e) )
    5737 !
    5738 !--       Get variable
    5739           nc_stat = NF90_GET_VAR( id, id_var, tmp,                             &
    5740                                start = (/ is+1,    js+1,   k1s+1, k2s+1 /),    &
    5741                                count = (/ ie-is+1, je-js+1,                    &
    5742                                           k1e-k1s+1, k2e-k2s+1 /) )
    5743 
    5744           CALL handle_error( 'get_variable_4d_real', 535, variable_name )
    5745 !
    5746 !--       Resort data. Please note, dimension subscripts of var all start at 1.
    5747           DO  i = is, ie
    5748              DO  j = js, je
    5749                 DO  k1 = k1s, k1e
    5750                    DO  k2 = k2s, k2e
    5751                       var(k2-k2s+1,k1-k1s+1,j-js+1,i-is+1) = tmp(i,j,k1,k2)
    5752                    ENDDO
     5956!
     5957!-- Resort data. Please note, dimension subscripts of var all start at 1.
     5958       DO  i = is, ie
     5959          DO  j = js, je
     5960             DO  k1 = k1s, k1e
     5961                DO  k2 = k2s, k2e
     5962                   var(k2-k2s+1,k1-k1s+1,j-js+1,i-is+1) = tmp(i,j,k1,k2)
    57535963                ENDDO
    57545964             ENDDO
    57555965          ENDDO
    5756 
    5757           DEALLOCATE( tmp )
    5758        ENDIF
     5966       ENDDO
     5967
     5968       DEALLOCATE( tmp )
     5969
    57595970#endif
     5971
    57605972    END SUBROUTINE get_variable_4d_real
    57615973
     
    58066018
    58076019      !Temporary solution for reading emission chemistry files:
    5808        IF ( id==id_emis ) THEN
     6020       IF ( id == id_emis ) THEN
    58096021
    58106022          !--    Allocate temporary variable according to memory access on file.
     
    59936205
    59946206      !Temporary solution for reading emission chemistry files:
    5995        IF ( id==id_emis ) THEN
     6207       IF ( id == id_emis ) THEN
    59966208
    59976209          !--    Allocate temporary variable according to memory access on file.
     
    60406252    END SUBROUTINE get_variable_5d_to_4d_real
    60416253
     6254   
     6255!------------------------------------------------------------------------------!
     6256! Description:
     6257! ------------
     6258!> Reads a 5D float variable from file.
     6259!> NOTE - This subroutine is used specific for reading NC variable
     6260!>        emission_values having a "z" dimension.  Said dimension
     6261!>        is to be removed in the future and this subroutine shall
     6262!>        be depreciated accordingly (ecc 20190418)
     6263!------------------------------------------------------------------------------!
     6264    SUBROUTINE get_variable_5d_real( id, variable_name, var, is, ie, js, je,   &
     6265                                     k1s, k1e, k2s, k2e, k3s, k3e )
     6266
     6267       USE indices
     6268       USE pegrid
     6269
     6270       IMPLICIT NONE
     6271
     6272       CHARACTER(LEN=*)          ::  variable_name  !< variable name
     6273
     6274       INTEGER(iwp)              :: i       !< i index
     6275       INTEGER(iwp)              :: ie      !< i index start
     6276       INTEGER(iwp)              :: is      !< i index end
     6277       INTEGER(iwp)              :: id_var  !< netCDF variable ID (varid)
     6278       INTEGER(iwp)              :: j       !< j index
     6279       INTEGER(iwp)              :: je      !< j index start
     6280       INTEGER(iwp)              :: js      !< j index end
     6281       INTEGER(iwp)              :: k1      !< k1 index
     6282       INTEGER(iwp)              :: k1e     !< k1 index start
     6283       INTEGER(iwp)              :: k1s     !< k1 index end
     6284       INTEGER(iwp)              :: k2      !< k2 index
     6285       INTEGER(iwp)              :: k2e     !< k2 index start
     6286       INTEGER(iwp)              :: k2s     !< k2 index end
     6287       INTEGER(iwp)              :: k3      !< k3 index
     6288       INTEGER(iwp)              :: k3e     !< k3 index start
     6289       INTEGER(iwp)              :: k3s     !< k3 index end
     6290       INTEGER(iwp), INTENT(IN)  :: id      !< netCDF file ID (ncid)
     6291
     6292       REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE    :: tmp  !< temp array to read data from file
     6293       REAL(wp), DIMENSION(:,:,:,:,:), INTENT(INOUT)  :: var  !< variable to be read
     6294
     6295#if defined( __netcdf )
     6296
     6297!
     6298!-- Inquire variable id
     6299
     6300       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
     6301
     6302!
     6303!-- Check for collective read-operation and set respective NetCDF flags if required.
     6304 
     6305       IF ( collective_read )  THEN
     6306
     6307#if defined( __netcdf4_parallel )       
     6308          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
     6309#endif
     6310
     6311       ENDIF
     6312
     6313!
     6314!-- Allocate temporary variable according to memory access on file.
     6315
     6316       ALLOCATE( tmp(is:ie,js:je,k1s:k1e,k2s:k2e,k3s:k3e) )
     6317
     6318!
     6319!-- Get variable from file
     6320
     6321       nc_stat = NF90_GET_VAR ( id, id_var, tmp,                                         &
     6322                      start = (/ is+1,    js+1,    k1s+1,     k2s+1,     k3s+1 /),       &
     6323                      count = (/ ie-is+1, je-js+1, k1e-k1s+1, k2e-k2s+1, k3e-k3s+1 /) )
     6324
     6325       CALL handle_error( 'get_variable_5d_real', 535, variable_name )
     6326
     6327!
     6328!-- Resort (reverse index order) and standardize (from 1 to N) output array
     6329
     6330       DO  i = is, ie
     6331          DO  j = js, je
     6332             DO  k1 = k1s, k1e
     6333                DO  k2 = k2s, k2e
     6334                   DO k3 = k3s, k3e
     6335                      var(k3-k3s+1,k2-k2s+1,k1-k1s+1,j-js+1,i-is+1) = tmp(i,j,k1,k2,k3)
     6336                   ENDDO
     6337                ENDDO
     6338             ENDDO
     6339          ENDDO
     6340       ENDDO
     6341
     6342       DEALLOCATE( tmp )
     6343
     6344#endif
     6345
     6346    END SUBROUTINE get_variable_5d_real
     6347
     6348
     6349!------------------------------------------------------------------------------!
     6350! Description:
     6351! ------------
     6352!> Reads a 5D float variables from dynamic driver, such as time-dependent xy-,
     6353!> xz- or yz-boundary data as well as 5D initialization data. Please note,
     6354!> the passed arguments are start indices and number of elements in each
     6355!> dimension, which is in contrast to the other 3d versions where start- and
     6356!> end indices are passed. The different handling of 5D dynamic variables is
     6357!> due to its asymmetry for the u- and v component.
     6358!> NOTE(1) - This subroutine is more flexible than get_variable_xd_real as it
     6359!>           provides much better control over starting and count indices
     6360!>           (ecc 20190418)
     6361!> NOTE(2) - This subroutine is used specific for reading NC variable
     6362!>           emission_values having a "z" dimension.  Said dimension
     6363!>           is to be removed in the future and this subroutine shall
     6364!>           be depreciated accordingly (ecc 20190418)
     6365!------------------------------------------------------------------------------!
     6366
     6367    SUBROUTINE get_variable_5d_real_dynamic( id, variable_name, var,                       &
     6368                                             i1s, i2s, i3s, i4s, i5s,                      &
     6369                                             count_1, count_2, count_3, count_4, count_5,  &
     6370                                             par_access )
     6371
     6372       USE indices
     6373       USE pegrid
     6374
     6375       IMPLICIT NONE
     6376
     6377       CHARACTER(LEN=*)          ::  variable_name  !< variable name
     6378
     6379       LOGICAL                   ::  par_access     !< additional flag indicating parallel read
     6380
     6381       INTEGER(iwp)              ::  count_1  !< # elements read in dimension 1 wrt file
     6382       INTEGER(iwp)              ::  count_2  !< # elements read in dimension 2 wrt file
     6383       INTEGER(iwp)              ::  count_3  !< # elements read in dimension 3 wrt file
     6384       INTEGER(iwp)              ::  count_4  !< # elements read in dimension 4 wrt file
     6385       INTEGER(iwp)              ::  count_5  !< # elements read in dimension 5 wrt file
     6386       INTEGER(iwp)              ::  i1       !< index for dimension 1 on file
     6387       INTEGER(iwp)              ::  i1s      !< starting index for dimension 1 hyperslab
     6388       INTEGER(iwp)              ::  i2       !< index for dimension 2 on file
     6389       INTEGER(iwp)              ::  i2s      !< starting index for dimension 2 hyperslab
     6390       INTEGER(iwp)              ::  i3       !< index for dimension 3 on file
     6391       INTEGER(iwp)              ::  i3s      !< starting index for dimension 3 hyperslab
     6392       INTEGER(iwp)              ::  i4       !< index for dimension 4 on file
     6393       INTEGER(iwp)              ::  i4s      !< starting index for dimension 4 hyperslab
     6394       INTEGER(iwp)              ::  i5       !< index for dimension 5 on file
     6395       INTEGER(iwp)              ::  i5s      !< starting index for dimension 5 hyperslab
     6396       INTEGER(iwp)              ::  id_var   !< netCDF variable id (varid)
     6397       INTEGER(iwp)              ::  lb1      !< lower bound of dimension 1 wrt file
     6398       INTEGER(iwp)              ::  lb2      !< lower bound of dimension 2 wrt file
     6399       INTEGER(iwp)              ::  lb3      !< lower bound of dimension 3 wrt file
     6400       INTEGER(iwp)              ::  lb4      !< lower bound of dimension 4 wrt file
     6401       INTEGER(iwp)              ::  lb5      !< lower bound of dimension 5 wrt file
     6402       INTEGER(iwp)              ::  ub1      !< upper bound of dimension 1 wrt file
     6403       INTEGER(iwp)              ::  ub2      !< upper bound of dimension 2 wrt file
     6404       INTEGER(iwp)              ::  ub3      !< upper bound of dimension 3 wrt file
     6405       INTEGER(iwp)              ::  ub4      !< upper bound of dimension 4 wrt file
     6406       INTEGER(iwp)              ::  ub5      !< upper bound of dimension 5 wrt file
     6407       INTEGER(iwp), INTENT(IN)  ::  id       !< netCDF file id (ncid)
     6408
     6409       REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE    ::  tmp  !< temporary variable to read data
     6410                                                               !< from file according is reverse
     6411                                                               !< array index order
     6412       REAL(wp), DIMENSION(:,:,:,:,:), INTENT(INOUT)  ::  var  !< input variable
     6413       
     6414#if defined( __netcdf )
     6415
     6416!
     6417!-- Inquire variable id.
     6418
     6419       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
     6420
     6421!
     6422!-- Check for collective read-operation and set respective NetCDF flags if required.
     6423!-- Please note, in contrast to the other input routines where each PEs
     6424!-- reads its subdomain data, dynamic input data not by all PEs, only
     6425!-- by those which encompass lateral model boundaries. Hence, collective
     6426!-- read operations are only enabled for top-boundary data.
     6427
     6428       IF ( collective_read  .AND.  par_access )  THEN
     6429
     6430#if defined( __netcdf4_parallel )       
     6431          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
     6432#endif
     6433
     6434       ENDIF
     6435
     6436!
     6437!-- Allocate temporary variable according to memory access on file.
     6438!-- Therefore, determine dimension bounds of input array.
     6439
     6440       lb1 = LBOUND(var,5)
     6441       ub1 = UBOUND(var,5)
     6442       lb2 = LBOUND(var,4)
     6443       ub2 = UBOUND(var,4)
     6444       lb3 = LBOUND(var,3)
     6445       ub3 = UBOUND(var,3)
     6446       lb4 = LBOUND(var,2)
     6447       ub4 = UBOUND(var,2)
     6448       lb5 = LBOUND(var,1)
     6449       ub5 = UBOUND(var,1)
     6450       ALLOCATE ( tmp(lb1:ub1,lb2:ub2,lb3:ub3,lb4:ub4,lb5:ub5) )
     6451
     6452!
     6453!-- Get variable
     6454
     6455       nc_stat = NF90_GET_VAR(  id, id_var, tmp,                                         &
     6456                      start = (/ i1s,     i2s,     i3s,     i4s,     i5s     /),         &
     6457                      count = (/ count_1, count_2, count_3, count_4, count_5 /) )
     6458
     6459       CALL handle_error( 'get_variable_3d_real_dynamic', 537, variable_name )
     6460
     6461!
     6462!-- Assign temp array to output.  Note reverse index order
     6463
     6464       DO  i5 = lb5, ub5
     6465          DO  i4 = lb4, ub4
     6466             DO  i3 = lb3, ub3
     6467                DO i2 = lb2, ub2
     6468                   DO  i1 = lb1, ub1
     6469                      var(i5,i4,i3,i2,i1) = tmp(i1,i2,i3,i4,i5)
     6470                   ENDDO
     6471                ENDDO
     6472             ENDDO
     6473          ENDDO
     6474       ENDDO
     6475
     6476       DEALLOCATE( tmp )
     6477
     6478#endif
     6479
     6480    END SUBROUTINE get_variable_5d_real_dynamic
     6481
    60426482
    60436483!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.