source: palm/trunk/UTIL/inifor/tests/test-grid.f90 @ 3395

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

last commit documented

  • Property svn:keywords set to Id
File size: 3.2 KB
Line 
1!> @file tests/test-grid.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: test-grid.f90 3183 2018-07-27 14:25:55Z eckhard $
28! Updated test for new PALM grid strechting
29!
30!
31! 3182 2018-07-27 13:36:03Z suehring
32! Initial revision
33!
34!
35!
36! Authors:
37! --------
38! @author Eckhard Kadasch
39!
40! Description:
41! ------------
42!> This program tests the PALM grid mode of INIFOR's init_grid_definition()
43!> routine.
44!------------------------------------------------------------------------------!
45 PROGRAM test_grid
46
47    USE grid, ONLY :  grid_definition, init_grid_definition, dx, dy, dz
48    USE test_utils
49   
50    IMPLICIT NONE
51
52    CHARACTER(LEN=*), PARAMETER ::  title = "grid initialization"
53    LOGICAL                     ::  res
54
55    TYPE(grid_definition)   ::  mygrid
56    INTEGER                 ::  i
57    INTEGER, PARAMETER      ::  nx = 9,   ny = 19,   nz = 29
58    REAL, PARAMETER         ::  lx = 100., ly = 200., lz = 300.
59    REAL, DIMENSION(0:nx)   ::  x, xu
60    REAL, DIMENSION(0:ny)   ::  y, yv
61    REAL, DIMENSION(1:nz)   ::  z
62    REAL, DIMENSION(1:nz-1) ::  zw
63
64    CALL begin_test(title, res)
65
66    ! Arange
67    dx = lx / (nx + 1)
68    DO i = 0, nx
69       xu(i) = real(i) / (nx+1) * lx
70       x(i)  = 0.5*dx + xu(i)
71    END DO
72
73    dy = ly / (ny + 1)
74    DO i = 0, ny
75       yv(i) = real(i) / (ny+1) * ly
76       y(i)  = 0.5*dy + yv(i)
77    END DO
78
79    dz(:) = lz / (nz + 1)
80    DO i = 1, nz
81       IF (i < nz)  zw(i) = real(i) / (nz+1) * lz
82       z(i) = 0.5*dz(1) + zw(i)
83    END DO
84
85    ! Act
86    CALL init_grid_definition('palm', grid = mygrid,                           &
87                              xmin = 0., xmax = lx,                            &
88                              ymin = 0., ymax = ly,                            &
89                              x0 = 0.0, y0 = 0.0, z0 = 0.0,                    &
90                              nx = nx, ny = ny, nz = nz,                       &
91                              z = z, zw = zw)
92
93    ! Assert coordinates match
94    res = res .AND. assert_equal(x,      mygrid%x,  "x" )
95    res = res .AND. assert_equal(xu(1:), mygrid%xu, "xu")
96    res = res .AND. assert_equal(y,      mygrid%y,  "y" )
97    res = res .AND. assert_equal(yv(1:), mygrid%yv, "yv")
98    res = res .AND. assert_equal(z,      mygrid%z,  "z" )
99    res = res .AND. assert_equal(zw(1:), mygrid%zw, "zw")
100
101    CALL end_test(title, res)
102
103 END PROGRAM test_grid
Note: See TracBrowser for help on using the repository browser.