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

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

inifor: Removed unused variables, improved coding style

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