/[MITgcm]/MITgcm/pkg/gmredi/gmredi_k3d.F
ViewVC logotype

Annotation of /MITgcm/pkg/gmredi/gmredi_k3d.F

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


Revision 1.21 - (hide annotations) (download)
Sun Feb 22 01:52:18 2015 UTC (9 years, 3 months ago) by m_bates
Branch: MAIN
CVS Tags: checkpoint65j
Changes since 1.20: +70 -16 lines
For the k3d module in gmredi: 1/ Fixed bug in velocity rotation & conversion to A grid. 2/ Fixed bug in barotropic velocity calculation. 3/ Changed a couple of logicals.

1 m_bates 1.21 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_k3d.F,v 1.20 2015/01/20 20:52:12 jmc Exp $
2 m_bates 1.1 C $Name: $
3 jmc 1.19
4 m_bates 1.1 #include "GMREDI_OPTIONS.h"
5    
6     C !ROUTINE: GMREDI_K3D
7     C !INTERFACE:
8     SUBROUTINE GMREDI_K3D(
9     I iMin, iMax, jMin, jMax,
10     I sigmaX, sigmaY, sigmaR,
11 m_bates 1.4 I bi, bj, myTime, myThid )
12 m_bates 1.1
13     C !DESCRIPTION: \bv
14     C *==========================================================*
15     C | SUBROUTINE GMREDI_K3D
16     C | o Calculates the 3D diffusivity as per Bates et al. (2013)
17     C *==========================================================*
18     C \ev
19    
20     IMPLICIT NONE
21    
22     C == Global variables ==
23     #include "SIZE.h"
24 jmc 1.19 #include "EEPARAMS.h"
25     #include "PARAMS.h"
26 m_bates 1.1 #include "GRID.h"
27     #include "DYNVARS.h"
28 jmc 1.20 #include "FFIELDS.h"
29 m_bates 1.1 #include "GMREDI.h"
30    
31     C !INPUT/OUTPUT PARAMETERS:
32     C == Routine arguments ==
33     C bi, bj :: tile indices
34     C myThid :: My Thread Id. number
35    
36     INTEGER iMin,iMax,jMin,jMax
37     _RL sigmaX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
38     _RL sigmaY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
39     _RL sigmaR(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
40     INTEGER bi, bj
41 m_bates 1.4 _RL myTime
42 m_bates 1.1 INTEGER myThid
43    
44     #ifdef GM_K3D
45    
46 m_bates 1.4 C === Functions ====
47     LOGICAL DIFFERENT_MULTIPLE
48     EXTERNAL DIFFERENT_MULTIPLE
49    
50 m_bates 1.1 C !LOCAL VARIABLES:
51     C == Local variables ==
52 m_bates 1.4 INTEGER i,j,k,kk,m
53    
54     C update_modes :: Whether to update the eigenmodes
55     LOGICAL update_modes
56    
57     C surfk :: index of the depth of the surface layer
58     C kLow_C :: Local version of the index of deepest wet grid cell on tracer grid
59     C kLow_U :: Local version of the index of deepest wet grid cell on U grid
60     C kLow_V :: Local version of the index of deepest wet grid cell on V grid
61 m_bates 1.1 INTEGER surfk(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
62     INTEGER kLow_C(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
63     INTEGER kLow_U(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
64     INTEGER kLow_V(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
65 m_bates 1.4
66     C N2loc :: local N**2
67     C slope :: local slope
68     C Req :: local equatorial deformation radius (m)
69     C deltaH :: local thickness of Eady integration (m)
70     C g_reciprho_sq :: (gravity*recip_rhoConst)**2
71     C M4loc :: local M**4
72     C maxDRhoDz :: maximum value of d(rho)/dz (derived from GM_K3D_minN2)
73     C sigx :: local d(rho)/dx
74     C sigy :: local d(rho)/dy
75     C sigz :: local d(rho)/dz
76     C hsurf :: local surface layer depth
77     C small :: a small number (to avoid floating point exceptions)
78 m_bates 1.10 _RL N2loc(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
79 m_bates 1.1 _RL slope
80 m_bates 1.10 _RL slopeC(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
81 m_bates 1.4 _RL Req
82 m_bates 1.10 _RL deltaH(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
83 m_bates 1.1 _RL g_reciprho_sq
84 m_bates 1.10 _RL M4loc(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
85 m_bates 1.13 _RL M4onN2(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
86 m_bates 1.1 _RL maxDRhoDz
87     _RL sigx, sigy, sigz
88     _RL hsurf
89     _RL small
90 m_bates 1.4
91     C dfdy :: gradient of the Coriolis paramter, df/dy, 1/(m*s)
92     C dfdx :: gradient of the Coriolis paramter, df/dx, 1/(m*s)
93 m_bates 1.6 C gradf :: gradient of the Coriolis paramter at a cell centre, 1/(m*s)
94 m_bates 1.8 C Rurms :: a local mixing length used in calculation of urms (m)
95 m_bates 1.4 C RRhines :: The Rhines scale (m)
96     C Rmix :: Mixing length
97     C N2 :: Square of the buoyancy frequency (1/s**2)
98     C N2W :: Square of the buoyancy frequency (1/s**2) averaged to west of grid cell
99     C N2S :: Square of the buoyancy frequency (1/s**2) averaged to south of grid cell
100     C N :: Buoyancy frequency, SQRT(N2)
101     C BVint :: The vertical integral of N (m/s)
102     C ubar :: Zonal velocity on a tracer point (m/s)
103     C vbar :: Meridional velocity on a tracer point (m/s)
104     C Ubaro :: Barotropic velocity (m/s)
105     _RL dfdy( 1-Olx:sNx+Olx,1-Oly:sNy+Oly)
106     _RL dfdx( 1-Olx:sNx+Olx,1-Oly:sNy+Oly)
107     _RL gradf( 1-Olx:sNx+Olx,1-Oly:sNy+Oly)
108     _RL dummy( 1-Olx:sNx+Olx,1-Oly:sNy+Oly)
109 m_bates 1.8 _RL Rurms( 1-Olx:sNx+Olx,1-Oly:sNy+Oly)
110 m_bates 1.4 _RL RRhines(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
111     _RL Rmix( 1-Olx:sNx+Olx,1-Oly:sNy+Oly)
112     _RL N2( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
113     _RL N2W( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
114     _RL N2S( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
115     _RL N( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
116     _RL BVint( 1-Olx:sNx+Olx,1-Oly:sNy+Oly)
117     _RL Ubaro( 1-Olx:sNx+Olx,1-Oly:sNy+Oly)
118 m_bates 1.21 _RL ubar( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
119    
120     _RL tmpU( 1-Olx:sNx+Olx,1-Oly:sNy+Oly )
121     _RL tmpV( 1-Olx:sNx+Olx,1-Oly:sNy+Oly )
122     _RL uFldX( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr )
123     _RL vFldY( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr )
124 m_bates 1.4
125     C Rmid :: Rossby radius (m)
126     C KPV :: Diffusivity (m**2/s)
127 m_bates 1.13 C Kdqdx :: diffusivity multiplied by zonal PV gradient
128     C Kdqdy :: diffusivity multiplied by meridional PV gradient
129 m_bates 1.4 C SlopeX :: isopycnal slope in x direction
130     C SlopeY :: isopycnal slope in y direction
131     C dSigmaDx :: sigmaX averaged onto tracer grid
132     C dSigmaDy :: sigmaY averaged onto tracer grid
133     C tfluxX :: thickness flux in x direction
134     C tfluxY :: thickness flux in y direction
135     C fCoriU :: Coriolis parameter averaged to U points
136     C fCoriV :: Coriolis parameter averaged to V points
137     C cori :: Coriolis parameter forced to be finite near the equator
138     C coriU :: As for cori, but, at U point
139     C coriV :: As for cori, but, at V point
140     C surfkz :: Depth of surface layer (in r units)
141     _RL Rmid(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
142 m_bates 1.3 _RL KPV(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
143 m_bates 1.13 _RL Kdqdy(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
144     _RL Kdqdx(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
145 m_bates 1.1 _RL SlopeX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
146     _RL SlopeY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
147     _RL dSigmaDx(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
148     _RL dSigmaDy(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
149     _RL tfluxX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
150     _RL tfluxY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
151     _RL cori(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
152     _RL coriU(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
153     _RL coriV(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
154     _RL fCoriU(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
155     _RL fCoriV(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
156     _RL surfkz(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
157 m_bates 1.4
158 m_bates 1.16 C centreX,centreY :: used for calculating averages at centre of cell
159     C numerator,denominator :: of the renormalisation factor
160     C uInt :: column integral of u velocity (sum u*dz)
161     C vInt :: column integral of v velocity (sum v*dz)
162     C KdqdxInt :: column integral of K*dqdx (sum K*dqdx*dz)
163     C KdqdyInt :: column integral of K*dqdy (sum K*dqdy*dz)
164     C uKdqdyInt :: column integral of u*K*dqdy (sum u*K*dqdy*dz)
165     C vKdqdxInt :: column integral of v*K*dqdx (sum v*K*dqdx*dz)
166     C uXiyInt :: column integral of u*Xiy (sum u*Xiy*dz)
167     C vXixInt :: column integral of v*Xix (sum v*Xix*dz)
168     C Renorm :: renormalisation factor at the centre of a cell
169     C RenormU :: renormalisation factor at the western face of a cell
170     C RenormV :: renormalisation factor at the southern face of a cell
171 m_bates 1.15 _RL centreX, centreY
172     _RL numerator, denominator
173     _RL uInt(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
174     _RL vInt(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
175     _RL KdqdxInt(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
176     _RL KdqdyInt(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
177     _RL uKdqdyInt(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
178     _RL vKdqdxInt(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
179     _RL uXiyInt(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
180     _RL vXixInt(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
181     _RL Renorm(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
182     _RL RenormU(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
183     _RL RenormV(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
184    
185 m_bates 1.4 C gradqx :: Potential vorticity gradient in x direction
186     C gradqy :: Potential vorticity gradient in y direction
187     C XimX :: Vertical integral of phi_m*K*gradqx
188     C XimY :: Vertical integral of phi_m*K*gradqy
189     C cDopp :: Quasi-Doppler shifted long Rossby wave speed (m/s)
190     C umc :: ubar-c (m/s)
191     C eady :: Eady growth rate (1/s)
192     C urms :: the rms eddy velocity (m/s)
193     C supp :: The suppression factor
194     C ustar :: The eddy induced velocity in the x direction
195     C vstar :: The eddy induced velocity in the y direction
196     C Xix :: Xi in the x direction (m/s**2)
197     C Xiy :: Xi in the y direction (m/s**2)
198 m_bates 1.1 _RL gradqx(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
199     _RL gradqy(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
200     _RL XimX(GM_K3D_NModes,1-Olx:sNx+Olx,1-Oly:sNy+Oly)
201     _RL XimY(GM_K3D_NModes,1-Olx:sNx+Olx,1-Oly:sNy+Oly)
202 m_bates 1.4 _RL cDopp(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
203 m_bates 1.1 _RL umc( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,1:Nr)
204     _RL eady( 1-Olx:sNx+Olx,1-Oly:sNy+Oly)
205     _RL urms( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,1:Nr)
206     _RL supp( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,1:Nr)
207     _RL ustar(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1:Nr)
208     _RL vstar(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1:Nr)
209     _RL Xix( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
210     _RL Xiy( 1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
211 m_bates 1.4 #ifdef GM_K3D_PASSIVE
212     C psistar :: eddy induced streamfunction in the y direction
213 m_bates 1.1 _RL psistar(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1:Nr)
214 m_bates 1.4 #endif
215 m_bates 1.1
216     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
217    
218     C ======================================
219     C Initialise some variables
220     C ======================================
221     small = TINY(zeroRL)
222 m_bates 1.4 update_modes=.FALSE.
223     IF ( DIFFERENT_MULTIPLE(GM_K3D_vecFreq,myTime,deltaTClock) )
224     & update_modes=.TRUE.
225    
226 m_bates 1.1 DO j=1-Oly,sNy+Oly
227     DO i=1-Olx,sNx+Olx
228     kLow_C(i,j) = kLowC(i,j,bi,bj)
229     ENDDO
230     ENDDO
231     DO j=1-Oly,sNy+Oly
232     DO i=1-Olx+1,sNx+Olx
233     kLow_U(i,j) = MIN( kLow_C(i,j), kLow_C(i-1,j) )
234     ENDDO
235     ENDDO
236     DO j=1-Oly+1,sNy+Oly
237     DO i=1-Olx,sNx+Olx
238     kLow_V(i,j) = MIN( kLow_C(i,j), kLow_C(i,j-1) )
239     ENDDO
240     ENDDO
241    
242 m_bates 1.18 C Dummy values for the edges. This does not affect the results
243     C but avoids problems when solving for the eigenvalues.
244 m_bates 1.1 i=1-Olx
245     DO j=1-Oly,sNy+Oly
246 m_bates 1.18 kLow_U(i,j) = 0
247 m_bates 1.1 ENDDO
248     j=1-Oly
249     DO i=1-Olx,sNx+Olx
250 m_bates 1.18 kLow_V(i,j) = 0
251 m_bates 1.1 ENDDO
252    
253     g_reciprho_sq = (gravity*recip_rhoConst)**2
254     C Gradient of Coriolis
255     DO j=1-Oly+1,sNy+Oly
256     DO i=1-Olx+1,sNx+Olx
257     dfdx(i,j) = ( fCori(i,j,bi,bj)-fCori(i-1,j,bi,bj) )
258     & *recip_dxC(i,j,bi,bj)
259     dfdy(i,j) = ( fCori(i,j,bi,bj)-fCori(i,j-1,bi,bj) )
260     & *recip_dyC(i,j,bi,bj)
261     ENDDO
262     ENDDO
263    
264 jmc 1.20 C Coriolis at C points enforcing a minimum value so
265 m_bates 1.1 C that it is defined at the equator
266     DO j=1-Oly,sNy+Oly
267     DO i=1-Olx,sNx+Olx
268     cori(i,j) = SIGN( MAX( ABS(fCori(i,j,bi,bj)),GM_K3D_minCori ),
269     & fCori(i,j,bi,bj) )
270     ENDDO
271     ENDDO
272     C Coriolis at U and V points
273 m_bates 1.17 DO j=1-Oly,sNy+Oly
274 m_bates 1.1 DO i=1-Olx+1,sNx+Olx
275     C Limited so that the inverse is defined at the equator
276     coriU(i,j) = op5*( cori(i,j)+cori(i-1,j) )
277 jmc 1.20 coriU(i,j) = SIGN( MAX( ABS(coriU(i,j)),GM_K3D_minCori ),
278 m_bates 1.1 & coriU(i,j) )
279    
280 m_bates 1.17 C Not limited
281     fCoriU(i,j) = op5*( fCori(i,j,bi,bj)+fCori(i-1,j,bi,bj) )
282     ENDDO
283     ENDDO
284     DO j=1-Oly+1,sNy+Oly
285     DO i=1-Olx,sNx+Olx
286     C Limited so that the inverse is defined at the equator
287 m_bates 1.1 coriV(i,j) = op5*( cori(i,j)+cori(i,j-1) )
288 jmc 1.20 coriV(i,j) = SIGN( MAX( ABS(coriV(i,j)),GM_K3D_minCori ),
289 m_bates 1.1 & coriV(i,j) )
290    
291     C Not limited
292     fCoriV(i,j) = op5*( fCori(i,j,bi,bj)+fCori(i,j-1,bi,bj) )
293     ENDDO
294     ENDDO
295     DO j=1-Oly,sNy+Oly
296     DO i=1-Olx,sNx+Olx
297 m_bates 1.6 gradf(i,j) = recip_rSphere*fCoriCos(i,j,bi,bj)
298 m_bates 1.1 ENDDO
299     ENDDO
300 m_bates 1.17 C Some dummy values at the edges
301     i=1-Olx
302     DO j=1-Oly,sNy+Oly
303     coriU(i,j)=cori(i,j)
304     fCoriU(i,j)=fCori(i,j,bi,bj)
305     ENDDO
306     j=1-Oly
307     DO i=1-Olx,sNx+Olx
308     coriV(i,j)=cori(i,j)
309     fCoriV(i,j)=fCori(i,j,bi,bj)
310     ENDDO
311 m_bates 1.1
312     C Zeroing some cumulative fields
313     DO j=1-Oly,sNy+Oly
314     DO i=1-Olx,sNx+Olx
315 m_bates 1.10 eady(i,j) = zeroRL
316     BVint(i,j) = zeroRL
317     Ubaro(i,j) = zeroRL
318     deltaH(i,j) = zeroRL
319     ENDDO
320     ENDDO
321     DO k=1,Nr
322     DO j=1-Oly,sNy+Oly
323     DO i=1-Olx,sNx+Olx
324     slopeC(i,j,k)=zeroRL
325     ENDDO
326 m_bates 1.1 ENDDO
327     ENDDO
328    
329 m_bates 1.17 C initialise remaining 2d variables
330     DO j=1-Oly,sNy+Oly
331     DO i=1-Olx,sNx+Olx
332     dfdy(i,j)=zeroRL
333     dfdy(i,j)=zeroRL
334     Rurms(i,j)=zeroRL
335     RRhines(i,j)=zeroRL
336     Rmix(i,j)=zeroRL
337     ENDDO
338     ENDDO
339     C initialise remaining 3d variables
340     DO k=1,Nr
341     DO j=1-Oly,sNy+Oly
342     DO i=1-Olx,sNx+Olx
343     N2loc(i,j,k)=GM_K3D_minN2
344     N2W(i,j,k) = GM_K3D_minN2
345     N2S(i,j,k) = GM_K3D_minN2
346     M4loc(i,j,k)=zeroRL
347     M4onN2(i,j,k)=zeroRL
348     urms(i,j,k)=zeroRL
349     SlopeX(i,j,k)=zeroRL
350     SlopeY(i,j,k)=zeroRL
351     dSigmaDx(i,j,k)=zeroRL
352     dSigmaDy(i,j,k)=zeroRL
353     gradqx(i,j,k)=zeroRL
354     gradqy(i,j,k)=zeroRL
355     ENDDO
356     ENDDO
357     ENDDO
358    
359 m_bates 1.1 C Find the zonal velocity at the cell centre
360 jmc 1.20 #ifdef ALLOW_EDDYPSI
361 m_bates 1.9 IF (GM_InMomAsStress) THEN
362 m_bates 1.21 DO k=1,Nr
363     DO i = 1-olx,snx+olx
364     DO j = 1-oly,sny+oly
365     uFldX(i,j,k) = uEulerMean(i,j,k,bi,bj)
366     vFldY(i,j,k) = vEulerMean(i,j,k,bi,bj)
367     ENDDO
368     ENDDO
369     ENDDO
370 m_bates 1.9 ELSE
371     #endif
372 m_bates 1.21 DO k=1,Nr
373     DO i = 1-olx,snx+olx
374     DO j = 1-oly,sny+oly
375     uFldX(i,j,k) = uVel(i,j,k,bi,bj)
376     vFldY(i,j,k) = vVel(i,j,k,bi,bj)
377     ENDDO
378     ENDDO
379     ENDDO
380 jmc 1.20 #ifdef ALLOW_EDDYPSI
381 m_bates 1.9 ENDIF
382     #endif
383 m_bates 1.1
384 m_bates 1.21 C The following comes from rotate_uv2en_rl
385     C This code does two things:
386     C 1) go from C grid velocity points to A grid velocity points
387     C 2) go from model grid directions to east/west directions
388     DO k = 1,Nr
389    
390     DO i = 1-Olx,sNx+Olx
391     j=sNy+Oly
392     tmpU(i,j)=zeroRL
393     tmpV(i,j)=zeroRL
394     ENDDO
395     DO j = 1-Oly,sNy+Oly-1
396     i=sNx+Olx
397     tmpU(i,j)=zeroRL
398     tmpV(i,j)=zeroRL
399     DO i = 1-Olx,sNx+Olx-1
400     tmpU(i,j) = 0.5 _d 0
401     & *( uFldX(i+1,j,k) + uFldX(i,j,k) )
402     tmpV(i,j) = 0.5 _d 0
403     & *( vFldY(i,j+1,k) + vFldY(i,j,k) )
404    
405     tmpU(i,j) = tmpU(i,j) * maskC(i,j,k,bi,bj)
406     tmpV(i,j) = tmpV(i,j) * maskC(i,j,k,bi,bj)
407     ENDDO
408     ENDDO
409    
410     DO j = 1-oly,sny+oly
411     DO i = 1-olx,snx+olx
412     ENDDO
413     ENDDO
414    
415     C rotation
416     DO j = 1-oly,sny+oly
417     DO i = 1-olx,snx+olx
418     ubar(i,j,k) =
419     & angleCosC(i,j,bi,bj)*tmpU(i,j)
420     & -angleSinC(i,j,bi,bj)*tmpV(i,j)
421     ENDDO
422     ENDDO
423     ENDDO
424    
425 m_bates 1.1 C Square of the buoyancy frequency at the top of a grid cell
426     DO k=2,Nr
427     DO j=1-Oly,sNy+Oly
428     DO i=1-Olx,sNx+Olx
429     N2(i,j,k) = -gravity*recip_rhoConst*sigmaR(i,j,k)
430     ENDDO
431     ENDDO
432     ENDDO
433     C N2(k=1) is always zero
434     k=1
435     DO j=1-Oly,sNy+Oly
436     DO i=1-Olx,sNx+Olx
437 m_bates 1.17 N2(i,j,k) = zeroRL
438     N(i,j,k) = zeroRL
439 m_bates 1.1 ENDDO
440     ENDDO
441 jmc 1.20 C Enforce a minimum N2
442 m_bates 1.1 DO k=2,Nr
443     DO j=1-Oly,sNy+Oly
444     DO i=1-Olx,sNx+Olx
445     IF (N2(i,j,k).LT.GM_K3D_minN2) N2(i,j,k)=GM_K3D_minN2
446     N(i,j,k) = SQRT(N2(i,j,k))
447     ENDDO
448     ENDDO
449     ENDDO
450     C Calculate the minimum drho/dz
451     maxDRhoDz = -rhoConst*GM_K3D_minN2/gravity
452    
453 jmc 1.20 C Calculate the barotropic velocity by vertically integrating
454 m_bates 1.1 C and the dividing by the depth of the water column
455     C Note that Ubaro is on the U grid.
456     DO k=1,Nr
457     DO j=1-Oly,sNy+Oly
458     DO i=1-Olx,sNx+Olx
459 jmc 1.20 Ubaro(i,j) = Ubaro(i,j) +
460 m_bates 1.21 & drF(k)*hfacC(i,j,k,bi,bj)*ubar(i,j,k)
461 m_bates 1.1 ENDDO
462     ENDDO
463     ENDDO
464     DO j=1-Oly,sNy+Oly
465     DO i=1-Olx,sNx+Olx
466     IF (kLow_C(i,j).GT.0) THEN
467     C The minus sign is because r_Low<0
468     Ubaro(i,j) = -Ubaro(i,j)/r_Low(i,j,bi,bj)
469     ENDIF
470     ENDDO
471     ENDDO
472    
473     C Integrate the buoyancy frequency vertically using the trapezoidal method.
474     DO k=1,Nr
475     DO j=1-Oly,sNy+Oly
476     DO i=1-Olx,sNx+Olx
477     IF (k.LT.kLow_C(i,j)) THEN
478     BVint(i,j) = BVint(i,j) + hFacC(i,j,k,bi,bj)*drF(k)
479     & *(N(i,j,k)+N(i,j,k+1))
480     ELSEIF (k.EQ.kLow_C(i,j)) THEN
481     C Assume that N(z=-H)=0
482     BVint(i,j) = BVint(i,j) + hFacC(i,j,k,bi,bj)*drF(k)*N(i,j,k)
483     ENDIF
484     ENDDO
485     ENDDO
486     ENDDO
487     DO j=1-Oly,sNy+Oly
488     DO i=1-Olx,sNx+Olx
489     BVint(i,j) = op5*BVint(i,j)
490     ENDDO
491     ENDDO
492    
493     C Calculate the eigenvalues and eigenvectors
494 m_bates 1.4 IF (update_modes) THEN
495     CALL GMREDI_CALC_EIGS(
496     I iMin,iMax,jMin,jMax,bi,bj,N2,myThid,
497     I kLow_C, maskC(:,:,:,bi,bj),
498     I hfacC(:,:,:,bi,bj), recip_hfacC(:,:,:,bi,bj),
499     I R_Low(:,:,bi,bj), 1, .TRUE.,
500     O Rmid, modesC(:,:,:,:,bi,bj))
501    
502     C Calculate the Rossby Radius
503     DO j=1-Oly+1,sNy+Oly
504     DO i=1-Olx+1,sNx+Olx
505     Req = SQRT(BVint(i,j)/(2*pi*gradf(i,j)))
506     Rdef(i,j,bi,bj) = MIN(Rmid(i,j),Req)
507     ENDDO
508     ENDDO
509     ENDIF
510 m_bates 1.1
511     C Average dsigma/dx and dsigma/dy onto the centre points
512 jmc 1.20
513 m_bates 1.1 DO k=1,Nr
514     DO j=1-Oly,sNy+Oly-1
515     DO i=1-Olx,sNx+Olx-1
516     dSigmaDx(i,j,k) = op5*(sigmaX(i,j,k)+sigmaX(i+1,j,k))
517     dSigmaDy(i,j,k) = op5*(sigmaY(i,j,k)+sigmaY(i,j+1,k))
518     ENDDO
519     ENDDO
520     ENDDO
521    
522     C ===============================
523     C Calculate the Eady growth rate
524     C ===============================
525     DO k=1,Nr
526    
527 m_bates 1.10 DO j=1-Oly,sNy+Oly-1
528     DO i=1-Olx,sNx+Olx-1
529 jmc 1.20 M4loc(i,j,k) = g_reciprho_sq*( dSigmaDx(i,j,k)**2
530 m_bates 1.10 & +dSigmaDy(i,j,k)**2 )
531     IF (k.NE.kLow_C(i,j)) THEN
532     N2loc(i,j,k) = op5*(N2(i,j,k)+N2(i,j,k+1))
533     ELSE
534     N2loc(i,j,k) = op5*N2(i,j,k)
535     ENDIF
536     ENDDO
537     ENDDO
538 m_bates 1.1 C The bottom of the grid cell is shallower than the top
539     C integration level, so, advance the depth.
540 m_bates 1.10 IF (-rF(k+1) .LE. GM_K3D_EadyMinDepth) CYCLE
541 m_bates 1.1
542 jmc 1.7 C Do not bother going any deeper since the top of the
543 m_bates 1.1 C cell is deeper than the bottom integration level
544     IF (-rF(k).GE.GM_K3D_EadyMaxDepth) EXIT
545    
546     C We are in the integration depth range
547     DO j=1-Oly,sNy+Oly-1
548     DO i=1-Olx,sNx+Olx-1
549 jmc 1.20 IF ( (kLow_C(i,j).GE.k) .AND.
550 m_bates 1.10 & (-hMixLayer(i,j,bi,bj).LE.-rC(k)) ) THEN
551 m_bates 1.1
552 m_bates 1.12 slopeC(i,j,k) = SQRT(M4loc(i,j,k))/N2loc(i,j,k)
553 m_bates 1.1 C Limit the slope. Note, this is not all the Eady calculations.
554 m_bates 1.13 IF (slopeC(i,j,k).LE.GM_maxSlope) THEN
555     M4onN2(i,j,k) = M4loc(i,j,k)/N2loc(i,j,k)
556 m_bates 1.1 ELSE
557 m_bates 1.13 slopeC(i,j,k) = GM_maxslope
558     M4onN2(i,j,k) = SQRT(M4loc(i,j,k))*GM_maxslope
559 m_bates 1.1 ENDIF
560 jmc 1.20 eady(i,j) = eady(i,j)
561 m_bates 1.13 & + hfacC(i,j,k,bi,bj)*drF(k)*M4onN2(i,j,k)
562 m_bates 1.10 deltaH(i,j) = deltaH(i,j) + drF(k)
563 m_bates 1.1 ENDIF
564     ENDDO
565     ENDDO
566     ENDDO
567    
568     DO j=1-Oly,sNy+Oly
569     DO i=1-Olx,sNx+Olx
570 m_bates 1.10 C If the minimum depth for the integration is deeper than the ocean
571 jmc 1.20 C bottom OR the mixed layer is deeper than the maximum depth of
572 m_bates 1.10 C integration, we set the Eady growth rate to something small
573     C to avoid floating point exceptions.
574     C Later, these areas will be given a small diffusivity.
575     IF (deltaH(i,j).EQ.zeroRL) THEN
576 m_bates 1.1 eady(i,j) = small
577    
578 m_bates 1.10 C Otherwise, divide over the integration and take the square root
579     C to actually find the Eady growth rate.
580 m_bates 1.1 ELSE
581 m_bates 1.10 eady(i,j) = SQRT(eady(i,j)/deltaH(i,j))
582 jmc 1.20
583 m_bates 1.1 ENDIF
584    
585     ENDDO
586     ENDDO
587    
588     C ======================================
589     C Calculate the diffusivity
590     C ======================================
591     DO j=1-Oly+1,sNy+Oly
592     DO i=1-Olx+1,sNx+Olx-1
593     C Calculate the Visbeck velocity
594 m_bates 1.13 Rurms(i,j) = MIN(Rdef(i,j,bi,bj),GM_K3D_Rmax)
595 m_bates 1.8 urms(i,j,1) = GM_K3D_Lambda*eady(i,j)*Rurms(i,j)
596 m_bates 1.1 C Set the bottom urms to zero
597     k=kLow_C(i,j)
598     IF (k.GT.0) urms(i,j,k) = 0.0
599    
600     C Calculate the Rhines scale
601     RRhines(i,j) = SQRT(urms(i,j,1)/gradf(i,j))
602    
603     C Calculate the estimated length scale
604 m_bates 1.4 Rmix(i,j) = MIN(Rdef(i,j,bi,bj), RRhines(i,j))
605 m_bates 1.13 Rmix(i,j) = MAX(Rmix(i,j),GM_K3D_Rmin)
606 m_bates 1.1
607     C Calculate the Doppler shifted long Rossby wave speed
608     C Ubaro is on the U grid so we must average onto the M grid.
609 m_bates 1.21 cDopp(i,j) = Ubaro(i,j)
610 m_bates 1.4 & - gradf(i,j)*Rdef(i,j,bi,bj)*Rdef(i,j,bi,bj)
611 m_bates 1.1 C Limit the wave speed to the namelist variable GM_K3D_maxC
612     IF (ABS(cDopp(i,j)).GT.GM_K3D_maxC) THEN
613     cDopp(i,j) = MAX(GM_K3D_maxC, cDopp(i,j))
614     ENDIF
615    
616     ENDDO
617     ENDDO
618    
619     C Project the surface urms to the subsurface using the first baroclinic mode
620 m_bates 1.4 CALL GMREDI_CALC_URMS(
621     I iMin,iMax,jMin,jMax,bi,bj,N2,myThid,
622     U urms)
623 m_bates 1.1
624     C Calculate the diffusivity (on the mass grid)
625     DO k=1,Nr
626     DO j=1-Oly,sNy+Oly
627     DO i=1-Olx,sNx+Olx
628     IF (k.LE.kLow_C(i,j)) THEN
629 m_bates 1.10 IF (deltaH(i,j).EQ.zeroRL) THEN
630 m_bates 1.1 K3D(i,j,k,bi,bj) = GM_K3D_smallK
631     ELSE
632     IF (urms(i,j,k).EQ.0.0) THEN
633     K3D(i,j,k,bi,bj) = GM_K3D_smallK
634     ELSE
635 m_bates 1.21 umc(i,j,k) =ubar(i,j,k) - cDopp(i,j)
636 m_bates 1.13 supp(i,j,k)=1/(1+GM_K3D_b1*umc(i,j,k)**2/urms(i,j,1)**2)
637     C 2*Rmix gives the diameter
638 m_bates 1.1 K3D(i,j,k,bi,bj) = GM_K3D_gamma*urms(i,j,k)
639 m_bates 1.13 & *2*Rmix(i,j)*supp(i,j,k)
640 m_bates 1.1 ENDIF
641    
642     C Enforce lower and upper bounds on the diffusivity
643     IF (K3D(i,j,k,bi,bj).LT.GM_K3D_smallK)
644     & K3D(i,j,k,bi,bj) = GM_K3D_smallK
645     IF (K3D(i,j,k,bi,bj).GT.GM_maxK3D)
646     & K3D(i,j,k,bi,bj) = GM_maxK3D
647     ENDIF
648     ENDIF
649     ENDDO
650     ENDDO
651     ENDDO
652    
653     C ======================================
654     C Find the PV gradient
655     C ======================================
656 m_bates 1.3 C Calculate the surface layer thickness.
657 jmc 1.20 C Use hMixLayer (calculated in model/src/calc_oce_mxlayer)
658 m_bates 1.3 C for the mixed layer depth.
659 m_bates 1.1
660 m_bates 1.3 C Enforce a minimum surface layer depth
661 m_bates 1.1 DO j=1-Oly,sNy+Oly
662     DO i=1-Olx,sNx+Olx
663 m_bates 1.3 surfkz(i,j) = MIN(-GM_K3D_surfMinDepth,-hMixLayer(i,j,bi,bj))
664     surfkz(i,j) = MAX(surfkz(i,j),R_low(i,j,bi,bj))
665     IF(maskC(i,j,1,bi,bj).EQ.0.0) surfkz(i,j)=0.0
666     surfk(i,j) = 0
667 m_bates 1.1 ENDDO
668     ENDDO
669 m_bates 1.4 DO k=1,Nr
670 m_bates 1.1 DO j=1-Oly,sNy+Oly
671     DO i=1-Olx,sNx+Olx
672 jmc 1.20 IF (rF(k).GT.surfkz(i,j) .AND. surfkz(i,j).GE.rF(k+1))
673 m_bates 1.3 & surfk(i,j) = k
674 m_bates 1.1 ENDDO
675     ENDDO
676     ENDDO
677 m_bates 1.3
678 m_bates 1.1 C Calculate the isopycnal slope
679     DO j=1-Oly,sNy+Oly-1
680     DO i=1-Olx,sNx+Olx-1
681     SlopeX(i,j,1) = zeroRL
682     SlopeY(i,j,1) = zeroRL
683     ENDDO
684     ENDDO
685     DO k=2,Nr
686     DO j=1-Oly+1,sNy+Oly
687     DO i=1-Olx+1,sNx+Olx
688     IF(surfk(i,j).GE.kLowC(i,j,bi,bj)) THEN
689     C If the surface layer is thinner than the water column
690     C the set the slope to zero to avoid problems.
691     SlopeX(i,j,k) = zeroRL
692     SlopeY(i,j,k) = zeroRL
693    
694     ELSE
695     C Calculate the zonal slope at the western cell face (U grid)
696 m_bates 1.4 sigz = MIN( op5*(sigmaR(i,j,k)+sigmaR(i-1,j,k)), maxDRhoDz )
697 m_bates 1.1 sigx = op5*( sigmaX(i,j,k)+sigmaX(i,j,k-1) )
698     slope = sigx/sigz
699     IF(ABS(slope).GT.GM_maxSlope)
700     & slope = SIGN(GM_maxSlope,slope)
701     SlopeX(i,j,k)=-maskW(i,j,k-1,bi,bj)*maskW(i,j,k,bi,bj)*slope
702 jmc 1.20
703 m_bates 1.1 C Calculate the meridional slope at the southern cell face (V grid)
704 m_bates 1.4 sigz = MIN( op5*(sigmaR(i,j,k)+sigmaR(i,j-1,k)), maxDRhoDz )
705 m_bates 1.1 sigy = op5*( sigmaY(i,j,k) + sigmaY(i,j,k-1) )
706     slope = sigy/sigz
707     IF(ABS(slope).GT.GM_maxSlope)
708     & slope = SIGN(GM_maxSlope,slope)
709     SlopeY(i,j,k)=-maskS(i,j,k-1,bi,bj)*maskS(i,j,k,bi,bj)*slope
710     ENDIF
711     ENDDO
712     ENDDO
713     ENDDO
714    
715 jmc 1.20 C Calculate the thickness flux and diffusivity. These may be altered later
716 m_bates 1.14 C depending on namelist options.
717 m_bates 1.1 C Enforce a zero slope bottom boundary condition for the bottom most cells (k=Nr)
718     k=Nr
719     DO j=1-Oly,sNy+Oly
720     DO i=1-Olx,sNx+Olx
721     C Zonal thickness flux at the western cell face
722     tfluxX(i,j,k) = -fCoriU(i,j)*SlopeX(i,j,k)
723     & *recip_drF(k)*recip_hFacW(i,j,k,bi,bj)
724     C Meridional thickness flux at the southern cell face
725     tfluxY(i,j,k) = -fCoriV(i,j)*SlopeY(i,j,k)
726     & *recip_drF(k)*recip_hFacS(i,j,k,bi,bj)
727 m_bates 1.14
728 jmc 1.20 C Use the interior diffusivity. Note: if we are using a
729 m_bates 1.14 C constant diffusivity KPV is overwritten later
730     KPV(i,j,k) = K3D(i,j,k,bi,bj)
731    
732 m_bates 1.1 ENDDO
733     ENDDO
734    
735 m_bates 1.14 C Calculate the thickness flux and diffusivity and for other cells (k<Nr)
736 m_bates 1.1 DO k=Nr-1,1,-1
737 m_bates 1.14 DO j=1-Oly,sNy+Oly
738     DO i=1-Olx,sNx+Olx
739     C Zonal thickness flux at the western cell face
740     tfluxX(i,j,k)=-fCoriU(i,j)*(SlopeX(i,j,k)-SlopeX(i,j,k+1))
741     & *recip_drF(k)*recip_hFacW(i,j,k,bi,bj)
742     & *maskW(i,j,k,bi,bj)
743 jmc 1.20
744 m_bates 1.14 C Meridional thickness flux at the southern cell face
745     tfluxY(i,j,k)=-fCoriV(i,j)*(SlopeY(i,j,k)-SlopeY(i,j,k+1))
746     & *recip_drF(k)*recip_hFacS(i,j,k,bi,bj)
747     & *maskS(i,j,k,bi,bj)
748 jmc 1.20
749     C Use the interior diffusivity. Note: if we are using a
750 m_bates 1.14 C constant diffusivity KPV is overwritten later
751     KPV(i,j,k) = K3D(i,j,k,bi,bj)
752     ENDDO
753     ENDDO
754     ENDDO
755    
756 jmc 1.20 C Special treatment for the surface layer (if necessary), which overwrites
757 m_bates 1.14 C values in the previous loops.
758     IF (GM_K3D_ThickSheet .OR. GM_K3D_surfK) THEN
759     DO k=Nr-1,1,-1
760     DO j=1-Oly,sNy+Oly
761     DO i=1-Olx,sNx+Olx
762 jmc 1.20 IF(k.LE.surfk(i,j)) THEN
763     C We are in the surface layer. Change the thickness flux
764 m_bates 1.14 C and diffusivity as necessary.
765    
766     IF (GM_K3D_ThickSheet) THEN
767     C We are in the surface layer, so set the thickness flux
768     C based on the average slope over the surface layer
769     C If we are on the edge of a "cliff" the surface layer at the
770 jmc 1.20 C centre of the grid point could be deeper than the U or V point.
771 m_bates 1.14 C So, we ensure that we always take a sensible slope.
772     IF(kLow_U(i,j).LT.surfk(i,j)) THEN
773     kk=kLow_U(i,j)
774     hsurf = -rLowW(i,j,bi,bj)
775     ELSE
776     kk=surfk(i,j)
777     hsurf = -surfkz(i,j)
778     ENDIF
779     IF(kk.GT.0) THEN
780     IF(kk.EQ.Nr) THEN
781     tfluxX(i,j,k) = -fCoriU(i,j)*maskW(i,j,k,bi,bj)
782     & *SlopeX(i,j,kk)/hsurf
783     ELSE
784     tfluxX(i,j,k) = -fCoriU(i,j)*maskW(i,j,k,bi,bj)
785     & *( SlopeX(i,j,kk)-SlopeX(i,j,kk+1) )/hsurf
786     ENDIF
787     ELSE
788     tfluxX(i,j,k) = zeroRL
789     ENDIF
790 jmc 1.20
791 m_bates 1.14 IF(kLow_V(i,j).LT.surfk(i,j)) THEN
792     kk=kLow_V(i,j)
793     hsurf = -rLowS(i,j,bi,bj)
794     ELSE
795     kk=surfk(i,j)
796     hsurf = -surfkz(i,j)
797     ENDIF
798     IF(kk.GT.0) THEN
799     IF(kk.EQ.Nr) THEN
800     tfluxY(i,j,k) = -fCoriV(i,j)*maskS(i,j,k,bi,bj)
801     & *SlopeY(i,j,kk)/hsurf
802     ELSE
803     tfluxY(i,j,k) = -fCoriV(i,j)*maskS(i,j,k,bi,bj)
804     & *( SlopeY(i,j,kk)-SlopeY(i,j,kk+1) )/hsurf
805     ENDIF
806     ELSE
807     tfluxY(i,j,k) = zeroRL
808     ENDIF
809 m_bates 1.4 ENDIF
810 m_bates 1.1
811 m_bates 1.14 IF (GM_K3D_surfK) THEN
812     C Use a constant K in the surface layer.
813     KPV(i,j,k) = GM_K3D_constK
814 m_bates 1.4 ENDIF
815 m_bates 1.1 ENDIF
816 m_bates 1.14 ENDDO
817     ENDDO
818 m_bates 1.1 ENDDO
819 m_bates 1.14 ENDIF
820 m_bates 1.1
821     C Calculate gradq
822 m_bates 1.21 IF (GM_K3D_beta_eq_0) THEN
823 m_bates 1.5 C Ignore beta in the calculation of grad(q)
824 m_bates 1.2 DO k=1,Nr
825     DO j=1-Oly+1,sNy+Oly
826     DO i=1-Olx+1,sNx+Olx
827     gradqx(i,j,k) = maskW(i,j,k,bi,bj)*tfluxX(i,j,k)
828     gradqy(i,j,k) = maskS(i,j,k,bi,bj)*tfluxY(i,j,k)
829     ENDDO
830     ENDDO
831     ENDDO
832 jmc 1.20
833 m_bates 1.2 ELSE
834     C Do not ignore beta
835     DO k=1,Nr
836     DO j=1-Oly+1,sNy+Oly
837     DO i=1-Olx+1,sNx+Olx
838     gradqx(i,j,k) = maskW(i,j,k,bi,bj)*(dfdx(i,j)+tfluxX(i,j,k))
839     gradqy(i,j,k) = maskS(i,j,k,bi,bj)*(dfdy(i,j)+tfluxY(i,j,k))
840     ENDDO
841     ENDDO
842 m_bates 1.1 ENDDO
843 m_bates 1.2 ENDIF
844 m_bates 1.1
845     C ======================================
846     C Find Xi and the eddy induced velocities
847     C ======================================
848     C Find the buoyancy frequency at the west and south faces of a cell
849     C This is necessary to find the eigenvectors at those points
850     DO k=1,Nr
851     DO j=1-Oly+1,sNy+Oly
852     DO i=1-Olx+1,sNx+Olx
853     N2W(i,j,k) = maskW(i,j,k,bi,bj)
854     & *( N2(i,j,k)+N2(i-1,j,k) )
855     N2S(i,j,k) = maskS(i,j,k,bi,bj)
856     & *( N2(i,j,k)+N2(i,j-1,k) )
857     ENDDO
858     ENDDO
859     ENDDO
860    
861 m_bates 1.21 C If GM_K3D_use_constK=.TRUE., the diffusivity for the eddy transport is
862 m_bates 1.14 C set to a constant equal to GM_K3D_constK.
863 m_bates 1.11 C If the diffusivity is constant the method here is the same as GM.
864 m_bates 1.14 C If GM_K3D_constRedi=.TRUE. K3D will be set equal to GM_K3D_constK later.
865 m_bates 1.21 IF(GM_K3D_use_constK) THEN
866 m_bates 1.3 DO k=1,Nr
867     DO j=1-Oly,sNy+Oly
868     DO i=1-Olx,sNx+Olx
869     KPV(i,j,k) = GM_K3D_constK
870     ENDDO
871 m_bates 1.2 ENDDO
872     ENDDO
873 m_bates 1.3 ENDIF
874 m_bates 1.2
875 m_bates 1.3 IF (.NOT. GM_K3D_smooth) THEN
876     C Do not expand K grad(q) => no smoothing
877 jmc 1.20 C May only be done with a constant K, otherwise the
878 m_bates 1.3 C integral constraint is violated.
879 m_bates 1.2 DO k=1,Nr
880     DO j=1-Oly,sNy+Oly
881     DO i=1-Olx,sNx+Olx
882 m_bates 1.3 Xix(i,j,k) = -maskW(i,j,k,bi,bj)*KPV(i,j,k)*gradqx(i,j,k)
883     Xiy(i,j,k) = -maskS(i,j,k,bi,bj)*KPV(i,j,k)*gradqy(i,j,k)
884 m_bates 1.2 ENDDO
885     ENDDO
886     ENDDO
887    
888     ELSE
889 m_bates 1.3 C Expand K grad(q) in terms of baroclinic modes to smooth
890     C and satisfy the integral constraint
891 m_bates 1.2
892 m_bates 1.1 C Start with the X direction
893     C ------------------------------
894     C Calculate the eigenvectors at the West face of a cell
895 m_bates 1.4 IF (update_modes) THEN
896     CALL GMREDI_CALC_EIGS(
897     I iMin,iMax,jMin,jMax,bi,bj,N2W,myThid,
898     I kLow_U,maskW(:,:,:,bi,bj),
899     I hfacW(:,:,:,bi,bj),recip_hfacW(:,:,:,bi,bj),
900     I rLowW(:,:,bi,bj),GM_K3D_NModes,.FALSE.,
901     O dummy,modesW(:,:,:,:,bi,bj))
902     ENDIF
903 jmc 1.20
904 m_bates 1.1 C Calculate Xi_m at the west face of a cell
905     DO j=1-Oly,sNy+Oly
906     DO i=1-Olx,sNx+Olx
907     DO m=1,GM_K3D_NModes
908     XimX(m,i,j) = zeroRL
909     ENDDO
910     ENDDO
911     ENDDO
912     DO k=1,Nr
913     DO j=1-Oly,sNy+Oly
914     DO i=1-Olx,sNx+Olx
915     DO m=1,GM_K3D_NModes
916 m_bates 1.13 Kdqdx(i,j,k) = KPV(i,j,k)*gradqx(i,j,k)
917 jmc 1.20 XimX(m,i,j) = XimX(m,i,j)
918 m_bates 1.13 & - maskW(i,j,k,bi,bj)*drF(k)*hfacW(i,j,k,bi,bj)
919     & *Kdqdx(i,j,k)*modesW(m,i,j,k,bi,bj)
920 m_bates 1.1 ENDDO
921     ENDDO
922     ENDDO
923     ENDDO
924 jmc 1.20
925 m_bates 1.1 C Calculate Xi in the X direction at the west face
926     DO k=1,Nr
927     DO j=1-Oly,sNy+Oly
928     DO i=1-Olx,sNx+Olx
929     Xix(i,j,k) = zeroRL
930     ENDDO
931     ENDDO
932     ENDDO
933     DO k=1,Nr
934     DO j=1-Oly,sNy+Oly
935     DO i=1-Olx,sNx+Olx
936     DO m=1,GM_K3D_NModes
937 jmc 1.20 Xix(i,j,k) = Xix(i,j,k)
938 m_bates 1.4 & + maskW(i,j,k,bi,bj)*XimX(m,i,j)*modesW(m,i,j,k,bi,bj)
939 m_bates 1.1 ENDDO
940     ENDDO
941     ENDDO
942     ENDDO
943    
944     C Now the Y direction
945     C ------------------------------
946     C Calculate the eigenvectors at the West face of a cell
947 m_bates 1.4 IF (update_modes) THEN
948     CALL GMREDI_CALC_EIGS(
949     I iMin,iMax,jMin,jMax,bi,bj,N2S,myThid,
950     I kLow_V,maskS(:,:,:,bi,bj),
951     I hfacS(:,:,:,bi,bj),recip_hfacS(:,:,:,bi,bj),
952     I rLowS(:,:,bi,bj), GM_K3D_NModes, .FALSE.,
953     O dummy,modesS(:,:,:,:,bi,bj))
954     ENDIF
955    
956 m_bates 1.1 DO j=1-Oly,sNy+Oly
957     DO i=1-Olx,sNx+Olx
958     DO m=1,GM_K3D_NModes
959     XimY(m,i,j) = zeroRL
960     ENDDO
961     ENDDO
962     ENDDO
963     DO k=1,Nr
964     DO j=1-Oly,sNy+Oly
965     DO i=1-Olx,sNx+Olx
966     DO m=1,GM_K3D_NModes
967 m_bates 1.13 Kdqdy(i,j,k) = KPV(i,j,k)*gradqy(i,j,k)
968 m_bates 1.3 XimY(m,i,j) = XimY(m,i,j)
969     & - drF(k)*hfacS(i,j,k,bi,bj)
970 m_bates 1.13 & *Kdqdy(i,j,k)*modesS(m,i,j,k,bi,bj)
971 m_bates 1.1 ENDDO
972     ENDDO
973     ENDDO
974     ENDDO
975 jmc 1.20
976 m_bates 1.1 C Calculate Xi for Y direction at the south face
977     DO k=1,Nr
978     DO j=1-Oly,sNy+Oly
979     DO i=1-Olx,sNx+Olx
980     Xiy(i,j,k) = zeroRL
981     ENDDO
982     ENDDO
983     ENDDO
984     DO k=1,Nr
985     DO j=1-Oly,sNy+Oly
986     DO i=1-Olx,sNx+Olx
987     DO m=1,GM_K3D_NModes
988 jmc 1.20 Xiy(i,j,k) = Xiy(i,j,k)
989 m_bates 1.4 & + maskS(i,j,k,bi,bj)*XimY(m,i,j)*modesS(m,i,j,k,bi,bj)
990 m_bates 1.1 ENDDO
991     ENDDO
992     ENDDO
993     ENDDO
994    
995 m_bates 1.11 C ENDIF (.NOT. GM_K3D_smooth)
996 m_bates 1.1 ENDIF
997    
998 m_bates 1.15 C Calculate the renormalisation factor
999     DO j=1-Oly,sNy+Oly
1000     DO i=1-Olx,sNx+Olx
1001     uInt(i,j)=zeroRL
1002     vInt(i,j)=zeroRL
1003     KdqdyInt(i,j)=zeroRL
1004     KdqdxInt(i,j)=zeroRL
1005     uKdqdyInt(i,j)=zeroRL
1006     vKdqdxInt(i,j)=zeroRL
1007     uXiyInt(i,j)=zeroRL
1008     vXixInt(i,j)=zeroRL
1009 m_bates 1.16 Renorm(i,j)=oneRL
1010     RenormU(i,j)=oneRL
1011     RenormV(i,j)=oneRL
1012 m_bates 1.15 ENDDO
1013     ENDDO
1014     DO k=1,Nr
1015     DO j=1-Oly,sNy+Oly-1
1016     DO i=1-Olx,sNx+Olx-1
1017     centreX = op5*(uVel(i,j,k,bi,bj)+uVel(i+1,j,k,bi,bj))
1018     centreY = op5*(Kdqdy(i,j,k) +Kdqdy(i,j+1,k) )
1019     C For the numerator
1020 jmc 1.20 uInt(i,j) = uInt(i,j)
1021 m_bates 1.15 & + centreX*hfacC(i,j,k,bi,bj)*drF(k)
1022     KdqdyInt(i,j) = KdqdyInt(i,j)
1023     & + centreY*hfacC(i,j,k,bi,bj)*drF(k)
1024     uKdqdyInt(i,j) = uKdqdyInt(i,j)
1025     & + centreX*centreY*hfacC(i,j,k,bi,bj)*drF(k)
1026     C For the denominator
1027     centreY = op5*(Xiy(i,j,k) + Xiy(i,j+1,k))
1028     uXiyInt(i,j) = uXiyInt(i,j)
1029     & + centreX*centreY*hfacC(i,j,k,bi,bj)*drF(k)
1030    
1031     centreX = op5*(Kdqdx(i,j,k) +Kdqdx(i+1,j,k))
1032     centreY = op5*(vVel(i,j,k,bi,bj)+vVel(i,j+1,k,bi,bj) )
1033     C For the numerator
1034     vInt(i,j) = vInt(i,j)
1035     & + centreY*hfacC(i,j,k,bi,bj)*drF(k)
1036     KdqdxInt(i,j) = KdqdxInt(i,j)
1037     & + CentreX*hfacC(i,j,k,bi,bj)*drF(k)
1038     vKdqdxInt(i,j) = vKdqdxInt(i,j)
1039     & + centreY*centreX*hfacC(i,j,k,bi,bj)*drF(k)
1040     C For the denominator
1041     centreX = op5*(Xix(i,j,k) + Xix(i+1,j,k))
1042     vXixInt(i,j) = vXixInt(i,j)
1043     & + centreY*centreX*hfacC(i,j,k,bi,bj)*drF(k)
1044    
1045     ENDDO
1046     ENDDO
1047     ENDDO
1048    
1049     DO j=1-Oly,sNy+Oly-1
1050     DO i=1-Olx,sNx+Olx-1
1051     IF (kLowC(i,j,bi,bj).GT.0) THEN
1052 jmc 1.20 numerator =
1053 m_bates 1.15 & (uKdqdyInt(i,j)-uInt(i,j)*KdqdyInt(i,j)/R_low(i,j,bi,bj))
1054     & -(vKdqdxInt(i,j)-vInt(i,j)*KdqdxInt(i,j)/R_low(i,j,bi,bj))
1055     denominator = uXiyInt(i,j) - vXixInt(i,j)
1056 jmc 1.20 C We can have troubles with floating point exceptions if the denominator
1057     C of the renormalisation if the ocean is resting (e.g. intial conditions).
1058 m_bates 1.16 C So we make the renormalisation factor one if the denominator is very small
1059     C The renormalisation factor is supposed to correct the error in the extraction of
1060     C potential energy associated with the truncation of the expansion. Thus, we
1061     C enforce a minimum value for the renormalisation factor.
1062     C We also enforce a maximum renormalisation factor.
1063     IF (denominator.GT.small) THEN
1064 m_bates 1.15 Renorm(i,j) = ABS(numerator/denominator)
1065 m_bates 1.16 Renorm(i,j) = MAX(Renorm(i,j),GM_K3D_minRenorm)
1066     Renorm(i,j) = MIN(Renorm(i,j),GM_K3D_maxRenorm)
1067 m_bates 1.15 ENDIF
1068     ENDIF
1069     ENDDO
1070     ENDDO
1071     C Now put it back on to the velocity grids
1072     DO j=1-Oly+1,sNy+Oly-1
1073     DO i=1-Olx+1,sNx+Olx-1
1074     RenormU(i,j) = op5*(Renorm(i-1,j)+Renorm(i,j))
1075     RenormV(i,j) = op5*(Renorm(i,j-1)+Renorm(i,j))
1076     ENDDO
1077     ENDDO
1078    
1079 m_bates 1.1 C Calculate the eddy induced velocity in the X direction at the west face
1080     DO k=1,Nr
1081     DO j=1-Oly+1,sNy+Oly
1082     DO i=1-Olx+1,sNx+Olx
1083 m_bates 1.16 ustar(i,j,k) = -RenormU(i,j)*Xix(i,j,k)/coriU(i,j)
1084 m_bates 1.1 ENDDO
1085     ENDDO
1086 jmc 1.20 ENDDO
1087 m_bates 1.1
1088     C Calculate the eddy induced velocity in the Y direction at the south face
1089     DO k=1,Nr
1090     DO j=1-Oly+1,sNy+Oly
1091     DO i=1-Olx+1,sNx+Olx
1092 m_bates 1.16 vstar(i,j,k) = -RenormV(i,j)*Xiy(i,j,k)/coriV(i,j)
1093 m_bates 1.1 ENDDO
1094     ENDDO
1095 jmc 1.20 ENDDO
1096 m_bates 1.1
1097     C ======================================
1098     C Calculate the eddy induced overturning streamfunction
1099     C ======================================
1100     #ifdef GM_K3D_PASSIVE
1101     k=Nr
1102     DO j=1-Oly,sNy+Oly
1103     DO i=1-Olx,sNx+Olx
1104     psistar(i,j,Nr) = -hfacS(i,j,k,bi,bj)*drF(k)*vstar(i,j,k)
1105     ENDDO
1106     ENDDO
1107     DO k=Nr-1,1,-1
1108     DO j=1-Oly,sNy+Oly
1109     DO i=1-Olx,sNx+Olx
1110     psistar(i,j,k) = psistar(i,j,k+1)
1111     & - hfacS(i,j,k,bi,bj)*drF(k)*vstar(i,j,k)
1112     ENDDO
1113     ENDDO
1114     ENDDO
1115 jmc 1.20
1116 m_bates 1.1 #else
1117    
1118     IF (GM_AdvForm) THEN
1119     k=Nr
1120     DO j=1-Oly+1,sNy+1
1121     DO i=1-Olx+1,sNx+1
1122     GM_PsiX(i,j,k,bi,bj) = -hfacW(i,j,k,bi,bj)*drF(k)*ustar(i,j,k)
1123     GM_PsiY(i,j,k,bi,bj) = -hfacS(i,j,k,bi,bj)*drF(k)*vstar(i,j,k)
1124     ENDDO
1125     ENDDO
1126     DO k=Nr-1,1,-1
1127     DO j=1-Oly+1,sNy+1
1128     DO i=1-Olx+1,sNx+1
1129     GM_PsiX(i,j,k,bi,bj) = GM_PsiX(i,j,k+1,bi,bj)
1130     & - hfacW(i,j,k,bi,bj)*drF(k)*ustar(i,j,k)
1131     GM_PsiY(i,j,k,bi,bj) = GM_PsiY(i,j,k+1,bi,bj)
1132     & - hfacS(i,j,k,bi,bj)*drF(k)*vstar(i,j,k)
1133     ENDDO
1134     ENDDO
1135     ENDDO
1136    
1137     ENDIF
1138     #endif
1139    
1140     #ifdef ALLOW_DIAGNOSTICS
1141     C Diagnostics
1142     IF ( useDiagnostics ) THEN
1143 jmc 1.20 CALL DIAGNOSTICS_FILL(K3D, 'GM_K3D ',0,Nr,1,bi,bj,myThid)
1144     CALL DIAGNOSTICS_FILL(KPV, 'GM_KPV ',0,Nr,2,bi,bj,myThid)
1145     CALL DIAGNOSTICS_FILL(urms, 'GM_URMS ',0,Nr,2,bi,bj,myThid)
1146     CALL DIAGNOSTICS_FILL(Rdef, 'GM_RDEF ',0, 1,1,bi,bj,myThid)
1147     CALL DIAGNOSTICS_FILL(Rurms, 'GM_RURMS',0, 1,2,bi,bj,myThid)
1148     CALL DIAGNOSTICS_FILL(RRhines,'GM_RRHNS',0, 1,2,bi,bj,myThid)
1149     CALL DIAGNOSTICS_FILL(Rmix, 'GM_RMIX ',0, 1,2,bi,bj,myThid)
1150     CALL DIAGNOSTICS_FILL(supp, 'GM_SUPP ',0,Nr,2,bi,bj,myThid)
1151     CALL DIAGNOSTICS_FILL(Xix, 'GM_Xix ',0,Nr,2,bi,bj,myThid)
1152     CALL DIAGNOSTICS_FILL(Xiy, 'GM_Xiy ',0,Nr,2,bi,bj,myThid)
1153     CALL DIAGNOSTICS_FILL(cDopp, 'GM_C ',0, 1,2,bi,bj,myThid)
1154     CALL DIAGNOSTICS_FILL(Ubaro, 'GM_UBARO',0, 1,2,bi,bj,myThid)
1155     CALL DIAGNOSTICS_FILL(eady, 'GM_EADY ',0, 1,2,bi,bj,myThid)
1156     CALL DIAGNOSTICS_FILL(SlopeX, 'GM_Sx ',0,Nr,2,bi,bj,myThid)
1157     CALL DIAGNOSTICS_FILL(SlopeY, 'GM_Sy ',0,Nr,2,bi,bj,myThid)
1158     CALL DIAGNOSTICS_FILL(tfluxX, 'GM_TFLXX',0,Nr,2,bi,bj,myThid)
1159     CALL DIAGNOSTICS_FILL(tfluxY, 'GM_TFLXY',0,Nr,2,bi,bj,myThid)
1160     CALL DIAGNOSTICS_FILL(gradqx, 'GM_dqdx ',0,Nr,2,bi,bj,myThid)
1161     CALL DIAGNOSTICS_FILL(gradqy, 'GM_dqdy ',0,Nr,2,bi,bj,myThid)
1162     CALL DIAGNOSTICS_FILL(Kdqdy, 'GM_Kdqdy',0,Nr,2,bi,bj,myThid)
1163     CALL DIAGNOSTICS_FILL(Kdqdx, 'GM_Kdqdx',0,Nr,2,bi,bj,myThid)
1164     CALL DIAGNOSTICS_FILL(surfkz, 'GM_SFLYR',0, 1,2,bi,bj,myThid)
1165     CALL DIAGNOSTICS_FILL(ustar, 'GM_USTAR',0,Nr,2,bi,bj,myThid)
1166     CALL DIAGNOSTICS_FILL(vstar, 'GM_VSTAR',0,Nr,2,bi,bj,myThid)
1167     CALL DIAGNOSTICS_FILL(umc, 'GM_UMC ',0,Nr,2,bi,bj,myThid)
1168     CALL DIAGNOSTICS_FILL(ubar, 'GM_UBAR ',0,Nr,2,bi,bj,myThid)
1169     CALL DIAGNOSTICS_FILL(modesC, 'GM_MODEC',0,Nr,1,bi,bj,myThid)
1170     CALL DIAGNOSTICS_FILL(M4loc, 'GM_M4 ',0,Nr,2,bi,bj,myThid)
1171     CALL DIAGNOSTICS_FILL(N2loc, 'GM_N2 ',0,Nr,2,bi,bj,myThid)
1172     CALL DIAGNOSTICS_FILL(M4onN2, 'GM_M4_N2',0,Nr,2,bi,bj,myThid)
1173     CALL DIAGNOSTICS_FILL(slopeC, 'GM_SLOPE',0,Nr,2,bi,bj,myThid)
1174     CALL DIAGNOSTICS_FILL(Renorm, 'GM_RENRM',0, 1,2,bi,bj,myThid)
1175 m_bates 1.1 ENDIF
1176     #endif
1177    
1178 jmc 1.20 C For the Redi diffusivity, we set K3D to a constant if
1179 m_bates 1.14 C GM_K3D_constRedi=.TRUE.
1180     IF (GM_K3D_constRedi) THEN
1181 m_bates 1.11 DO k=1,Nr
1182     DO j=1-Oly,sNy+Oly
1183     DO i=1-Olx,sNx+Olx
1184     K3D(i,j,k,bi,bj) = GM_K3D_constK
1185     ENDDO
1186     ENDDO
1187     ENDDO
1188     ENDIF
1189    
1190 m_bates 1.14 #ifdef ALLOW_DIAGNOSTICS
1191 jmc 1.20 IF ( useDiagnostics )
1192     & CALL DIAGNOSTICS_FILL(K3D, 'GM_K3D_T',0,Nr,1,bi,bj,myThid)
1193 m_bates 1.14 #endif
1194    
1195 m_bates 1.1 #endif /* GM_K3D */
1196     RETURN
1197     END

  ViewVC Help
Powered by ViewVC 1.1.22