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

Contents of /MITgcm/pkg/gmredi/gmredi_calc_tensor.F

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


Revision 1.3 - (show annotations) (download)
Mon Jan 29 20:07:39 2001 UTC (23 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint34
Changes since 1.2: +17 -17 lines
Corrected array dimensions.
Temporary scalars introduced to avoid storing by TAMC.

1 C $Header: /u/gcmpack/models/MITgcmUV/pkg/gmredi/gmredi_calc_tensor.F,v 1.2 2001/01/08 20:11:04 heimbach Exp $
2
3 #include "GMREDI_OPTIONS.h"
4
5 CStartOfInterface
6 SUBROUTINE GMREDI_CALC_TENSOR(
7 I bi, bj, iMin, iMax, jMin, jMax, K,
8 I sigmaX, sigmaY, sigmaR,
9 I myThid )
10 C /==========================================================\
11 C | SUBROUTINE GMREDI_CALC_TENSOR |
12 C | o Calculate tensor elements for GM/Redi tensor. |
13 C |==========================================================|
14 C \==========================================================/
15 IMPLICIT NONE
16
17 C == Global variables ==
18 #include "SIZE.h"
19 #include "GRID.h"
20 #include "DYNVARS.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "GMREDI.h"
24 #include "GMREDI_DIAGS.h"
25
26 C == Routine arguments ==
27 C
28 _RL sigmaX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
29 _RL sigmaY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
30 _RL sigmaR(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
31 INTEGER bi,bj,iMin,iMax,jMin,jMax,K
32 INTEGER myThid
33 CEndOfInterface
34
35 #ifdef ALLOW_GMREDI
36
37 C == Local variables ==
38 INTEGER i,j,km1,kp1
39 _RL SlopeX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
40 _RL SlopeY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
41 _RL dSigmaDrReal(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
42 _RL dRdSigmaLtd(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
43 _RL Ssq
44
45 #ifdef GM_VISBECK_VARIABLE_K
46 _RS deltaH,zero_rs
47 PARAMETER(zero_rs=0.)
48 _RL N2,SN
49 #endif
50
51
52 km1=max(1,K-1)
53 kp1=min(Nr,K)
54
55
56 #ifdef ALLOW_AUTODIFF_TAMC
57 !HPF$ INDEPENDENT
58 #endif
59 DO j=1-Oly+1,sNy+Oly-1
60 #ifdef ALLOW_AUTODIFF_TAMC
61 !HPF$ INDEPENDENT
62 #endif
63 DO i=1-Olx+1,sNx+Olx-1
64
65 C Gradient of Sigma at rVel points
66 SlopeX(i,j)=0.25*( sigmaX(i+1, j ,km1) +sigmaX(i,j,km1)
67 & +sigmaX(i+1, j , k ) +sigmaX(i,j, k ) )
68 SlopeY(i,j)=0.25*( sigmaY( i ,j+1,km1) +sigmaY(i,j,km1)
69 & +sigmaY( i ,j+1, k ) +sigmaY(i,j, k ) )
70 dSigmaDrReal(i,j)=sigmaR(i,j,k)
71
72 if (hFacC(i,j,k,bi,bj).eq.0.) then
73 SlopeX(i,j)=0.
74 SlopeY(i,j)=0.
75 endif
76
77 ENDDO
78 ENDDO
79
80 C Calculate slopes for use in tensor, taper and/or clip
81 CALL GMREDI_SLOPE_LIMIT(
82 I dSigmadRReal,
83 I rF(K),
84 U SlopeX, SlopeY,
85 O dRdSigmaLtd,
86 I bi, bj, myThid )
87
88 DO j=1-Oly+1,sNy+Oly-1
89 DO i=1-Olx+1,sNx+Olx-1
90
91 C Mask Iso-neutral slopes
92 if (hFacC(i,j,k,bi,bj).eq.0.) then
93 SlopeX(i,j)=0.
94 SlopeY(i,j)=0.
95 endif
96 Ssq=SlopeX(i,j)*SlopeX(i,j)+SlopeY(i,j)*SlopeY(i,j)
97
98 C Components of Redi/GM tensor
99 Kwx(i,j,k,bi,bj)=2.*SlopeX(i,j)
100 Kwy(i,j,k,bi,bj)=2.*SlopeY(i,j)
101 Kwz(i,j,k,bi,bj)=Ssq
102
103 #ifdef GM_VISBECK_VARIABLE_K
104 C-- Depth average of M^2/N^2 * N
105
106 C Calculate terms for mean Richardson number
107 C which is used in the "variable K" parameterisaton.
108 C Distance between interface above layer and the integration depth
109 deltaH=abs(GM_Visbeck_depth)-abs(rF(k))
110 C If positive we limit this to the layer thickness
111 deltaH=min(deltaH,drF(k))
112 C If negative then we are below the integration level
113 deltaH=max(deltaH,zero_rs)
114 C Now we convert deltaH to a non-dimensional fraction
115 deltaH=deltaH/GM_Visbeck_depth
116
117 if (K.eq.2) VisbeckK(i,j,bi,bj)=0.
118 Calt? if (dSigmaDrReal(i,j).NE.0.) then
119 Calt? N2=(-Gravity*recip_Rhonil)*dSigmaDrReal(i,j)
120 if (dRdSigmaLtd(i,j).NE.0.) then
121 N2=(-Gravity*recip_Rhonil)/dRdSigmaLtd(i,j)
122 SN=sqrt(Ssq*N2)
123 VisbeckK(i,j,bi,bj)=VisbeckK(i,j,bi,bj)+deltaH
124 & *GM_Visbeck_alpha*GM_Visbeck_length*GM_Visbeck_length*SN
125 endif
126
127 C Limit range that KapGM can take
128 VisbeckK(i,j,bi,bj)=
129 & min(VisbeckK(i,j,bi,bj),GM_Visbeck_maxval_K)
130
131 #endif /* GM_VISBECK_VARIABLE_K */
132
133
134 #ifdef INCLUDE_DIAGNOSTICS_INTERFACE_CODE
135 C-- Time-average
136 GM_Kwx_T(i,j,k,bi,bj)=GM_Kwx_T(i,j,k,bi,bj)
137 & +Kwx(i,j,k,bi,bj)*deltaTclock
138 GM_Kwy_T(i,j,k,bi,bj)=GM_Kwy_T(i,j,k,bi,bj)
139 & +Kwy(i,j,k,bi,bj)*deltaTclock
140 GM_Kwz_T(i,j,k,bi,bj)=GM_Kwz_T(i,j,k,bi,bj)
141 & +Kwz(i,j,k,bi,bj)*deltaTclock
142 #ifdef GM_VISBECK_VARIABLE_K
143 IF (K.EQ.Nr)
144 & Visbeck_K_T(i,j,bi,bj)=Visbeck_K_T(i,j,bi,bj)
145 & +VisbeckK(i,j,bi,bj)*deltaTclock
146 #endif
147 ENDDO
148 ENDDO
149 GM_TimeAve(k,bi,bj)=GM_TimeAve(k,bi,bj)+deltaTclock
150 #endif /* INCLUDE_DIAGNOSTICS_INTERFACE_CODE */
151
152
153
154 #ifdef GM_NON_UNITY_DIAGONAL
155 C Gradient of Sigma at U points
156 DO j=1-Oly+1,sNy+Oly-1
157 DO i=1-Olx+1,sNx+Olx-1
158 SlopeX(i,j)=sigmaX(i,j,km1)
159 & *_maskW(i,j,k,bi,bj)
160 SlopeY(i,j)=0.25*( sigmaY(i-1,j+1,k) +sigmaY(i,j+1,k)
161 & +sigmaY(i-1, j ,k) +sigmaY(i, j ,k) )
162 & *_maskW(i,j,k,bi,bj)
163 dSigmaDrReal(i,j)=0.25*( sigmaR(i-1,j, k ) +sigmaR(i,j, k )
164 & +sigmaR(i-1,j,kp1) +sigmaR(i,j,kp1) )
165 & *_maskW(i,j,k,bi,bj)
166 ENDDO
167 ENDDO
168
169 C Calculate slopes for use in tensor, taper and/or clip
170 CALL GMREDI_SLOPE_LIMIT(
171 I dSigmadRReal,
172 I rF(K),
173 U SlopeX, SlopeY,
174 O dRdSigmaLtd,
175 I bi, bj, myThid )
176
177 DO j=1-Oly+1,sNy+Oly-1
178 DO i=1-Olx+1,sNx+Olx-1
179 Kux(i,j,k,bi,bj)=(dSigmaDrReal(i,j)*dRdSigmaLtd(i,j))**2
180 ENDDO
181 ENDDO
182
183 C Gradient of Sigma at V points
184 DO j=1-Oly+1,sNy+Oly-1
185 DO i=1-Olx+1,sNx+Olx-1
186 SlopeX(i,j)=0.25*( sigmaX(i, j ,k) +sigmaX(i+1, j ,k)
187 & +sigmaX(i,j-1,k) +sigmaX(i+1,j-1,k) )
188 & *_maskS(i,j,k,bi,bj)
189 SlopeY(i,j)=sigmaY(i,j,km1)
190 & *_maskS(i,j,k,bi,bj)
191 dSigmaDrReal(i,j)=0.25*( sigmaR(i,j-1, k ) +sigmaR(i,j, k )
192 & +sigmaR(i,j-1,kp1) +sigmaR(i,j,kp1) )
193 & *_maskS(i,j,k,bi,bj)
194 ENDDO
195 ENDDO
196
197 C Calculate slopes for use in tensor, taper and/or clip
198 CALL GMREDI_SLOPE_LIMIT(
199 I dSigmadRReal,
200 I rF(K),
201 U SlopeX, SlopeY,
202 O dRdSigmaLtd,
203 I bi, bj, myThid )
204
205 DO j=1-Oly+1,sNy+Oly-1
206 DO i=1-Olx+1,sNx+Olx-1
207 Kvy(i,j,k,bi,bj)=(dSigmaDrReal(i,j)*dRdSigmaLtd(i,j))**2
208 ENDDO
209 ENDDO
210
211 #endif /* GM_NON_UNITY_DIAGONAL */
212
213
214
215 #endif /* ALLOW_GMREDI */
216
217 RETURN
218 END
219
220
221 SUBROUTINE GMREDI_CALC_TENSOR_DUMMY(
222 I bi, bj, iMin, iMax, jMin, jMax, K,
223 I sigmaX, sigmaY, sigmaR,
224 I myThid )
225 C /==========================================================\
226 C | SUBROUTINE GMREDI_CALC_TENSOR |
227 C | o Calculate tensor elements for GM/Redi tensor. |
228 C |==========================================================|
229 C \==========================================================/
230 IMPLICIT NONE
231
232 C == Global variables ==
233 #include "SIZE.h"
234 #include "GRID.h"
235 #include "DYNVARS.h"
236 #include "EEPARAMS.h"
237 #include "PARAMS.h"
238 #include "GMREDI.h"
239
240 C == Routine arguments ==
241 C
242 _RL sigmaX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
243 _RL sigmaY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
244 _RL sigmaR(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
245 INTEGER bi,bj,iMin,iMax,jMin,jMax,K
246 INTEGER myThid
247 CEndOfInterface
248
249 INTEGER i, j
250
251 #ifdef ALLOW_GMREDI
252
253 DO j=1-Oly+1,sNy+Oly-1
254 DO i=1-Olx+1,sNx+Olx-1
255 Kwx(i,j,k,bi,bj) = 0.0
256 Kwy(i,j,k,bi,bj) = 0.0
257 Kwz(i,j,k,bi,bj) = 0.0
258 ENDDO
259 ENDDO
260 #endif /* ALLOW_GMREDI */
261
262 end

  ViewVC Help
Powered by ViewVC 1.1.22