Ignore:
Timestamp:
Nov 18, 2020 1:05:58 PM (3 years ago)
Author:
eckhard
Message:

inifor: Validate netCDF dimensions of COSMO input files

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/UTIL/inifor/src/inifor_io.f90

    r4675 r4790  
    2626! -----------------
    2727! $Id$
     28! Validate mesoscale input data by the number of dimensions and their lengths
     29!
     30!
     31! 4675 2020-09-11 10:00:26Z eckhard
    2832! New command-line options for soil profile initialization and homogeneous
    2933!    boundary conditions
     
    409413 SUBROUTINE netcdf_define_variable(var, ncid)
    410414
    411      TYPE(nc_var), INTENT(INOUT) ::  var
    412      INTEGER, INTENT(IN)         ::  ncid
    413 
    414      CALL check(nf90_def_var(ncid, var%name, NF90_FLOAT,       var%dimids(1:var%ndim), var%varid))
    415      CALL check(nf90_put_att(ncid, var%varid, "long_name",     var%long_name))
    416      CALL check(nf90_put_att(ncid, var%varid, "units",         var%units))
    417      IF ( var%lod .GE. 0 )  THEN
    418         CALL check(nf90_put_att(ncid, var%varid, "lod",           var%lod))
    419      ENDIF
    420      CALL check(nf90_put_att(ncid, var%varid, "source",        var%source))
    421      CALL check(nf90_put_att(ncid, var%varid, "_FillValue",    NF90_FILL_REAL))
     415    TYPE(nc_var), INTENT(INOUT) ::  var
     416    INTEGER, INTENT(IN)         ::  ncid
     417
     418    CALL check(nf90_def_var(ncid, var%name, NF90_FLOAT,       var%dimids(1:var%ndim), var%varid))
     419    CALL check(nf90_put_att(ncid, var%varid, "long_name",     var%long_name))
     420    CALL check(nf90_put_att(ncid, var%varid, "units",         var%units))
     421    IF ( var%lod .GE. 0 )  THEN
     422       CALL check(nf90_put_att(ncid, var%varid, "lod",           var%lod))
     423    ENDIF
     424    CALL check(nf90_put_att(ncid, var%varid, "source",        var%source))
     425    CALL check(nf90_put_att(ncid, var%varid, "_FillValue",    NF90_FILL_REAL))
    422426
    423427 END SUBROUTINE netcdf_define_variable
     
    433437 SUBROUTINE netcdf_get_dimensions(var, ncid)
    434438
    435      TYPE(nc_var), INTENT(INOUT) ::  var
    436      INTEGER, INTENT(IN)         ::  ncid
    437      INTEGER                     ::  i
    438      CHARACTER(SNAME)            ::  null
    439 
    440      DO  i = 1, var%ndim
    441         CALL check(nf90_inquire_dimension(ncid, var%dimids(i), &
    442                                           name = null, &
    443                                           len  = var%dimlen(i)  ) )
    444      ENDDO
     439    TYPE(nc_var), INTENT(INOUT) ::  var
     440    INTEGER, INTENT(IN)         ::  ncid
     441    INTEGER                     ::  i
     442    CHARACTER(SNAME)            ::  null
     443
     444    DO  i = 1, var%ndim
     445       CALL check(nf90_inquire_dimension(ncid, var%dimids(i), &
     446                                         name = null, &
     447                                         len  = var%dimlen(i)  ) )
     448    ENDDO
    445449
    446450 END SUBROUTINE netcdf_get_dimensions
     
    819823
    820824
     825!------------------------------------------------------------------------------!
     826! Description:
     827! ------------
     828!> Checks wheather the COSMO grid matches the shape of the meteorological input
     829!> data by comparing the number of netCDF dimensions and their lengths in the
     830!> hhl.nc and the first of the *-flow files.
     831!------------------------------------------------------------------------------!
     832 SUBROUTINE validate_dataset(flow_files, hhl_file)
     833    CHARACTER(LEN=PATH), INTENT(IN) ::  flow_files(:) !< paths to files containing atmospheric variables
     834    CHARACTER(LEN=PATH), INTENT(IN) ::  hhl_file      !< path to file containing the HHL variable (height of half layers)
     835
     836    CHARACTER(SNAME), PARAMETER ::  NC_W_NAME = 'W'
     837    TYPE(nc_var)                ::  hhl_var, flow_var
     838    INTEGER                     ::  dim_idx, ncid, ndims_flow, ndims_hhl, varid
     839    REAL(wp), ALLOCATABLE       ::  hhl_dim_vector(:), flow_dim_vector(:)
     840    LOGICAL                     ::  dims_have_same_length
     841
     842    IF ( nf90_open( TRIM( flow_files(1) ), NF90_NOWRITE, ncid ) .EQ. NF90_NOERR )  THEN
     843
     844       CALL check( nf90_inq_varid( ncid, NC_W_NAME, varid=varid ) )
     845       CALL check( nf90_inquire_variable( ncid, varid, ndims=ndims_flow ) )
     846       CALL netcdf_get_dimensions( flow_var, ncid )
     847       CALL check( nf90_close( ncid ) )
     848
     849    ELSE
     850
     851       message = "Failed to read netCDF dimensions'" //                        &
     852                 "' from file '" // TRIM( flow_files(1) ) // "'."
     853       CALL inifor_abort( 'validate_dataset', message )
     854
     855    ENDIF
     856
     857    IF ( nf90_open( TRIM( hhl_file ), NF90_NOWRITE, ncid ) .EQ. NF90_NOERR )  THEN
     858
     859       CALL check( nf90_inq_varid( ncid, NC_HHL_NAME, varid=varid ) )
     860       CALL check( nf90_inquire_variable( ncid, varid, ndims=ndims_hhl ) )
     861       CALL netcdf_get_dimensions( hhl_var, ncid )
     862       CALL check( nf90_close( ncid ) )
     863
     864    ELSE
     865
     866       message = "Failed to read netCDF dimensions'" //                        &
     867                 "' from file '" // TRIM(hhl_file) // "'."
     868       CALL inifor_abort( 'validate_dataset', message )
     869
     870    ENDIF
     871
     872!
     873!-- Compare number dimensions of 'HHL' in hhl file and 'W' in first flow file
     874    IF  ( .NOT. ndims_flow .EQ. ndims_hhl )  THEN
     875       message = "Mesoscale data inconsistent. Number of dimensions in the " //&
     876                 "hhl file does not match with the meteorologial fields " //   &
     877                 "in the *-flow files (" //                                    &
     878                 "HHL: ndims = " // TRIM( str( ndims_hhl ) )  // ", " //       &
     879                 "W: ndims = "   // TRIM( str( ndims_flow ) ) // ")."
     880       CALL inifor_abort( 'validate_dataset', message )
     881    ENDIF
     882
     883
     884!
     885!-- Compare lengths of each dimension, ignoring time (dim_idx = 1)
     886    DO dim_idx = 2, ndims_hhl
     887
     888       CALL get_dimension_vector_of_variable(                                  &
     889          NC_HHL_NAME,                                                         &
     890          dim_idx = dim_idx,                                                   &
     891          filename = hhl_file,                                                 &
     892          dim_vector = hhl_dim_vector                                          &
     893       )
     894
     895       CALL get_dimension_vector_of_variable(                                  &
     896          NC_W_NAME,                                                           &
     897          dim_idx = dim_idx,                                                   &
     898          filename = flow_files(1),                                            &
     899          dim_vector = flow_dim_vector                                         &
     900       )
     901
     902       dims_have_same_length = SIZE( flow_dim_vector ) .EQ. SIZE( hhl_dim_vector )
     903       IF  ( .NOT. dims_have_same_length )  THEN
     904          message = &
     905             "Mesoscale data inconsistent. Number of grid points " //          &
     906             "in dimension #" // TRIM( str( dim_idx ) ) //                     &
     907             " do not match in the hhl and *-flow files (" //                  &
     908             "HHL: len = " // TRIM( str( SIZE( hhl_dim_vector ) ) ) // ", " // &
     909             "W: len = "   // TRIM( str( SIZE( flow_dim_vector ) ) )// ")."
     910          CALL inifor_abort( 'validate_dataset', message )
     911       ENDIF
     912
     913    ENDDO
     914
     915 END SUBROUTINE validate_dataset
     916
    821917 SUBROUTINE get_cosmo_grid( hhl_file, soil_file, rlon, rlat, hhl, hfl, depths, &
    822                             d_depth, d_depth_rho_inv, phi_n, lambda_n,       &
    823                             phi_equat,                                       &
    824                             lonmin_cosmo, lonmax_cosmo,                      &
    825                             latmin_cosmo, latmax_cosmo,                      &
     918                            d_depth, d_depth_rho_inv, phi_n, lambda_n,         &
     919                            phi_equat,                                         &
     920                            lonmin_cosmo, lonmax_cosmo,                        &
     921                            latmin_cosmo, latmax_cosmo,                        &
    826922                            nlon, nlat, nlev, ndepths )
    827923
Note: See TracChangeset for help on using the changeset viewer.