/[MITgcm]/MITgcm/model/src/rotate_spherical_polar_grid.F
ViewVC logotype

Contents of /MITgcm/model/src/rotate_spherical_polar_grid.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.2 - (show annotations) (download)
Fri Feb 8 13:01:25 2008 UTC (16 years, 2 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59o, checkpoint59n, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.1: +80 -6 lines
add the computation of the cos/sin(angle between model north and
geographical north). I put the new routine into
rotate_spherical_polar_grid.F, and so far the only place where it is
called is from ini_spherical_polar_grid.F. But I guess it could also
be called elsewhere (whenever AngleCosN and AngleSinN are not read or
incorrect[=0]).

1 C $Header: /u/gcmpack/MITgcm/model/src/rotate_spherical_polar_grid.F,v 1.1 2008/02/05 13:32:49 mlosch Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: ROTATE_SPHERICAL_POLAR_GRID
8 C !INTERFACE:
9 SUBROUTINE ROTATE_SPHERICAL_POLAR_GRID(
10 U X, Y,
11 I myThid )
12 C !DESCRIPTION: \bv
13 C /===================================================================\
14 C | SUBROUTINE ROTATE_SPHERICAL_POLAR_GRID |
15 C | o rotate the model coordinates on the input arrays to |
16 C | geographical coordinates |
17 C | o this is useful when a rotated spherical grid is used, |
18 C | e.g., in order to avoid the pole singularity. |
19 C | The three Euler angles PhiEuler, ThetaEuler, and PsiEuler |
20 C | define the rotation about the original z-axis (of an sphere |
21 C | centered cartesian grid), the new x-axis, and the new z-axis, |
22 C | respectively. |
23 C | The input coordinates X, Y are assumed to be the model coordinates|
24 C | on a rotated grid defined by the Euler angles. In this S/R they |
25 C | are rotated *BACK* to the geographical coordinate; that is why |
26 C | all rotation matrices are the inverses of the original matrices. |
27 C | On exit X and Y are the geographical coordinates, that are |
28 C | used to compute the Coriolis parameter and also to interpolate |
29 C | forcing fields to as in pkg/exf/exf_interf.F |
30 C | Naturally, this feature does not work with all packages, so the |
31 C | some combinations are prohibited in config_summary (flt, |
32 C | flt_zonal, ecco, profiles), because there the coordinates are |
33 C | assumed to be regular spherical grid coordinates. |
34 C \===================================================================/
35 C \ev
36
37 C !USES:
38 IMPLICIT NONE
39 C === Global variables ===
40 #include "SIZE.h"
41 #include "EEPARAMS.h"
42 #include "PARAMS.h"
43
44 C !INPUT/OUTPUT PARAMETERS:
45 C == Routine arguments ==
46 C myThid - Number of this instance of ROTATECARTESIAN_GRID
47 INTEGER myThid
48 C X, Y - on entry: model coordinate location
49 C - on exit: geographical coordinate location
50 _RS X(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
51 _RS Y(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
52 CEndOfInterface
53
54 C !LOCAL VARIABLES:
55 C == Local variables ==
56 C xLoc, yLoc - local copies of X, Y
57 C bi,bj - Loop counters
58 C I, J
59 INTEGER bi, bj
60 INTEGER I, J, iA, jA, kA
61 C Euler angles in radians
62 _RL phiRad, thetaRad, psiRad
63 C inverted rotation matrix
64 _RL Ainv(3,3), Binv(3,3), Cinv(3,3), Dinv(3,3), CB(3,3)
65 C cartesian coordinates
66 _RL XYZgeo(3), XYZrot(3)
67 C some auxilliary variables
68 _RL hypotxy
69 CEOP
70
71 C convert to radians
72 phiRad = phiEuler *deg2rad
73 thetaRad = thetaEuler*deg2rad
74 psiRad = psiEuler *deg2rad
75
76 C create inverse of full rotation matrix
77 Dinv(1,1) = COS(phiRad)
78 Dinv(1,2) = -SIN(phiRad)
79 Dinv(1,3) = 0. _d 0
80 C
81 Dinv(2,1) = SIN(phiRad)
82 Dinv(2,2) = COS(phiRad)
83 Dinv(2,3) = 0. _d 0
84 C
85 Dinv(3,1) = 0. _d 0
86 Dinv(3,2) = 0. _d 0
87 Dinv(3,3) = 1. _d 0
88 C
89 Cinv(1,1) = 1. _d 0
90 Cinv(1,2) = 0. _d 0
91 Cinv(1,3) = 0. _d 0
92 C
93 Cinv(2,1) = 0. _d 0
94 Cinv(2,2) = COS(thetaRad)
95 Cinv(2,3) = -SIN(thetaRad)
96 C
97 Cinv(3,1) = 0. _d 0
98 Cinv(3,2) = SIN(thetaRad)
99 Cinv(3,3) = COS(thetaRad)
100 C
101 Binv(1,1) = COS(psiRad)
102 Binv(1,2) = -SIN(psiRad)
103 Binv(1,3) = 0. _d 0
104 C
105 Binv(2,1) = SIN(psiRad)
106 Binv(2,2) = COS(psiRad)
107 Binv(2,3) = 0. _d 0
108 C
109 Binv(3,1) = 0. _d 0
110 Binv(3,2) = 0. _d 0
111 Binv(3,3) = 1. _d 0
112 C Ainv = Binv*Cinv*Dinv (matrix multiplications)
113 DO ja=1,3
114 DO ia=1,3
115 Ainv(ia,ja) = 0. _d 0
116 CB (ia,ja) = 0. _d 0
117 ENDDO
118 ENDDO
119 DO ja=1,3
120 DO ia=1,3
121 DO ka=1,3
122 CB (ia,ja) = CB (ia,ja) + Cinv(ia,ka)*Binv(ka,ja)
123 ENDDO
124 ENDDO
125 ENDDO
126 DO ja=1,3
127 DO ia=1,3
128 DO ka=1,3
129 Ainv(ia,ja) = Ainv(ia,ja) + Dinv(ia,ka)*CB(ka,ja)
130 ENDDO
131 ENDDO
132 ENDDO
133 C
134
135 C For each tile ...
136 DO bj = myByLo(myThid), myByHi(myThid)
137 DO bi = myBxLo(myThid), myBxHi(myThid)
138
139 C loop over grid points
140 DO J = 1-Oly,sNy+Oly
141 DO I = 1-Olx,sNx+Olx
142 C transform spherical coordinates with unit radius
143 C to sphere centered cartesian coordinates
144 XYZrot(1) =
145 & COS( Y(I,J,bi,bj)*deg2rad )*COS( X(I,J,bi,bj)*deg2rad )
146 XYZrot(2) =
147 & COS( Y(I,J,bi,bj)*deg2rad )*SIN( X(I,J,bi,bj)*deg2rad )
148 XYZrot(3) = SIN( Y(I,J,bi,bj)*deg2rad )
149 C rotate cartesian coordinate (matrix multiplication)
150 DO iA=1,3
151 XYZgeo(iA) = 0. _d 0
152 ENDDO
153 DO iA=1,3
154 DO jA=1,3
155 XYZgeo(iA) = XYZgeo(iA) + Ainv(iA,jA)*XYZrot(jA)
156 ENDDO
157 ENDDO
158 C tranform cartesian coordinates back to spherical coordinates
159 hypotxy = SQRT( ABS(XYZgeo(1))*ABS(XYZgeo(1))
160 & + ABS(XYZgeo(2))*ABS(XYZgeo(2)) )
161 IF(XYZgeo(1) .EQ. 0. _d 0 .AND. XYZgeo(2) .EQ. 0. _d 0)THEN
162 C happens exactly at the poles
163 X(I,J,bi,bj) = 0. _d 0
164 ELSE
165 X(I,J,bi,bj) = ATAN2(XYZgeo(2),XYZgeo(1))/deg2rad
166 IF ( X(I,J,bi,bj) .LT. 0. _d 0 )
167 & X(I,J,bi,bj) = X(I,J,bi,bj) + 360. _d 0
168 ENDIF
169 IF(hypotxy .EQ. 0. _d 0 .AND. XYZgeo(3) .EQ. 0. _d 0)THEN
170 C this can not happen for a sphere with unit radius
171 Y(I,J,bi,bj) = 0. _d 0
172 ELSE
173 Y(I,J,bi,bj) = ATAN2(XYZgeo(3),hypotxy)/deg2rad
174 ENDIF
175 ENDDO
176 ENDDO
177 C bi,bj-loops
178 ENDDO
179 ENDDO
180
181 RETURN
182 END
183
184 CBOP
185 C !ROUTINE: ROTATE_ANGLES
186 C !INTERFACE:
187 SUBROUTINE CALC_ANGLES(
188 I myThid )
189 C !DESCRIPTION: \bv
190 C /===================================================================\
191 C | SUBROUTINE CALC_ANGLES |
192 C | o calculate the angle between geographical north and model grid |
193 C | north, assuming that yG holds the geographical coordinates |
194 C \===================================================================/
195 C \ev
196
197 C !USES:
198 IMPLICIT NONE
199 C === Global variables ===
200 #include "SIZE.h"
201 #include "EEPARAMS.h"
202 #include "PARAMS.h"
203 #include "GRID.h"
204
205 C !INPUT/OUTPUT PARAMETERS:
206 C == Routine arguments ==
207 C myThid - Number of this instance of ROTATECARTESIAN_GRID
208 INTEGER myThid
209 CEndOfInterface
210
211 C !LOCAL VARIABLES:
212 C == Local variables ==
213 C xLoc, yLoc - local copies of X, Y
214 C bi,bj - Loop counters
215 C I, J
216 INTEGER bi, bj
217 INTEGER I, J
218 C pseudo velocities
219 _RS uPseudo(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
220 _RS vPseudo(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
221 _RS uC, vC, uNorm
222 CEOP
223
224
225 C For each tile ...
226 DO bj = myByLo(myThid), myByHi(myThid)
227 DO bi = myBxLo(myThid), myBxHi(myThid)
228
229 C compute pseudo velocities from stream function psi = -yG*deg2rad,
230 C that is, zonal flow
231 DO J = 1-Oly,sNy+Oly-1
232 DO I = 1-Olx,sNx+Olx
233 IF ( _dyG(I,J,bi,bj) .GT. 0 ) uPseudo(I,J) =
234 & - ( yG(I,J,bi,bj) - yG(I,J+1,bi,bj) )*deg2rad
235 & / _dyG(I,J,bi,bj)
236 ENDDO
237 ENDDO
238 DO J = 1-Oly,sNy+Oly
239 DO I = 1-Olx,sNx+Olx-1
240 IF ( _dxG(I,J,bi,bj) .GT. 0 ) vPseudo(I,J) =
241 & + ( yG(I,J,bi,bj) - yG(I+1,J,bi,bj) )*deg2rad
242 & / _dxG(I,J,bi,bj)
243 ENDDO
244 ENDDO
245 DO J = 1-Oly,sNy+Oly-1
246 DO I = 1-Olx,sNx+Olx-1
247 uC = 0.5*(uPseudo(I,J) + uPseudo(I+1,J))
248 vC = 0.5*(vPseudo(I,J) + vPseudo(I,J+1))
249 uNorm = SQRT(uC*uC+vC*vC)
250 IF ( uNorm .NE. 0. _d 0 ) uNorm = 1./uNorm
251 angleCosC(I,J,bi,bj) = uC*uNorm
252 angleSinC(I,J,bi,bj) = -vC*uNorm
253 ENDDO
254 ENDDO
255 C bi,bj-loops
256 ENDDO
257 ENDDO
258
259 RETURN
260 END

  ViewVC Help
Powered by ViewVC 1.1.22