source: palm/trunk/UTIL/inifor/tests/test-transform.f90 @ 3159

Last change on this file since 3159 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.1 KB
Line 
1!> @file tests/test-transform.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-transform.f90 2718 2018-01-02 08:49:38Z sward $
28! Initial revision
29!
30!
31!
32! Authors:
33! --------
34! @author Eckhard Kadasch
35!
36! Description:
37! ------------
38!> This program tests INIFOR's rotated-pole coordinate transforms.
39!------------------------------------------------------------------------------!
40 PROGRAM test_transform
41
42    USE defs, ONLY :  TO_RADIANS, TO_DEGREES
43    USE grid, ONLY :  grid_definition, init_grid_definition
44    USE transform, ONLY :  phi2phirot, rla2rlarot, phirot2phi, rlarot2rla
45    USE test_utils
46   
47    IMPLICIT NONE
48
49    CHARACTER(LEN=30) ::  title
50    LOGICAL           ::  res
51
52    REAL, PARAMETER ::  lx = 100., ly = 200., lz = 300.
53
54    ! Angels in degrees
55    REAL ::  phi, lambda, phi_c, lambda_c, phi2, lambda2, phi_n, lambda_n
56
57    title = "rotation north-east"
58    CALL begin_test(title, res)
59    ! Arange
60    phi    = 52.5166670000000000
61    lambda = 13.3833330000000000
62
63    phi_n    =   40.
64    lambda_n = -170.
65
66    ! Act
67    phi_c     = phi2phirot(phi,   lambda, phi_n, lambda_n)
68    lambda_c  = rla2rlarot(phi,   lambda, phi_n, lambda_n, 0.)
69
70    phi2      = phirot2phi(phi_c, lambda_c, phi_n, lambda_n, 0.)
71    lambda2   = rlarot2rla(phi_c, lambda_c, phi_n, lambda_n, 0.)
72
73    ! Assert
74    res = assert_equal( (/phi, lambda/), (/phi2, lambda2/),  "rotated grid transformations" )
75    PRINT *, " Angles before transformation:  ", phi, lambda
76    PRINT *, " and after back transformation: ", phi2, lambda2
77
78    CALL end_test(title, res)
79
80    title = "rotation south-west"
81    CALL begin_test(title, res)
82    ! Arange
83    phi    = 49.
84    lambda =  9.
85
86    phi_n    =   40.
87    lambda_n = -170.
88
89    ! Act
90    phi_c     = phi2phirot(phi,   lambda, phi_n, lambda_n)
91    lambda_c  = rla2rlarot(phi,   lambda, phi_n, lambda_n, 0.)
92
93    phi2      = phirot2phi(phi_c, lambda_c, phi_n, lambda_n, 0.)
94    lambda2   = rlarot2rla(phi_c, lambda_c, phi_n, lambda_n, 0.)
95
96    ! Assert
97    res = assert_equal( (/phi, lambda/), (/phi2, lambda2/),  "rotated grid transformations" )
98    PRINT *, " Angles before transformation:  ", phi, lambda
99    PRINT *, " and after back transformation: ", phi2, lambda2
100
101    CALL end_test(title, res)
102 END PROGRAM test_transform
Note: See TracBrowser for help on using the repository browser.