/[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.26 - (hide annotations) (download)
Fri Oct 30 10:33:24 2015 UTC (8 years, 7 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, HEAD
Changes since 1.25: +18 -32 lines
Simplify computations of additional Coriolis parameters

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

  ViewVC Help
Powered by ViewVC 1.1.22