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

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

inifor: Prefixed all INIFOR modules with inifor_ and removed unused variables

  • Property svn:keywords set to Id
File size: 3.8 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 3618 2018-12-10 13:25:22Z eckhard $
28! Prefixed all INIFOR modules with inifor_
29!
30!
31! 3183 2018-07-27 14:25:55Z suehring
32! Updated test for new PALM grid strechting
33!
34!
35! 3182 2018-07-27 13:36:03Z suehring
36! Initial revision
37!
38!
39!
40! Authors:
41! --------
42! @author Eckhard Kadasch
43!
44! Description:
45! ------------
46!> This program tests the boundary grid mode of INIFOR's init_grid_definition()
47!> routine.
48!------------------------------------------------------------------------------!
49 PROGRAM test_boundaries
50
51    USE inifor_grid,                                                           &
52        ONLY  :  init_grid_definition
53    USE inifor_types,                                                          &
54        ONLY :  grid_definition
55    USE test_utils
56   
57    IMPLICIT NONE
58
59    CHARACTER(LEN=*), PARAMETER     ::  title = 'boundary initialization'
60    CHARACTER(LEN=20), DIMENSION(2) ::  kind_list = (/ 'boundary', 'boundary' /)
61    LOGICAL                         ::  res
62
63    INTEGER                         ::  i, nx, ny, nz
64    TYPE(grid_definition)           ::  boundary_grid
65
66    REAL ::  dx, dy, dz, lx, ly, lz, x(2), y(10)
67    REAL, TARGET :: z(10)
68
69    CALL begin_test(title, res)
70
71    ! Arange
72    dx = 1e-3
73    dy = 1.0
74    dz = 10.
75    nx = 9
76    ny = 9
77    nz = 9
78    lx = 1.0
79    ly = 1e1
80    lz = 1e2
81    x =   (/ -0.5*dx, lx + 0.5*dx /)
82    y = ( (/0.0, 1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, 8.0, 9.0/) + 0.5 )
83    z = ( (/0.0, 1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, 8.0, 9.0/) + 0.5 ) * 10
84
85    DO i = 1, SIZE(kind_list)
86   
87       ! Act
88       CALL init_grid_definition(                                              &
89          kind = kind_list(i), grid = boundary_grid,                           &
90          xmin = x(i), xmax = x(i),                                            &
91          ymin =  0.5 * dy, ymax = ly - 0.5 * dy,                              &
92          x0 = 0.0, y0 = 0.0, z0 = 0.0,                                        &
93          nx = 0, ny = ny, nz = nz, z = z)
94         
95   
96       ! Assert
97       ! asserting that grid % x has exactly two entries and that they match
98       ! expected coordinates
99       res = res .AND. assert_equal(boundary_grid % x, (/ x(i) /), 'x coordinates')
100
101       ! asserting that grid % y and % z have expected ranges and coordinates
102       res = res .AND. assert_equal( boundary_grid % y, y, 'y coordinates')
103       res = res .AND. assert_equal( boundary_grid % z, z, 'z coordinates')
104   
105       CALL fini_grid_definition(boundary_grid)
106    END DO
107
108    CALL end_test(title, res)
109
110 CONTAINS
111
112 SUBROUTINE fini_grid_definition(grid)
113    TYPE(grid_definition), INTENT(INOUT) ::  grid
114
115    DEALLOCATE( grid % x, grid % y )
116    DEALLOCATE( grid % kk )
117    DEALLOCATE( grid % w_verti )
118
119 END SUBROUTINE fini_grid_definition
120
121 END PROGRAM test_boundaries
Note: See TracBrowser for help on using the repository browser.