/[MITgcm]/MITgcm_contrib/ksnow/press_release/code/integr_continuity.F
ViewVC logotype

Contents of /MITgcm_contrib/ksnow/press_release/code/integr_continuity.F

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


Revision 1.2 - (show annotations) (download)
Sun Feb 5 15:45:23 2017 UTC (8 years, 5 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
Changes since 1.1: +1 -3 lines
updates to allow parallel computation

1 C $Header: /u/gcmpack/MITgcm_contrib/ksnow/press_release/code/integr_continuity.F,v 1.1 2016/12/16 15:23:18 ksnow Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: INTEGR_CONTINUITY
9 C !INTERFACE:
10 SUBROUTINE INTEGR_CONTINUITY(
11 I uFld, vFld,
12 I myTime, myIter, myThid )
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | SUBROUTINE INTEGR_CONTINUITY
16 C | o Integrate the continuity Eq : compute vertical velocity
17 C | and free surface "r-anomaly" (etaN,etaH) to satisfy
18 C | exactly the conservation of the Total Volume
19 C *==========================================================*
20 C \ev
21
22 C !USES:
23 IMPLICIT NONE
24 C == Global variables
25 #include "SIZE.h"
26 #include "EEPARAMS.h"
27 #include "PARAMS.h"
28 #include "DYNVARS.h"
29 #include "GRID.h"
30 #include "SURFACE.h"
31 #include "FFIELDS.h"
32
33 C !INPUT/OUTPUT PARAMETERS:
34 C == Routine arguments ==
35 C uFld :: Zonal velocity ( m/s )
36 C vFld :: Meridional velocity ( m/s )
37 C myTime :: Current time in simulation
38 C myIter :: Current iteration number in simulation
39 C myThid :: my Thread Id. number
40 _RL myTime
41 INTEGER myIter
42 INTEGER myThid
43 _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
44 _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
45 _RL depth, depth_fac
46
47 C !LOCAL VARIABLES:
48 C Local variables in common block
49
50 C Local variables
51 C bi,bj :: tile index
52 C i,j,k :: Loop counters
53 C uTrans :: Volume transports ( uVel.xA )
54 C vTrans :: Volume transports ( vVel.yA )
55 C hDivFlow :: Div. Barotropic Flow [transport unit m3/s]
56 INTEGER k,bi,bj
57 #ifdef EXACT_CONSERV
58 INTEGER i, j
59 INTEGER ks
60 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
62 _RL hDivFlow(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63 _RL facEmP, facMass
64 #else /* EXACT_CONSERV */
65 # ifdef ALLOW_OBCS
66 INTEGER i, j
67 # endif
68 #endif /* EXACT_CONSERV */
69 #ifndef ALLOW_ADDFLUID
70 _RL addMass(1)
71 #endif /* ndef ALLOW_ADDFLUID */
72 #if (defined NONLIN_FRSURF) && !(defined DISABLE_RSTAR_CODE)
73 _RL rStarDhDt(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74 #else
75 _RL rStarDhDt(1)
76 #endif
77 CEOP
78
79 C-- Start bi,bj loops
80 DO bj=myByLo(myThid),myByHi(myThid)
81 DO bi=myBxLo(myThid),myBxHi(myThid)
82
83 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
84
85 #ifdef EXACT_CONSERV
86 IF (exactConserv) THEN
87
88 facEmP = 0.
89 IF ( fluidIsWater.AND.useRealFreshWaterFlux ) facEmP=mass2rUnit
90 facMass = 0.
91 IF ( selectAddFluid.GE.1 ) facMass = mass2rUnit
92
93 C-- Compute the Divergence of The Barotropic Flow :
94
95 C- Initialise
96 DO j=1-OLy,sNy+OLy
97 DO i=1-OLx,sNx+OLx
98 hDivFlow(i,j) = 0. _d 0
99 utrans(i,j) = 0. _d 0
100 vtrans(i,j) = 0. _d 0
101 ENDDO
102 ENDDO
103
104 DO k=1,Nr
105
106 C- Calculate velocity field "volume transports" through tracer cell faces
107 C anelastic: uTrans,vTrans are scaled by rhoFacC (~ mass transport).
108 DO j=1,sNy+1
109 DO i=1,sNx+1
110
111 uTrans(i,j) = uFld(i,j,k,bi,bj)*_dyG(i,j,bi,bj)
112 & *deepFacC(k)*rhoFacC(k)
113 & *drF(k)*_hFacW(i,j,k,bi,bj)
114
115 vTrans(i,j) = vFld(i,j,k,bi,bj)*_dxG(i,j,bi,bj)
116 & *deepFacC(k)*rhoFacC(k)
117 & *drF(k)*_hFacS(i,j,k,bi,bj)
118
119 ENDDO
120 ENDDO
121
122 C- Integrate vertically the Horizontal Divergence
123 DO j=1,sNy
124 DO i=1,sNx
125 hDivFlow(i,j) = hDivFlow(i,j)
126 & +maskC(i,j,k,bi,bj)*( uTrans(i+1,j)-uTrans(i,j)
127 & +vTrans(i,j+1)-vTrans(i,j) )
128 #ifdef ALLOW_ADDFLUID
129 & -facMass*addMass(i,j,k,bi,bj)
130 #endif /* ALLOW_ADDFLUID */
131 ENDDO
132 ENDDO
133
134 C- End DO k=1,Nr
135 ENDDO
136
137 #ifdef ALLOW_PRESSURE_RELEASE_CODE
138 DO j=1,sNy
139 DO i=1,sNx
140 hDivFlow(i,j) = hDivFlow(i,j)
141 & +maskinC(i,j,bi,bj)*_dyG(i,j,bi,bj)*
142 & (pReleaseTransX(i+1,j,bi,bj)-pReleaseTransX(i,j,bi,bj))
143 hDivFlow(i,j) = hDivFlow(i,j)
144 & +maskinC(i,j,bi,bj)*_dxG(i,j,bi,bj)*
145 & (pReleaseTransY(i,j+1,bi,bj)-pReleaseTransY(i,j,bi,bj))
146 ENDDO
147 ENDDO
148 #endif
149
150
151 C------------------------------------
152 C note: deep-model not implemented for P-coordinate + realFreshWaterFlux ;
153 C anelastic: always assumes that rhoFacF(1) = 1
154 IF ( myIter.EQ.nIter0 .AND. myIter.NE.0
155 & .AND. fluidIsWater .AND. useRealFreshWaterFlux ) THEN
156
157 C needs previous time-step value of E-P-R, that has not been loaded
158 C and was not in old pickup-file ; try to use etaN & etaH instead.
159 IF ( usePickupBeforeC54 ) THEN
160 DO j=1,sNy
161 DO i=1,sNx
162 dEtaHdt(i,j,bi,bj) = (etaN(i,j,bi,bj)-etaH(i,j,bi,bj))
163 & / (implicDiv2Dflow*deltaTfreesurf)
164 ENDDO
165 ENDDO
166 ENDIF
167
168 DO j=1,sNy
169 DO i=1,sNx
170 PmEpR(i,j,bi,bj) = dEtaHdt(i,j,bi,bj)
171 & + hDivFlow(i,j)*recip_rA(i,j,bi,bj)
172 & *recip_deepFac2F(1)
173 PmEpR(i,j,bi,bj) = PmEpR(i,j,bi,bj)*rUnit2mass
174 ENDDO
175 ENDDO
176 ELSEIF ( myIter.EQ.nIter0 ) THEN
177 DO j=1,sNy
178 DO i=1,sNx
179 ks = kSurfC(I,J,bi,bj)
180 PmEpR(i,j,bi,bj) = 0. _d 0
181 dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)
182 & *recip_deepFac2F(ks)
183 ENDDO
184 ENDDO
185 ELSE
186 C-- Needs to get valid PmEpR (for T,S forcing) also in overlap regions
187 C (e.g., if using KPP) => set over full index range
188 DO j=1-OLy,sNy+OLy
189 DO i=1-OLx,sNx+OLx
190 PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
191 ENDDO
192 ENDDO
193 DO j=1,sNy
194 DO i=1,sNx
195 ks = kSurfC(i,j,bi,bj)
196 dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)
197 & *recip_deepFac2F(ks)
198 & -facEmP*EmPmR(i,j,bi,bj)
199 ENDDO
200 ENDDO
201 ENDIF
202 C------------------------------------
203
204 #ifdef ALLOW_OBCS
205 C-- reset dEtaHdt to zero outside the OB interior region
206 IF ( useOBCS ) THEN
207 DO j=1,sNy
208 DO i=1,sNx
209 dEtaHdt(i,j,bi,bj) = dEtaHdt(i,j,bi,bj)*maskInC(i,j,bi,bj)
210 ENDDO
211 ENDDO
212 ENDIF
213 #endif /* ALLOW_OBCS */
214
215 C-- end if exactConserv block
216 ENDIF
217
218 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
219
220 IF ( exactConserv .AND. myIter.NE.nIter0 ) THEN
221 C-- Update etaN at the end of the time step :
222 C Incorporate the Implicit part of -Divergence(Barotropic_Flow)
223
224 IF (implicDiv2Dflow.EQ. 0. _d 0) THEN
225 DO j=1-OLy,sNy+OLy
226 DO i=1-OLx,sNx+OLx
227 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
228 ENDDO
229 ENDDO
230 ELSE
231 DO j=1,sNy
232 DO i=1,sNx
233 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
234 & + implicDiv2Dflow*dEtaHdt(i,j,bi,bj)*deltaTfreesurf
235 ENDDO
236 ENDDO
237 ENDIF
238
239 #ifdef ALLOW_OBCS
240 C-- Was added on Dec 30, 2004 (to fix unrealistic etaN ?), but no longer
241 C needed with proper masking in solver (matrix+cg2d_b,x) and masking
242 C of dEtaHdt above. etaN next to OB does not enter present algorithm but
243 C leave it commented out in case we would implement an aternative scheme.
244 c IF ( useOBCS ) CALL OBCS_APPLY_ETA( bi, bj, etaN, myThid )
245 #endif /* ALLOW_OBCS */
246
247 C-- end if exactConserv and not myIter=nIter0 block
248 ENDIF
249
250 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
251
252 # ifdef NONLIN_FRSURF
253 IF (select_rStar .NE. 0) THEN
254 # ifndef DISABLE_RSTAR_CODE
255 C-- note: rStarDhDt is similar to rStarDhCDt from S/R CALC_R_STAR
256 C except for deep-factor and rho factor.
257 DO j=1,sNy
258 DO i=1,sNx
259 ks = kSurfC(i,j,bi,bj)
260 rStarDhDt(i,j) = dEtaHdt(i,j,bi,bj)
261 & *deepFac2F(ks)*rhoFacF(ks)
262 & *recip_Rcol(i,j,bi,bj)
263 ENDDO
264 ENDDO
265 # endif /* DISABLE_RSTAR_CODE */
266 ENDIF
267 # endif /* NONLIN_FRSURF */
268
269 #endif /* EXACT_CONSERV */
270
271 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
272
273 DO k=Nr,1,-1
274 C-- Integrate continuity vertically for vertical velocity
275
276 CALL INTEGRATE_FOR_W(
277 I bi, bj, k, uFld, vFld,
278 I addMass, rStarDhDt,
279 O wVel,
280 I myThid )
281
282 #ifdef EXACT_CONSERV
283 IF ( k.EQ.Nr .AND. myIter.NE.0 .AND. usingPCoords
284 & .AND. fluidIsWater .AND. useRealFreshWaterFlux ) THEN
285
286 DO j=1,sNy
287 DO i=1,sNx
288 wVel(i,j,k,bi,bj) = wVel(i,j,k,bi,bj)
289 & +mass2rUnit*PmEpR(i,j,bi,bj)*maskC(i,j,k,bi,bj)
290 ENDDO
291 ENDDO
292
293 ENDIF
294 #endif /* EXACT_CONSERV */
295
296 #ifdef ALLOW_OBCS
297 C-- reset W to zero outside the OB interior region
298 IF ( useOBCS ) THEN
299 DO j=1,sNy
300 DO i=1,sNx
301 wVel(i,j,k,bi,bj) = wVel(i,j,k,bi,bj)*maskInC(i,j,bi,bj)
302 ENDDO
303 ENDDO
304 ENDIF
305 C-- Apply OBC to W (non-hydrostatic):
306 IF ( useOBCS.AND.nonHydrostatic )
307 & CALL OBCS_APPLY_W( bi, bj, k, wVel, myThid )
308 #endif /* ALLOW_OBCS */
309
310 C- End DO k=Nr,1,-1
311 ENDDO
312
313 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
314
315 C-- End bi,bj loops
316 ENDDO
317 ENDDO
318
319 IF ( exactConserv .AND. myIter.NE.nIter0
320 & .AND. implicDiv2Dflow .NE. 0. _d 0 )
321 & _EXCH_XY_RL( etaN , myThid )
322 IF ( implicitIntGravWave .OR. myIter.EQ.nIter0 )
323 & _EXCH_XYZ_RL( wVel , myThid )
324
325 #ifdef EXACT_CONSERV
326 C-- Update etaH (from etaN and dEtaHdt):
327 IF (exactConserv) THEN
328 c IF ( useRealFreshWaterFlux .AND. myIter.EQ.nIter0 )
329 c & _EXCH_XY_RL( PmEpR, myThid )
330 #ifdef ALLOW_DEBUG
331 IF (debugMode) CALL DEBUG_CALL('UPDATE_ETAH',myThid)
332 #endif
333 CALL UPDATE_ETAH( myTime, myIter, myThid )
334 ENDIF
335
336 #ifdef NONLIN_FRSURF
337 # ifndef DISABLE_SIGMA_CODE
338 IF ( nonlinFreeSurf.GT.0 .AND. selectSigmaCoord.NE.0 ) THEN
339 CALL EXCH_XY_RL( dEtaHdt, myThid )
340 CALL UPDATE_ETAWS( myTime, myIter, myThid )
341 ENDIF
342 # endif /* DISABLE_SIGMA_CODE */
343 #endif /* NONLIN_FRSURF */
344
345 #endif /* EXACT_CONSERV */
346
347 RETURN
348 END

  ViewVC Help
Powered by ViewVC 1.1.22