/[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.35 - (show annotations) (download)
Wed Sep 25 19:36:50 2002 UTC (21 years, 8 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint46j_pre, checkpoint46i_post, checkpoint46h_post
Changes since 1.34: +11 -7 lines
o cleaned up the use of rhoNil and rhoConst.
  - rhoNil should only appear in the LINEAR equation of state, everywhere
    else rhoNil is replaced by rhoConst, e.g. find_rho computes rho-rhoConst
    and the dynamical equations are all divided by rhoConst
o introduced new parameter rhoConstFresh, a reference density of fresh
  water, to remove the fresh water flux's dependence on rhoNil. The default
  value is 999.8 kg/m^3
o cleanup up external_forcing.F and external_forcing_surf.F
  - can now be used by both OCEANIC and OCEANICP

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

  ViewVC Help
Powered by ViewVC 1.1.22