Ignore:
Timestamp:
Feb 14, 2020 10:04:39 AM (4 years ago)
Author:
gronemeier
Message:

write fill_value attribute in virtual-measurements module; enable character-array output in data-output module

File:
1 edited

Legend:

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

    r4406 r4408  
    2525! -----------------
    2626! $Id$
     27! write fill_value attribute
     28!
     29! 4406 2020-02-13 20:06:29Z knoop
    2730! Bugix: removed oro_rel wrong loop bounds and removed unnecessary restart method
    28 ! 
     31!
    2932! 4400 2020-02-10 20:32:41Z suehring
    3033! Revision of the module:
     
    268271       INTEGER(iwp) ::  start_coord_s = 0   !< start coordinate in NetCDF file for local soil observations
    269272
    270        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  dim_t !< number observations individual for each trajectory 
     273       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  dim_t !< number observations individual for each trajectory
    271274                                                         !< or station that are no _FillValues
    272275
     
    287290       REAL(wp) ::  fill_nutm                            !< fill value for UTM coordinates in case of missing values
    288291       REAL(wp) ::  fill_zar                             !< fill value for heigth coordinates in case of missing values
    289        REAL(wp) ::  fillout = -9999.0                    !< fill value for output in case a observation is taken 
     292       REAL(wp) ::  fillout = -9999.0                    !< fill value for output in case a observation is taken
    290293                                                         !< e.g. from inside a building
    291294       REAL(wp) ::  origin_x_obs                         !< origin of the observation in UTM coordiates in x-direction
     
    306309
    307310    ! This need to be generalized
    308 !     CHARACTER(LEN=10) ::  char_fill = '_FillValue'
     311    CHARACTER(LEN=10) ::  char_fill = '_FillValue'                 !< attribute name for fill value
    309312    CHARACTER(LEN=9)  ::  char_long = 'long_name'                  !< attribute name for long_name
    310313    CHARACTER(LEN=13) ::  char_standard = 'standard_name'          !< attribute name for standard_name
     
    462465
    463466 END SUBROUTINE vm_check_parameters
    464  
     467
    465468!------------------------------------------------------------------------------!
    466469! Description:
     
    893896!
    894897!-- Allocate flag array. This dummy array is used to identify grid points
    895 !-- where virtual measurements should be taken. Please note, in order to 
     898!-- where virtual measurements should be taken. Please note, in order to
    896899!-- include also the surrounding grid points of the original coordinate
    897900!-- ghost points are required.
     
    10001003       ALLOCATE( vmea(l)%var_atts(1:vmea(l)%nmeas) )
    10011004!
    1002 !--    Store the variable names in a data structures, which assigns further 
    1003 !--    attributes to this name. Further, for data output reasons, create a 
     1005!--    Store the variable names in a data structures, which assigns further
     1006!--    attributes to this name. Further, for data output reasons, create a
    10041007!--    string of output variables, which will be written into the attribute
    10051008!--    data_content.
     
    10141017!--    define the grid-index space on each subdomain where virtual measurements
    10151018!--    should be taken. Note, the entire coordinate array (on the entire model
    1016 !--    domain) won't be stored as this would exceed memory requirements, 
     1019!--    domain) won't be stored as this would exceed memory requirements,
    10171020!--    particularly for trajectories.
    10181021       IF ( vmea(l)%nmeas > 0 )  THEN
     
    13441347    DEALLOCATE( meas_flag )
    13451348!
    1346 !-- Close input file for virtual measurements. 
     1349!-- Close input file for virtual measurements.
    13471350    CALL close_input_file( pids_id )
    13481351!
     
    13981401!-- Note, start coordinates are initialized with zero for sake of simplicity
    13991402!-- in summation. However, in NetCDF the start coordinates must be >= 1,
    1400 !-- so that a one needs to be added at the end. 
     1403!-- so that a one needs to be added at the end.
    14011404    DO  l = 1, vmea_general%nvm
    14021405       DO  n  = 0, myid - 1
     
    22372240                                      value = TRIM( vmea(l)%var_atts(n)%coordinates ) )
    22382241
    2239 !           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2240 !                                       variable_name = variable_name,           &
    2241 !                                       attribute_name = char_fill,              &
    2242 !                                       value = vmea(l)%var_atts(n)%fill_value )
     2242          return_value = dom_def_att( vmea(l)%nc_filename,                     &
     2243                                      variable_name = variable_name,           &
     2244                                      attribute_name = char_fill,              &
     2245                                      value = REAL( vmea(l)%var_atts(n)%fill_value, KIND=4 ) )
    22432246
    22442247       ENDDO  ! loop over variables per site
     
    23452348          DEALLOCATE( output_values_1d_target )
    23462349!
    2347 !--       In case of sampled soil quantities, output also the respective 
     2350!--       In case of sampled soil quantities, output also the respective
    23482351!--       coordinate arrays.
    23492352          IF ( vmea(l)%soil_sampling )  THEN
     
    24122415!
    24132416!--          Write the stations name
    2414              
     2417
    24152418          ENDIF
    24162419
     
    29102913!                     i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
    29112914!                     i = MERGE( i           , nxr, i            < nxr )
    2912 ! 
     2915!
    29132916!                     DO  mm = surf_lsm_h%start_index(j,i),                      &
    29142917!                              surf_lsm_h%end_index(j,i)
Note: See TracChangeset for help on using the changeset viewer.