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

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

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


Revision 1.3 - (show annotations) (download)
Thu Nov 14 22:43:49 2002 UTC (21 years, 5 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint47e_post, checkpoint47c_post, checkpoint47d_pre, checkpoint47a_post, checkpoint47d_post, checkpoint47g_post, branch-exfmods-tag, checkpoint47b_post, checkpoint47f_post, checkpoint47
Branch point for: branch-exfmods-curt
Changes since 1.2: +138 -39 lines
o * "clean" adjoint code (in terms of extensive recomputations)
    can now be obtained for all GMREDI options (i.e. for
    - GM_VISBECK_VARIABLE_K
    - GM_NON_UNITY_DIAGONAL
    - GM_EXTRA_DIAGONAL
    - GM_BOLUS_ADVEC )
  * However, wrong gradient check problem remains unsolved.
  * New CPP options have been introduced for different
    tapering schemes

1 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_slope_psi.F,v 1.2 2002/02/15 21:28:07 heimbach Exp $
2 C $Name: $
3
4 #include "GMREDI_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE GMREDI_SLOPE_PSI_B(
8 I dSigmaDrW,dSigmaDrS,
9 I depthZ,K,
10 U SlopeX, SlopeY,
11 O taperX, taperY,
12 I bi,bj, myThid )
13 C /==========================================================\
14 C | SUBROUTINE GMREDI_SLOPE_PSI_B |
15 C | o Calculate slopes for use in GM/Redi tensor |
16 C |==========================================================|
17 C | On entry: |
18 C | dSigmaDrW conatins the d/dz Sigma |
19 C | SlopeX/Y contains X/Y gradients of sigma |
20 C | depthZ conatins the height (m) of level |
21 C | On exit: |
22 C | dSigmaDrW conatins the effective dSig/dz |
23 C | SlopeX/Y contains X/Y slopes |
24 C | taperFct contains tapering funct. value ; |
25 C | = 1 when using no tapering |
26 C \==========================================================/
27 IMPLICIT NONE
28
29 C == Global variables ==
30 #include "SIZE.h"
31 #include "EEPARAMS.h"
32 #include "GMREDI.h"
33 #include "PARAMS.h"
34
35 #ifdef ALLOW_AUTODIFF_TAMC
36 #include "tamc.h"
37 #include "tamc_keys.h"
38 #endif /* ALLOW_AUTODIFF_TAMC */
39
40 C == Routine arguments ==
41 C
42 _RL SlopeX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
43 _RL SlopeY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
44 _RL dSigmaDrW(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
45 _RL dSigmaDrS(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
46 _RL taperX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
47 _RL taperY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
48 _RL depthZ
49 INTEGER K,bi,bj,myThid
50 CEndOfInterface
51
52 #ifdef ALLOW_GMREDI
53 #ifdef GM_BOLUS_ADVEC
54
55 C == Local variables ==
56 _RL gradSmod(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
57 _RL dSigmaDrLtd(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
58 _RL drdsigmaltd(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
59 _RL f1,Smod,f2,Rnondim,Cspd,Lrho
60 _RL maxSlopeSqr
61 _RL fpi
62 PARAMETER(fpi=3.141592653589793047592d0)
63 INTEGER i,j
64
65 #ifdef ALLOW_AUTODIFF_TAMC
66 act1 = bi - myBxLo(myThid)
67 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
68 act2 = bj - myByLo(myThid)
69 max2 = myByHi(myThid) - myByLo(myThid) + 1
70 act3 = myThid - 1
71 max3 = nTx*nTy
72 act4 = ikey_dynamics - 1
73 ikey = (act1 + 1) + act2*max1
74 & + act3*max1*max2
75 & + act4*max1*max2*max3
76 kkey = (ikey-1)*Nr + k
77 #endif /* ALLOW_AUTODIFF_TAMC */
78
79 #ifdef ALLOW_AUTODIFF_TAMC
80 CADJ STORE slopeX(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
81 CADJ STORE slopeY(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
82 #endif
83
84 IF (GM_taper_scheme.EQ.'orig' .OR.
85 & GM_taper_scheme.EQ.'clipping') THEN
86
87 C- Original implementation in mitgcmuv
88 C (this turns out to be the same as Cox slope clipping)
89
90 C-- X-comp
91
92 #ifdef ALLOW_AUTODIFF_TAMC
93 DO j=1-Oly+1,sNy+Oly-1
94 DO i=1-Olx+1,sNx+Olx-1
95 dSigmaDrLtd(i,j) = 0. _d 0
96 ENDDO
97 ENDDO
98 #endif /* ALLOW_AUTODIFF_TAMC */
99
100 C- Cox 1987 "Slope clipping"
101 DO j=1-Oly+1,sNy+Oly-1
102 DO i=1-Olx+1,sNx+Olx-1
103 dsigmadrltd(i,j) = -(GM_Small_Number+
104 & abs(SlopeX(i,j))*GM_rMaxSlope)
105 ENDDO
106 ENDDO
107 #ifdef ALLOW_AUTODIFF_TAMC
108 CADJ STORE dSigmaDrltd(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
109 CADJ STORE dSigmaDrW(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
110 #endif
111 DO j=1-Oly+1,sNy+Oly-1
112 DO i=1-Olx+1,sNx+Olx-1
113 IF (dSigmaDrW(i,j).GE.dsigmadrltd(i,j))
114 & dSigmaDrW(i,j) = dsigmadrltd(i,j)
115 ENDDO
116 ENDDO
117 #ifdef ALLOW_AUTODIFF_TAMC
118 CADJ STORE dSigmaDrW(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
119 #endif
120 DO j=1-Oly+1,sNy+Oly-1
121 DO i=1-Olx+1,sNx+Olx-1
122 SlopeX(i,j) = -SlopeX(i,j)/dSigmaDrW(i,j)
123 taperX(i,j)=1. _d 0
124 ENDDO
125 ENDDO
126
127 C-- Y-comp
128
129 #ifdef ALLOW_AUTODIFF_TAMC
130 DO j=1-Oly+1,sNy+Oly-1
131 DO i=1-Olx+1,sNx+Olx-1
132 dSigmaDrLtd(i,j) = 0. _d 0
133 ENDDO
134 ENDDO
135 #endif /* ALLOW_AUTODIFF_TAMC */
136 DO j=1-Oly+1,sNy+Oly-1
137 DO i=1-Olx+1,sNx+Olx-1
138 dsigmadrltd(i,j) = -(GM_Small_Number+
139 & abs(SlopeY(i,j))*GM_rMaxSlope)
140 ENDDO
141 ENDDO
142 #ifdef ALLOW_AUTODIFF_TAMC
143 CADJ STORE dSigmaDrltd(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
144 CADJ STORE dSigmaDrS(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
145 #endif
146 DO j=1-Oly+1,sNy+Oly-1
147 DO i=1-Olx+1,sNx+Olx-1
148 IF (dSigmaDrS(i,j).GE.dsigmadrltd(i,j))
149 & dSigmaDrS(i,j) = dsigmadrltd(i,j)
150 ENDDO
151 ENDDO
152 #ifdef ALLOW_AUTODIFF_TAMC
153 CADJ STORE dSigmaDrS(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
154 #endif
155 DO j=1-Oly+1,sNy+Oly-1
156 DO i=1-Olx+1,sNx+Olx-1
157 SlopeY(i,j) = -SlopeY(i,j)/dSigmaDrS(i,j)
158 taperY(i,j)=1. _d 0
159 ENDDO
160 ENDDO
161
162 ELSE
163
164 #ifdef ALLOW_AUTODIFF_TAMC
165 CADJ STORE slopeX(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
166 CADJ STORE dSigmaDrW(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
167 #endif
168
169 C- Compute the slope, no clipping, but avoid reverse slope in negatively
170 C stratified (Sigma_Z > 0) region :
171 DO j=1-Oly+1,sNy+Oly-1
172 DO i=1-Olx+1,sNx+Olx-1
173 dsigmadrltd(i,j) = -GM_Small_Number
174 IF (dSigmaDrW(i,j).GE.dsigmadrltd(i,j))
175 & dSigmaDrW(i,j) = dsigmadrltd(i,j)
176 ENDDO
177 ENDDO
178 #ifdef ALLOW_AUTODIFF_TAMC
179 CADJ STORE dsigmadrW(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
180 #endif
181 DO j=1-Oly+1,sNy+Oly-1
182 DO i=1-Olx+1,sNx+Olx-1
183 drdsigmaltd(i,j) = 1./dSigmaDrW(i,j)
184 SlopeX(i,j) = -SlopeX(i,j)/dSigmaDrW(i,j)
185 taperX(i,j)=1. _d 0
186 ENDDO
187 ENDDO
188
189 #ifdef ALLOW_AUTODIFF_TAMC
190 CADJ STORE slopeY(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
191 CADJ STORE dSigmaDrS(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
192 #endif
193
194 DO j=1-Oly+1,sNy+Oly-1
195 DO i=1-Olx+1,sNx+Olx-1
196 dsigmadrltd(i,j) = -GM_Small_Number
197 IF (dSigmaDrS(i,j).GE.dsigmadrltd(i,j))
198 & dSigmaDrS(i,j) = dsigmadrltd(i,j)
199 ENDDO
200 ENDDO
201 #ifdef ALLOW_AUTODIFF_TAMC
202 CADJ STORE dsigmadrS(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
203 #endif
204 DO j=1-Oly+1,sNy+Oly-1
205 DO i=1-Olx+1,sNx+Olx-1
206 SlopeY(i,j) = -SlopeY(i,j)/dSigmaDrS(i,j)
207 taperY(i,j)=1. _d 0
208 ENDDO
209 ENDDO
210
211 C- Compute the tapering function for the GM+Redi tensor :
212
213 #ifdef ALLOW_AUTODIFF_TAMC
214 CADJ STORE slopeX(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
215 CADJ STORE slopeY(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
216 #endif
217
218 IF (GM_taper_scheme.EQ.'linear') THEN
219
220 C- Simplest adiabatic tapering = Smax/Slope (linear)
221 DO j=1-Oly+1,sNy+Oly-1
222 DO i=1-Olx+1,sNx+Olx-1
223
224 IF (abs(SlopeX(i,j)).GT.GM_maxSlope)
225 & taperX(i,j)=GM_maxSlope/abs(SlopeX(i,j))
226 IF (abs(SlopeY(i,j)).GT.GM_maxSlope)
227 & taperY(i,j)=GM_maxSlope/abs(SlopeY(i,j))
228
229 ENDDO
230 ENDDO
231
232 ELSEIF (GM_taper_scheme.EQ.'gkw91') THEN
233
234 C- Gerdes, Koberle and Willebrand, Clim. Dyn. 1991
235 maxSlopeSqr = GM_maxSlope*GM_maxSlope
236 DO j=1-Oly+1,sNy+Oly-1
237 DO i=1-Olx+1,sNx+Olx-1
238
239 IF (abs(SlopeX(i,j)).GT.GM_maxSlope)
240 & taperX(i,j)=maxSlopeSqr/(SlopeX(i,j)*SlopeX(i,j))
241 IF (abs(SlopeY(i,j)).GT.GM_maxSlope)
242 & taperY(i,j)=maxSlopeSqr/(SlopeY(i,j)*SlopeY(i,j))
243
244 ENDDO
245 ENDDO
246
247 ELSEIF (GM_taper_scheme.EQ.'dm95') THEN
248
249 C- Danabasoglu and McWilliams, J. Clim. 1995
250 DO j=1-Oly+1,sNy+Oly-1
251 DO i=1-Olx+1,sNx+Olx-1
252
253 Smod = abs(SlopeX(i,j))
254 taperX(i,j)=0.5*(1.+tanh( (GM_Scrit-Smod)/GM_Sd ))
255 Smod = abs(SlopeY(i,j))
256 taperY(i,j)=0.5*(1.+tanh( (GM_Scrit-Smod)/GM_Sd ))
257
258 ENDDO
259 ENDDO
260
261 ELSEIF (GM_taper_scheme.EQ.'ldd97') THEN
262
263 C- Large, Danabasoglu and Doney, JPO 1997
264 DO j=1-Oly+1,sNy+Oly-1
265 DO i=1-Olx+1,sNx+Olx-1
266
267 Cspd=2.
268 Lrho=100.e3
269 if (FCori(i,j,bi,bj).NE.0.) Lrho=Cspd/abs(Fcori(i,j,bi,bj))
270 Lrho=min(Lrho , 100. _d 3)
271 Lrho=max(Lrho , 15. _d 3)
272
273 Smod = abs(SlopeX(i,j))
274 f1=0.5*(1.+tanh( (GM_Scrit-Smod)/GM_Sd ))
275 if (Smod.NE.0.) then
276 Rnondim=depthZ/(Lrho*Smod)
277 else
278 Rnondim=0.
279 endif
280 f2=0.5*(1.+sin( fpi*(Rnondim-0.5)))
281 taperX(i,j)=f1*f2
282
283 Smod = abs(SlopeY(i,j))
284 f1=0.5*(1.+tanh( (GM_Scrit-Smod)/GM_Sd ))
285 if (Smod.NE.0.) then
286 Rnondim=depthZ/(Lrho*Smod)
287 else
288 Rnondim=0.
289 endif
290 f2=0.5*(1.+sin( fpi*(Rnondim-0.5)))
291 taperY(i,j)=f1*f2
292
293 ENDDO
294 ENDDO
295
296 ELSEIF (GM_taper_scheme.NE.' ') THEN
297 STOP 'GMREDI_SLOPE_PSI: Bad GM_taper_scheme'
298 ENDIF
299
300 ENDIF
301
302
303 #endif /* BOLUS_ADVEC */
304 #endif /* ALLOW_GMREDI */
305
306 RETURN
307 END

  ViewVC Help
Powered by ViewVC 1.1.22