Changeset 3537 for palm


Ignore:
Timestamp:
Nov 20, 2018 10:53:14 AM (5 years ago)
Author:
eckhard
Message:

inifor: COSMO-D2 support

Location:
palm/trunk/UTIL/inifor/src
Files:
5 edited

Legend:

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

    r3456 r3537  
    2626! -----------------
    2727! $Id$
     28! Print version number on program start
     29!
     30!
     31! 3456 2018-10-30 14:29:54Z eckhard
    2832! NetCDf output of internal arrays only with --debug option
    2933!
     
    110114!------------------------------------------------------------------------------
    111115 CALL run_control('init', 'void')
     116    CALL report('main_loop', 'Running INIFOR version ' // VERSION)
    112117
    113118    ! Initialize INIFOR's parameters from command-line interface and namelists
  • palm/trunk/UTIL/inifor/src/inifor_defs.f90

    r3534 r3537  
    2626! -----------------
    2727! $Id$
     28! Bumped version number
     29!
     30!
     31! 3534 2018-11-19 15:35:16Z raasch
    2832! NEW_LINE intrinsic replaced by ACHAR to avoid compile time error
    2933!
     
    101105 INTEGER, PARAMETER          ::  FORCING_STEP = 1             !< Number of hours between forcing time steps [h]
    102106 REAL(dp), PARAMETER         ::  NUDGING_TAU = 21600.0_dp     !< Nudging relaxation time scale [s]
    103  CHARACTER(LEN=*), PARAMETER ::  VERSION = '1.4.1'            !< INIFOR version number
     107 CHARACTER(LEN=*), PARAMETER ::  VERSION = '1.4.2'            !< INIFOR version number
    104108 CHARACTER(LEN=*), PARAMETER ::  COPYRIGHT = 'Copyright 2017-2018 Leibniz Universitaet Hannover' // &
    105109     ACHAR( 10 ) // ' Copyright 2017-2018 Deutscher Wetterdienst Offenbach' !< Copyright notice
  • palm/trunk/UTIL/inifor/src/inifor_grid.f90

    r3456 r3537  
    2626! -----------------
    2727! $Id$
     28! Read COSMO domain extents and soil depths from input files
     29! Report averaging mode and debugging mode in log
     30!
     31!
     32! 3456 2018-10-30 14:29:54Z eckhard
    2833! Remove surface forcing from netCDF output (radiation + precipitation)
    2934! NetCDf output of internal arrays only with --debug option
     
    8388               RHO_L, OMEGA, HECTO
    8489    USE io,                                                                    &
    85         ONLY:  get_netcdf_variable, get_netcdf_attribute,                      &
    86                parse_command_line_arguments, validate_config
     90        ONLY:  get_netcdf_attribute, get_netcdf_dim_vector,                    &
     91               get_netcdf_variable, parse_command_line_arguments,              &
     92               validate_config
    8793    USE netcdf,                                                                &
    8894        ONLY:  NF90_MAX_NAME, NF90_MAX_VAR_DIMS
     
    154160    REAL(dp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  hfl             !< heights of full layers (cell centres) above sea level in COSMO-DE, computed as arithmetic average of hhl
    155161    REAL(dp), DIMENSION(:), ALLOCATABLE, TARGET     ::  depths          !< COSMO-DE's TERRA-ML soil layer depths
    156     REAL(dp), DIMENSION(:), ALLOCATABLE, TARGET     ::  d_depth_rho_inv !< COSMO-DE's TERRA-ML soil layer thicknesses
     162    REAL(dp), DIMENSION(:), ALLOCATABLE, TARGET     ::  d_depth         !< COSMO-DE's TERRA-ML soil layer thicknesses
     163    REAL(dp), DIMENSION(:), ALLOCATABLE, TARGET     ::  d_depth_rho_inv !< inverted soil water mass
    157164    REAL(dp), DIMENSION(:), ALLOCATABLE, TARGET     ::  rlon            !< longitudes of COSMO-DE's rotated-pole grid
    158165    REAL(dp), DIMENSION(:), ALLOCATABLE, TARGET     ::  rlat            !< latitudes of COSMO-DE's rotated-pole grid
     
    177184    INTEGER ::  nlat  !< number of latitudal points in target grid (COSMO-DE)
    178185    INTEGER ::  nlev  !< number of levels in target grid (COSMO-DE)
    179     INTEGER ::  layers !< number of COSMO-DE soil layers
     186    INTEGER ::  ndepths !< number of COSMO-DE soil layers
    180187    INTEGER ::  start_hour_flow         !< start of flow forcing in number of hours relative to start_date
    181188    INTEGER ::  start_hour_soil         !< start of soil forcing in number of hours relative to start_date, typically equals start_hour_flow
     
    293300       start_hour_soilmoisture = - (4 * 7 * 24) - 2
    294301
    295        lonmin =  -5.0_dp * TO_RADIANS
    296        lonmax =   5.5_dp * TO_RADIANS
    297        latmin =  -5.0_dp * TO_RADIANS
    298        latmax =   6.5_dp * TO_RADIANS
    299 
    300302       ! COSMO-DE default rotated pole
    301303       phi_n     =   40.0_dp * TO_RADIANS
    302304       phi_equat =   50.0_dp * TO_RADIANS
    303305       lambda_n  = -170.0_dp * TO_RADIANS
    304 
    305        ! COMSMO-DE soil layers
    306        layers = 8   
    307        ALLOCATE( depths(layers), d_depth_rho_inv(layers) )
    308        depths = (/0.005_dp, 0.02_dp, 0.06_dp, 0.18_dp, 0.54_dp, 1.62_dp, 4.86_dp, 14.58_dp/)
    309        d_depth_rho_inv = 1.0_dp / &
    310           ( (/0.01_dp, 0.02_dp, 0.06_dp, 0.18_dp, 0.54_dp, 1.62_dp, 4.86_dp, 14.58_dp/) * RHO_L )
    311306
    312307       ! Defaultmain centre (_c) of the PALM-4U grid in the geographical system (_g)
     
    395390       CALL report('setup_parameters', "initialization mode: " // TRIM(cfg % ic_mode))
    396391       CALL report('setup_parameters', "       forcing mode: " // TRIM(cfg % bc_mode))
     392       CALL report('setup_parameters', "     averaging mode: " // TRIM(cfg % averaging_mode))
    397393       CALL report('setup_parameters', "          data path: " // TRIM(cfg % input_path))
    398394       CALL report('setup_parameters', "           hhl file: " // TRIM(cfg % hhl_file))
     
    400396       CALL report('setup_parameters', "      namelist file: " // TRIM(cfg % namelist_file))
    401397       CALL report('setup_parameters', "   output data file: " // TRIM(output_file % name))
     398       IF (cfg % debug )  CALL report('setup_parameters', "     debugging mode: enabled")
    402399
    403400 CALL run_control('time', 'init')
     
    472469       cosmo_var % name = 'HHL'
    473470       CALL get_netcdf_variable(cfg % hhl_file, cosmo_var, hhl)
     471       CALL get_netcdf_dim_vector(cfg % hhl_file, 'rlon', rlon)
     472       CALL get_netcdf_dim_vector(cfg % hhl_file, 'rlat', rlat)
     473       CALL get_netcdf_dim_vector(soil_files(1), 'depth_2', depths)
    474474 CALL run_control('time', 'read')
    475475
     
    478478       nlat = SIZE(hhl, 2)
    479479       nlev = SIZE(hhl, 3)
    480 
     480       ndepths = SIZE(depths)
     481
     482       lonmin = MINVAL(rlon) * TO_RADIANS
     483       lonmax = MAXVAL(rlon) * TO_RADIANS
     484       latmin = MINVAL(rlat) * TO_RADIANS
     485       latmax = MAXVAL(rlat) * TO_RADIANS
    481486 CALL run_control('time', 'comp')
    482487
    483488       ! Appoximate COSMO-DE heights of full layers (cell centres)
    484489       ALLOCATE( hfl(nlon, nlat, nlev-1) )
     490       ALLOCATE( d_depth(ndepths), d_depth_rho_inv(ndepths) )
     491
    485492 CALL run_control('time', 'alloc')
     493       CALL get_soil_layer_thickness( depths, d_depth )
     494       d_depth_rho_inv = 1.0_dp / ( d_depth * RHO_L )
     495
     496       ! Appoximate COSMO-DE heights of full layers (cell centres)
    486497       DO k = 1, nlev-1
    487498          hfl(:,:,k) = 0.5_dp * ( hhl(:,:,k) +                                 &
    488499                                  hhl(:,:,k+1) )
    489500       END DO
     501 CALL run_control('time', 'comp')
     502
     503
    490504
    491505!------------------------------------------------------------------------------
     
    14891503       END IF
    14901504
    1491        ! Copy averaged grid to all COSMO columnts, leads to computing the same
     1505       ! Copy averaged grid to all COSMO columns, leads to computing the same
    14921506       ! vertical interpolation weights for all columns and to COSMO grid level
    14931507       ! based averaging onto the averaged COSMO heights.
     
    15421556
    15431557       imin = CEILING( (avg_grid % lon(1) - cosmo_lon(0)) / dlon )
    1544        imax = FLOOR (avg_grid % lon(2) - cosmo_lon(0)) / dlon )
     1558       imax = FLOOR  ( (avg_grid % lon(2) - cosmo_lon(0)) / dlon )
    15451559
    15461560       jmin = CEILING( (avg_grid % lat(1) - cosmo_lat(0)) / dlat )
    1547        jmax = FLOOR (avg_grid % lat(2) - cosmo_lat(0)) / dlat )
     1561       jmax = FLOOR  ( (avg_grid % lat(2) - cosmo_lat(0)) / dlat )
    15481562       
    1549        message = "Averaging over "//                                           &
    1550                  TRIM(str(imin)) // " < i < " // TRIM(str(imax)) //            &
     1563       message = "Averaging '" // TRIM(avg_grid % kind) // "' over "//         &
     1564                 TRIM(str(imin)) // " <= i <= " // TRIM(str(imax)) //          &
    15511565                 " and " //                                                    &
    1552                  TRIM(str(jmin)) // " < j < " // TRIM(str(jmax))
     1566                 TRIM(str(jmin)) // " <= j <= " // TRIM(str(jmax))
    15531567       CALL report( 'get_cosmo_averaging_region', message )
    15541568
     
    15571571       avg_grid % n_columns = nx * ny
    15581572
    1559        ALLOCATE( avg_grid % iii(avg_grid % n_columns),                                 &
     1573       ALLOCATE( avg_grid % iii(avg_grid % n_columns),                         &
    15601574                 avg_grid % jjj(avg_grid % n_columns) )
    15611575
     
    39333947    END SUBROUTINE fill_water_cells
    39343948
     3949
     3950!------------------------------------------------------------------------------!
     3951! Description:
     3952! ------------
     3953!> Fills the thickness array of the COSMO soil layers. Since COSMO's (i.e.
     3954!> TERRA_ML's [1]) soil layer boundaries follow the rule
     3955!>
     3956!>    depth(0) = 0.0, and
     3957!>    depth(k) = 0.01 * 3**(k-1), k in [1,2,3,...,7]
     3958!>
     3959!> and full levels are defined as the midpoints between two layer boundaries,
     3960!> all except the first layer thicknesses equal the depth of the midpoint.
     3961!>
     3962!> [1] A Description of the Nonhydrostatic Regional COSMO Model Part II :
     3963!>     Physical Parameterization*, Sect. 11 TERRA_ML.
     3964!>     http://www.cosmo-model.org/content/model/documentation/core/cosmoPhysParamtr.pdf)
     3965!>
     3966!> Input parameters:
     3967!> -----------------
     3968!>
     3969!> depths: array of full soil layer depths (cell midpoints)
     3970!>
     3971!>
     3972!> Output parameters:
     3973!> ------------------
     3974!>
     3975!> d_depth: array of soil layer thicknesses
     3976!>
     3977!------------------------------------------------------------------------------!
     3978    SUBROUTINE get_soil_layer_thickness(depths, d_depth)
     3979       
     3980       REAL(dp), INTENT(IN)  ::  depths(:)
     3981       REAL(dp), INTENT(OUT) ::  d_depth(:)
     3982
     3983       d_depth(:) = depths(:)
     3984       d_depth(1) = 2.0_dp * depths(1)
     3985
     3986    END SUBROUTINE get_soil_layer_thickness
     3987
    39353988 END MODULE grid
  • palm/trunk/UTIL/inifor/src/inifor_io.f90

    r3534 r3537  
    2626! -----------------
    2727! $Id$
     28! New routine get_netcdf_dim_vector()
     29!
     30!
     31! 3534 2018-11-19 15:35:16Z raasch
    2832! bugfix: INTENT attribute changed
    2933!
     
    173177
    174178
     179    SUBROUTINE get_netcdf_dim_vector(filename, varname, array)
     180
     181       CHARACTER(LEN=*), INTENT(IN)         ::  filename
     182       CHARACTER(LEN=*), INTENT(IN)         ::  varname
     183       REAL(dp), ALLOCATABLE, INTENT(INOUT) ::  array(:)
     184
     185       INTEGER ::  ncid, varid, dimlen
     186       INTEGER ::  dimids(NF90_MAX_VAR_DIMS)
     187
     188       IF ( nf90_open( TRIM(filename), NF90_NOWRITE, ncid ) .EQ. NF90_NOERR .AND. &
     189            nf90_inq_varid( ncid, varname, varid ) .EQ. NF90_NOERR )  THEN
     190
     191          CALL check(nf90_inquire_variable( ncid, varid, dimids = dimids ))
     192          CALL check(nf90_inquire_dimension( ncid, dimids(1), len = dimlen ))
     193
     194          ALLOCATE(array(dimlen))
     195          CALL check(nf90_get_var( ncid, varid, array ))
     196
     197       ELSE
     198
     199          message = "Failed to read '" // TRIM(varname) // &
     200             "' from file '" // TRIM(filename) // "'."
     201          CALL abort('get_netcdf_dim_vector', message)
     202
     203       END IF
     204
     205    END SUBROUTINE get_netcdf_dim_vector
     206
     207
    175208    SUBROUTINE get_input_dimensions(in_var, ncid)
    176209
     
    209242
    210243          message = "Failed reading NetCDF variable " //                       &
    211              TRIM(in_var % name) // " with " // TRIM(str(in_var%ndim)) //      &
     244             TRIM(in_var % name) // " with " // TRIM(str(in_var % ndim)) //    &
    212245             " dimensions because only two- and and three-dimensional" //      &
    213246             " variables are supported."
  • palm/trunk/UTIL/inifor/src/inifor_transform.f90

    r3534 r3537  
    271271                k_source = avg_grid % kkk(l, k_profile, m)
    272272
    273                 profile_array(k_profile) = profile_array(k_profile)    &
     273                profile_array(k_profile) = profile_array(k_profile)            &
    274274                   + avg_grid % w(l, k_profile, m)                             &
    275275                   * source_array(i_source, j_source, k_source)
Note: See TracChangeset for help on using the changeset viewer.