Ignore:
Timestamp:
Jul 5, 2019 1:05:19 PM (5 years ago)
Author:
eckhard
Message:

inifor: Changed initialization mode from 'volume' to 'profile'

File:
1 edited

Legend:

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

    r3997 r4074  
    2626! -----------------
    2727! $Id$
     28! Pass hhl_file directly instead of entire INIFOR configuration
     29!
     30!
     31! 3997 2019-05-23 12:35:57Z eckhard
    2832! Added boolean indicator for --elevation option invocation
    2933! Stop INIFOR if no command-line options given
     
    759763
    760764
    761  SUBROUTINE get_cosmo_grid( cfg, soil_file, rlon, rlat, hhl, hfl, depths, &
     765 SUBROUTINE get_cosmo_grid( hhl_file, soil_file, rlon, rlat, hhl, hfl, depths, &
    762766                            d_depth, d_depth_rho_inv, phi_n, lambda_n,       &
    763767                            phi_equat,                                       &
     
    766770                            nlon, nlat, nlev, ndepths )
    767771
    768     TYPE(inifor_config), INTENT(IN)                      ::  cfg
    769     CHARACTER(LEN=PATH), INTENT(IN)                      ::  soil_file !< list of soil input files (temperature, moisture, <prefix>YYYYMMDDHH-soil.nc)
     772    CHARACTER(LEN=PATH), INTENT(IN)                      ::  hhl_file  !< path to file containing the HHL variable (height of half layers)
     773    CHARACTER(LEN=PATH), INTENT(IN)                      ::  soil_file !< path to one of the soil input files for reading soil layer depths
    770774    REAL(wp), DIMENSION(:), ALLOCATABLE, INTENT(OUT)     ::  rlon      !< longitudes of COSMO-DE's rotated-pole grid
    771775    REAL(wp), DIMENSION(:), ALLOCATABLE, INTENT(OUT)     ::  rlat      !< latitudes of COSMO-DE's rotated-pole grid
     
    790794!-- Read in COSMO's heights of half layers (vertical cell faces)
    791795    cosmo_var%name = NC_HHL_NAME
    792     CALL get_netcdf_variable( cfg%hhl_file, cosmo_var, hhl )
    793     CALL get_netcdf_dim_vector( cfg%hhl_file, NC_RLON_NAME, rlon )
    794     CALL get_netcdf_dim_vector( cfg%hhl_file, NC_RLAT_NAME, rlat )
     796    CALL get_netcdf_variable( hhl_file, cosmo_var, hhl )
     797    CALL get_netcdf_dim_vector( hhl_file, NC_RLON_NAME, rlon )
     798    CALL get_netcdf_dim_vector( hhl_file, NC_RLAT_NAME, rlat )
    795799    CALL get_netcdf_dim_vector( soil_file, NC_DEPTH_NAME, depths)
    796800    CALL log_runtime( 'time', 'read' )
     
    820824!-- COSMO rotated pole coordinates
    821825    phi_n = TO_RADIANS                                                       &
    822           * get_netcdf_variable_attribute( cfg%hhl_file,                   &
     826          * get_netcdf_variable_attribute( hhl_file,                         &
    823827                                           NC_ROTATED_POLE_NAME,             &
    824828                                           NC_POLE_LATITUDE_NAME )
    825829
    826830    lambda_n = TO_RADIANS                                                    &
    827              * get_netcdf_variable_attribute( cfg%hhl_file,                &
     831             * get_netcdf_variable_attribute( hhl_file,                      &
    828832                                              NC_ROTATED_POLE_NAME,          &
    829833                                              NC_POLE_LONGITUDE_NAME )
Note: See TracChangeset for help on using the changeset viewer.