source: palm/trunk/UTIL/inifor/tests/test-interpolation.f90 @ 3198

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

last commit documented

  • Property svn:keywords set to Id
File size: 9.4 KB
Line 
1!> @file tests/test-interpolation.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-interpolation.f90 3183 2018-07-27 14:25:55Z sward $
28! Updated test for new grid_definition
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 INIFOR's horizontal interpolation.
43!------------------------------------------------------------------------------!
44 PROGRAM test_interpolation
45
46    USE grid, &
47        ONLY:  grid_definition, init_grid_definition, TO_RADIANS, TO_DEGREES, &
48               linspace, hhl
49    USE transform, &
50        ONLY:  find_horizontal_neighbours, compute_horizontal_interp_weights
51    USE test_utils
52   
53    IMPLICIT NONE
54
55!
56!------------------------------------------------------------------------------
57!- Test 1: Find neighbours
58!------------------------------------------------------------------------------
59    CHARACTER(LEN=30) ::  title = "find neighbours"
60    LOGICAL           ::  res
61
62    TYPE(grid_definition) ::  palm_grid, cosmo_grid
63    INTEGER               ::  i, j, ii_ref(0:1, 0:1, 4), jj_ref(0:1, 0:1, 4)
64    INTEGER, PARAMETER    ::  nlon=3, nlat=3, nlev=2
65    REAL                  ::  w_ref(4), lat(0:2), lon(0:2)
66
67    title = "find neighbours"
68    CALL begin_test(title, res)
69
70    ! Arange.
71    ! Make a COSMO-DE grid with just two horizotal cells/three h. points
72    PRINT *, "INIT GRID"
73
74    ! Allocate grid.hhl for use in init_grid_definition. In INIFOR, this is done
75    ! in get_netcdf_variable_2d. In this test, grid.hhl is not used and only
76    ! defined manually because it is used in init_grid_definition.
77    ALLOCATE (hhl (nlon, nlat, nlev) )
78    hhl(:,:,:) = 0.0
79    CALL init_grid_definition('cosmo-de', grid = cosmo_grid,                   &
80                              xmin = -5.0 * TO_RADIANS, xmax = 5.5 * TO_RADIANS, &
81                              ymin = -5.0 * TO_RADIANS, ymax = 6.5 * TO_RADIANS, &
82                              x0 = 0.0, y0 = 0.0, z0 = 0.0,                    &
83                              nx = nlon-1, ny = nlat-1, nz = nlev-1)
84
85    PRINT *, "GRID DONE"
86    PRINT *, "COSMO lats: ", cosmo_grid % lat * TO_DEGREES
87    PRINT *, "COSMO lons: ", cosmo_grid % lon * TO_DEGREES
88   
89    res = assert_equal( (/cosmo_grid%lat(0), cosmo_grid % lon(0),              &
90                          cosmo_grid%lat(2), cosmo_grid % lon(2),              &
91                          (cosmo_grid%lon(1) - cosmo_grid%lon(0))*TO_DEGREES,  &
92                          (cosmo_grid%lat(1) - cosmo_grid%lat(0))*TO_DEGREES/),&
93                        (/-5.0 * TO_RADIANS, -5.0 * TO_RADIANS,                &
94                           6.5 * TO_RADIANS,  5.5 * TO_RADIANS,                &
95                           5.25, 5.75 /),    &
96                        "COSMO grid coordinates" )
97    ! Define a PALM-4U grid with only one cell, i.e. four points in the
98    ! horizontal plane. The points are located at the centres of
99    ! the COSMO-DE cells.
100    CALL init_grid_definition('palm intermediate', grid = palm_grid,           &
101                              xmin = 0.0, xmax = 1.0,                          &
102                              ymin = 0.0, ymax = 1.0,                          &
103                              x0 = 0.0, y0 = 0.0, z0 = 0.0,                    &
104                              nx = 1, ny = 1, nz = 1)
105
106    palm_grid % clon(0,0) = 0.5 * cosmo_grid % lon(0)
107    palm_grid % clat(0,0) = 0.5 * cosmo_grid % lat(0)
108   
109    palm_grid % clon(0,1) = 0.5 * cosmo_grid % lon(0)
110    palm_grid % clat(0,1) = 0.5 * cosmo_grid % lat(2)
111
112    palm_grid % clon(1,1) = 0.5 * cosmo_grid % lon(2)
113    palm_grid % clat(1,1) = 0.5 * cosmo_grid % lat(2)
114
115    palm_grid % clon(1,0) = 0.5 * cosmo_grid % lon(2)
116    palm_grid % clat(1,0) = 0.5 * cosmo_grid % lat(0)
117
118    ii_ref(0,0,:) = (/0, 0, 1, 1/)
119    jj_ref(0,0,:) = (/0, 1, 1, 0/)
120
121    ii_ref(0,1,:) = (/0, 0, 1, 1/)
122    jj_ref(0,1,:) = (/1, 2, 2, 1/)
123   
124    ii_ref(1,1,:) = (/1, 1, 2, 2/)
125    jj_ref(1,1,:) = (/1, 2, 2, 1/)
126
127    ii_ref(1,0,:) = (/1, 1, 2, 2/)
128    jj_ref(1,0,:) = (/0, 1, 1, 0/)
129
130    ! Act
131    CALL find_horizontal_neighbours(cosmo_grid % lat, cosmo_grid % lon,        &
132                                    palm_grid % clat, palm_grid % clon,        &
133                                    palm_grid % ii, palm_grid % jj)
134
135    ! Assert
136    DO j = 0, 1
137    DO i = 0, 1
138       res = res .AND. ALL(palm_grid%ii(i,j,:) == ii_ref(i,j,:))
139       PRINT *, "ii     : ", palm_grid%ii(i,j,:)
140       PRINT *, "ii_ref : ", ii_ref(i,j,:), " indices match? ", res
141       res = res .AND. ALL(palm_grid%jj(i,j,:) == jj_ref(i,j,:))
142       PRINT *, "jj     : ", palm_grid%jj(i,j,:)
143       PRINT *, "jj_ref : ", jj_ref(i,j,:), " indices match? ", res
144    END DO
145    END DO
146
147    CALL end_test(title, res)
148   
149
150!
151!------------------------------------------------------------------------------
152!- Test 2: Compute weights for linear interpolation
153!------------------------------------------------------------------------------
154    title = "interpolation weights"
155    CALL begin_test(title, res)
156
157    ! Arange
158    ! defining some shorthands
159    lon(:) = cosmo_grid % lon(:)
160    lat(:) = cosmo_grid % lat(:)
161
162    ! set up PALM-4U points at 1/4 and 1/3 of the COSMO grid widths
163    palm_grid % clon(0,0) = -0.25  * (lon(1) - lon(0)) + lon(1)
164    palm_grid % clat(0,0) = -2./3. * (lat(1) - lat(0)) + lat(1)
165   
166    palm_grid % clon(0,1) = -2./3. * (lon(1) - lon(0)) + lon(1)
167    palm_grid % clat(0,1) = +0.25  * (lat(2) - lat(1)) + lat(1)
168
169    palm_grid % clon(1,1) = +0.25  * (lon(2) - lon(1)) + lon(1)
170    palm_grid % clat(1,1) = +2./3. * (lat(2) - lat(1)) + lat(1)
171
172    palm_grid % clon(1,0) = +2./3. * (lon(2) - lon(1)) + lon(1)
173    palm_grid % clat(1,0) = -0.25  * (lat(1) - lat(0)) + lat(1)
174
175    DO j = 0, 1
176    DO i = 0, 1
177       PRINT *, "PALM lon, lat: ", palm_grid % clon(i,j) * TO_DEGREES, palm_grid % clat(i,j)*TO_DEGREES
178    END DO
179    END DO
180
181    ! Act
182    CALL find_horizontal_neighbours(cosmo_grid % lat, cosmo_grid % lon,        &
183                                    palm_grid % clat, palm_grid % clon,        &
184                                    palm_grid % ii, palm_grid % jj)
185
186    CALL compute_horizontal_interp_weights(cosmo_grid % lat, cosmo_grid % lon, &
187                                           palm_grid % clat, palm_grid % clon, &
188                                           palm_grid % ii, palm_grid % jj,     &
189                                           palm_grid % w_horiz)
190
191    ! Assert
192    ! asserting that neighbours are still correct
193    DO j = 0, 1
194    DO i = 0, 1
195       res = res .AND. ALL(palm_grid%ii(i,j,:) == ii_ref(i,j,:))
196       PRINT *, "ii     : ", palm_grid%ii(i,j,:)
197       PRINT *, "ii_ref : ", ii_ref(i,j,:), " indices match? ", res
198       res = res .AND. ALL(palm_grid%jj(i,j,:) == jj_ref(i,j,:))
199       PRINT *, "jj     : ", palm_grid%jj(i,j,:)
200       PRINT *, "jj_ref : ", jj_ref(i,j,:), " indices match? ", res
201    END DO
202    END DO
203
204    ! asserting that all four weights equal, 0.5, 0.25, 1./6., and 1./12., resp.
205    w_ref = (/1./6., 1./12., 0.25, 0.5/)
206    res = res .AND. assert_equal(palm_grid % w_horiz(0, 0, :), w_ref(:), "weights at (0,0)")
207    !res = res .AND. palm_grid % w_horiz(0, 0, 1) == w_ref(1)
208    !res = res .AND. palm_grid % w_horiz(0, 0, 2) == w_ref(2)
209    !res = res .AND. palm_grid % w_horiz(0, 0, 3) == w_ref(3)
210    !res = res .AND. palm_grid % w_horiz(0, 0, 4) == w_ref(4)
211
212    w_ref = (/0.5, 1./6., 1./12., 0.25/)
213    res = res .AND. assert_equal(palm_grid % w_horiz(0, 1, :), w_ref(:), "weights at (0,1)")
214    !res = res .AND. palm_grid % w_horiz(0, 1, 1) == w_ref(4)
215    !res = res .AND. palm_grid % w_horiz(0, 1, 2) == w_ref(1)
216    !res = res .AND. palm_grid % w_horiz(0, 1, 3) == w_ref(2)
217    !res = res .AND. palm_grid % w_horiz(0, 1, 4) == w_ref(3)
218
219    w_ref = (/0.25, 0.5, 1./6., 1./12./)
220    res = res .AND. assert_equal(palm_grid % w_horiz(1, 1, :), w_ref(:), "weights at (1,1)")
221    !res = res .AND. palm_grid % w_horiz(1, 1, 1) == w_ref(3)
222    !res = res .AND. palm_grid % w_horiz(1, 1, 2) == w_ref(4)
223    !res = res .AND. palm_grid % w_horiz(1, 1, 3) == w_ref(1)
224    !res = res .AND. palm_grid % w_horiz(1, 1, 4) == w_ref(2)
225
226    w_ref = (/1./12., 0.25, 0.5, 1./6./)
227    res = res .AND. assert_equal(palm_grid % w_horiz(1, 0, :), w_ref(:), "weights at (1,0)")
228    !res = res .AND. palm_grid % w_horiz(1, 0, 1) == w_ref(2)
229    !res = res .AND. palm_grid % w_horiz(1, 0, 2) == w_ref(3)
230    !res = res .AND. palm_grid % w_horiz(1, 0, 3) == w_ref(4)
231    !res = res .AND. palm_grid % w_horiz(1, 0, 4) == w_ref(1)
232
233    CALL end_test(title, res)
234
235 END PROGRAM test_interpolation
Note: See TracBrowser for help on using the repository browser.