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

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

last commit documented

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!
24!
25! Former revisions:
26! -----------------
27! $Id$
28! Initial revision
29!
30!
31!
32!
33!
34! Authors:
35! --------
36! @author Eckhard Kadasch
37!
38! Description:
39! ------------
40!> This program tests INIFOR's implementation of PALM's grid stretching.
41!>
42!------------------------------------------------------------------------------!
43 PROGRAM test_stretching
44
45    USE defs, &
46        ONLY :  dp
47
48    USE grid, &
49        ONLY :  stretched_z
50
51    USE test_utils
52   
53    IMPLICIT NONE
54
55    CHARACTER(LEN=*), PARAMETER ::  title = "stretched grid"
56    LOGICAL                     ::  res
57
58    INTEGER, PARAMETER ::  nz = 9
59    INTEGER            ::  k  = nz - 2
60
61    REAL(dp) ::  z(1:nz)
62    REAL(dp) ::  dz(10)            = -1.0_dp
63    REAL(dp) ::  dz_max            = 1000.0_dp
64    REAL(dp) ::  dz_stretch_factor = 1.08_dp
65    REAL(dp) ::  dz_stretch_level  = 2.0_dp
66    REAL(dp) ::  dz_stretch_level_start(9) = -9999999.9_dp
67    REAL(dp) ::  dz_stretch_level_end(9) = 9999999.9_dp
68    REAL(dp) ::  dz_stretch_factor_array(9) = 1.08_dp
69
70    CALL begin_test(title, res)
71
72    ! Arange
73    z(:)   = 0.0_dp
74    dz(1)  = 1.0_dp
75
76    ! Act
77    CALL stretched_z(z, dz, dz_max=dz_max, &
78                     dz_stretch_factor=dz_stretch_factor,                   &
79                     dz_stretch_level=dz_stretch_level,                     &
80                     dz_stretch_level_start=dz_stretch_level_start,         &
81                     dz_stretch_level_end=dz_stretch_level_end,             &
82                     dz_stretch_factor_array=dz_stretch_factor_array)
83
84    ! Assert, that the total distance covered by the stretched region
85    ! matches the therotetial distance, i.e. the sum over the finite
86    ! exponential series
87    !
88    !          Sum_{i=0}^n( dz[i] ) = dz[0] * Sum_{i=0}^n( f^i )
89    !                               = dz[0] * (1 - f^(i+1)) / (1-f)
90    !
91    ! with f being the stretch factor.
92    res = res .AND. &
93          assert_equal( (/ z(UBOUND(z, 1)) - z(1)              /),             &
94                        (/ (1.0_dp - dz_stretch_factor**(k+1)) /               &
95                           (1.0_dp - dz_stretch_factor)        /),             &
96                        'length of stretched grid' )
97
98    CALL end_test(title, res)
99
100 END PROGRAM test_stretching
Note: See TracBrowser for help on using the repository browser.