/[MITgcm]/MITgcm/model/src/calc_r_star.F
ViewVC logotype

Contents of /MITgcm/model/src/calc_r_star.F

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


Revision 1.18 - (show annotations) (download)
Mon Sep 20 15:54:36 2010 UTC (13 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62q, checkpoint62p, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l
Changes since 1.17: +4 -4 lines
use simple average (not area weighted) of rStarFac at U,V point
 when using vectorInvariant with selectKEscheme=1,3 (consitent with
 momentum vertical advection)

1 C $Header: /u/gcmpack/MITgcm/model/src/calc_r_star.F,v 1.17 2010/09/10 17:52:05 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6 #ifdef ALLOW_EXCH2
7 # include "W2_OPTIONS.h"
8 #endif
9
10 CBOP
11 C !ROUTINE: CALC_R_STAR
12 C !INTERFACE:
13 SUBROUTINE CALC_R_STAR( etaFld,
14 I myTime, myIter, myThid )
15 C !DESCRIPTION: \bv
16 C *==========================================================*
17 C | SUBROUTINE CALC_R_STAR
18 C | o Calculate new column thickness & scaling factor for r*
19 C | according to the surface r-position (Non-Lin Free-Surf)
20 C *==========================================================*
21 C \ev
22
23 C !USES:
24 IMPLICIT NONE
25 C == Global variables
26 #include "SIZE.h"
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #include "GRID.h"
30 #include "SURFACE.h"
31
32 C !INPUT/OUTPUT PARAMETERS:
33 C == Routine arguments ==
34 C myTime :: Current time in simulation
35 C myIter :: Current iteration number in simulation
36 C myThid :: Thread number for this instance of the routine.
37 C etaFld :: current eta field used to update the hFactor
38 _RL myTime
39 INTEGER myIter
40 INTEGER myThid
41 _RL etaFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
42
43 #ifdef NONLIN_FRSURF
44
45 C !LOCAL VARIABLES:
46 C Local variables
47 C rStarAreaWeight :: use area weighted average for rStarFac at U & V point
48 C i,j, bi,bj :: loop counter
49 C numbWrite :: count the Number of warning written on STD-ERR file
50 C numbWrMax :: maximum Number of warning written on STD-ERR file
51 LOGICAL rStarAreaWeight
52 INTEGER i,j,bi,bj
53 INTEGER numbWrite, numbWrMax
54 INTEGER icntc1, icntc2, icntw, icnts
55 INTEGER iic, jjc, iic2, jjc2, iiw, jjw, iis, jjs
56 _RL tmpfldW, tmpfldS
57 c CHARACTER*(MAX_LEN_MBUF) suff
58 CEOP
59
60 rStarAreaWeight = .TRUE.
61 C- Area-weighted average consistent with KE (& vert. advection):
62 IF ( vectorInvariantMomentum .AND.
63 & (selectKEscheme.EQ.1 .OR. selectKEscheme.EQ.3)
64 & ) rStarAreaWeight =.FALSE.
65
66 #ifdef W2_FILL_NULL_REGIONS
67 INTEGER ii,jj
68 #endif
69 DATA numbWrite / 0 /
70 numbWrMax = Nx*Ny
71
72 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
73
74 #ifdef ALLOW_DEBUG
75 IF (debugMode) CALL DEBUG_ENTER('CALC_R_STAR',myThid)
76 #endif
77
78 DO bj=myByLo(myThid), myByHi(myThid)
79 DO bi=myBxLo(myThid), myBxHi(myThid)
80 C- 1rst bi,bj loop :
81
82 C-- copy rStarFacX -> rStarExpX
83 DO j=1-Oly,sNy+Oly
84 DO i=1-Olx,sNx+Olx
85 rStarExpC(i,j,bi,bj) = rStarFacC(i,j,bi,bj)
86 rStarExpW(i,j,bi,bj) = rStarFacW(i,j,bi,bj)
87 rStarExpS(i,j,bi,bj) = rStarFacS(i,j,bi,bj)
88 ENDDO
89 ENDDO
90
91 C-- Compute the new column thikness :
92 DO j=0,sNy+1
93 DO i=0,sNx+1
94 IF (kSurfC(i,j,bi,bj).LE.Nr ) THEN
95 rStarFacC(i,j,bi,bj) =
96 & (etaFld(i,j,bi,bj)+Ro_surf(i,j,bi,bj)-R_low(i,j,bi,bj))
97 & *recip_Rcol(i,j,bi,bj)
98 ELSE
99 rStarFacC(i,j,bi,bj) = 1.
100 ENDIF
101 ENDDO
102 ENDDO
103 IF ( rStarAreaWeight ) THEN
104 C- Area weighted average
105 DO j=1,sNy
106 DO i=1,sNx+1
107 IF ( kSurfW(i,j,bi,bj).LE.Nr ) THEN
108 tmpfldW = rSurfW(i,j,bi,bj) - rLowW(i,j,bi,bj)
109 rStarFacW(i,j,bi,bj) =
110 & ( 0.5 _d 0 *( etaFld(i-1,j,bi,bj)*rA(i-1,j,bi,bj)
111 & +etaFld(i,j,bi,bj)*rA(i,j,bi,bj)
112 & )*recip_rAw(i,j,bi,bj)
113 & +tmpfldW )/tmpfldW
114 ELSE
115 rStarFacW(i,j,bi,bj) = 1.
116 ENDIF
117 ENDDO
118 ENDDO
119 DO j=1,sNy+1
120 DO i=1,sNx
121 IF ( kSurfS(i,j,bi,bj).LE.Nr ) THEN
122 tmpfldS = rSurfS(i,j,bi,bj) - rLowS(i,j,bi,bj)
123 rStarFacS(i,j,bi,bj) =
124 & ( 0.5 _d 0 *( etaFld(i,j-1,bi,bj)*rA(i,j-1,bi,bj)
125 & +etaFld(i,j,bi,bj)*rA(i,j,bi,bj)
126 & )*recip_rAs(i,j,bi,bj)
127 & +tmpfldS )/tmpfldS
128 ELSE
129 rStarFacS(i,j,bi,bj) = 1.
130 ENDIF
131 ENDDO
132 ENDDO
133 ELSE
134 C- Simple average
135 DO j=1,sNy
136 DO i=1,sNx+1
137 IF ( kSurfW(i,j,bi,bj).LE.Nr ) THEN
138 tmpfldW = rSurfW(i,j,bi,bj) - rLowW(i,j,bi,bj)
139 rStarFacW(i,j,bi,bj) =
140 & ( 0.5 _d 0 *( etaFld(i-1,j,bi,bj) + etaFld(i,j,bi,bj) )
141 & +tmpfldW )/tmpfldW
142 ELSE
143 rStarFacW(i,j,bi,bj) = 1.
144 ENDIF
145 ENDDO
146 ENDDO
147 DO j=1,sNy+1
148 DO i=1,sNx
149 IF ( kSurfS(i,j,bi,bj).LE.Nr ) THEN
150 tmpfldS = rSurfS(i,j,bi,bj) - rLowS(i,j,bi,bj)
151 rStarFacS(i,j,bi,bj) =
152 & ( 0.5 _d 0 *( etaFld(i,j-1,bi,bj) + etaFld(i,j,bi,bj) )
153 & +tmpfldS )/tmpfldS
154 ELSE
155 rStarFacS(i,j,bi,bj) = 1.
156 ENDIF
157 ENDDO
158 ENDDO
159 ENDIF
160
161 C- Needs to do something when r* ratio is too small ;
162 C for now, just stop
163 icntc1 = 0
164 icntc2 = 0
165 icntw = 0
166 icnts = 0
167 DO j=1,sNy+1
168 DO i=1,sNx+1
169 IF ( rStarFacC(i,j,bi,bj).LT.hFacInf ) THEN
170 icntc1 = icntc1 + 1
171 iic = i
172 jjc = j
173 ENDIF
174 IF ( rStarFacW(i,j,bi,bj).LT.hFacInf ) THEN
175 icntw = icntw + 1
176 iiw = i
177 jjw = j
178 ENDIF
179 IF ( rStarFacS(i,j,bi,bj).LT.hFacInf ) THEN
180 icnts = icnts + 1
181 iis = i
182 jjs = j
183 ENDIF
184 IF ( rStarFacC(i,j,bi,bj).GT.hFacSup ) THEN
185 icntc2 = icntc2 + 1
186 iic2 = i
187 jjc2 = j
188 ENDIF
189 ENDDO
190 ENDDO
191 IF ( icntc1+icnts+icntw .GT. 0 ) THEN
192 C- Print an error msg and then stop:
193 IF ( icntw .GT. 0 ) THEN
194 tmpfldW = rSurfW(iiw,jjw,bi,bj) - rLowW(iiw,jjw,bi,bj)
195 WRITE(errorMessageUnit,'(A,I8,A,3I4,I10)')
196 & 'WARNING: r*FacW < hFacInf at',icntw,
197 & ' pts : bi,bj,Thid,Iter=',bi,bj,myThid,myIter
198 WRITE(errorMessageUnit,'(A,2I4,A,1F10.6,1P3E14.6)')
199 & ' e.g. at i,j=',iiw,jjw,' ; rStarFac,H,eta =',
200 & rStarFacW(iiw,jjw,bi,bj), tmpfldW,
201 & etaFld(iiw-1,jjw,bi,bj), etaFld(iiw,jjw,bi,bj)
202 WRITE(errorMessageUnit,'(A)')
203 & 'STOP in CALC_R_STAR : too SMALL rStarFacW !'
204 ENDIF
205 IF ( icnts .GT. 0 ) THEN
206 tmpfldS = rSurfS(iis,jjs,bi,bj) - rLowS(iis,jjs,bi,bj)
207 WRITE(errorMessageUnit,'(A,I8,A,3I4,I10)')
208 & 'WARNING: r*FacS < hFacInf at',icnts,
209 & ' pts : bi,bj,Thid,Iter=',bi,bj,myThid,myIter
210 WRITE(errorMessageUnit,'(A,2I4,A,1F10.6,1P3E14.6)')
211 & ' e.g. at i,j=',iis,jjs,' ; rStarFac,H,eta =',
212 & rStarFacS(iis,jjs,bi,bj), tmpfldS,
213 & etaFld(iis,jjs-1,bi,bj), etaFld(iis,jjs,bi,bj)
214 WRITE(errorMessageUnit,'(A)')
215 & 'STOP in CALC_R_STAR : too SMALL rStarFacS !'
216 ENDIF
217 IF ( icntc1 .GT. 0 ) THEN
218 WRITE(errorMessageUnit,'(A,I8,A,3I4,I10)')
219 & 'WARNING: r*FacC < hFacInf at',icntc1,
220 & ' pts : bi,bj,Thid,Iter=',bi,bj,myThid,myIter
221 WRITE(errorMessageUnit,'(A,2I4,A,1F10.6,1P2E14.6)')
222 & ' e.g. at i,j=',iic,jjc,' ; rStarFac,H,eta =',
223 & rStarFacC(iic,jjc,bi,bj),
224 & Ro_surf(iic,jjc,bi,bj)-R_low(iic,jjc,bi,bj),
225 & etaFld(iic,jjc,bi,bj)
226 WRITE(errorMessageUnit,'(A)')
227 & 'STOP in CALC_R_STAR : too SMALL rStarFacC !'
228 ENDIF
229 STOP 'ABNORMAL END: S/R CALC_R_STAR'
230 ENDIF
231 C-- Usefull warning when r*Fac becomes very large:
232 IF ( icntc2.GT.0 .AND. numbWrite.LE.numbWrMax ) THEN
233 numbWrite = numbWrite + 1
234 WRITE(errorMessageUnit,'(A,I8,A,3I4,I10)')
235 & 'WARNING: r*FacC > hFacSup at',icntc2,
236 & ' pts : bi,bj,Thid,Iter=',bi,bj,myThid,myIter
237 WRITE(errorMessageUnit,'(A,2I4,A,1F10.6,1P2E14.6)')
238 & ' e.g. at i,j=',iic2,jjc2,' ; rStarFac,H,eta =',
239 & rStarFacC(iic2,jjc2,bi,bj),
240 & Ro_surf(iic2,jjc2,bi,bj)-R_low(iic2,jjc2,bi,bj),
241 & etaFld(iic2,jjc2,bi,bj)
242 ENDIF
243
244 C- end 1rst bi,bj loop.
245 ENDDO
246 ENDDO
247
248 _EXCH_XY_RL( rStarFacC, myThid )
249 CALL EXCH_UV_XY_RL(rStarFacW,rStarFacS,.FALSE.,myThid)
250
251 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
252
253 DO bj=myByLo(myThid), myByHi(myThid)
254 DO bi=myBxLo(myThid), myBxHi(myThid)
255 C- 2nd bi,bj loop :
256
257 #ifdef ALLOW_EXCH2
258 #ifdef W2_FILL_NULL_REGIONS
259 C- Note: rStarFacC was non-zero EVERYWHERE before exch, but exch2 put zeros
260 C in the corner regions of the tile (e.g.:[1-Olx:0,1-Oly:0])
261 C => need to add those lines (or to fix exch2):
262 DO j=1,Oly
263 DO i=1,Olx
264 ii = sNx+i
265 jj = sNy+j
266
267 IF (kSurfC(1-i,1-j,bi,bj).GT.Nr) rStarFacC(1-i,1-j,bi,bj)= 1.
268 IF (kSurfC(ii, 1-j,bi,bj).GT.Nr) rStarFacC(ii, 1-j,bi,bj)= 1.
269 IF (kSurfC(1-i,jj, bi,bj).GT.Nr) rStarFacC(1-i,jj, bi,bj)= 1.
270 IF (kSurfC(ii, jj, bi,bj).GT.Nr) rStarFacC(ii, jj, bi,bj)= 1.
271
272 IF (kSurfW(1-i,1-j,bi,bj).GT.Nr) rStarFacW(1-i,1-j,bi,bj)= 1.
273 IF (kSurfW(ii, 1-j,bi,bj).GT.Nr) rStarFacW(ii, 1-j,bi,bj)= 1.
274 IF (kSurfW(1-i,jj, bi,bj).GT.Nr) rStarFacW(1-i,jj, bi,bj)= 1.
275 IF (kSurfW(ii, jj, bi,bj).GT.Nr) rStarFacW(ii, jj, bi,bj)= 1.
276
277 IF (kSurfS(1-i,1-j,bi,bj).GT.Nr) rStarFacS(1-i,1-j,bi,bj)= 1.
278 IF (kSurfS(ii, 1-j,bi,bj).GT.Nr) rStarFacS(ii, 1-j,bi,bj)= 1.
279 IF (kSurfS(1-i,jj, bi,bj).GT.Nr) rStarFacS(1-i,jj, bi,bj)= 1.
280 IF (kSurfS(ii, jj, bi,bj).GT.Nr) rStarFacS(ii, jj, bi,bj)= 1.
281
282 ENDDO
283 ENDDO
284 #endif /* W2_FILL_NULL_REGIONS */
285 #endif /* ALLOW_EXCH2 */
286
287 DO j=1-Oly,sNy+Oly
288 DO i=1-Olx,sNx+Olx
289 rStarDhCDt(i,j,bi,bj)=(rStarFacC(i,j,bi,bj)
290 & -rStarExpC(i,j,bi,bj))/deltaTfreesurf
291 rStarDhWDt(i,j,bi,bj)=(rStarFacW(i,j,bi,bj)
292 & -rStarExpW(i,j,bi,bj))/deltaTfreesurf
293 rStarDhSDt(i,j,bi,bj)=(rStarFacS(i,j,bi,bj)
294 & -rStarExpS(i,j,bi,bj))/deltaTfreesurf
295 rStarExpC(i,j,bi,bj) = rStarFacC(i,j,bi,bj)
296 & / rStarExpC(i,j,bi,bj)
297 rStarExpW(i,j,bi,bj) = rStarFacW(i,j,bi,bj)
298 & / rStarExpW(i,j,bi,bj)
299 rStarExpS(i,j,bi,bj) = rStarFacS(i,j,bi,bj)
300 & / rStarExpS(i,j,bi,bj)
301 ENDDO
302 ENDDO
303
304 C- end 2nd bi,bj loop.
305 ENDDO
306 ENDDO
307
308 #ifdef ALLOW_DEBUG
309 IF (debugMode) CALL DEBUG_LEAVE('CALC_R_STAR',myThid)
310 #endif
311
312 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
313 #endif /* NONLIN_FRSURF */
314
315 RETURN
316 END

  ViewVC Help
Powered by ViewVC 1.1.22