Ignore:
Timestamp:
Oct 30, 2020 12:06:47 PM (4 years ago)
Author:
suehring
Message:

Revision of setting-up virtual measurements. virtual_measurement_mod: Simplified input of coordinates. All coordinate and height arrays are now 1D, independent on featuretype. This allows easier usage also for other campaign data sets independent of UC2; Avoid type conversion from 64 to 32 bit when output the data; Increase dimension size of sample-variable string (sometimes more than 100 variables are listed for heavy measured locations); Remove quantities that cannot be sampled; | Further, revision of the script palm_cvd to convert measurement coordinates from UC2 data standard towards a PALM readable format: Convert trajectory and timeseriesProfile coordinates into 1-D coordinates equivalent to timeseries coordiates. This simplifies processing in PALM and makes the virtual-measurement module also applicable to other campaigns; Check automatically for data organization (stored in subdirectories or not).

File:
1 edited

Legend:

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

    r4752 r4763  
    2525! -----------------
    2626! $Id$
     27! - Simplified input of coordinates. All coordinate and height arrays are now 1D, independent on
     28!   featuretype. This allows easier usage also for other campaign data sets independent of UC2.
     29! - Avoid type conversion from 64 to 32 bit when output the data
     30! - Increase dimension size of sample-variable string (sometimes more than 100 variables are listed
     31!   for heavy measured locations)
     32! - Remove quantities that cannot be sampled
     33!
     34! 4752 2020-10-21 13:54:51Z suehring
    2735! Remove unnecessary output and merge output for quantities that are represented by the same
    2836! variable in PALM, e.g. surface temperature and brightness temperature
     
    191199        ONLY:  air_chemistry,                                                                      &
    192200               coupling_char,                                                                      &
     201               debug_output,                                                                       &
    193202               dz,                                                                                 &
    194203               end_time,                                                                           &
     
    305314       INTEGER(iwp) ::  ns              = 0  !< number of observation coordinates on subdomain, for atmospheric measurements
    306315       INTEGER(iwp) ::  ns_tot          = 0  !< total number of observation coordinates, for atmospheric measurements
    307        INTEGER(iwp) ::  n_tr_st              !< number of trajectories / station of a measurement
     316       INTEGER(iwp) ::  nst                  !< number of coordinate points given for a measurement
    308317       INTEGER(iwp) ::  nmeas                !< number of measured variables (atmosphere + soil)
    309318       INTEGER(iwp) ::  ns_soil         = 0  !< number of observation coordinates on subdomain, for soil measurements
     
    677686          output_variable%units         = 'm2 s-2'
    678687
    679        CASE ( 'plev' )
    680           output_variable%long_name     = 'air pressure'
    681           output_variable%standard_name = 'air_pressure'
    682           output_variable%units         = 'Pa'
    683 
    684688       CASE ( 'm_soil' )
    685689          output_variable%long_name     = 'soil moisture volumetric'
     
    731735          output_variable%units         = 'hPa'
    732736
    733        CASE ( 'pswrtg' )
    734           output_variable%long_name     = 'platform speed wrt ground'
    735           output_variable%standard_name = 'platform_speed_wrt_ground'
    736           output_variable%units         = 'm s-1'
    737 
    738        CASE ( 'pswrta' )
    739           output_variable%long_name     = 'platform speed wrt air'
    740           output_variable%standard_name = 'platform_speed_wrt_air'
    741           output_variable%units         = 'm s-1'
    742 
    743737       CASE ( 'pwv' )
    744738          output_variable%long_name     = 'water vapor partial pressure in air'
     
    746740          output_variable%units         = 'hPa'
    747741
    748        CASE ( 'ssdu' )
    749           output_variable%long_name     = 'duration of sunshine'
    750           output_variable%standard_name = 'duration_of_sunshine'
    751           output_variable%units         = 's'
    752 
    753742       CASE ( 't_lw' )
    754743          output_variable%long_name     = 'land water temperature'
     
    771760          output_variable%long_name     = 'upward kinematic latent heat flux in air'
    772761          output_variable%units         = 'g kg-1 m s-1'
    773 
    774        CASE ( 'zcb' )
    775           output_variable%long_name     = 'cloud base altitude'
    776           output_variable%standard_name = 'cloud_base_altitude'
    777           output_variable%units         = 'm'
    778 
    779        CASE ( 'zmla' )
    780           output_variable%long_name     = 'atmosphere boundary layer thickness'
    781           output_variable%standard_name = 'atmosphere_boundary_layer_thickness'
    782           output_variable%units         = 'm'
    783762
    784763       CASE ( 'mcpm1' )
     
    880859
    881860    CHARACTER(LEN=5)                  ::  dum                           !< dummy string indicating station id
    882     CHARACTER(LEN=100), DIMENSION(50) ::  measured_variables_file = ''  !< array with all measured variables read from NetCDF
    883     CHARACTER(LEN=100), DIMENSION(50) ::  measured_variables      = ''  !< dummy array with all measured variables that are allowed
    884 
    885     INTEGER(iwp) ::  dim_ntime  !< dimension size of time coordinate
     861    CHARACTER(LEN=100), DIMENSION(200) ::  measured_variables_file = ''  !< array with all measured variables read from NetCDF
     862    CHARACTER(LEN=100), DIMENSION(200) ::  measured_variables      = ''  !< dummy array with all measured variables that are allowed
     863
    886864    INTEGER(iwp) ::  i          !< grid index of virtual observation point in x-direction
    887865    INTEGER(iwp) ::  is         !< grid index of real observation point of the respective station in x-direction
     
    897875    INTEGER(iwp) ::  ll         !< running index over all measured variables in file
    898876    INTEGER(iwp) ::  m          !< running index for surface elements
    899     INTEGER(iwp) ::  n          !< running index over trajectory coordinates
    900877    INTEGER(iwp) ::  nofill     !< dummy for nofill return value (not used)
    901878    INTEGER(iwp) ::  ns         !< counter variable for number of observation points on subdomain
     
    922899    REAL(wp) ::  fill_zar    !< _FillValue for zar coordinate
    923900
    924     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  e_utm      !< easting UTM coordinate, temporary variable
    925     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  e_utm_tmp  !< EUTM coordinate before rotation
    926     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  height     !< observation height above ground (for trajectories)
    927     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  n_utm      !< northing UTM coordinate, temporary variable
    928     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  n_utm_tmp  !< NUTM coordinate before rotation
    929     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  station_h  !< station height above reference
    930     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zar        !< observation height above reference
     901    REAL(wp), DIMENSION(:), ALLOCATABLE ::  e_utm      !< easting UTM coordinate, temporary variable
     902    REAL(wp), DIMENSION(:), ALLOCATABLE ::  e_utm_tmp  !< EUTM coordinate before rotation
     903    REAL(wp), DIMENSION(:), ALLOCATABLE ::  height     !< observation height above ground (for trajectories)
     904    REAL(wp), DIMENSION(:), ALLOCATABLE ::  n_utm      !< northing UTM coordinate, temporary variable
     905    REAL(wp), DIMENSION(:), ALLOCATABLE ::  n_utm_tmp  !< NUTM coordinate before rotation
     906    REAL(wp), DIMENSION(:), ALLOCATABLE ::  station_h  !< station height above reference
     907    REAL(wp), DIMENSION(:), ALLOCATABLE ::  zar        !< observation height above reference
     908
     909    IF ( debug_output )  CALL debug_message( 'vm_init', 'start' )
    931910#if defined( __netcdf )
    932911!
     
    10421021       IF ( vmea(l)%nmeas > 0 )  THEN
    10431022!
    1044 !--       For stationary measurements UTM coordinates are just one value and its dimension is
    1045 !--       "station", while for mobile measurements UTM coordinates are arrays depending on the
    1046 !--       number of trajectories and time, according to (UC)2 standard. First, inquire dimension
    1047 !--       length of the UTM coordinates.
    1048           IF ( vmea(l)%trajectory )  THEN
    1049 !
    1050 !--          For non-stationary measurements read the number of trajectories and the number of time
    1051 !--          coordinates.
    1052              CALL get_dimension_length( pids_id, vmea(l)%n_tr_st, "traj" // TRIM( dum ) )
    1053              CALL get_dimension_length( pids_id, dim_ntime, "ntime" // TRIM( dum ) )
    1054 !
    1055 !--       For stationary measurements the dimension for UTM is station and for the time-coordinate
    1056 !--       it is one.
    1057           ELSE
    1058              CALL get_dimension_length( pids_id, vmea(l)%n_tr_st, "station" // TRIM( dum ) )
    1059              dim_ntime = 1
    1060           ENDIF
    1061 !
    1062 !-        Allocate array which defines individual time/space frame for each trajectory or station.
    1063           ALLOCATE( vmea(l)%dim_t(1:vmea(l)%n_tr_st) )
     1023!--       For stationary and mobile measurements UTM coordinates are just one value and its dimension
     1024!--       is "station".
     1025          CALL get_dimension_length( pids_id, vmea(l)%nst, "station" // TRIM( dum ) )
    10641026!
    10651027!--       Allocate temporary arrays for UTM and height coordinates. Note, on file UTM coordinates
    10661028!--       might be 1D or 2D variables
    1067           ALLOCATE( e_utm(1:vmea(l)%n_tr_st,1:dim_ntime)       )
    1068           ALLOCATE( n_utm(1:vmea(l)%n_tr_st,1:dim_ntime)       )
    1069           ALLOCATE( station_h(1:vmea(l)%n_tr_st,1:dim_ntime)   )
    1070           ALLOCATE( zar(1:vmea(l)%n_tr_st,1:dim_ntime)         )
    1071           IF ( vmea(l)%trajectory )  ALLOCATE( height(1:vmea(l)%n_tr_st,1:dim_ntime) )
     1029          ALLOCATE( e_utm(1:vmea(l)%nst)       )
     1030          ALLOCATE( n_utm(1:vmea(l)%nst)       )
     1031          ALLOCATE( station_h(1:vmea(l)%nst)   )
     1032          ALLOCATE( zar(1:vmea(l)%nst)         )
     1033          IF ( vmea(l)%trajectory )  ALLOCATE( height(1:vmea(l)%nst) )
    10721034          e_utm     = 0.0_wp
    10731035          n_utm     = 0.0_wp
     
    10761038          IF ( vmea(l)%trajectory )  height = 0.0_wp
    10771039
    1078           ALLOCATE( e_utm_tmp(1:vmea(l)%n_tr_st,1:dim_ntime) )
    1079           ALLOCATE( n_utm_tmp(1:vmea(l)%n_tr_st,1:dim_ntime) )
     1040          ALLOCATE( e_utm_tmp(1:vmea(l)%nst) )
     1041          ALLOCATE( n_utm_tmp(1:vmea(l)%nst) )
    10801042!
    10811043!--       Read UTM and height coordinates for all trajectories and times. Note, in case
     
    10941056!--       UC2-standard.
    10951057          IF ( vmea(l)%trajectory )  THEN
    1096              CALL get_variable( pids_id, char_eutm   // TRIM( dum ), e_utm,  0, dim_ntime-1, 0,    &
    1097                                 vmea(l)%n_tr_st-1 )
    1098              CALL get_variable( pids_id, char_nutm   // TRIM( dum ), n_utm,  0, dim_ntime-1, 0,    &
    1099                                 vmea(l)%n_tr_st-1 )
    1100              CALL get_variable( pids_id, char_zar    // TRIM( dum ), zar,    0, dim_ntime-1, 0,    &
    1101                                 vmea(l)%n_tr_st-1 )
    1102              CALL get_variable( pids_id, char_height // TRIM( dum ), height, 0, dim_ntime-1, 0,    &
    1103                                 vmea(l)%n_tr_st-1 )
     1058             CALL get_variable( pids_id, char_eutm      // TRIM( dum ), e_utm(:)     )
     1059             CALL get_variable( pids_id, char_nutm      // TRIM( dum ), n_utm(:)     )
     1060             CALL get_variable( pids_id, char_height    // TRIM( dum ), height(:)    )
    11041061          ELSE
    1105              CALL get_variable( pids_id, char_eutm      // TRIM( dum ), e_utm(:,1)     )
    1106              CALL get_variable( pids_id, char_nutm      // TRIM( dum ), n_utm(:,1)     )
    1107              CALL get_variable( pids_id, char_station_h // TRIM( dum ), station_h(:,1) )
    1108              CALL get_variable( pids_id, char_zar       // TRIM( dum ), zar(:,1)       )
     1062             CALL get_variable( pids_id, char_eutm      // TRIM( dum ), e_utm(:)     )
     1063             CALL get_variable( pids_id, char_nutm      // TRIM( dum ), n_utm(:)     )
     1064             CALL get_variable( pids_id, char_station_h // TRIM( dum ), station_h(:) )
     1065             CALL get_variable( pids_id, char_zar       // TRIM( dum ), zar(:)       )
    11091066          ENDIF
    11101067
     
    11161073!
    11171074!--       Compute observation height above ground. Note, for trajectory measurements the height
    1118 !--       above the surface is actually stored in 'height'
     1075!--       above the surface is actually stored in 'height'.
    11191076          IF ( vmea(l)%trajectory )  THEN
    11201077             zar      = height
     
    11271084!--       on subdomain. This case, setup grid index space sample these quantities.
    11281085          meas_flag = 0
    1129           DO  t = 1, vmea(l)%n_tr_st
     1086          DO  t = 1, vmea(l)%nst
    11301087!
    11311088!--          First, compute relative x- and y-coordinates with respect to the lower-left origin of
     
    11331090!--          is not correct, the virtual sites will be misplaced. Further, in case of an rotated
    11341091!--          model domain, the UTM coordinates must also be rotated.
    1135              e_utm_tmp(t,1:dim_ntime) = e_utm(t,1:dim_ntime) - init_model%origin_x
    1136              n_utm_tmp(t,1:dim_ntime) = n_utm(t,1:dim_ntime) - init_model%origin_y
    1137              e_utm(t,1:dim_ntime) = COS( init_model%rotation_angle * pi / 180.0_wp )               &
    1138                                     * e_utm_tmp(t,1:dim_ntime)                                     &
     1092             e_utm_tmp(t) = e_utm(t) - init_model%origin_x
     1093             n_utm_tmp(t) = n_utm(t) - init_model%origin_y
     1094             e_utm(t) = COS( init_model%rotation_angle * pi / 180.0_wp )                           &
     1095                                    * e_utm_tmp(t)                                                 &
    11391096                                  - SIN( init_model%rotation_angle * pi / 180.0_wp )               &
    1140                                     * n_utm_tmp(t,1:dim_ntime)
    1141              n_utm(t,1:dim_ntime) = SIN( init_model%rotation_angle * pi / 180.0_wp )               &
    1142                                     * e_utm_tmp(t,1:dim_ntime)                                     &
     1097                                    * n_utm_tmp(t)
     1098             n_utm(t) = SIN( init_model%rotation_angle * pi / 180.0_wp )                           &
     1099                                    * e_utm_tmp(t)                                                 &
    11431100                                  + COS( init_model%rotation_angle * pi / 180.0_wp )               &
    1144                                     * n_utm_tmp(t,1:dim_ntime)
    1145 !
    1146 !--          Determine the individual time coordinate length for each station and trajectory. This
    1147 !--          is required as several stations and trajectories are merged into one file but they do
    1148 !--          not have the same number of points in time, hence, missing values may occur and cannot
    1149 !--          be processed further. This is actually a work-around for the specific (UC)2 dataset,
    1150 !--          but it won't harm anyway.
    1151              vmea(l)%dim_t(t) = 0
    1152              DO  n = 1, dim_ntime
    1153                 IF ( e_utm(t,n) /= fill_eutm  .AND.  n_utm(t,n) /= fill_nutm  .AND.                &
    1154                      zar(t,n)   /= fill_zar )  vmea(l)%dim_t(t) = n
    1155              ENDDO
     1101                                    * n_utm_tmp(t)
    11561102!
    11571103!--          Compute grid indices relative to origin and check if these are on the subdomain. Note,
     
    11701116             ENDIF
    11711117
    1172              DO  n = 1, vmea(l)%dim_t(t)
    1173                  is = INT( ( e_utm(t,n) + 0.5_wp * dx ) * ddx, KIND = iwp )
    1174                  js = INT( ( n_utm(t,n) + 0.5_wp * dy ) * ddy, KIND = iwp )
    1175 !
    1176 !--             Is the observation point on subdomain?
    1177                 on_pe = ( is >= nxl  .AND.  is <= nxr  .AND.  js >= nys  .AND.  js <= nyn )
    1178 !
    1179 !--             Check if observation coordinate is on subdomain.
    1180                 IF ( on_pe )  THEN
    1181 !
    1182 !--                Determine vertical index which corresponds to the observation height.
    1183                    ksurf = topo_top_ind(js,is,0)
    1184                    ks = MINLOC( ABS( zu - zw(ksurf) - zar(t,n) ), DIM = 1 ) - 1
    1185 !
    1186 !--                Set mask array at the observation coordinates. Also, flag the surrounding
    1187 !--                coordinate points, but first check whether the surrounding coordinate points are
    1188 !--                on the subdomain.
    1189                    kl = MERGE( ks-off_z, ksurf, ks-off_z >= nzb  .AND. ks-off_z >= ksurf )
    1190                    ku = MERGE( ks+off_z, nzt,   ks+off_z < nzt+1 )
    1191 
    1192                    DO  i = is-off, is+off
    1193                       DO  j = js-off, js+off
    1194                          DO  k = kl, ku
    1195                             meas_flag(k,j,i) = MERGE( IBSET( meas_flag(k,j,i), 0 ), 0,             &
    1196                                                       BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1197                          ENDDO
     1118             is = INT( ( e_utm(t) + 0.5_wp * dx ) * ddx, KIND = iwp )
     1119             js = INT( ( n_utm(t) + 0.5_wp * dy ) * ddy, KIND = iwp )
     1120!
     1121!--          Is the observation point on subdomain?
     1122             on_pe = ( is >= nxl  .AND.  is <= nxr  .AND.  js >= nys  .AND.  js <= nyn )
     1123!
     1124!--          Check if observation coordinate is on subdomain.
     1125             IF ( on_pe )  THEN
     1126!
     1127!--             Determine vertical index which corresponds to the observation height.
     1128                ksurf = topo_top_ind(js,is,0)
     1129                ks = MINLOC( ABS( zu - zw(ksurf) - zar(t) ), DIM = 1 ) - 1
     1130!
     1131!--             Set mask array at the observation coordinates. Also, flag the surrounding
     1132!--             coordinate points, but first check whether the surrounding coordinate points are
     1133!--             on the subdomain.
     1134                kl = MERGE( ks-off_z, ksurf, ks-off_z >= nzb  .AND. ks-off_z >= ksurf )
     1135                ku = MERGE( ks+off_z, nzt,   ks+off_z < nzt+1 )
     1136
     1137                DO  i = is-off, is+off
     1138                   DO  j = js-off, js+off
     1139                      DO  k = kl, ku
     1140                         meas_flag(k,j,i) = MERGE( IBSET( meas_flag(k,j,i), 0 ), 0,                &
     1141                                                          BTEST( wall_flags_total_0(k,j,i), 0 ) )
    11981142                      ENDDO
    11991143                   ENDDO
    1200                 ENDIF
    1201              ENDDO
     1144                ENDDO
     1145             ENDIF
    12021146
    12031147          ENDDO
     
    13171261          IF ( ALLOCATED( n_utm_tmp ) )  DEALLOCATE( n_utm_tmp )
    13181262          IF ( ALLOCATED( n_utm )     )  DEALLOCATE( n_utm )
    1319           IF ( ALLOCATED( zar  )      )  DEALLOCATE( vmea(l)%dim_t )
    13201263          IF ( ALLOCATED( zar  )      )  DEALLOCATE( zar  )
    13211264          IF ( ALLOCATED( height )    )  DEALLOCATE( height )
     
    13361279    ns_all = 0
    13371280#if defined( __parallel )
    1338     CALL MPI_ALLREDUCE( vmea(:)%ns, ns_all(:), vmea_general%nvm,                                   &
    1339                         MPI_INTEGER, MPI_SUM, comm2d, ierr )
     1281    CALL MPI_ALLREDUCE( vmea(:)%ns, ns_all(:), vmea_general%nvm, MPI_INTEGER, MPI_SUM, comm2d, ierr )
    13401282#else
    13411283    ns_all(:) = vmea(:)%ns
     
    13461288    ns_all = 0
    13471289#if defined( __parallel )
    1348     CALL MPI_ALLREDUCE( vmea(:)%ns_soil, ns_all(:), vmea_general%nvm,                              &
    1349                         MPI_INTEGER, MPI_SUM, comm2d, ierr )
     1290    CALL MPI_ALLREDUCE( vmea(:)%ns_soil, ns_all(:), vmea_general%nvm, MPI_INTEGER, MPI_SUM, comm2d, ierr )
    13501291#else
    13511292    ns_all(:) = vmea(:)%ns_soil
     
    14031344
    14041345#endif
    1405 
     1346    IF ( debug_output )  CALL debug_message( 'vm_init', 'end' )
    14061347 END SUBROUTINE vm_init
    14071348
     
    19991940    REAL(wp), DIMENSION(:), ALLOCATABLE           ::  dum_lon                   !< transformed geographical coordinate (longitude)
    20001941    REAL(wp), DIMENSION(:), ALLOCATABLE           ::  oro_rel                   !< relative altitude of model surface
    2001     REAL(wp), DIMENSION(:), POINTER               ::  output_values_1d_pointer  !< pointer for 1d output array
    2002     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET   ::  output_values_1d_target   !< target for 1d output array
    2003     REAL(wp), DIMENSION(:,:), POINTER             ::  output_values_2d_pointer  !< pointer for 2d output array
    2004     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET ::  output_values_2d_target   !< target for 2d output array
     1942    REAL(sp), DIMENSION(:), POINTER               ::  output_values_1d_pointer  !< pointer for 1d output array
     1943    REAL(sp), DIMENSION(:), ALLOCATABLE, TARGET   ::  output_values_1d_target   !< target for 1d output array
     1944    REAL(sp), DIMENSION(:,:), POINTER             ::  output_values_2d_pointer  !< pointer for 2d output array
     1945    REAL(sp), DIMENSION(:,:), ALLOCATABLE, TARGET ::  output_values_2d_target   !< target for 2d output array
    20051946
    20061947    CALL cpu_log( log_point_s(26), 'VM output', 'start' )
     
    20271968
    20281969          return_value = dom_write_var( vmea(l)%nc_filename, 'E_UTM',                              &
    2029                                         values_realwp_1d = output_values_1d_pointer,               &
     1970                                        values_real32_1d = output_values_1d_pointer,               &
    20301971                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
    20311972                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
     
    20401981          output_values_1d_pointer => output_values_1d_target
    20411982          return_value = dom_write_var( vmea(l)%nc_filename, 'N_UTM',                              &
    2042                                         values_realwp_1d = output_values_1d_pointer,               &
     1983                                        values_real32_1d = output_values_1d_pointer,               &
    20431984                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
    20441985                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
     
    20662007          output_values_1d_pointer => output_values_1d_target
    20672008          return_value = dom_write_var( vmea(l)%nc_filename, 'lat',                                &
    2068                                         values_realwp_1d = output_values_1d_pointer,               &
     2009                                        values_real32_1d = output_values_1d_pointer,               &
    20692010                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
    20702011                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
     
    20732014          output_values_1d_pointer => output_values_1d_target
    20742015          return_value = dom_write_var( vmea(l)%nc_filename, 'lon',                                &
    2075                                         values_realwp_1d = output_values_1d_pointer,               &
     2016                                        values_real32_1d = output_values_1d_pointer,               &
    20762017                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
    20772018                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
     
    20892030          output_values_1d_pointer => output_values_1d_target
    20902031          return_value = dom_write_var( vmea(l)%nc_filename, 'z',                                  &
    2091                                         values_realwp_1d = output_values_1d_pointer,               &
     2032                                        values_real32_1d = output_values_1d_pointer,               &
    20922033                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
    20932034                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
     
    20982039          output_values_1d_pointer => output_values_1d_target
    20992040          return_value = dom_write_var( vmea(l)%nc_filename, 'station_h',                          &
    2100                                         values_realwp_1d = output_values_1d_pointer,               &
     2041                                        values_real32_1d = output_values_1d_pointer,               &
    21012042                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
    21022043                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
     
    21412082             output_values_1d_pointer => output_values_1d_target
    21422083             return_value = dom_write_var( vmea(l)%nc_filename, 'E_UTM_soil',                      &
    2143                                            values_realwp_1d = output_values_1d_pointer,            &
     2084                                           values_real32_1d = output_values_1d_pointer,            &
    21442085                                           bounds_start = (/vmea(l)%start_coord_s/),               &
    21452086                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
     
    21542095             output_values_1d_pointer => output_values_1d_target
    21552096             return_value = dom_write_var( vmea(l)%nc_filename, 'N_UTM_soil',                      &
    2156                                            values_realwp_1d = output_values_1d_pointer,            &
     2097                                           values_real32_1d = output_values_1d_pointer,            &
    21572098                                           bounds_start = (/vmea(l)%start_coord_s/),               &
    21582099                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
     
    21802121             output_values_1d_pointer => output_values_1d_target
    21812122             return_value = dom_write_var( vmea(l)%nc_filename, 'lat_soil',                        &
    2182                                            values_realwp_1d = output_values_1d_pointer,            &
     2123                                           values_real32_1d = output_values_1d_pointer,            &
    21832124                                           bounds_start = (/vmea(l)%start_coord_s/),               &
    21842125                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
     
    21872128             output_values_1d_pointer => output_values_1d_target
    21882129             return_value = dom_write_var( vmea(l)%nc_filename, 'lon_soil',                        &
    2189                                            values_realwp_1d = output_values_1d_pointer,            &
     2130                                           values_real32_1d = output_values_1d_pointer,            &
    21902131                                           bounds_start = (/vmea(l)%start_coord_s/),               &
    21912132                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
     
    22032144             output_values_1d_pointer => output_values_1d_target
    22042145             return_value = dom_write_var( vmea(l)%nc_filename, 'z_soil',                          &
    2205                                            values_realwp_1d = output_values_1d_pointer,            &
     2146                                           values_real32_1d = output_values_1d_pointer,            &
    22062147                                           bounds_start = (/vmea(l)%start_coord_s/),               &
    22072148                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
     
    22122153             output_values_1d_pointer => output_values_1d_target
    22132154             return_value = dom_write_var( vmea(l)%nc_filename, 'station_h_soil',                  &
    2214                                            values_realwp_1d = output_values_1d_pointer,            &
     2155                                           values_real32_1d = output_values_1d_pointer,            &
    22152156                                           bounds_start = (/vmea(l)%start_coord_s/),               &
    22162157                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
     
    22702211
    22712212             return_value = dom_write_var( vmea(l)%nc_filename, variable_name,                     &
    2272                                            values_realwp_2d = output_values_2d_pointer,            &
     2213                                           values_real32_2d = output_values_2d_pointer,            &
    22732214                                           bounds_start = (/vmea(l)%start_coord_s, t_ind/),        &
    22742215                                           bounds_end   = (/vmea(l)%end_coord_s, t_ind /) )
     
    22782219             output_values_2d_pointer => output_values_2d_target
    22792220             return_value = dom_write_var( vmea(l)%nc_filename, variable_name,                     &
    2280                                            values_realwp_2d = output_values_2d_pointer,            &
     2221                                           values_real32_2d = output_values_2d_pointer,            &
    22812222                                           bounds_start = (/vmea(l)%start_coord_s, t_ind/),        &
    22822223                                           bounds_end   = (/vmea(l)%end_coord_s, t_ind  /) )
     
    22912232
    22922233             return_value = dom_write_var( vmea(l)%nc_filename, variable_name,                     &
    2293                                            values_realwp_2d = output_values_2d_pointer,            &
     2234                                           values_real32_2d = output_values_2d_pointer,            &
    22942235                                           bounds_start = (/vmea(l)%start_coord_a, t_ind/),        &
    22952236                                           bounds_end   = (/vmea(l)%end_coord_a, t_ind/) )
     
    23002241             output_values_2d_pointer => output_values_2d_target
    23012242             return_value = dom_write_var( vmea(l)%nc_filename, variable_name,                     &
    2302                                            values_realwp_2d = output_values_2d_pointer,            &
     2243                                           values_real32_2d = output_values_2d_pointer,            &
    23032244                                           bounds_start = (/ vmea(l)%start_coord_a, t_ind /),      &
    23042245                                           bounds_end   = (/ vmea(l)%end_coord_a, t_ind /) )
Note: See TracChangeset for help on using the changeset viewer.