/[MITgcm]/MITgcm_contrib/ksnow/press_release/code/solve_for_pressure.F
ViewVC logotype

Annotation of /MITgcm_contrib/ksnow/press_release/code/solve_for_pressure.F

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


Revision 1.2 - (hide annotations) (download)
Sun Feb 5 15:45:23 2017 UTC (8 years, 10 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
Changes since 1.1: +6 -16 lines
updates to allow parallel computation

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

  ViewVC Help
Powered by ViewVC 1.1.22