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

Last change on this file since 2796 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.6 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 2718 2018-01-02 08:49:38Z suehring $
28! Initial revision
29!
30!
31!
32! Authors:
33! --------
34! @author Eckhard Kadasch
35!
36! Description:
37! ------------
38!> This program tests the boundary grid mode of INIFOR's init_grid_definition()
39!> routine.
40!------------------------------------------------------------------------------!
41 PROGRAM test_boundaries
42
43    USE grid, ONLY  :  init_grid_definition
44    USE types, ONLY :  grid_definition
45    USE test_utils
46   
47    IMPLICIT NONE
48
49    CHARACTER(LEN=*), PARAMETER     ::  title = 'boundary initialization'
50    CHARACTER(LEN=20), DIMENSION(2) ::  kind_list = (/ 'boundary', 'boundary' /)
51    LOGICAL                         ::  res
52
53    INTEGER                         ::  i, nx, ny, nz
54    TYPE(grid_definition)           ::  boundary_grid
55
56    REAL ::  dx, dy, dz, lx, ly, lz, x(2), y(10), z(10)
57
58    CALL begin_test(title, res)
59
60    ! Arange
61    dx = 1e-3
62    dy = 1.0
63    dz = 10.
64    nx = 9
65    ny = 9
66    nz = 9
67    lx = 1.0
68    ly = 1e1
69    lz = 1e2
70    x =   (/ -0.5*dx, lx + 0.5*dx /)
71    y = ( (/0.0, 1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, 8.0, 9.0/) + 0.5 )
72    z = ( (/0.0, 1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, 8.0, 9.0/) + 0.5 ) * 10
73
74    DO i = 1, SIZE(kind_list)
75   
76       ! Act
77       CALL init_grid_definition(                                              &
78          kind = kind_list(i), grid = boundary_grid,                           &
79          xmin = x(i), xmax = x(i),                                            &
80          ymin =  0.5 * dy, ymax = ly - 0.5 * dy,                              &
81          zmin =  0.5 * dz, zmax = lz - 0.5 * dz,                              &
82          x0 = 0.0, y0 = 0.0, z0 = 0.0,                                        &
83          nx = 0, ny = ny, nz = nz,                                            &
84          dx = dx, dy = dy, dz = dz )
85   
86       ! Assert
87       ! asserting that grid % x has exactly two entries and that they match
88       ! expected coordinates
89       res = res .AND. assert_equal(boundary_grid % x, (/ x(i) /), 'x coordinates')
90
91       ! asserting that grid % y and % z have expected ranges and coordinates
92       res = res .AND. assert_equal( boundary_grid % y, y, 'y coordinates')
93       res = res .AND. assert_equal( boundary_grid % z, z, 'z coordinates')
94   
95       CALL fini_grid_definition(boundary_grid)
96    END DO
97
98    CALL end_test(title, res)
99
100 CONTAINS
101
102 SUBROUTINE fini_grid_definition(grid)
103    TYPE(grid_definition), INTENT(INOUT) ::  grid
104
105    DEALLOCATE( grid % x, grid % y, grid % z )
106    DEALLOCATE( grid % kk )
107    DEALLOCATE( grid % w_verti )
108
109 END SUBROUTINE fini_grid_definition
110
111 END PROGRAM test_boundaries
Note: See TracBrowser for help on using the repository browser.