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

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

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


Revision 1.40 - (show annotations) (download)
Tue Oct 28 22:57:59 2003 UTC (20 years, 7 months ago) by edhill
Branch: MAIN
Changes since 1.39: +2 -2 lines
 o add a "cd_code" package and update all the verification tests
   so that they use the new package instead of "INCLUDE_CD_CODE"

1 C $Header: /u/u3/gcmpack/MITgcm/model/src/solve_for_pressure.F,v 1.39 2003/10/09 04:19:18 edhill Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: SOLVE_FOR_PRESSURE
9 C !INTERFACE:
10 SUBROUTINE SOLVE_FOR_PRESSURE(myTime, myIter, myThid)
11
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | SUBROUTINE SOLVE_FOR_PRESSURE
15 C | o Controls inversion of two and/or three-dimensional
16 C | elliptic problems for the pressure field.
17 C *==========================================================*
18 C \ev
19
20 C !USES:
21 IMPLICIT NONE
22 C == Global variables
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "DYNVARS.h"
27 #include "GRID.h"
28 #include "SURFACE.h"
29 #include "FFIELDS.h"
30 #ifdef ALLOW_NONHYDROSTATIC
31 #include "SOLVE_FOR_PRESSURE3D.h"
32 #include "GW.h"
33 #endif
34 #ifdef ALLOW_OBCS
35 #include "OBCS.h"
36 #endif
37 #include "SOLVE_FOR_PRESSURE.h"
38
39 C === Functions ====
40 LOGICAL DIFFERENT_MULTIPLE
41 EXTERNAL DIFFERENT_MULTIPLE
42
43 C !INPUT/OUTPUT PARAMETERS:
44 C == Routine arguments ==
45 C myTime - Current time in simulation
46 C myIter - Current iteration number in simulation
47 C myThid - Thread number for this instance of SOLVE_FOR_PRESSURE
48 _RL myTime
49 INTEGER myIter
50 INTEGER myThid
51
52 C !LOCAL VARIABLES:
53 C == Local variables ==
54 INTEGER i,j,k,bi,bj
55 _RS uf(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
56 _RS vf(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
57 _RL firstResidual,lastResidual
58 _RL tmpFac
59 INTEGER numIters
60 CHARACTER*(MAX_LEN_MBUF) msgBuf
61 CEOP
62
63 C-- Save previous solution & Initialise Vector solution and source term :
64 DO bj=myByLo(myThid),myByHi(myThid)
65 DO bi=myBxLo(myThid),myBxHi(myThid)
66 DO j=1-OLy,sNy+OLy
67 DO i=1-OLx,sNx+OLx
68 #ifdef ALLOW_CD_CODE
69 etaNm1(i,j,bi,bj) = etaN(i,j,bi,bj)
70 #endif
71 cg2d_x(i,j,bi,bj) = Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
72 cg2d_b(i,j,bi,bj) = 0.
73 ENDDO
74 ENDDO
75 IF (useRealFreshWaterFlux) THEN
76 tmpFac = freeSurfFac*convertEmP2rUnit
77 IF (exactConserv)
78 & tmpFac = freeSurfFac*convertEmP2rUnit*implicDiv2DFlow
79 DO j=1,sNy
80 DO i=1,sNx
81 cg2d_b(i,j,bi,bj) =
82 & tmpFac*_rA(i,j,bi,bj)*EmPmR(i,j,bi,bj)/deltaTMom
83 ENDDO
84 ENDDO
85 ENDIF
86 ENDDO
87 ENDDO
88
89 DO bj=myByLo(myThid),myByHi(myThid)
90 DO bi=myBxLo(myThid),myBxHi(myThid)
91 DO K=Nr,1,-1
92 DO j=1,sNy+1
93 DO i=1,sNx+1
94 uf(i,j) = _dyG(i,j,bi,bj)
95 & *drF(k)*_hFacW(i,j,k,bi,bj)
96 vf(i,j) = _dxG(i,j,bi,bj)
97 & *drF(k)*_hFacS(i,j,k,bi,bj)
98 ENDDO
99 ENDDO
100 CALL CALC_DIV_GHAT(
101 I bi,bj,1,sNx,1,sNy,K,
102 I uf,vf,
103 U cg2d_b,
104 I myThid)
105 ENDDO
106 ENDDO
107 ENDDO
108
109 C-- Add source term arising from w=d/dt (p_s + p_nh)
110 DO bj=myByLo(myThid),myByHi(myThid)
111 DO bi=myBxLo(myThid),myBxHi(myThid)
112 #ifdef ALLOW_NONHYDROSTATIC
113 IF ( nonHydrostatic ) THEN
114 DO j=1,sNy
115 DO i=1,sNx
116 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
117 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTfreesurf
118 & *( etaN(i,j,bi,bj)
119 & +phi_nh(i,j,1,bi,bj)*horiVertRatio/gravity )
120 cg3d_b(i,j,1,bi,bj) = cg3d_b(i,j,1,bi,bj)
121 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTfreesurf
122 & *( etaN(i,j,bi,bj)
123 & +phi_nh(i,j,1,bi,bj)*horiVertRatio/gravity )
124 ENDDO
125 ENDDO
126 ELSEIF ( exactConserv ) THEN
127 #else
128 IF ( exactConserv ) THEN
129 #endif /* ALLOW_NONHYDROSTATIC */
130 DO j=1,sNy
131 DO i=1,sNx
132 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
133 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTfreesurf
134 & * etaH(i,j,bi,bj)
135 ENDDO
136 ENDDO
137 ELSE
138 DO j=1,sNy
139 DO i=1,sNx
140 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
141 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTfreesurf
142 & * etaN(i,j,bi,bj)
143 ENDDO
144 ENDDO
145 ENDIF
146
147 #ifdef ALLOW_OBCS
148 IF (useOBCS) THEN
149 DO i=1,sNx
150 C Northern boundary
151 IF (OB_Jn(I,bi,bj).NE.0) THEN
152 cg2d_b(I,OB_Jn(I,bi,bj),bi,bj)=0.
153 cg2d_x(I,OB_Jn(I,bi,bj),bi,bj)=0.
154 ENDIF
155 C Southern boundary
156 IF (OB_Js(I,bi,bj).NE.0) THEN
157 cg2d_b(I,OB_Js(I,bi,bj),bi,bj)=0.
158 cg2d_x(I,OB_Js(I,bi,bj),bi,bj)=0.
159 ENDIF
160 ENDDO
161 DO j=1,sNy
162 C Eastern boundary
163 IF (OB_Ie(J,bi,bj).NE.0) THEN
164 cg2d_b(OB_Ie(J,bi,bj),J,bi,bj)=0.
165 cg2d_x(OB_Ie(J,bi,bj),J,bi,bj)=0.
166 ENDIF
167 C Western boundary
168 IF (OB_Iw(J,bi,bj).NE.0) THEN
169 cg2d_b(OB_Iw(J,bi,bj),J,bi,bj)=0.
170 cg2d_x(OB_Iw(J,bi,bj),J,bi,bj)=0.
171 ENDIF
172 ENDDO
173 ENDIF
174 #endif
175 ENDDO
176 ENDDO
177
178 #ifndef DISABLE_DEBUGMODE
179 IF ( debugLevel .GE. debLevB ) THEN
180 CALL DEBUG_STATS_RL(1,cg2d_b,'cg2d_b (SOLVE_FOR_PRESSURE)',
181 & myThid)
182 ENDIF
183 #endif
184
185 C-- Find the surface pressure using a two-dimensional conjugate
186 C-- gradient solver.
187 C see CG2D.h for the interface to this routine.
188 firstResidual=0.
189 lastResidual=0.
190 numIters=cg2dMaxIters
191 CALL CG2D(
192 U cg2d_b,
193 U cg2d_x,
194 O firstResidual,
195 O lastResidual,
196 U numIters,
197 I myThid )
198 _EXCH_XY_R8(cg2d_x, myThid )
199
200 #ifndef DISABLE_DEBUGMODE
201 IF ( debugLevel .GE. debLevB ) THEN
202 CALL DEBUG_STATS_RL(1,cg2d_x,'cg2d_x (SOLVE_FOR_PRESSURE)',
203 & myThid)
204 ENDIF
205 #endif
206
207 C- dump CG2D output at monitorFreq (to reduce size of STD-OUTPUT files) :
208 IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,
209 & myTime-deltaTClock) ) THEN
210 IF ( debugLevel .GE. debLevA ) THEN
211 _BEGIN_MASTER( myThid )
212 WRITE(msgBuf,'(A34,1PE24.14)') 'cg2d_init_res =',firstResidual
213 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
214 WRITE(msgBuf,'(A34,I6)') 'cg2d_iters =',numIters
215 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
216 WRITE(msgBuf,'(A34,1PE24.14)') 'cg2d_res =',lastResidual
217 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
218 _END_MASTER( )
219 ENDIF
220 ENDIF
221
222 C-- Transfert the 2D-solution to "etaN" :
223 DO bj=myByLo(myThid),myByHi(myThid)
224 DO bi=myBxLo(myThid),myBxHi(myThid)
225 DO j=1-OLy,sNy+OLy
226 DO i=1-OLx,sNx+OLx
227 etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)*cg2d_x(i,j,bi,bj)
228 ENDDO
229 ENDDO
230 ENDDO
231 ENDDO
232
233 #ifdef ALLOW_NONHYDROSTATIC
234 IF ( nonHydrostatic ) THEN
235
236 C-- Solve for a three-dimensional pressure term (NH or IGW or both ).
237 C see CG3D.h for the interface to this routine.
238 DO bj=myByLo(myThid),myByHi(myThid)
239 DO bi=myBxLo(myThid),myBxHi(myThid)
240 DO j=1,sNy+1
241 DO i=1,sNx+1
242 uf(i,j)=-_recip_dxC(i,j,bi,bj)*
243 & (cg2d_x(i,j,bi,bj)-cg2d_x(i-1,j,bi,bj))
244 vf(i,j)=-_recip_dyC(i,j,bi,bj)*
245 & (cg2d_x(i,j,bi,bj)-cg2d_x(i,j-1,bi,bj))
246 ENDDO
247 ENDDO
248
249 #ifdef ALLOW_OBCS
250 IF (useOBCS) THEN
251 DO i=1,sNx+1
252 C Northern boundary
253 IF (OB_Jn(I,bi,bj).NE.0) THEN
254 vf(I,OB_Jn(I,bi,bj))=0.
255 ENDIF
256 C Southern boundary
257 IF (OB_Js(I,bi,bj).NE.0) THEN
258 vf(I,OB_Js(I,bi,bj)+1)=0.
259 ENDIF
260 ENDDO
261 DO j=1,sNy+1
262 C Eastern boundary
263 IF (OB_Ie(J,bi,bj).NE.0) THEN
264 uf(OB_Ie(J,bi,bj),J)=0.
265 ENDIF
266 C Western boundary
267 IF (OB_Iw(J,bi,bj).NE.0) THEN
268 uf(OB_Iw(J,bi,bj)+1,J)=0.
269 ENDIF
270 ENDDO
271 ENDIF
272 #endif
273
274 K=1
275 DO j=1,sNy
276 DO i=1,sNx
277 cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
278 & +dRF(K)*dYG(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
279 & -dRF(K)*dYG( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)*uf( i ,j)
280 & +dRF(K)*dXG(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
281 & -dRF(K)*dXG(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)*vf(i, j )
282 & +( freeSurfFac*etaN(i,j,bi,bj)/deltaTMom
283 & -wVel(i,j,k+1,bi,bj)
284 & )*_rA(i,j,bi,bj)/deltaTmom
285 ENDDO
286 ENDDO
287 DO K=2,Nr-1
288 DO j=1,sNy
289 DO i=1,sNx
290 cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
291 & +dRF(K)*dYG(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
292 & -dRF(K)*dYG( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)*uf( i ,j)
293 & +dRF(K)*dXG(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
294 & -dRF(K)*dXG(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)*vf(i, j )
295 & +( wVel(i,j,k ,bi,bj)
296 & -wVel(i,j,k+1,bi,bj)
297 & )*_rA(i,j,bi,bj)/deltaTmom
298
299 ENDDO
300 ENDDO
301 ENDDO
302 K=Nr
303 DO j=1,sNy
304 DO i=1,sNx
305 cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
306 & +dRF(K)*dYG(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
307 & -dRF(K)*dYG( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)*uf( i ,j)
308 & +dRF(K)*dXG(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
309 & -dRF(K)*dXG(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)*vf(i, j )
310 & +( wVel(i,j,k ,bi,bj)
311 & )*_rA(i,j,bi,bj)/deltaTmom
312
313 ENDDO
314 ENDDO
315
316 #ifdef ALLOW_OBCS
317 IF (useOBCS) THEN
318 DO K=1,Nr
319 DO i=1,sNx
320 C Northern boundary
321 IF (OB_Jn(I,bi,bj).NE.0) THEN
322 cg3d_b(I,OB_Jn(I,bi,bj),K,bi,bj)=0.
323 ENDIF
324 C Southern boundary
325 IF (OB_Js(I,bi,bj).NE.0) THEN
326 cg3d_b(I,OB_Js(I,bi,bj),K,bi,bj)=0.
327 ENDIF
328 ENDDO
329 DO j=1,sNy
330 C Eastern boundary
331 IF (OB_Ie(J,bi,bj).NE.0) THEN
332 cg3d_b(OB_Ie(J,bi,bj),J,K,bi,bj)=0.
333 ENDIF
334 C Western boundary
335 IF (OB_Iw(J,bi,bj).NE.0) THEN
336 cg3d_b(OB_Iw(J,bi,bj),J,K,bi,bj)=0.
337 ENDIF
338 ENDDO
339 ENDDO
340 ENDIF
341 #endif
342
343 ENDDO ! bi
344 ENDDO ! bj
345
346 firstResidual=0.
347 lastResidual=0.
348 numIters=cg2dMaxIters
349 CALL CG3D(
350 U cg3d_b,
351 U phi_nh,
352 O firstResidual,
353 O lastResidual,
354 U numIters,
355 I myThid )
356 _EXCH_XYZ_R8(phi_nh, myThid )
357
358 IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,
359 & myTime-deltaTClock) ) THEN
360 IF ( debugLevel .GE. debLevA ) THEN
361 _BEGIN_MASTER( myThid )
362 WRITE(msgBuf,'(A34,1PE24.14)') 'cg3d_init_res =',firstResidual
363 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
364 WRITE(msgBuf,'(A34,I6)') 'cg3d_iters =',numIters
365 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
366 WRITE(msgBuf,'(A34,1PE24.14)') 'cg3d_res =',lastResidual
367 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
368 _END_MASTER( )
369 ENDIF
370 ENDIF
371
372 ENDIF
373 #endif
374
375 RETURN
376 END

  ViewVC Help
Powered by ViewVC 1.1.22