Ignore:
Timestamp:
Sep 10, 2019 5:03:24 PM (5 years ago)
Author:
suehring
Message:

Offline nesting: data input modularized; time variable is defined relative to time_utc_init, so that input data is correctly mapped to actual model time; checks rephrased and new checks for the time dimension added; Netcdf input: routine to retrieve dimension length renamed

File:
1 edited

Legend:

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

    r4182 r4226  
    2626! -----------------
    2727! $Id$
     28! Netcdf input routine for dimension length renamed
     29!
     30! 4182 2019-08-22 15:20:23Z scharf
    2831! Corrected "Former revisions" section
    2932!
     
    17571760
    17581761    USE netcdf_data_input_mod,                                                                     &
    1759         ONLY:  check_existence, close_input_file, get_attribute, get_variable,                     &
     1762        ONLY:  check_existence, close_input_file, get_dimension_length,                            &
     1763               get_attribute, get_variable,                                                        &
    17601764               inquire_num_variables, inquire_variable_names,                                      &
    1761                netcdf_data_input_get_dimension_length, open_read_file
     1765               open_read_file
    17621766
    17631767    IMPLICIT NONE
     
    18361840!
    18371841!--       Inquire vertical dimension and number of aerosol chemical components
    1838           CALL netcdf_data_input_get_dimension_length( id_dyn, pr_nz, 'z' )
     1842          CALL get_dimension_length( id_dyn, pr_nz, 'z' )
    18391843          IF ( pr_nz /= nz )  THEN
    18401844             WRITE( message_string, * ) 'Number of inifor horizontal grid points does not match '//&
     
    18421846             CALL message( 'aerosol_init', 'PA0601', 1, 2, 0, 6, 0 )
    18431847          ENDIF
    1844           CALL netcdf_data_input_get_dimension_length( id_dyn, pr_ncc, 'composition_index' )
     1848          CALL get_dimension_length( id_dyn, pr_ncc, 'composition_index' )
    18451849!
    18461850!--       Allocate memory
     
    19151919!
    19161920!--          Bin mean diameters in the input file
    1917              CALL netcdf_data_input_get_dimension_length( id_dyn, pr_nbins, 'Dmid')
     1921             CALL get_dimension_length( id_dyn, pr_nbins, 'Dmid')
    19181922             IF ( pr_nbins /= nbins_aerosol )  THEN
    19191923                message_string = 'Number of size bins in init_atmosphere_aerosol does not match '  &
     
    20672071!
    20682072!--       Inquire dimensions:
    2069           CALL netcdf_data_input_get_dimension_length( id_dyn, pr_nz, 'z' )
     2073          CALL get_dimension_length( id_dyn, pr_nz, 'z' )
    20702074          IF ( pr_nz /= nz )  THEN
    20712075             WRITE( message_string, * ) 'Number of inifor horizontal grid points does not match '//&
     
    83888392        ONLY:  check_existence, close_input_file, get_attribute, get_variable,                     &
    83898393               inquire_num_variables, inquire_variable_names,                                      &
    8390                netcdf_data_input_get_dimension_length, open_read_file, street_type_f
     8394               get_dimension_length, open_read_file, street_type_f
    83918395
    83928396    USE surface_mod,                                                                               &
     
    85258529!
    85268530!--          Read the index and name of chemical components
    8527              CALL netcdf_data_input_get_dimension_length( id_salsa, aero_emission_att%ncc,         &
     8531             CALL get_dimension_length( id_salsa, aero_emission_att%ncc,         &
    85288532                                                          'composition_index' )
    85298533             ALLOCATE( aero_emission_att%cc_index(1:aero_emission_att%ncc) )
     
    85988602!
    85998603!--             Get number of emission categories and allocate emission arrays
    8600                 CALL netcdf_data_input_get_dimension_length( id_salsa, aero_emission_att%ncat,     &
    8601                                                              'ncat' )
     8604                CALL get_dimension_length( id_salsa, aero_emission_att%ncat, 'ncat' )
    86028605                ALLOCATE( aero_emission_att%cat_index(1:aero_emission_att%ncat),                   &
    86038606                          aero_emission_att%rho(1:aero_emission_att%ncat),                         &
     
    86368639!--             For each hour of year:
    86378640                IF ( check_existence( aero_emission_att%var_names, 'nhoursyear' ) )  THEN
    8638                    CALL netcdf_data_input_get_dimension_length( id_salsa,                          &
    8639                                                         aero_emission_att%nhoursyear, 'nhoursyear' )
     8641                   CALL get_dimension_length( id_salsa,                                            &
     8642                                              aero_emission_att%nhoursyear, 'nhoursyear' )
    86408643                   ALLOCATE( aero_emission_att%etf(1:aero_emission_att%ncat,                       &
    86418644                                                   1:aero_emission_att%nhoursyear) )
     
    86458648!--             Based on the month, day and hour:
    86468649                ELSEIF ( check_existence( aero_emission_att%var_names, 'nmonthdayhour' ) )  THEN
    8647                    CALL netcdf_data_input_get_dimension_length( id_salsa,                          &
    8648                                                                 aero_emission_att%nmonthdayhour,   &
    8649                                                                 'nmonthdayhour' )
     8650                   CALL get_dimension_length( id_salsa,                                            &
     8651                                              aero_emission_att%nmonthdayhour,                     &
     8652                                              'nmonthdayhour' )
    86508653                   ALLOCATE( aero_emission_att%etf(1:aero_emission_att%ncat,                       &
    86518654                                                   1:aero_emission_att%nmonthdayhour) )
     
    87348737!
    87358738!--             Number of aerosol size bins in the emission data
    8736                 CALL netcdf_data_input_get_dimension_length( id_salsa, aero_emission_att%nbins,    &
    8737                                                              'Dmid' )
     8739                CALL get_dimension_length( id_salsa, aero_emission_att%nbins, 'Dmid' )
    87388740                IF ( aero_emission_att%nbins /= nbins_aerosol )  THEN
    87398741                   message_string = 'The number of size bins in aerosol input data does not ' //   &
     
    87438745!
    87448746!--             Number of time steps in the emission data
    8745                 CALL netcdf_data_input_get_dimension_length( id_salsa, aero_emission_att%nt, 'time')
     8747                CALL get_dimension_length( id_salsa, aero_emission_att%nt, 'time')
    87468748!
    87478749!--             Allocate bin diameters, time and mass fraction array
     
    91249126        ONLY:  check_existence, close_input_file, get_attribute, get_variable,                     &
    91259127               inquire_num_variables, inquire_variable_names,                                      &
    9126                netcdf_data_input_get_dimension_length, open_read_file
     9128               get_dimension_length, open_read_file
    91279129
    91289130    USE surface_mod,                                                                               &
     
    91749176!
    91759177!--    Read the index and name of chemical components
    9176        CALL netcdf_data_input_get_dimension_length( id_chem, chem_emission_att%n_emiss_species,    &
    9177                                                     'nspecies' )
     9178       CALL get_dimension_length( id_chem, chem_emission_att%n_emiss_species, 'nspecies' )
    91789179       ALLOCATE( chem_emission_att%species_index(1:chem_emission_att%n_emiss_species) )
    91799180       CALL get_variable( id_chem, 'emission_index', chem_emission_att%species_index )
     
    92219222!
    92229223!--       Get number of emission categories and allocate emission arrays
    9223           CALL netcdf_data_input_get_dimension_length( id_chem, chem_emission_att%ncat, 'ncat' )
     9224          CALL get_dimension_length( id_chem, chem_emission_att%ncat, 'ncat' )
    92249225          ALLOCATE( chem_emission_att%cat_index(1:chem_emission_att%ncat),                         &
    92259226                    time_factor(1:chem_emission_att%ncat) )
     
    92359236!--       For each hour of year:
    92369237          IF ( check_existence( var_names, 'nhoursyear' ) )  THEN
    9237              CALL netcdf_data_input_get_dimension_length( id_chem, chem_emission_att%nhoursyear,   &
    9238                                                           'nhoursyear' )
     9238             CALL get_dimension_length( id_chem, chem_emission_att%nhoursyear, 'nhoursyear' )
    92399239             ALLOCATE( chem_emission_att%hourly_emis_time_factor(1:chem_emission_att%ncat,         &
    92409240                                                                 1:chem_emission_att%nhoursyear) )
     
    92459245!--       Based on the month, day and hour:
    92469246          ELSEIF ( check_existence( var_names, 'nmonthdayhour' ) )  THEN
    9247              CALL netcdf_data_input_get_dimension_length( id_chem, chem_emission_att%nmonthdayhour,&
    9248                                                           'nmonthdayhour' )
     9247             CALL get_dimension_length( id_chem, chem_emission_att%nmonthdayhour, 'nmonthdayhour' )
    92499248             ALLOCATE( chem_emission_att%mdh_emis_time_factor(1:chem_emission_att%ncat,            &
    92509249                                                              1:chem_emission_att%nmonthdayhour) )
     
    92849283!
    92859284!--       Number of time steps in the emission data
    9286           CALL netcdf_data_input_get_dimension_length( id_chem, chem_emission_att%dt_emission,     &
    9287                                                        'time' )
     9285          CALL get_dimension_length( id_chem, chem_emission_att%dt_emission, 'time' )
    92889286!
    92899287!--       Allocate and read time
Note: See TracChangeset for help on using the changeset viewer.