/[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.61 - (show annotations) (download)
Mon Aug 27 13:18:31 2007 UTC (16 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59g, checkpoint59h
Changes since 1.60: +6 -1 lines
output cg2d_b to file

1 C $Header: /u/gcmpack/MITgcm/model/src/solve_for_pressure.F,v 1.60 2007/06/01 16:42:16 heimbach 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 #ifdef ALLOW_OBCS
39 #include "OBCS.h"
40 #endif
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 _RL sumEmP, tileEmP
63 LOGICAL putPmEinXvector
64 INTEGER numIters, ks
65 CHARACTER*10 sufx
66 CHARACTER*(MAX_LEN_MBUF) msgBuf
67 #ifdef ALLOW_NONHYDROSTATIC
68 INTEGER kp1
69 _RL wFacKm, wFacKp
70 LOGICAL zeroPsNH
71 #endif
72 CEOP
73
74 #ifdef ALLOW_NONHYDROSTATIC
75 c zeroPsNH = .FALSE.
76 zeroPsNH = exactConserv
77 #endif
78
79 C deepAtmosphere & useRealFreshWaterFlux: only valid if deepFac2F(ksurf)=1
80 C anelastic (always Z-coordinate):
81 C 1) assume that rhoFacF(1)=1 (and ksurf == 1);
82 C (this reduces the number of lines of code to modify)
83 C 2) (a) 2-D continuity eq. compute div. of mass transport (<- add rhoFac)
84 C (b) gradient of surf.Press in momentum eq. (<- add 1/rhoFac)
85 C => 2 factors cancel in elliptic eq. for Phi_s ,
86 C but 1rst factor(a) remains in RHS cg2d_b.
87
88 C-- Initialise the Vector solution with etaN + deltaT*Global_mean_PmE
89 C instead of simply etaN ; This can speed-up the solver convergence in
90 C the case where |Global_mean_PmE| is large.
91 putPmEinXvector = .FALSE.
92 c putPmEinXvector = useRealFreshWaterFlux
93
94 C-- Save previous solution & Initialise Vector solution and source term :
95 sumEmP = 0.
96 DO bj=myByLo(myThid),myByHi(myThid)
97 DO bi=myBxLo(myThid),myBxHi(myThid)
98 DO j=1-OLy,sNy+OLy
99 DO i=1-OLx,sNx+OLx
100 #ifdef ALLOW_CD_CODE
101 etaNm1(i,j,bi,bj) = etaN(i,j,bi,bj)
102 #endif
103 cg2d_x(i,j,bi,bj) = Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
104 cg2d_b(i,j,bi,bj) = 0.
105 ENDDO
106 ENDDO
107 IF (useRealFreshWaterFlux) THEN
108 tmpFac = freeSurfFac*convertEmP2rUnit
109 IF (exactConserv)
110 & tmpFac = freeSurfFac*convertEmP2rUnit*implicDiv2DFlow
111 DO j=1,sNy
112 DO i=1,sNx
113 cg2d_b(i,j,bi,bj) =
114 & tmpFac*_rA(i,j,bi,bj)*EmPmR(i,j,bi,bj)/deltaTMom
115 ENDDO
116 ENDDO
117 ENDIF
118 IF ( putPmEinXvector ) THEN
119 tileEmP = 0.
120 DO j=1,sNy
121 DO i=1,sNx
122 tileEmP = tileEmP + rA(i,j,bi,bj)*EmPmR(i,j,bi,bj)
123 & *maskH(i,j,bi,bj)
124 ENDDO
125 ENDDO
126 sumEmP = sumEmP + tileEmP
127 ENDIF
128 ENDDO
129 ENDDO
130 IF ( putPmEinXvector ) THEN
131 _GLOBAL_SUM_R8( sumEmP, myThid )
132 ENDIF
133
134 DO bj=myByLo(myThid),myByHi(myThid)
135 DO bi=myBxLo(myThid),myBxHi(myThid)
136 IF ( putPmEinXvector ) THEN
137 tmpFac = 0.
138 IF (globalArea.GT.0.) tmpFac = freeSurfFac*deltaTfreesurf
139 & *convertEmP2rUnit*sumEmP/globalArea
140 DO j=1,sNy
141 DO i=1,sNx
142 cg2d_x(i,j,bi,bj) = cg2d_x(i,j,bi,bj)
143 & - tmpFac*Bo_surf(i,j,bi,bj)
144 ENDDO
145 ENDDO
146 ENDIF
147 C- RHS: similar to the divergence of the vertically integrated mass transport:
148 C del_i { Sum_k [ rhoFac.(dr.hFac).(dy.deepFac).(u*) ] } / deltaT
149 DO K=Nr,1,-1
150 DO j=1,sNy+1
151 DO i=1,sNx+1
152 uf(i,j) = _dyG(i,j,bi,bj)*deepFacC(k)
153 & *drF(k)*_hFacW(i,j,k,bi,bj)*rhoFacC(k)
154 vf(i,j) = _dxG(i,j,bi,bj)*deepFacC(k)
155 & *drF(k)*_hFacS(i,j,k,bi,bj)*rhoFacC(k)
156 ENDDO
157 ENDDO
158 CALL CALC_DIV_GHAT(
159 I bi,bj,1,sNx,1,sNy,K,
160 I uf,vf,
161 U cg2d_b,
162 I myThid)
163 ENDDO
164 ENDDO
165 ENDDO
166
167 C-- Add source term arising from w=d/dt (p_s + p_nh)
168 DO bj=myByLo(myThid),myByHi(myThid)
169 DO bi=myBxLo(myThid),myBxHi(myThid)
170 #ifdef ALLOW_NONHYDROSTATIC
171 IF ( use3Dsolver .AND. zeroPsNH ) THEN
172 DO j=1,sNy
173 DO i=1,sNx
174 ks = ksurfC(i,j,bi,bj)
175 IF ( ks.LE.Nr ) THEN
176 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
177 & -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)
178 & /deltaTMom/deltaTfreesurf
179 & * etaH(i,j,bi,bj)
180 cg3d_b(i,j,ks,bi,bj) = cg3d_b(i,j,ks,bi,bj)
181 & -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)
182 & /deltaTMom/deltaTfreesurf
183 & * etaH(i,j,bi,bj)
184 ENDIF
185 ENDDO
186 ENDDO
187 ELSEIF ( use3Dsolver ) THEN
188 DO j=1,sNy
189 DO i=1,sNx
190 ks = ksurfC(i,j,bi,bj)
191 IF ( ks.LE.Nr ) THEN
192 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
193 & -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)
194 & /deltaTMom/deltaTfreesurf
195 & *( etaN(i,j,bi,bj)
196 & +phi_nh(i,j,ks,bi,bj)*recip_Bo(i,j,bi,bj) )
197 cg3d_b(i,j,ks,bi,bj) = cg3d_b(i,j,ks,bi,bj)
198 & -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)
199 & /deltaTMom/deltaTfreesurf
200 & *( etaN(i,j,bi,bj)
201 & +phi_nh(i,j,ks,bi,bj)*recip_Bo(i,j,bi,bj) )
202 ENDIF
203 ENDDO
204 ENDDO
205 ELSEIF ( exactConserv ) THEN
206 #else
207 IF ( exactConserv ) THEN
208 #endif /* ALLOW_NONHYDROSTATIC */
209 DO j=1,sNy
210 DO i=1,sNx
211 ks = ksurfC(i,j,bi,bj)
212 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
213 & -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)
214 & /deltaTMom/deltaTfreesurf
215 & * etaH(i,j,bi,bj)
216 ENDDO
217 ENDDO
218 ELSE
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 & * etaN(i,j,bi,bj)
226 ENDDO
227 ENDDO
228 ENDIF
229
230 #ifdef ALLOW_OBCS
231 IF (useOBCS) THEN
232 DO i=1,sNx
233 C Northern boundary
234 IF (OB_Jn(I,bi,bj).NE.0) THEN
235 cg2d_b(I,OB_Jn(I,bi,bj),bi,bj)=0.
236 cg2d_x(I,OB_Jn(I,bi,bj),bi,bj)=0.
237 ENDIF
238 C Southern boundary
239 IF (OB_Js(I,bi,bj).NE.0) THEN
240 cg2d_b(I,OB_Js(I,bi,bj),bi,bj)=0.
241 cg2d_x(I,OB_Js(I,bi,bj),bi,bj)=0.
242 ENDIF
243 ENDDO
244 DO j=1,sNy
245 C Eastern boundary
246 IF (OB_Ie(J,bi,bj).NE.0) THEN
247 cg2d_b(OB_Ie(J,bi,bj),J,bi,bj)=0.
248 cg2d_x(OB_Ie(J,bi,bj),J,bi,bj)=0.
249 ENDIF
250 C Western boundary
251 IF (OB_Iw(J,bi,bj).NE.0) THEN
252 cg2d_b(OB_Iw(J,bi,bj),J,bi,bj)=0.
253 cg2d_x(OB_Iw(J,bi,bj),J,bi,bj)=0.
254 ENDIF
255 ENDDO
256 ENDIF
257 #endif /* ALLOW_OBCS */
258 C- end bi,bj loops
259 ENDDO
260 ENDDO
261
262 #ifdef ALLOW_DEBUG
263 IF ( debugLevel .GE. debLevB ) THEN
264 CALL DEBUG_STATS_RL(1,cg2d_b,'cg2d_b (SOLVE_FOR_PRESSURE)',
265 & myThid)
266 ENDIF
267 #endif
268 IF ( DIFFERENT_MULTIPLE(diagFreq, myTime, deltaTClock) ) THEN
269 WRITE(sufx,'(I10.10)') myIter
270 CALL WRITE_FLD_XY_RS( 'cg2d_b.', sufx, cg2d_b, myIter, myThid )
271 ENDIF
272
273 C-- Find the surface pressure using a two-dimensional conjugate
274 C-- gradient solver.
275 C see CG2D.h for the interface to this routine.
276 firstResidual=0.
277 lastResidual=0.
278 numIters=cg2dMaxIters
279 c CALL TIMER_START('CG2D [SOLVE_FOR_PRESSURE]',myThid)
280 #ifdef ALLOW_CG2D_NSA
281 C-- Call the not-self-adjoint version of cg2d
282 CALL CG2D_NSA(
283 U cg2d_b,
284 U cg2d_x,
285 O firstResidual,
286 O lastResidual,
287 U numIters,
288 I myThid )
289 #else /* not ALLOW_CG2D_NSA = default */
290 CALL CG2D(
291 U cg2d_b,
292 U cg2d_x,
293 O firstResidual,
294 O lastResidual,
295 U numIters,
296 I myThid )
297 #endif /* ALLOW_CG2D_NSA */
298 _EXCH_XY_R8(cg2d_x, myThid )
299 c CALL TIMER_STOP ('CG2D [SOLVE_FOR_PRESSURE]',myThid)
300
301 #ifdef ALLOW_DEBUG
302 IF ( debugLevel .GE. debLevB ) THEN
303 CALL DEBUG_STATS_RL(1,cg2d_x,'cg2d_x (SOLVE_FOR_PRESSURE)',
304 & myThid)
305 ENDIF
306 #endif
307
308 C- dump CG2D output at monitorFreq (to reduce size of STD-OUTPUT files) :
309 IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,deltaTClock)
310 & ) THEN
311 IF ( debugLevel .GE. debLevA ) THEN
312 _BEGIN_MASTER( myThid )
313 WRITE(msgBuf,'(A34,1PE24.14)') 'cg2d_init_res =',firstResidual
314 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
315 WRITE(msgBuf,'(A34,I6)') 'cg2d_iters =',numIters
316 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
317 WRITE(msgBuf,'(A34,1PE24.14)') 'cg2d_res =',lastResidual
318 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
319 _END_MASTER( myThid )
320 ENDIF
321 ENDIF
322
323 C-- Transfert the 2D-solution to "etaN" :
324 DO bj=myByLo(myThid),myByHi(myThid)
325 DO bi=myBxLo(myThid),myBxHi(myThid)
326 DO j=1-OLy,sNy+OLy
327 DO i=1-OLx,sNx+OLx
328 etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)*cg2d_x(i,j,bi,bj)
329 ENDDO
330 ENDDO
331 ENDDO
332 ENDDO
333
334 #ifdef ALLOW_NONHYDROSTATIC
335 IF ( use3Dsolver ) THEN
336
337 C-- Solve for a three-dimensional pressure term (NH or IGW or both ).
338 C see CG3D.h for the interface to this routine.
339 DO bj=myByLo(myThid),myByHi(myThid)
340 DO bi=myBxLo(myThid),myBxHi(myThid)
341 DO j=1,sNy+1
342 DO i=1,sNx+1
343 uf(i,j)=-_recip_dxC(i,j,bi,bj)*
344 & (cg2d_x(i,j,bi,bj)-cg2d_x(i-1,j,bi,bj))
345 vf(i,j)=-_recip_dyC(i,j,bi,bj)*
346 & (cg2d_x(i,j,bi,bj)-cg2d_x(i,j-1,bi,bj))
347 ENDDO
348 ENDDO
349
350 #ifdef ALLOW_OBCS
351 IF (useOBCS) THEN
352 DO i=1,sNx+1
353 C Northern boundary
354 IF (OB_Jn(I,bi,bj).NE.0) THEN
355 vf(I,OB_Jn(I,bi,bj))=0.
356 ENDIF
357 C Southern boundary
358 IF (OB_Js(I,bi,bj).NE.0) THEN
359 vf(I,OB_Js(I,bi,bj)+1)=0.
360 ENDIF
361 ENDDO
362 DO j=1,sNy+1
363 C Eastern boundary
364 IF (OB_Ie(J,bi,bj).NE.0) THEN
365 uf(OB_Ie(J,bi,bj),J)=0.
366 ENDIF
367 C Western boundary
368 IF (OB_Iw(J,bi,bj).NE.0) THEN
369 uf(OB_Iw(J,bi,bj)+1,J)=0.
370 ENDIF
371 ENDDO
372 ENDIF
373 #endif /* ALLOW_OBCS */
374
375 IF ( usingZCoords ) THEN
376 C- Z coordinate: assume surface @ level k=1
377 tmpFac = freeSurfFac*deepFac2F(1)
378 ELSE
379 C- Other than Z coordinate: no assumption on surface level index
380 tmpFac = 0.
381 DO j=1,sNy
382 DO i=1,sNx
383 ks = ksurfC(i,j,bi,bj)
384 IF ( ks.LE.Nr ) THEN
385 cg3d_b(i,j,ks,bi,bj) = cg3d_b(i,j,ks,bi,bj)
386 & +freeSurfFac*etaN(i,j,bi,bj)/deltaTfreesurf
387 & *_rA(i,j,bi,bj)*deepFac2F(ks)/deltaTmom
388 ENDIF
389 ENDDO
390 ENDDO
391 ENDIF
392 K=1
393 kp1 = MIN(k+1,Nr)
394 wFacKp = deepFac2F(kp1)*rhoFacF(kp1)
395 IF (k.GE.Nr) wFacKp = 0.
396 DO j=1,sNy
397 DO i=1,sNx
398 cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
399 & +drF(K)*dyG(i+1,j,bi,bj)*_hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
400 & -drF(K)*dyG( i ,j,bi,bj)*_hFacW( i ,j,k,bi,bj)*uf( i ,j)
401 & +drF(K)*dxG(i,j+1,bi,bj)*_hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
402 & -drF(K)*dxG(i, j ,bi,bj)*_hFacS(i, j ,k,bi,bj)*vf(i, j )
403 & +( tmpFac*etaN(i,j,bi,bj)/deltaTfreesurf
404 & -wVel(i,j,kp1,bi,bj)*wFacKp
405 & )*_rA(i,j,bi,bj)/deltaTmom
406 ENDDO
407 ENDDO
408 DO K=2,Nr
409 kp1 = MIN(k+1,Nr)
410 C- deepFac & rhoFac cancel with the ones in uf[=del_i(Phi)/dx],vf ;
411 C both appear in wVel term, but at 2 different levels
412 wFacKm = deepFac2F( k )*rhoFacF( k )
413 wFacKp = deepFac2F(kp1)*rhoFacF(kp1)
414 IF (k.GE.Nr) wFacKp = 0.
415 DO j=1,sNy
416 DO i=1,sNx
417 cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
418 & +drF(K)*dyG(i+1,j,bi,bj)*_hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
419 & -drF(K)*dyG( i ,j,bi,bj)*_hFacW( i ,j,k,bi,bj)*uf( i ,j)
420 & +drF(K)*dxG(i,j+1,bi,bj)*_hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
421 & -drF(K)*dxG(i, j ,bi,bj)*_hFacS(i, j ,k,bi,bj)*vf(i, j )
422 & +( wVel(i,j, k ,bi,bj)*wFacKm*maskC(i,j,k-1,bi,bj)
423 & -wVel(i,j,kp1,bi,bj)*wFacKp
424 & )*_rA(i,j,bi,bj)/deltaTmom
425
426 ENDDO
427 ENDDO
428 ENDDO
429
430 #ifdef ALLOW_OBCS
431 IF (useOBCS) THEN
432 DO K=1,Nr
433 DO i=1,sNx
434 C Northern boundary
435 IF (OB_Jn(I,bi,bj).NE.0) THEN
436 cg3d_b(I,OB_Jn(I,bi,bj),K,bi,bj)=0.
437 ENDIF
438 C Southern boundary
439 IF (OB_Js(I,bi,bj).NE.0) THEN
440 cg3d_b(I,OB_Js(I,bi,bj),K,bi,bj)=0.
441 ENDIF
442 ENDDO
443 DO j=1,sNy
444 C Eastern boundary
445 IF (OB_Ie(J,bi,bj).NE.0) THEN
446 cg3d_b(OB_Ie(J,bi,bj),J,K,bi,bj)=0.
447 ENDIF
448 C Western boundary
449 IF (OB_Iw(J,bi,bj).NE.0) THEN
450 cg3d_b(OB_Iw(J,bi,bj),J,K,bi,bj)=0.
451 ENDIF
452 ENDDO
453 ENDDO
454 ENDIF
455 #endif /* ALLOW_OBCS */
456 C- end bi,bj loops
457 ENDDO
458 ENDDO
459
460 firstResidual=0.
461 lastResidual=0.
462 numIters=cg3dMaxIters
463 CALL TIMER_START('CG3D [SOLVE_FOR_PRESSURE]',myThid)
464 CALL CG3D(
465 U cg3d_b,
466 U phi_nh,
467 O firstResidual,
468 O lastResidual,
469 U numIters,
470 I myThid )
471 _EXCH_XYZ_R8(phi_nh, myThid )
472 CALL TIMER_STOP ('CG3D [SOLVE_FOR_PRESSURE]',myThid)
473
474 IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,deltaTClock)
475 & ) THEN
476 IF ( debugLevel .GE. debLevA ) THEN
477 _BEGIN_MASTER( myThid )
478 WRITE(msgBuf,'(A34,1PE24.14)') 'cg3d_init_res =',firstResidual
479 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
480 WRITE(msgBuf,'(A34,I6)') 'cg3d_iters =',numIters
481 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
482 WRITE(msgBuf,'(A34,1PE24.14)') 'cg3d_res =',lastResidual
483 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
484 _END_MASTER( myThid )
485 ENDIF
486 ENDIF
487
488 C-- Update surface pressure (account for NH-p @ surface level) and NH pressure:
489 IF ( zeroPsNH ) THEN
490 DO bj=myByLo(myThid),myByHi(myThid)
491 DO bi=myBxLo(myThid),myBxHi(myThid)
492
493 IF ( usingZCoords ) THEN
494 C- Z coordinate: assume surface @ level k=1
495 DO k=2,Nr
496 DO j=1-OLy,sNy+OLy
497 DO i=1-OLx,sNx+OLx
498 phi_nh(i,j,k,bi,bj) = phi_nh(i,j,k,bi,bj)
499 & - phi_nh(i,j,1,bi,bj)
500 ENDDO
501 ENDDO
502 ENDDO
503 DO j=1-OLy,sNy+OLy
504 DO i=1-OLx,sNx+OLx
505 etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)
506 & *(cg2d_x(i,j,bi,bj) + phi_nh(i,j,1,bi,bj))
507 phi_nh(i,j,1,bi,bj) = 0.
508 ENDDO
509 ENDDO
510 ELSE
511 C- Other than Z coordinate: no assumption on surface level index
512 DO j=1-OLy,sNy+OLy
513 DO i=1-OLx,sNx+OLx
514 ks = ksurfC(i,j,bi,bj)
515 IF ( ks.LE.Nr ) THEN
516 etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)
517 & *(cg2d_x(i,j,bi,bj) + phi_nh(i,j,ks,bi,bj))
518 DO k=Nr,1,-1
519 phi_nh(i,j,k,bi,bj) = phi_nh(i,j,k,bi,bj)
520 & - phi_nh(i,j,ks,bi,bj)
521 ENDDO
522 ENDIF
523 ENDDO
524 ENDDO
525 ENDIF
526
527 ENDDO
528 ENDDO
529 ENDIF
530
531 ENDIF
532 #endif /* ALLOW_NONHYDROSTATIC */
533
534 #ifdef ALLOW_SHOWFLOPS
535 CALL SHOWFLOPS_INSOLVE( myThid)
536 #endif
537
538 RETURN
539 END

  ViewVC Help
Powered by ViewVC 1.1.22