Ignore:
Timestamp:
Jun 19, 2020 11:56:30 AM (4 years ago)
Author:
eckhard
Message:

Handle COSMO soil data with and without additional surface temperature

File:
1 edited

Legend:

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

    r4553 r4568  
    2626! -----------------
    2727! $Id$
     28! Handle COSMO soil data with and without additional surface temperature
     29!
     30!
     31! 4553 2020-06-03 16:34:15Z eckhard
    2832! Option --help now points the user to INIFOR's wiki page
    2933! Remove deprecated command-line options -clon and -clat
     
    146150    USE inifor_defs,                                                           &
    147151        ONLY:  DATE, SNAME, PATH, PI, TO_RADIANS, TO_DEGREES, VERSION,         &
    148                NC_DEPTH_NAME, NC_HHL_NAME, NC_RLAT_NAME, NC_RLON_NAME,         &
    149                NC_ROTATED_POLE_NAME, NC_POLE_LATITUDE_NAME,                    &
     152               NC_DEPTH_DIM_IDX, NC_DEPTH_NAME, NC_HHL_NAME, NC_RLAT_NAME,     &
     153               NC_RLON_NAME, NC_ROTATED_POLE_NAME, NC_POLE_LATITUDE_NAME,      &
    150154               NC_POLE_LONGITUDE_NAME, RHO_L, iwp, wp,                         &
    151155               PIDS_ORIGIN_LON, PIDS_ORIGIN_LAT, PIDS_ORIGIN_Z
    152156    USE inifor_types
    153157    USE inifor_util,                                                           &
    154         ONLY:  add_hours_to, reverse, str, real_to_str
     158        ONLY:  add_hours_to, nearly_equal, reverse, str, real_to_str
    155159    USE netcdf
    156160
     
    355359
    356360    start = (/ 1, 1, 1 /)
    357     IF ( TRIM(in_var%name) .EQ. 'T_SO' )  THEN
     361    IF ( TRIM(in_var%name) .EQ. 'T_SO' .AND.                                &
     362         in_var%has_redundant_first_level )  THEN
     363       
    358364!
    359365!--    Skip depth = 0.0 for T_SO and reduce number of depths from 9 to 8
     
    15781584 END SUBROUTINE set_palm_origin
    15791585
     1586
     1587!------------------------------------------------------------------------------!
     1588! Description:
     1589! ------------
     1590! This function is meant to check weather a COSMO soil variable has an
     1591! additional and redunant surface value at depth = 0.0. For instance operational
     1592! DWD COSMO output contains the surface temperature in T_SO as a copy of the
     1593! values in the first soil layer.
     1594!------------------------------------------------------------------------------!
     1595 LOGICAL FUNCTION has_surface_value( soil_var, filename )
     1596
     1597    TYPE(nc_var), INTENT(IN)     ::  soil_var
     1598    CHARACTER(LEN=*), INTENT(IN) ::  filename
     1599   
     1600    CHARACTER(LEN=NF90_MAX_NAME) ::  dimname
     1601    REAL(wp), ALLOCATABLE        ::  depths(:)
     1602
     1603    CALL get_dimension_vector_of_variable(                                     &
     1604       soil_var%name,                                                          &
     1605       dim_idx = NC_DEPTH_DIM_IDX,                                             &
     1606       filename = filename,                                                    &
     1607       dim_vector = depths                                                     &
     1608    )
     1609
     1610    has_surface_value = nearly_equal( depths(1), 0.0_wp, 10 * EPSILON(1.0_wp) )
     1611
     1612 END FUNCTION has_surface_value
     1613
     1614
     1615!------------------------------------------------------------------------------!
     1616! Description:
     1617! ------------
     1618! This routine reads the dim_idx-th dimension vector of the variable varname
     1619! from netCDF file filename. It is used for finding the depth coordinate vector
     1620! of COSMO soil variables without knowing its name.
     1621!------------------------------------------------------------------------------!
     1622 SUBROUTINE get_dimension_vector_of_variable( varname, dim_idx, filename, dim_vector )
     1623    CHARACTER(LEN=*), INTENT(IN)              ::  varname, filename
     1624    INTEGER, INTENT(IN)                       ::  dim_idx
     1625
     1626    REAL(wp), INTENT(OUT), ALLOCATABLE ::  dim_vector(:)
     1627
     1628    INTEGER                            ::  dimids(NF90_MAX_VAR_DIMS)
     1629    INTEGER                            ::  varid
     1630    CHARACTER(LEN=NF90_MAX_NAME)       ::  dimname
     1631
     1632    INTEGER ::  ncid
     1633
     1634    IF ( nf90_open( TRIM( filename ), NF90_NOWRITE, ncid ) .EQ. NF90_NOERR )  THEN
     1635
     1636!
     1637!--    get id of variable varname
     1638       CALL check( nf90_inq_varid( ncid, TRIM( varname ), varid ) )
     1639       
     1640!
     1641!--    get dimension ids of variable with varid
     1642       CALL check( nf90_inquire_variable( ncid, varid, dimids = dimids ) )
     1643
     1644!
     1645!--    get name of dim_idx-th dimension variable
     1646       CALL check( nf90_inquire_dimension( ncid, dimids(dim_idx), name = dimname ) )
     1647       CALL check( nf90_close( ncid ) )
     1648
     1649    ELSE
     1650
     1651       message = "Failed to open file '" // TRIM(filename) // "'."
     1652       CALL inifor_abort('get_netcdf_variable', message)
     1653
     1654    ENDIF
     1655
     1656    ! get dimension vector with dimname
     1657    CALL get_netcdf_dim_vector( filename, dimname, dim_vector )
     1658
     1659 END SUBROUTINE get_dimension_vector_of_variable
     1660
     1661
    15801662 END MODULE inifor_io
    15811663#endif
Note: See TracChangeset for help on using the changeset viewer.