Ignore:
Timestamp:
Nov 15, 2018 9:03:15 PM (6 years ago)
Author:
gronemeier
Message:

change date format in output files; add global attributes; change fill_value; move definition of UTM and lon/lat into subroutine; change attributes of time variable; read optional attributes from input netcdf file; update test cases

File:
1 edited

Legend:

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

    r3518 r3529  
    2525! -----------------
    2626! $Id$
     27! - read optional attributes from file
     28! - set default origin_time
     29!
     30! 3518 2018-11-12 18:10:23Z suehring
    2731! Additional checks
    2832!
     
    341345    TYPE init_type
    342346
    343        CHARACTER(LEN=23) ::  origin_time !< reference time of input data
     347       CHARACTER(LEN=23) ::  origin_time = '2000-01-01 00:00:00 +00' !< reference time of input data
    344348
    345349       INTEGER(iwp) ::  lod_msoil !< level of detail - soil moisture
     
    566570       CHARACTER(LEN=200) ::  author                             !< first name, last name, email adress
    567571       CHARACTER(LEN=6)   ::  author_char = 'author'             !< name of attribute
    568        CHARACTER(LEN=12 ) ::  campaign                           !< name of campaign
     572       CHARACTER(LEN=12 ) ::  campaign = 'PALM-4U'               !< name of campaign
    569573       CHARACTER(LEN=8)   ::  campaign_char = 'campaign'         !< name of attribute
    570574       CHARACTER(LEN=200) ::  comment                            !< comment to data
     
    586590       CHARACTER(LEN=200) ::  keywords                           !< keywords of data set
    587591       CHARACTER(LEN=8)   ::  keywords_char = 'keywords'         !< name of attribute
    588        CHARACTER(LEN=200) ::  license                            !< license of data set
    589        CHARACTER(LEN=7)   ::  license_char = 'license'           !< name of attribute
     592       CHARACTER(LEN=200) ::  licence                            !< licence of data set
     593       CHARACTER(LEN=7)   ::  licence_char = 'licence'           !< name of attribute
    590594       CHARACTER(LEN=200) ::  location                           !< place which refers to data set
    591595       CHARACTER(LEN=8)   ::  location_char = 'location'         !< name of attribute
    592596       CHARACTER(LEN=10)  ::  origin_lat_char = 'origin_lat'     !< name of attribute
    593597       CHARACTER(LEN=10)  ::  origin_lon_char = 'origin_lon'     !< name of attribute
    594        CHARACTER(LEN=23 ) ::  origin_time                        !< reference time
     598       CHARACTER(LEN=23 ) ::  origin_time = '2000-01-01 00:00:00 +00'  !< reference time
    595599       CHARACTER(LEN=11)  ::  origin_time_char = 'origin_time'   !< name of attribute
    596600       CHARACTER(LEN=8)   ::  origin_x_char = 'origin_x'         !< name of attribute
     
    823827           chem_emis, chem_emis_att, chem_emis_att_type, chem_emis_val_type,   &
    824828           coord_ref_sys,                                                      &
    825            init_3d, init_model, input_file_static, input_pids_static,          &
     829           init_3d, init_model, input_file_atts, input_file_static,            &
     830           input_pids_static,                                                  &
    826831           input_pids_dynamic, input_pids_vm, input_file_vm,                   &
    827832           leaf_area_density_f, nest_offl,                                     &
     
    932937       CALL get_attribute( id_mod, input_file_atts%rotation_angle_char,        &
    933938                           input_file_atts%rotation_angle, .TRUE. )
     939
     940       CALL get_attribute( id_mod, input_file_atts%author_char,         input_file_atts%author,         .TRUE., no_abort=.FALSE. )
     941       CALL get_attribute( id_mod, input_file_atts%contact_person_char, input_file_atts%contact_person, .TRUE., no_abort=.FALSE. )
     942       CALL get_attribute( id_mod, input_file_atts%institution_char,    input_file_atts%institution,    .TRUE., no_abort=.FALSE. )
     943       CALL get_attribute( id_mod, input_file_atts%acronym_char,        input_file_atts%acronym,        .TRUE., no_abort=.FALSE. )
     944
     945       CALL get_attribute( id_mod, input_file_atts%campaign_char, input_file_atts%campaign, .TRUE., no_abort=.FALSE. )
     946       CALL get_attribute( id_mod, input_file_atts%location_char, input_file_atts%location, .TRUE., no_abort=.FALSE. )
     947       CALL get_attribute( id_mod, input_file_atts%site_char,     input_file_atts%site,     .TRUE., no_abort=.FALSE. )
     948
     949       CALL get_attribute( id_mod, input_file_atts%source_char,     input_file_atts%source,     .TRUE., no_abort=.FALSE. )
     950       CALL get_attribute( id_mod, input_file_atts%references_char, input_file_atts%references, .TRUE., no_abort=.FALSE. )
     951       CALL get_attribute( id_mod, input_file_atts%keywords_char,   input_file_atts%keywords,   .TRUE., no_abort=.FALSE. )
     952       CALL get_attribute( id_mod, input_file_atts%licence_char,    input_file_atts%licence,    .TRUE., no_abort=.FALSE. )
     953       CALL get_attribute( id_mod, input_file_atts%comment_char,    input_file_atts%comment,    .TRUE., no_abort=.FALSE. )
    934954!
    935955!--    Read coordinate reference system if available
     
    49254945!------------------------------------------------------------------------------!
    49264946     SUBROUTINE get_attribute_string( id, attribute_name, value, global,       &
    4927                                       variable_name )
     4947                                      variable_name, no_abort )
    49284948
    49294949       USE pegrid
     
    49384958       INTEGER(iwp)                ::  id_var           !< variable id
    49394959
     4960       LOGICAL ::  check_error                          !< flag indicating if handle_error shall be checked
    49404961       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
     4962       LOGICAL, INTENT(IN), OPTIONAL ::  no_abort       !< flag indicating if errors should be checked
    49414963#if defined( __netcdf )
    49424964
     4965       IF ( PRESENT( no_abort ) )  THEN
     4966          check_error = no_abort
     4967       ELSE
     4968          check_error = .TRUE.
     4969       ENDIF
    49434970!
    49444971!--    Read global attribute
    49454972       IF ( global )  THEN
    49464973          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
    4947           CALL handle_error( 'get_attribute_string global', 525, attribute_name )
     4974          IF ( check_error)  CALL handle_error( 'get_attribute_string global', 525, attribute_name )
    49484975!
    49494976!--    Read attributes referring to a single variable. Therefore, first inquire
     
    49514978       ELSE
    49524979          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
    4953           CALL handle_error( 'get_attribute_string', 525, attribute_name )
     4980          IF ( check_error)  CALL handle_error( 'get_attribute_string', 525, attribute_name )
    49544981
    49554982          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
    4956           CALL handle_error( 'get_attribute_string',525, attribute_name )
     4983          IF ( check_error)  CALL handle_error( 'get_attribute_string',525, attribute_name )
    49574984
    49584985       ENDIF
Note: See TracChangeset for help on using the changeset viewer.