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

Last change on this file since 2726 was 2718, checked in by maronga, 6 years ago

deleting of deprecated files; headers updated where needed

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