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

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

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


Revision 1.17 - (show annotations) (download)
Sat Jul 22 03:53:13 2006 UTC (17 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58o_post, checkpoint58p_post, checkpoint58q_post, checkpoint58r_post, checkpoint58n_post
Changes since 1.16: +23 -17 lines
set PmEpR also in overlap (needed if useKPP with RealFreshWater & NonLin-FreeSurf)

1 C $Header: /u/gcmpack/MITgcm/model/src/integr_continuity.F,v 1.16 2005/12/08 15:44:34 heimbach 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 bi, bj, 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) to satisfy
18 C | exactly the convervation 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 bi,bj :: tile index
38 C myTime :: Current time in simulation
39 C myIter :: Current iteration number in simulation
40 C myThid :: Thread number for this instance of the routine.
41 _RL myTime
42 INTEGER myIter
43 INTEGER myThid
44 INTEGER bi,bj
45 _RL uFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
46 _RL vFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
47
48 C !LOCAL VARIABLES:
49 C Local variables in common block
50
51 C Local variables
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 i,j,k
57 _RL uTrans(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
58 _RL vTrans(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
59 _RL hDivFlow(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
60 _RL facEmP
61 CEOP
62
63 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
64
65 #ifdef EXACT_CONSERV
66 IF (exactConserv) THEN
67
68 C-- Compute the Divergence of The Barotropic Flow :
69
70 C- Initialise
71 DO j=1-Oly,sNy+Oly
72 DO i=1-Olx,sNx+Olx
73 hDivFlow(i,j) = 0. _d 0
74 utrans(i,j) = 0. _d 0
75 vtrans(i,j) = 0. _d 0
76 ENDDO
77 ENDDO
78
79 DO k=1,Nr
80
81 C- Calculate velocity field "volume transports" through tracer cell faces
82 DO j=1,sNy+1
83 DO i=1,sNx+1
84 uTrans(i,j) = uFld(i,j,k,bi,bj)*_dyG(i,j,bi,bj)
85 & *drF(k)*_hFacW(i,j,k,bi,bj)
86 vTrans(i,j) = vFld(i,j,k,bi,bj)*_dxG(i,j,bi,bj)
87 & *drF(k)*_hFacS(i,j,k,bi,bj)
88 ENDDO
89 ENDDO
90
91 C- Integrate vertically the Horizontal Divergence
92 DO j=1,sNy
93 DO i=1,sNx
94 hDivFlow(i,j) = hDivFlow(i,j)
95 & +maskC(i,j,k,bi,bj)*( uTrans(i+1,j)-uTrans(i,j)
96 & +vTrans(i,j+1)-vTrans(i,j) )
97 ENDDO
98 ENDDO
99
100 C- End DO k=1,Nr
101 ENDDO
102
103 C------------------------------------
104 facEmP = 0.
105 IF (useRealFreshWaterFlux) facEmP = convertEmP2rUnit
106 IF ( myTime.EQ.startTime .AND. myTime.NE.baseTime
107 & .AND. useRealFreshWaterFlux) THEN
108
109 C needs previous time-step value of E-P-R, that has not been loaded
110 C and was not in old pickup-file ; try to use etaN & etaH instead.
111 IF ( usePickupBeforeC54 ) THEN
112 DO j=1,sNy
113 DO i=1,sNx
114 dEtaHdt(i,j,bi,bj) = (etaN(i,j,bi,bj)-etaH(i,j,bi,bj))
115 & / (implicDiv2Dflow*deltaTfreesurf)
116 ENDDO
117 ENDDO
118 ENDIF
119
120 DO j=1,sNy
121 DO i=1,sNx
122 PmEpR(i,j,bi,bj) = dEtaHdt(i,j,bi,bj)
123 & + hDivFlow(i,j)*recip_rA(i,j,bi,bj)
124 PmEpR(i,j,bi,bj) = PmEpR(i,j,bi,bj)/convertEmP2rUnit
125 ENDDO
126 ENDDO
127 ELSEIF ( myTime.EQ.startTime ) THEN
128 DO j=1,sNy
129 DO i=1,sNx
130 PmEpR(i,j,bi,bj) = 0. _d 0
131 dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)
132 ENDDO
133 ENDDO
134 ELSE
135 C-- Needs to get valid PmEpR (for T,S forcing) also in overlap regions
136 C (e.g., if using KPP) => set over full index range
137 DO j=1-OLy,sNy+OLy
138 DO i=1-OLx,sNx+OLx
139 PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
140 ENDDO
141 ENDDO
142 DO j=1,sNy
143 DO i=1,sNx
144 dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)
145 & -facEmP*EmPmR(i,j,bi,bj)
146 ENDDO
147 ENDDO
148 ENDIF
149 C------------------------------------
150
151 ENDIF
152
153 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
154
155 IF (exactConserv .AND. myTime.NE.startTime) THEN
156 C-- Update etaN at the end of the time step :
157 C Incorporate the Implicit part of -Divergence(Barotropic_Flow)
158
159 IF (implicDiv2Dflow.EQ. 0. _d 0) THEN
160 DO j=1-Oly,sNy+Oly
161 DO i=1-Olx,sNx+Olx
162 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
163 ENDDO
164 ENDDO
165 ELSE
166 DO j=1,sNy
167 DO i=1,sNx
168 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
169 & + implicDiv2Dflow*dEtaHdt(i,j,bi,bj)*deltaTfreesurf
170 ENDDO
171 ENDDO
172 ENDIF
173
174 #ifdef ALLOW_OBCS
175 C-- Apply OBC to etaN if NonLin-FreeSurf, reset to zero otherwise:
176 IF ( useOBCS ) CALL OBCS_APPLY_ETA( bi, bj, etaN, myThid )
177 #endif /* ALLOW_OBCS */
178
179 ENDIF
180
181 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
182
183 # ifdef NONLIN_FRSURF
184 IF (select_rStar .NE. 0) THEN
185 # ifndef DISABLE_RSTAR_CODE
186 DO j=1,sNy
187 DO i=1,sNx
188 rStarDhCDt(i,j,bi,bj) =
189 & dEtaHdt(i,j,bi,bj)*recip_Rcol(i,j,bi,bj)
190 ENDDO
191 ENDDO
192 # endif /* DISABLE_RSTAR_CODE */
193 ENDIF
194 # endif /* NONLIN_FRSURF */
195
196 #endif /* EXACT_CONSERV */
197
198 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
199
200 DO k=Nr,1,-1
201 C-- Integrate continuity vertically for vertical velocity
202
203 CALL INTEGRATE_FOR_W(
204 I bi, bj, k, uFld, vFld,
205 O wVel,
206 I myThid )
207
208 #ifdef EXACT_CONSERV
209 IF ( k.EQ.Nr .AND. myTime.NE.baseTime .AND.
210 & useRealFreshWaterFlux .AND. usingPCoords ) THEN
211
212 DO j=1,sNy
213 DO i=1,sNx
214 wVel(i,j,k,bi,bj) = wVel(i,j,k,bi,bj)
215 & +convertEmP2rUnit*PmEpR(i,j,bi,bj)*maskC(i,j,k,bi,bj)
216 ENDDO
217 ENDDO
218
219 ENDIF
220 #endif /* EXACT_CONSERV */
221
222 #ifdef ALLOW_OBCS
223 C-- Apply OBC to W if in N-H mode, reset to zero otherwise:
224 IF ( useOBCS ) CALL OBCS_APPLY_W( bi, bj, k, wVel, myThid )
225 #endif /* ALLOW_OBCS */
226
227 C- End DO k=Nr,1,-1
228 ENDDO
229
230 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
231
232 RETURN
233 END

  ViewVC Help
Powered by ViewVC 1.1.22