/[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.13 - (show annotations) (download)
Mon Oct 29 18:15:29 2007 UTC (16 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59k, checkpoint61f, checkpoint61n, checkpoint59j, checkpoint61q, checkpoint61e, checkpoint61g, checkpoint61d, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.12: +3 -30 lines
clean-up: remove initialisation (done in ini_r_star)

1 C $Header: /u/gcmpack/MITgcm/model/src/calc_r_star.F,v 1.12 2007/08/19 21:58:41 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 i,j,k,bi,bj :: loop counter
48 C numbWrite :: count the Number of warning written on STD-ERR file
49 C numbWrMax :: maximum Number of warning written on STD-ERR file
50 INTEGER i,j,k,bi,bj
51 INTEGER numbWrite, numbWrMax
52 INTEGER icntc1, icntc2, icntw, icnts
53 INTEGER iic, jjc, iic2, jjc2, iiw, jjw, iis, jjs
54 _RL tmpfldW, tmpfldS
55 c CHARACTER*(MAX_LEN_MBUF) suff
56 CEOP
57 #ifdef W2_FILL_NULL_REGIONS
58 INTEGER ii,jj
59 #endif
60 DATA numbWrite / 0 /
61 numbWrMax = Nx*Ny
62
63 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
64
65 #ifdef ALLOW_DEBUG
66 IF (debugMode) CALL DEBUG_ENTER('CALC_R_STAR',myThid)
67 #endif
68
69 DO bj=myByLo(myThid), myByHi(myThid)
70 DO bi=myBxLo(myThid), myBxHi(myThid)
71 C- 1rst bi,bj loop :
72
73 C-- copy rStarFacX -> rStarExpX
74 DO j=1-Oly,sNy+Oly
75 DO i=1-Olx,sNx+Olx
76 rStarExpC(i,j,bi,bj) = rStarFacC(i,j,bi,bj)
77 rStarExpW(i,j,bi,bj) = rStarFacW(i,j,bi,bj)
78 rStarExpS(i,j,bi,bj) = rStarFacS(i,j,bi,bj)
79 ENDDO
80 ENDDO
81
82 C-- Compute the new column thikness :
83 DO j=0,sNy+1
84 DO i=0,sNx+1
85 IF (maskH(i,j,bi,bj).EQ.1. ) THEN
86 rStarFacC(i,j,bi,bj) =
87 & (etaFld(i,j,bi,bj)+Ro_surf(i,j,bi,bj)-R_low(i,j,bi,bj))
88 & *recip_Rcol(i,j,bi,bj)
89 ELSE
90 rStarFacC(i,j,bi,bj) = 1.
91 ENDIF
92 ENDDO
93 ENDDO
94 DO j=1,sNy
95 DO i=1,sNx+1
96 IF ( ksurfW(i,j,bi,bj).LE.Nr ) THEN
97 tmpfldW = MIN( Ro_surf(i-1,j,bi,bj), Ro_surf(i,j,bi,bj) )
98 & - MAX( R_low(i-1,j,bi,bj), R_low(i,j,bi,bj) )
99 rStarFacW(i,j,bi,bj) =
100 & ( 0.5 _d 0 *( etaFld(i-1,j,bi,bj)*rA(i-1,j,bi,bj)
101 & +etaFld(i,j,bi,bj)*rA(i,j,bi,bj)
102 & )*recip_rAw(i,j,bi,bj)
103 & +tmpfldW )/tmpfldW
104 ELSE
105 rStarFacW(i,j,bi,bj) = 1.
106 ENDIF
107 ENDDO
108 ENDDO
109 DO j=1,sNy+1
110 DO i=1,sNx
111 IF ( ksurfS(i,j,bi,bj).LE.Nr ) THEN
112 tmpfldS = MIN( Ro_surf(i,j-1,bi,bj), Ro_surf(i,j,bi,bj) )
113 & - MAX( R_low(i,j-1,bi,bj), R_low(i,j,bi,bj) )
114 rStarFacS(i,j,bi,bj) =
115 & ( 0.5 _d 0 *( etaFld(i,j-1,bi,bj)*rA(i,j-1,bi,bj)
116 & +etaFld(i,j,bi,bj)*rA(i,j,bi,bj)
117 & )*recip_rAs(i,j,bi,bj)
118 & +tmpfldS )/tmpfldS
119 ELSE
120 rStarFacS(i,j,bi,bj) = 1.
121 ENDIF
122 ENDDO
123 ENDDO
124
125 C- Needs to do something when r* ratio is too small ;
126 C for now, just stop
127 icntc1 = 0
128 icntc2 = 0
129 icntw = 0
130 icnts = 0
131 DO j=1,sNy+1
132 DO i=1,sNx+1
133 IF ( rStarFacC(i,j,bi,bj).LT.hFacInf ) THEN
134 icntc1 = icntc1 + 1
135 iic = i
136 jjc = j
137 ENDIF
138 IF ( rStarFacW(i,j,bi,bj).LT.hFacInf ) THEN
139 icntw = icntw + 1
140 iiw = i
141 jjw = j
142 ENDIF
143 IF ( rStarFacS(i,j,bi,bj).LT.hFacInf ) THEN
144 icnts = icnts + 1
145 iis = i
146 jjs = j
147 ENDIF
148 IF ( rStarFacC(i,j,bi,bj).GT.hFacSup ) THEN
149 icntc2 = icntc2 + 1
150 iic2 = i
151 jjc2 = j
152 ENDIF
153 ENDDO
154 ENDDO
155 IF ( icntc1+icnts+icntw .GT. 0 ) THEN
156 C- Print an error msg and then stop:
157 IF ( icntw .GT. 0 ) THEN
158 tmpfldW =
159 & MIN( Ro_surf(iiw-1,jjw,bi,bj),Ro_surf(iiw,jjw,bi,bj) )
160 & - MAX( R_low(iiw-1,jjw,bi,bj), R_low(iiw,jjw,bi,bj) )
161 WRITE(errorMessageUnit,'(A,I8,A,3I4,I10)')
162 & 'WARNING: r*FacW < hFacInf at',icntw,
163 & ' pts : bi,bj,Thid,Iter=',bi,bj,myThid,myIter
164 WRITE(errorMessageUnit,'(A,2I4,A,1F10.6,1P3E14.6)')
165 & ' e.g. at i,j=',iiw,jjw,' ; rStarFac,H,eta =',
166 & rStarFacW(iiw,jjw,bi,bj), tmpfldW,
167 & etaFld(iiw-1,jjw,bi,bj), etaFld(iiw,jjw,bi,bj)
168 WRITE(errorMessageUnit,'(A)')
169 & 'STOP in CALC_R_STAR : too SMALL rStarFacW !'
170 ENDIF
171 IF ( icnts .GT. 0 ) THEN
172 tmpfldS =
173 & MIN( Ro_surf(iis,jjs-1,bi,bj),Ro_surf(iis,jjs,bi,bj) )
174 & - MAX( R_low(iis,jjs-1,bi,bj), R_low(iis,jjs,bi,bj) )
175 WRITE(errorMessageUnit,'(A,I8,A,3I4,I10)')
176 & 'WARNING: r*FacS < hFacInf at',icnts,
177 & ' pts : bi,bj,Thid,Iter=',bi,bj,myThid,myIter
178 WRITE(errorMessageUnit,'(A,2I4,A,1F10.6,1P3E14.6)')
179 & ' e.g. at i,j=',iis,jjs,' ; rStarFac,H,eta =',
180 & rStarFacS(iis,jjs,bi,bj), tmpfldS,
181 & etaFld(iis,jjs-1,bi,bj), etaFld(iis,jjs,bi,bj)
182 WRITE(errorMessageUnit,'(A)')
183 & 'STOP in CALC_R_STAR : too SMALL rStarFacS !'
184 ENDIF
185 IF ( icntc1 .GT. 0 ) THEN
186 WRITE(errorMessageUnit,'(A,I8,A,3I4,I10)')
187 & 'WARNING: r*FacC < hFacInf at',icntc1,
188 & ' pts : bi,bj,Thid,Iter=',bi,bj,myThid,myIter
189 WRITE(errorMessageUnit,'(A,2I4,A,1F10.6,1P2E14.6)')
190 & ' e.g. at i,j=',iic,jjc,' ; rStarFac,H,eta =',
191 & rStarFacC(iic,jjc,bi,bj),
192 & Ro_surf(iic,jjc,bi,bj)-R_low(iic,jjc,bi,bj),
193 & etaFld(iic,jjc,bi,bj)
194 WRITE(errorMessageUnit,'(A)')
195 & 'STOP in CALC_R_STAR : too SMALL rStarFacC !'
196 ENDIF
197 STOP 'ABNORMAL END: S/R CALC_R_STAR'
198 ENDIF
199 C-- Usefull warning when r*Fac becomes very large:
200 IF ( icntc2.GT.0 .AND. numbWrite.LE.numbWrMax ) THEN
201 numbWrite = numbWrite + 1
202 WRITE(errorMessageUnit,'(A,I8,A,3I4,I10)')
203 & 'WARNING: r*FacC > hFacSup at',icntc2,
204 & ' pts : bi,bj,Thid,Iter=',bi,bj,myThid,myIter
205 WRITE(errorMessageUnit,'(A,2I4,A,1F10.6,1P2E14.6)')
206 & ' e.g. at i,j=',iic2,jjc2,' ; rStarFac,H,eta =',
207 & rStarFacC(iic2,jjc2,bi,bj),
208 & Ro_surf(iic2,jjc2,bi,bj)-R_low(iic2,jjc2,bi,bj),
209 & etaFld(iic2,jjc2,bi,bj)
210 ENDIF
211
212 C- end 1rst bi,bj loop.
213 ENDDO
214 ENDDO
215
216 _EXCH_XY_RL( rStarFacC, myThid )
217 CALL EXCH_UV_XY_RL(rStarFacW,rStarFacS,.FALSE.,myThid)
218
219 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
220
221 DO bj=myByLo(myThid), myByHi(myThid)
222 DO bi=myBxLo(myThid), myBxHi(myThid)
223 C- 2nd bi,bj loop :
224
225 #ifdef ALLOW_EXCH2
226 #ifdef W2_FILL_NULL_REGIONS
227 C- Note: rStarFacC was non-zero EVERYWHERE before exch, but exch2 put zeros
228 C in the corner regions of the tile (e.g.:[1-Olx:0,1-Oly:0])
229 C => need to add those lines (or to fix exch2):
230 DO j=1,Oly
231 DO i=1,Olx
232 ii = sNx+i
233 jj = sNy+j
234
235 IF (ksurfC(1-i,1-j,bi,bj).GT.Nr) rStarFacC(1-i,1-j,bi,bj)= 1.
236 IF (ksurfC(ii, 1-j,bi,bj).GT.Nr) rStarFacC(ii, 1-j,bi,bj)= 1.
237 IF (ksurfC(1-i,jj, bi,bj).GT.Nr) rStarFacC(1-i,jj, bi,bj)= 1.
238 IF (ksurfC(ii, jj, bi,bj).GT.Nr) rStarFacC(ii, jj, bi,bj)= 1.
239
240 IF (ksurfW(1-i,1-j,bi,bj).GT.Nr) rStarFacW(1-i,1-j,bi,bj)= 1.
241 IF (ksurfW(ii, 1-j,bi,bj).GT.Nr) rStarFacW(ii, 1-j,bi,bj)= 1.
242 IF (ksurfW(1-i,jj, bi,bj).GT.Nr) rStarFacW(1-i,jj, bi,bj)= 1.
243 IF (ksurfW(ii, jj, bi,bj).GT.Nr) rStarFacW(ii, jj, bi,bj)= 1.
244
245 IF (ksurfS(1-i,1-j,bi,bj).GT.Nr) rStarFacS(1-i,1-j,bi,bj)= 1.
246 IF (ksurfS(ii, 1-j,bi,bj).GT.Nr) rStarFacS(ii, 1-j,bi,bj)= 1.
247 IF (ksurfS(1-i,jj, bi,bj).GT.Nr) rStarFacS(1-i,jj, bi,bj)= 1.
248 IF (ksurfS(ii, jj, bi,bj).GT.Nr) rStarFacS(ii, jj, bi,bj)= 1.
249
250 ENDDO
251 ENDDO
252 #endif /* W2_FILL_NULL_REGIONS */
253 #endif /* ALLOW_EXCH2 */
254
255 DO j=1-Oly,sNy+Oly
256 DO i=1-Olx,sNx+Olx
257 rStarDhCDt(i,j,bi,bj)=(rStarFacC(i,j,bi,bj)
258 & -rStarExpC(i,j,bi,bj))/deltaTfreesurf
259 rStarDhWDt(i,j,bi,bj)=(rStarFacW(i,j,bi,bj)
260 & -rStarExpW(i,j,bi,bj))/deltaTfreesurf
261 rStarDhSDt(i,j,bi,bj)=(rStarFacS(i,j,bi,bj)
262 & -rStarExpS(i,j,bi,bj))/deltaTfreesurf
263 rStarExpC(i,j,bi,bj) = rStarFacC(i,j,bi,bj)
264 & / rStarExpC(i,j,bi,bj)
265 rStarExpW(i,j,bi,bj) = rStarFacW(i,j,bi,bj)
266 & / rStarExpW(i,j,bi,bj)
267 rStarExpS(i,j,bi,bj) = rStarFacS(i,j,bi,bj)
268 & / rStarExpS(i,j,bi,bj)
269 ENDDO
270 ENDDO
271
272 C- end 2nd bi,bj loop.
273 ENDDO
274 ENDDO
275
276 #ifdef ALLOW_DEBUG
277 IF (debugMode) CALL DEBUG_LEAVE('CALC_R_STAR',myThid)
278 #endif
279
280 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
281 #endif /* NONLIN_FRSURF */
282
283 RETURN
284 END

  ViewVC Help
Powered by ViewVC 1.1.22