source: palm/trunk/UTIL/inifor/tests/test-boundaries.f90 @ 3396

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

last commit documented

  • Property svn:keywords set to Id
File size: 3.5 KB
Line 
1!> @file tests/test-boundaries.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-boundaries.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 boundary grid mode of INIFOR's init_grid_definition()
43!> routine.
44!------------------------------------------------------------------------------!
45 PROGRAM test_boundaries
46
47    USE grid, ONLY  :  init_grid_definition
48    USE types, ONLY :  grid_definition
49    USE test_utils
50   
51    IMPLICIT NONE
52
53    CHARACTER(LEN=*), PARAMETER     ::  title = 'boundary initialization'
54    CHARACTER(LEN=20), DIMENSION(2) ::  kind_list = (/ 'boundary', 'boundary' /)
55    LOGICAL                         ::  res
56
57    INTEGER                         ::  i, nx, ny, nz
58    TYPE(grid_definition)           ::  boundary_grid
59
60    REAL ::  dx, dy, dz, lx, ly, lz, x(2), y(10)
61    REAL, TARGET :: z(10)
62
63    CALL begin_test(title, res)
64
65    ! Arange
66    dx = 1e-3
67    dy = 1.0
68    dz = 10.
69    nx = 9
70    ny = 9
71    nz = 9
72    lx = 1.0
73    ly = 1e1
74    lz = 1e2
75    x =   (/ -0.5*dx, lx + 0.5*dx /)
76    y = ( (/0.0, 1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, 8.0, 9.0/) + 0.5 )
77    z = ( (/0.0, 1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, 8.0, 9.0/) + 0.5 ) * 10
78
79    DO i = 1, SIZE(kind_list)
80   
81       ! Act
82       CALL init_grid_definition(                                              &
83          kind = kind_list(i), grid = boundary_grid,                           &
84          xmin = x(i), xmax = x(i),                                            &
85          ymin =  0.5 * dy, ymax = ly - 0.5 * dy,                              &
86          x0 = 0.0, y0 = 0.0, z0 = 0.0,                                        &
87          nx = 0, ny = ny, nz = nz, z = z)
88         
89   
90       ! Assert
91       ! asserting that grid % x has exactly two entries and that they match
92       ! expected coordinates
93       res = res .AND. assert_equal(boundary_grid % x, (/ x(i) /), 'x coordinates')
94
95       ! asserting that grid % y and % z have expected ranges and coordinates
96       res = res .AND. assert_equal( boundary_grid % y, y, 'y coordinates')
97       res = res .AND. assert_equal( boundary_grid % z, z, 'z coordinates')
98   
99       CALL fini_grid_definition(boundary_grid)
100    END DO
101
102    CALL end_test(title, res)
103
104 CONTAINS
105
106 SUBROUTINE fini_grid_definition(grid)
107    TYPE(grid_definition), INTENT(INOUT) ::  grid
108
109    DEALLOCATE( grid % x, grid % y )
110    DEALLOCATE( grid % kk )
111    DEALLOCATE( grid % w_verti )
112
113 END SUBROUTINE fini_grid_definition
114
115 END PROGRAM test_boundaries
Note: See TracBrowser for help on using the repository browser.