/[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.83 - (show annotations) (download)
Fri Mar 24 15:41:19 2017 UTC (7 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.82: +5 -10 lines
use 'I10' suffix to simplify debug writing of cg2/3d_b/x (similar to cg3d.F, cg3d_ex0.F)

1 C $Header: /u/gcmpack/MITgcm/model/src/solve_for_pressure.F,v 1.82 2016/05/28 23:25:55 jmc 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 "GRID.h"
27 #include "SURFACE.h"
28 #include "FFIELDS.h"
29 #include "DYNVARS.h"
30 #include "SOLVE_FOR_PRESSURE.h"
31 #ifdef ALLOW_NONHYDROSTATIC
32 #include "SOLVE_FOR_PRESSURE3D.h"
33 #include "NH_VARS.h"
34 #endif
35 #ifdef ALLOW_CD_CODE
36 #include "CD_CODE_VARS.h"
37 #endif
38
39 C === Functions ====
40 LOGICAL DIFFERENT_MULTIPLE
41 EXTERNAL DIFFERENT_MULTIPLE
42 #ifdef ALLOW_DIAGNOSTICS
43 LOGICAL DIAGNOSTICS_IS_ON
44 EXTERNAL DIAGNOSTICS_IS_ON
45 #endif /* ALLOW_DIAGNOSTICS */
46
47 C !INPUT/OUTPUT PARAMETERS:
48 C == Routine arguments ==
49 C myTime :: Current time in simulation
50 C myIter :: Current iteration number in simulation
51 C myThid :: Thread number for this instance of SOLVE_FOR_PRESSURE
52 _RL myTime
53 INTEGER myIter
54 INTEGER myThid
55
56 C !LOCAL VARIABLES:
57 C == Local variables ==
58 INTEGER i,j,k,bi,bj
59 INTEGER ks
60 INTEGER numIters, nIterMin
61 _RL firstResidual, minResidualSq, lastResidual
62 _RL tmpFac
63 _RL sumEmP, tileEmP(nSx,nSy)
64 LOGICAL putPmEinXvector
65 INTEGER ioUnit
66 CHARACTER*(MAX_LEN_MBUF) msgBuf
67 #ifdef ALLOW_NONHYDROSTATIC
68 LOGICAL zeroPsNH, zeroMeanPnh, oldFreeSurfTerm
69 #else
70 _RL cg3d_b(1)
71 #endif
72 #ifdef ALLOW_DIAGNOSTICS
73 CHARACTER*8 diagName
74 _RL tmpVar (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75 #endif /* ALLOW_DIAGNOSTICS */
76 CEOP
77
78 #ifdef ALLOW_NONHYDROSTATIC
79 zeroPsNH = .FALSE.
80 c zeroPsNH = use3Dsolver .AND. exactConserv
81 c & .AND. select_rStar.EQ.0
82 zeroMeanPnh = .FALSE.
83 c zeroMeanPnh = use3Dsolver .AND. select_rStar.NE.0
84 c oldFreeSurfTerm = use3Dsolver .AND. select_rStar.EQ.0
85 c & .AND. .NOT.zeroPsNH
86 oldFreeSurfTerm = use3Dsolver .AND. .NOT.exactConserv
87 #else
88 cg3d_b(1) = 0.
89 #endif
90
91 C deepAtmosphere & useRealFreshWaterFlux: only valid if deepFac2F(ksurf)=1
92 C anelastic (always Z-coordinate):
93 C 1) assume that rhoFacF(1)=1 (and ksurf == 1);
94 C (this reduces the number of lines of code to modify)
95 C 2) (a) 2-D continuity eq. compute div. of mass transport (<- add rhoFac)
96 C (b) gradient of surf.Press in momentum eq. (<- add 1/rhoFac)
97 C => 2 factors cancel in elliptic eq. for Phi_s ,
98 C but 1rst factor(a) remains in RHS cg2d_b.
99
100 C-- Initialise the Vector solution with etaN + deltaT*Global_mean_PmE
101 C instead of simply etaN ; This can speed-up the solver convergence in
102 C the case where |Global_mean_PmE| is large.
103 putPmEinXvector = .FALSE.
104 c putPmEinXvector = useRealFreshWaterFlux.AND.fluidIsWater
105
106 IF ( myIter.EQ.1+nIter0 .AND. debugLevel .GE. debLevA ) THEN
107 _BEGIN_MASTER( myThid )
108 ioUnit = standardMessageUnit
109 WRITE(msgBuf,'(2A,L5)') 'SOLVE_FOR_PRESSURE:',
110 & ' putPmEinXvector =', putPmEinXvector
111 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
112 #ifdef ALLOW_NONHYDROSTATIC
113 WRITE(msgBuf,'(A,2(A,L5))') 'SOLVE_FOR_PRESSURE:',
114 & ' zeroPsNH=', zeroPsNH, ' , zeroMeanPnh=', zeroMeanPnh
115 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
116 WRITE(msgBuf,'(2A,L5)') 'SOLVE_FOR_PRESSURE:',
117 & ' oldFreeSurfTerm =', oldFreeSurfTerm
118 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
119 #endif
120 _END_MASTER( myThid )
121 ENDIF
122
123 C-- Save previous solution & Initialise Vector solution and source term :
124 sumEmP = 0.
125 DO bj=myByLo(myThid),myByHi(myThid)
126 DO bi=myBxLo(myThid),myBxHi(myThid)
127 DO j=1-OLy,sNy+OLy
128 DO i=1-OLx,sNx+OLx
129 #ifdef ALLOW_CD_CODE
130 etaNm1(i,j,bi,bj) = etaN(i,j,bi,bj)
131 #endif
132 cg2d_x(i,j,bi,bj) = Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
133 cg2d_b(i,j,bi,bj) = 0.
134 ENDDO
135 ENDDO
136 IF (useRealFreshWaterFlux.AND.fluidIsWater) THEN
137 tmpFac = freeSurfFac*mass2rUnit*implicDiv2DFlow
138 DO j=1,sNy
139 DO i=1,sNx
140 cg2d_b(i,j,bi,bj) =
141 & tmpFac*_rA(i,j,bi,bj)*EmPmR(i,j,bi,bj)/deltaTMom
142 & *maskInC(i,j,bi,bj)
143 ENDDO
144 ENDDO
145 ENDIF
146 IF ( putPmEinXvector ) THEN
147 tileEmP(bi,bj) = 0.
148 DO j=1,sNy
149 DO i=1,sNx
150 tileEmP(bi,bj) = tileEmP(bi,bj)
151 & + rA(i,j,bi,bj)*EmPmR(i,j,bi,bj)
152 & *maskInC(i,j,bi,bj)
153 ENDDO
154 ENDDO
155 ENDIF
156 ENDDO
157 ENDDO
158 IF ( putPmEinXvector ) THEN
159 CALL GLOBAL_SUM_TILE_RL( tileEmP, sumEmP, myThid )
160 ENDIF
161
162 DO bj=myByLo(myThid),myByHi(myThid)
163 DO bi=myBxLo(myThid),myBxHi(myThid)
164 IF ( putPmEinXvector ) THEN
165 tmpFac = 0.
166 IF (globalArea.GT.0.) tmpFac =
167 & freeSurfFac*deltaTFreeSurf*mass2rUnit*sumEmP/globalArea
168 DO j=1,sNy
169 DO i=1,sNx
170 cg2d_x(i,j,bi,bj) = cg2d_x(i,j,bi,bj)
171 & - tmpFac*Bo_surf(i,j,bi,bj)
172 ENDDO
173 ENDDO
174 ENDIF
175 C- RHS: similar to the divergence of the vertically integrated mass transport:
176 C del_i { Sum_k [ rhoFac.(dr.hFac).(dy.deepFac).(u*) ] } / deltaT
177 DO k=Nr,1,-1
178 CALL CALC_DIV_GHAT(
179 I bi,bj,k,
180 U cg2d_b, cg3d_b,
181 I myThid )
182 ENDDO
183 ENDDO
184 ENDDO
185
186 DO bj=myByLo(myThid),myByHi(myThid)
187 DO bi=myBxLo(myThid),myBxHi(myThid)
188 #ifdef ALLOW_NONHYDROSTATIC
189 IF ( oldFreeSurfTerm ) THEN
190 C-- Add source term arising from w=d/dt (p_s + p_nh)
191 DO j=1,sNy
192 DO i=1,sNx
193 ks = kSurfC(i,j,bi,bj)
194 IF ( ks.LE.Nr ) THEN
195 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
196 & -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)
197 & /deltaTMom/deltaTFreeSurf
198 & *( etaN(i,j,bi,bj)
199 & +phi_nh(i,j,ks,bi,bj)*recip_Bo(i,j,bi,bj) )
200 cg3d_b(i,j,ks,bi,bj) = cg3d_b(i,j,ks,bi,bj)
201 & -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)
202 & /deltaTMom/deltaTFreeSurf
203 & *( etaN(i,j,bi,bj)
204 & +phi_nh(i,j,ks,bi,bj)*recip_Bo(i,j,bi,bj) )
205 ENDIF
206 ENDDO
207 ENDDO
208 ELSEIF ( exactConserv ) THEN
209 #else
210 C-- Add source term arising from w=d/dt (p_s)
211 IF ( exactConserv ) THEN
212 #endif /* ALLOW_NONHYDROSTATIC */
213 DO j=1,sNy
214 DO i=1,sNx
215 ks = kSurfC(i,j,bi,bj)
216 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
217 & -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)
218 & /deltaTMom/deltaTFreeSurf
219 & * etaH(i,j,bi,bj)
220 ENDDO
221 ENDDO
222 ELSE
223 DO j=1,sNy
224 DO i=1,sNx
225 ks = kSurfC(i,j,bi,bj)
226 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
227 & -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)
228 & /deltaTMom/deltaTFreeSurf
229 & * etaN(i,j,bi,bj)
230 ENDDO
231 ENDDO
232 ENDIF
233
234 #ifdef ALLOW_OBCS
235 C- Note: solver matrix is trivial outside OB region (main diagonal only)
236 C => no real need to reset RHS (=cg2d_b) & cg2d_x, except that:
237 C a) normalisation is fct of Max(RHS), which can be large ouside OB region
238 C (would be different if we were solving for increment of eta/g
239 C instead of directly for eta/g).
240 C => need to reset RHS to ensure that interior solution does not depend
241 C on ouside OB region.
242 C b) provide directly the trivial solution cg2d_x == 0 for outside OB region
243 C (=> no residual => no effect on solver convergence and interior solution)
244 IF (useOBCS) THEN
245 DO j=1,sNy
246 DO i=1,sNx
247 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)*maskInC(i,j,bi,bj)
248 cg2d_x(i,j,bi,bj) = cg2d_x(i,j,bi,bj)*maskInC(i,j,bi,bj)
249 ENDDO
250 ENDDO
251 ENDIF
252 #endif /* ALLOW_OBCS */
253 C- end bi,bj loops
254 ENDDO
255 ENDDO
256
257 #ifdef ALLOW_DEBUG
258 IF ( debugLevel .GE. debLevD ) THEN
259 CALL DEBUG_STATS_RL(1,cg2d_b,'cg2d_b (SOLVE_FOR_PRESSURE)',
260 & myThid)
261 ENDIF
262 #endif
263 IF ( DIFFERENT_MULTIPLE(diagFreq, myTime, deltaTClock) ) THEN
264 CALL WRITE_FLD_XY_RL( 'cg2d_b', 'I10', cg2d_b, myIter, myThid )
265 ENDIF
266
267 C-- Find the surface pressure using a two-dimensional conjugate
268 C gradient solver. See CG2D.h for the interface to this routine.
269 C In rare cases of a poor solver convergence, better to select the
270 C solver minimum-residual solution (instead of the last-iter solution)
271 C by setting cg2dUseMinResSol=1 (<-> nIterMin=0 in input)
272 numIters = cg2dMaxIters
273 nIterMin = cg2dUseMinResSol - 1
274 c CALL TIMER_START('CG2D [SOLVE_FOR_PRESSURE]',myThid)
275 #ifdef DISCONNECTED_TILES
276 C-- Call the not-self-adjoint version of cg2d
277 CALL CG2D_EX0(
278 U cg2d_b, cg2d_x,
279 O firstResidual, minResidualSq, lastResidual,
280 U numIters, nIterMin,
281 I myThid )
282 #else /* not DISCONNECTED_TILES = default */
283 #ifdef ALLOW_CG2D_NSA
284 C-- Call the not-self-adjoint version of cg2d
285 CALL CG2D_NSA(
286 U cg2d_b, cg2d_x,
287 O firstResidual, minResidualSq, lastResidual,
288 U numIters, nIterMin,
289 I myThid )
290 #else /* not ALLOW_CG2D_NSA = default */
291 #ifdef ALLOW_SRCG
292 IF ( useSRCGSolver ) THEN
293 C-- Call the single reduce CG solver
294 CALL CG2D_SR(
295 U cg2d_b, cg2d_x,
296 O firstResidual, minResidualSq, lastResidual,
297 U numIters, nIterMin,
298 I myThid )
299 ELSE
300 #else
301 IF (.TRUE.) THEN
302 C-- Call the default CG solver
303 #endif /* ALLOW_SRCG */
304 CALL CG2D(
305 U cg2d_b, cg2d_x,
306 O firstResidual, minResidualSq, lastResidual,
307 U numIters, nIterMin,
308 I myThid )
309 ENDIF
310 #endif /* ALLOW_CG2D_NSA */
311 #endif /* DISCONNECTED_TILES */
312 _EXCH_XY_RL( cg2d_x, myThid )
313 c CALL TIMER_STOP ('CG2D [SOLVE_FOR_PRESSURE]',myThid)
314
315 #ifdef ALLOW_DEBUG
316 IF ( debugLevel .GE. debLevD ) THEN
317 CALL DEBUG_STATS_RL(1,cg2d_x,'cg2d_x (SOLVE_FOR_PRESSURE)',
318 & myThid)
319 ENDIF
320 #endif
321
322 C- dump CG2D output at monitorFreq (to reduce size of STD-OUTPUT files) :
323 IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,deltaTClock)
324 & ) THEN
325 IF ( debugLevel .GE. debLevA ) THEN
326 _BEGIN_MASTER( myThid )
327 WRITE(msgBuf,'(A20,1PE23.14)') 'cg2d_init_res =',firstResidual
328 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
329 WRITE(msgBuf,'(A27,2I8)')
330 & 'cg2d_iters(min,last) =', nIterMin, numIters
331 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
332 IF ( minResidualSq.GE.0. ) THEN
333 minResidualSq = SQRT(minResidualSq)
334 WRITE(msgBuf,'(A20,1PE23.14)') 'cg2d_min_res =',minResidualSq
335 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
336 ENDIF
337 WRITE(msgBuf,'(A20,1PE23.14)') 'cg2d_last_res =',lastResidual
338 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
339 _END_MASTER( myThid )
340 ENDIF
341 ENDIF
342
343 #ifdef ALLOW_DIAGNOSTICS
344 C-- Fill diagnostics
345 IF ( useDiagnostics .AND. implicSurfPress.NE.oneRL ) THEN
346 diagName = 'PHI_SURF'
347 IF ( DIAGNOSTICS_IS_ON(diagName,myThid) ) THEN
348 DO bj=myByLo(myThid),myByHi(myThid)
349 DO bi=myBxLo(myThid),myBxHi(myThid)
350 DO j=1-OLy,sNy+OLy
351 DO i=1-OLx,sNx+OLx
352 tmpVar(i,j) = implicSurfPress * cg2d_x(i,j,bi,bj)
353 & + (oneRL - implicSurfPress)* Bo_surf(i,j,bi,bj)
354 & * etaN(i,j,bi,bj)
355 ENDDO
356 ENDDO
357 CALL DIAGNOSTICS_FILL( tmpVar,diagName,1,1,2,bi,bj,myThid )
358 ENDDO
359 ENDDO
360 ENDIF
361 ELSEIF ( useDiagnostics ) THEN
362 CALL DIAGNOSTICS_FILL( cg2d_x,'PHI_SURF', 0,1, 0,1,1, myThid )
363 ENDIF
364 #endif /* ALLOW_DIAGNOSTICS */
365
366 C-- Transfert the 2D-solution to "etaN" :
367 DO bj=myByLo(myThid),myByHi(myThid)
368 DO bi=myBxLo(myThid),myBxHi(myThid)
369 DO j=1-OLy,sNy+OLy
370 DO i=1-OLx,sNx+OLx
371 etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)*cg2d_x(i,j,bi,bj)
372 ENDDO
373 ENDDO
374 ENDDO
375 ENDDO
376
377 #ifdef ALLOW_NONHYDROSTATIC
378 IF ( use3Dsolver ) THEN
379 IF ( DIFFERENT_MULTIPLE(diagFreq, myTime, deltaTClock) ) THEN
380 CALL WRITE_FLD_XY_RL( 'cg2d_x','I10', cg2d_x, myIter, myThid )
381 ENDIF
382
383 C-- Solve for a three-dimensional pressure term (NH or IGW or both ).
384 C see CG3D.h for the interface to this routine.
385
386 C-- Finish updating cg3d_b: 1) Add EmPmR contribution to top level cg3d_b:
387 C 2) Update or Add free-surface contribution
388 C 3) increment in horiz velocity due to new cg2d_x
389 C 4) add vertical velocity contribution.
390 CALL PRE_CG3D(
391 I oldFreeSurfTerm,
392 I cg2d_x,
393 U cg3d_b,
394 I myTime, myIter, myThid )
395
396 #ifdef ALLOW_DEBUG
397 IF ( debugLevel .GE. debLevD ) THEN
398 CALL DEBUG_STATS_RL(Nr,cg3d_b,'cg3d_b (SOLVE_FOR_PRESSURE)',
399 & myThid)
400 ENDIF
401 #endif
402 IF ( DIFFERENT_MULTIPLE( diagFreq, myTime, deltaTClock) ) THEN
403 CALL WRITE_FLD_XYZ_RL('cg3d_b','I10', cg3d_b, myIter,myThid )
404 ENDIF
405
406 firstResidual=0.
407 lastResidual=0.
408 numIters=cg3dMaxIters
409 CALL TIMER_START('CG3D [SOLVE_FOR_PRESSURE]',myThid)
410 #ifdef DISCONNECTED_TILES
411 CALL CG3D_EX0(
412 U cg3d_b, phi_nh,
413 O firstResidual, lastResidual,
414 U numIters,
415 I myIter, myThid )
416 #else /* not DISCONNECTED_TILES = default */
417 CALL CG3D(
418 U cg3d_b, phi_nh,
419 O firstResidual, lastResidual,
420 U numIters,
421 I myIter, myThid )
422 #endif /* DISCONNECTED_TILES */
423 _EXCH_XYZ_RL( phi_nh, myThid )
424 CALL TIMER_STOP ('CG3D [SOLVE_FOR_PRESSURE]',myThid)
425
426 IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,deltaTClock)
427 & ) THEN
428 IF ( debugLevel .GE. debLevA ) THEN
429 _BEGIN_MASTER( myThid )
430 WRITE(msgBuf,'(A20,1PE23.14)') 'cg3d_init_res =',firstResidual
431 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
432 WRITE(msgBuf,'(A27,I16)') 'cg3d_iters (last) = ',numIters
433 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
434 WRITE(msgBuf,'(A20,1PE23.14)') 'cg3d_last_res =',lastResidual
435 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
436 _END_MASTER( myThid )
437 ENDIF
438 ENDIF
439
440 C-- Separate the Hydrostatic Surface Pressure adjusment (=> put it in dPhiNH)
441 C from the Non-hydrostatic pressure (since cg3d_x contains both contribution)
442 IF ( nonHydrostatic .AND. exactConserv ) THEN
443 IF ( DIFFERENT_MULTIPLE( diagFreq, myTime, deltaTClock) ) THEN
444 CALL WRITE_FLD_XYZ_RL('cg3d_x','I10', phi_nh, myIter,myThid )
445 ENDIF
446 CALL POST_CG3D(
447 I zeroPsNH, zeroMeanPnh,
448 I myTime, myIter, myThid )
449 ENDIF
450
451 ENDIF
452 #endif /* ALLOW_NONHYDROSTATIC */
453
454 #ifdef ALLOW_SHOWFLOPS
455 CALL SHOWFLOPS_INSOLVE( myThid)
456 #endif
457
458 RETURN
459 END

  ViewVC Help
Powered by ViewVC 1.1.22