/[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.44 - (show annotations) (download)
Thu Jan 13 00:46:33 2005 UTC (19 years, 4 months ago) by ce107
Branch: MAIN
CVS Tags: checkpoint57d_post, checkpoint57c_post, checkpoint57c_pre, checkpoint57e_post, eckpoint57e_pre, checkpoint57f_pre
Changes since 1.43: +37 -1 lines
By compiling with -DTIME_PER_TIMESTEP one gets user, system and wallclock
time per timestep for each process in STDOUT.

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

  ViewVC Help
Powered by ViewVC 1.1.22