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

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

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


Revision 1.12 - (hide annotations) (download)
Sun Mar 24 02:33:16 2002 UTC (22 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint46n_post, checkpoint46l_post, checkpoint46g_pre, checkpoint46f_post, checkpoint46b_post, checkpoint46l_pre, checkpoint46d_pre, checkpoint45d_post, checkpoint46j_pre, checkpoint46a_post, checkpoint46j_post, checkpoint46k_post, checkpoint45a_post, checkpoint46e_pre, checkpoint45b_post, checkpoint46b_pre, checkpoint46c_pre, checkpoint46, checkpoint46h_pre, checkpoint46m_post, checkpoint46a_pre, checkpoint45c_post, checkpoint44h_post, checkpoint46g_post, checkpoint46i_post, checkpoint46c_post, checkpoint46e_post, checkpoint45, checkpoint46h_post, checkpoint46d_post
Changes since 1.11: +89 -63 lines
Various modifications to generate more stable adjoint of GMRedi.

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

  ViewVC Help
Powered by ViewVC 1.1.22