source: palm/trunk/UTIL/inifor/tests/test-stretching.f90 @ 3182

Last change on this file since 3182 was 3182, checked in by suehring, 6 years ago

New Inifor features: grid stretching, improved command-interface, support start dates in different formats in both YYYYMMDD and YYYYMMDDHH, Ability to manually control input file prefixes (--radiation-prefix, --soil-preifx, --flow-prefix, --soilmoisture-prefix) for compatiblity with DWD forcast naming scheme; GNU-style short and long option; Prepared output of large-scale forcing profiles (no computation yet); Added preprocessor flag netcdf4 to switch output format between netCDF 3 and 4; Updated netCDF variable names and attributes to comply with PIDS v1.9; Inifor bugfixes: Improved compatibility with older Intel Intel compilers by avoiding implicit array allocation; Added origin_lon/_lat values and correct reference time in dynamic driver global attributes; corresponding PALM changes: adjustments to revised Inifor; variables names in dynamic driver adjusted; enable geostrophic forcing also in offline nested mode; variable names in LES-LES and COSMO offline nesting changed; lateral boundary flags for nesting, in- and outflow conditions renamed

File size: 3.2 KB
Line 
1!> @file tests/test-stretching.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 2017-2018 Leibniz Universitaet Hannover
18! Copyright 2017-2018 Deutscher Wetterdienst Offenbach
19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23! Initial revision
24!
25!
26! Former revisions:
27! -----------------
28! $Id$
29!
30!
31! Authors:
32! --------
33! @author Eckhard Kadasch
34!
35! Description:
36! ------------
37!> This program tests INIFOR's implementation of PALM's grid stretching.
38!>
39!------------------------------------------------------------------------------!
40 PROGRAM test_stretching
41
42    USE defs, &
43        ONLY :  dp
44
45    USE grid, &
46        ONLY :  stretched_z
47
48    USE test_utils
49   
50    IMPLICIT NONE
51
52    CHARACTER(LEN=*), PARAMETER ::  title = "stretched grid"
53    LOGICAL                     ::  res
54
55    INTEGER, PARAMETER ::  nz = 9
56    INTEGER            ::  k  = nz - 2
57
58    REAL(dp) ::  z(1:nz)
59    REAL(dp) ::  dz(10)            = -1.0_dp
60    REAL(dp) ::  dz_max            = 1000.0_dp
61    REAL(dp) ::  dz_stretch_factor = 1.08_dp
62    REAL(dp) ::  dz_stretch_level  = 2.0_dp
63    REAL(dp) ::  dz_stretch_level_start(9) = -9999999.9_dp
64    REAL(dp) ::  dz_stretch_level_end(9) = 9999999.9_dp
65    REAL(dp) ::  dz_stretch_factor_array(9) = 1.08_dp
66
67    CALL begin_test(title, res)
68
69    ! Arange
70    z(:)   = 0.0_dp
71    dz(1)  = 1.0_dp
72
73    ! Act
74    CALL stretched_z(z, dz, dz_max=dz_max, &
75                     dz_stretch_factor=dz_stretch_factor,                   &
76                     dz_stretch_level=dz_stretch_level,                     &
77                     dz_stretch_level_start=dz_stretch_level_start,         &
78                     dz_stretch_level_end=dz_stretch_level_end,             &
79                     dz_stretch_factor_array=dz_stretch_factor_array)
80
81    ! Assert, that the total distance covered by the stretched region
82    ! matches the therotetial distance, i.e. the sum over the finite
83    ! exponential series
84    !
85    !          Sum_{i=0}^n( dz[i] ) = dz[0] * Sum_{i=0}^n( f^i )
86    !                               = dz[0] * (1 - f^(i+1)) / (1-f)
87    !
88    ! with f being the stretch factor.
89    res = res .AND. &
90          assert_equal( (/ z(UBOUND(z, 1)) - z(1)              /),             &
91                        (/ (1.0_dp - dz_stretch_factor**(k+1)) /               &
92                           (1.0_dp - dz_stretch_factor)        /),             &
93                        'length of stretched grid' )
94
95    CALL end_test(title, res)
96
97 END PROGRAM test_stretching
Note: See TracBrowser for help on using the repository browser.