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

Last change on this file since 3802 was 3785, checked in by eckhard, 5 years ago

inifor: Removed unused variables, improved coding style

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