/[MITgcm]/MITgcm/model/src/solve_for_pressure.F
ViewVC logotype

Diff of /MITgcm/model/src/solve_for_pressure.F

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

revision 1.64 by jmc, Sun Aug 24 21:40:18 2008 UTC revision 1.74 by jmc, Mon Dec 21 00:24:58 2009 UTC
# Line 7  C $Name$ Line 7  C $Name$
7  CBOP  CBOP
8  C     !ROUTINE: SOLVE_FOR_PRESSURE  C     !ROUTINE: SOLVE_FOR_PRESSURE
9  C     !INTERFACE:  C     !INTERFACE:
10        SUBROUTINE SOLVE_FOR_PRESSURE(myTime, myIter, myThid)        SUBROUTINE SOLVE_FOR_PRESSURE( myTime, myIter, myThid )
11    
12  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
13  C     *==========================================================*  C     *==========================================================*
# Line 55  C     myThid :: Thread number for this i Line 55  C     myThid :: Thread number for this i
55  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
56  C     == Local variables ==  C     == Local variables ==
57        INTEGER i,j,k,bi,bj        INTEGER i,j,k,bi,bj
58          INTEGER ks
59          INTEGER numIters
60        _RL firstResidual,lastResidual        _RL firstResidual,lastResidual
61        _RL tmpFac        _RL tmpFac
62        _RL sumEmP, tileEmP        _RL sumEmP, tileEmP(nSx,nSy)
63        LOGICAL putPmEinXvector        LOGICAL putPmEinXvector
64        INTEGER numIters, ks        INTEGER ioUnit
65        CHARACTER*10 sufx        CHARACTER*10 sufx
66        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
67  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
68        INTEGER kp1        LOGICAL zeroPsNH, zeroMeanPnh, oldFreeSurfTerm
       _RL     wFacKm, wFacKp  
       LOGICAL zeroPsNH  
       _RL     uf(1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
       _RL     vf(1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
69  #else  #else
70        _RL     cg3d_b(1)        _RL     cg3d_b(1)
71  #endif  #endif
72  CEOP  CEOP
73    
74  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
75  c       zeroPsNH = .FALSE.          zeroPsNH = .FALSE.
76          zeroPsNH = exactConserv  c       zeroPsNH = use3Dsolver .AND. exactConserv
77    c    &                         .AND. select_rStar.EQ.0
78            zeroMeanPnh = .FALSE.
79    c       zeroMeanPnh = use3Dsolver .AND. select_rStar.NE.0
80    c       oldFreeSurfTerm = use3Dsolver .AND. select_rStar.EQ.0
81    c    &                                .AND. .NOT.zeroPsNH
82            oldFreeSurfTerm = use3Dsolver .AND. .NOT.exactConserv
83  #else  #else
84          cg3d_b(1) = 0.          cg3d_b(1) = 0.
85  #endif  #endif
# Line 95  C     the case where |Global_mean_PmE| i Line 99  C     the case where |Global_mean_PmE| i
99        putPmEinXvector = .FALSE.        putPmEinXvector = .FALSE.
100  c     putPmEinXvector = useRealFreshWaterFlux.AND.fluidIsWater  c     putPmEinXvector = useRealFreshWaterFlux.AND.fluidIsWater
101    
102          IF ( myIter.EQ.1+nIter0 .AND. debugLevel .GE. debLevA ) THEN
103            _BEGIN_MASTER( myThid )
104            ioUnit = standardMessageUnit
105            WRITE(msgBuf,'(2A,L5)') 'SOLVE_FOR_PRESSURE:',
106         &       ' putPmEinXvector =', putPmEinXvector
107            CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
108    #ifdef ALLOW_NONHYDROSTATIC
109            WRITE(msgBuf,'(A,2(A,L5))') 'SOLVE_FOR_PRESSURE:',
110         &       ' zeroPsNH=', zeroPsNH, ' , zeroMeanPnh=', zeroMeanPnh
111            CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
112            WRITE(msgBuf,'(2A,L5)') 'SOLVE_FOR_PRESSURE:',
113         &       ' oldFreeSurfTerm =', oldFreeSurfTerm
114            CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
115    #endif
116            _END_MASTER( myThid )
117          ENDIF
118    
119  C--   Save previous solution & Initialise Vector solution and source term :  C--   Save previous solution & Initialise Vector solution and source term :
120        sumEmP = 0.        sumEmP = 0.
121        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
# Line 120  C--   Save previous solution & Initialis Line 141  C--   Save previous solution & Initialis
141           ENDDO           ENDDO
142          ENDIF          ENDIF
143          IF ( putPmEinXvector ) THEN          IF ( putPmEinXvector ) THEN
144           tileEmP = 0.           tileEmP(bi,bj) = 0.
145           DO j=1,sNy           DO j=1,sNy
146            DO i=1,sNx            DO i=1,sNx
147              tileEmP = tileEmP + rA(i,j,bi,bj)*EmPmR(i,j,bi,bj)              tileEmP(bi,bj) = tileEmP(bi,bj)
148       &                                       *maskH(i,j,bi,bj)       &                     + rA(i,j,bi,bj)*EmPmR(i,j,bi,bj)
149         &                                    *maskInC(i,j,bi,bj)
150            ENDDO            ENDDO
151           ENDDO           ENDDO
          sumEmP = sumEmP + tileEmP  
152          ENDIF          ENDIF
153         ENDDO         ENDDO
154        ENDDO        ENDDO
155        IF ( putPmEinXvector ) THEN        IF ( putPmEinXvector ) THEN
156          _GLOBAL_SUM_R8( sumEmP, myThid )          CALL GLOBAL_SUM_TILE_RL( tileEmP, sumEmP, myThid )
157        ENDIF        ENDIF
158    
159        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
# Line 159  C       del_i { Sum_k [ rhoFac.(dr.hFac) Line 180  C       del_i { Sum_k [ rhoFac.(dr.hFac)
180         ENDDO         ENDDO
181        ENDDO        ENDDO
182    
 C--   Add source term arising from w=d/dt (p_s + p_nh)  
183        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
184         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
185  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
186          IF ( use3Dsolver .AND. zeroPsNH ) THEN          IF ( oldFreeSurfTerm ) THEN
187           DO j=1,sNy  C--   Add source term arising from w=d/dt (p_s + p_nh)
           DO i=1,sNx  
            ks = ksurfC(i,j,bi,bj)  
            IF ( ks.LE.Nr ) THEN  
             cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)  
      &       -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)  
      &         /deltaTMom/deltaTfreesurf  
      &         * etaH(i,j,bi,bj)  
             cg3d_b(i,j,ks,bi,bj) = cg3d_b(i,j,ks,bi,bj)  
      &       -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)  
      &         /deltaTMom/deltaTfreesurf  
      &         * etaH(i,j,bi,bj)  
            ENDIF  
           ENDDO  
          ENDDO  
         ELSEIF ( use3Dsolver ) THEN  
188           DO j=1,sNy           DO j=1,sNy
189            DO i=1,sNx            DO i=1,sNx
190             ks = ksurfC(i,j,bi,bj)             ks = ksurfC(i,j,bi,bj)
# Line 199  C--   Add source term arising from w=d/d Line 204  C--   Add source term arising from w=d/d
204           ENDDO           ENDDO
205          ELSEIF ( exactConserv ) THEN          ELSEIF ( exactConserv ) THEN
206  #else  #else
207    C--   Add source term arising from w=d/dt (p_s)
208          IF ( exactConserv ) THEN          IF ( exactConserv ) THEN
209  #endif /* ALLOW_NONHYDROSTATIC */  #endif /* ALLOW_NONHYDROSTATIC */
210           DO j=1,sNy           DO j=1,sNy
# Line 262  C-    end bi,bj loops Line 268  C-    end bi,bj loops
268  #endif  #endif
269        IF ( DIFFERENT_MULTIPLE(diagFreq, myTime, deltaTClock) ) THEN        IF ( DIFFERENT_MULTIPLE(diagFreq, myTime, deltaTClock) ) THEN
270         WRITE(sufx,'(I10.10)') myIter         WRITE(sufx,'(I10.10)') myIter
271         CALL WRITE_FLD_XY_RS( 'cg2d_b.', sufx, cg2d_b, myIter, myThid )         CALL WRITE_FLD_XY_RL( 'cg2d_b.', sufx, cg2d_b, myIter, myThid )
272        ENDIF        ENDIF
273    
274  C--   Find the surface pressure using a two-dimensional conjugate  C--   Find the surface pressure using a two-dimensional conjugate
# Line 282  C--   Call the not-self-adjoint version Line 288  C--   Call the not-self-adjoint version
288       U           numIters,       U           numIters,
289       I           myThid )       I           myThid )
290  #else /* not ALLOW_CG2D_NSA = default */  #else /* not ALLOW_CG2D_NSA = default */
291        CALL CG2D(  #ifdef ALLOW_SRCG
292          IF ( useSRCGSolver ) THEN
293    C--   Call the single reduce CG solver
294           CALL CG2D_SR(
295         U           cg2d_b,
296         U           cg2d_x,
297         O           firstResidual,
298         O           lastResidual,
299         U           numIters,
300         I           myThid )
301          ELSE
302    #else
303          IF (.TRUE.) THEN
304    C--   Call the default CG solver
305    #endif /* ALLOW_SRCG */
306           CALL CG2D(
307       U           cg2d_b,       U           cg2d_b,
308       U           cg2d_x,       U           cg2d_x,
309       O           firstResidual,       O           firstResidual,
310       O           lastResidual,       O           lastResidual,
311       U           numIters,       U           numIters,
312       I           myThid )       I           myThid )
313          ENDIF
314  #endif /* ALLOW_CG2D_NSA */  #endif /* ALLOW_CG2D_NSA */
315        _EXCH_XY_R8(cg2d_x, myThid )        _EXCH_XY_RL( cg2d_x, myThid )
316  c     CALL TIMER_STOP ('CG2D   [SOLVE_FOR_PRESSURE]',myThid)  c     CALL TIMER_STOP ('CG2D   [SOLVE_FOR_PRESSURE]',myThid)
317    
318  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
# Line 328  C--   Transfert the 2D-solution to "etaN Line 350  C--   Transfert the 2D-solution to "etaN
350    
351  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
352        IF ( use3Dsolver ) THEN        IF ( use3Dsolver ) THEN
353           IF ( DIFFERENT_MULTIPLE(diagFreq, myTime, deltaTClock) ) THEN
354            WRITE(sufx,'(I10.10)') myIter
355            CALL WRITE_FLD_XY_RL( 'cg2d_x.',sufx, cg2d_x, myIter, myThid )
356           ENDIF
357    
358  C--   Solve for a three-dimensional pressure term (NH or IGW or both ).  C--   Solve for a three-dimensional pressure term (NH or IGW or both ).
359  C     see CG3D.h for the interface to this routine.  C     see CG3D.h for the interface to this routine.
        DO bj=myByLo(myThid),myByHi(myThid)  
         DO bi=myBxLo(myThid),myBxHi(myThid)  
          DO j=1,sNy+1  
           DO i=1,sNx+1  
            uf(i,j)=-_recip_dxC(i,j,bi,bj)*  
      &         (cg2d_x(i,j,bi,bj)-cg2d_x(i-1,j,bi,bj))  
            vf(i,j)=-_recip_dyC(i,j,bi,bj)*  
      &         (cg2d_x(i,j,bi,bj)-cg2d_x(i,j-1,bi,bj))  
           ENDDO  
          ENDDO  
360    
361  #ifdef ALLOW_OBCS  C--   Finish updating cg3d_b: 1) Add EmPmR contribution to top level cg3d_b:
362           IF (useOBCS) THEN  C                             2) Update or Add free-surface contribution
363            DO i=1,sNx+1  C                             3) increment in horiz velocity due to new cg2d_x
364  C Northern boundary  C                             4) add vertical velocity contribution.
365            IF (OB_Jn(i,bi,bj).NE.0) THEN         CALL PRE_CG3D(
366             vf(i,OB_Jn(i,bi,bj))=0.       I                oldFreeSurfTerm,
367            ENDIF       I                cg2d_x,
368  C Southern boundary       U                cg3d_b,
369            IF (OB_Js(i,bi,bj).NE.0) THEN       I                myTime, myIter, myThid )
            vf(i,OB_Js(i,bi,bj)+1)=0.  
           ENDIF  
           ENDDO  
           DO j=1,sNy+1  
 C Eastern boundary  
           IF (OB_Ie(j,bi,bj).NE.0) THEN  
            uf(OB_Ie(j,bi,bj),j)=0.  
           ENDIF  
 C Western boundary  
           IF (OB_Iw(j,bi,bj).NE.0) THEN  
            uf(OB_Iw(j,bi,bj)+1,J)=0.  
           ENDIF  
           ENDDO  
          ENDIF  
 #endif /* ALLOW_OBCS */  
   
          IF ( usingZCoords ) THEN  
 C-       Z coordinate: assume surface @ level k=1  
            tmpFac = freeSurfFac*deepFac2F(1)  
          ELSE  
 C-       Other than Z coordinate: no assumption on surface level index  
            tmpFac = 0.  
            DO j=1,sNy  
             DO i=1,sNx  
               ks = ksurfC(i,j,bi,bj)  
               IF ( ks.LE.Nr ) THEN  
                cg3d_b(i,j,ks,bi,bj) = cg3d_b(i,j,ks,bi,bj)  
      &              +freeSurfFac*etaN(i,j,bi,bj)/deltaTfreesurf  
      &                  *_rA(i,j,bi,bj)*deepFac2F(ks)/deltaTmom  
               ENDIF  
             ENDDO  
            ENDDO  
          ENDIF  
          k=1  
          kp1 = MIN(k+1,Nr)  
          wFacKp = deepFac2F(kp1)*rhoFacF(kp1)  
          IF (k.GE.Nr) wFacKp = 0.  
          DO j=1,sNy  
           DO i=1,sNx  
             cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)  
      &       +drF(k)*dyG(i+1,j,bi,bj)*_hFacW(i+1,j,k,bi,bj)*uf(i+1,j)  
      &       -drF(k)*dyG( i ,j,bi,bj)*_hFacW( i ,j,k,bi,bj)*uf( i ,j)  
      &       +drF(k)*dxG(i,j+1,bi,bj)*_hFacS(i,j+1,k,bi,bj)*vf(i,j+1)  
      &       -drF(k)*dxG(i, j ,bi,bj)*_hFacS(i, j ,k,bi,bj)*vf(i, j )  
      &       +( tmpFac*etaN(i,j,bi,bj)/deltaTfreesurf  
      &         -wVel(i,j,kp1,bi,bj)*wFacKp  
      &        )*_rA(i,j,bi,bj)/deltaTmom  
           ENDDO  
          ENDDO  
          DO k=2,Nr  
           kp1 = MIN(k+1,Nr)  
 C-       deepFac & rhoFac cancel with the ones in uf[=del_i(Phi)/dx],vf ;  
 C        both appear in wVel term, but at 2 different levels  
           wFacKm = deepFac2F( k )*rhoFacF( k )  
           wFacKp = deepFac2F(kp1)*rhoFacF(kp1)  
           IF (k.GE.Nr) wFacKp = 0.  
           DO j=1,sNy  
            DO i=1,sNx  
             cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)  
      &       +drF(k)*dyG(i+1,j,bi,bj)*_hFacW(i+1,j,k,bi,bj)*uf(i+1,j)  
      &       -drF(k)*dyG( i ,j,bi,bj)*_hFacW( i ,j,k,bi,bj)*uf( i ,j)  
      &       +drF(k)*dxG(i,j+1,bi,bj)*_hFacS(i,j+1,k,bi,bj)*vf(i,j+1)  
      &       -drF(k)*dxG(i, j ,bi,bj)*_hFacS(i, j ,k,bi,bj)*vf(i, j )  
      &       +( wVel(i,j, k ,bi,bj)*wFacKm*maskC(i,j,k-1,bi,bj)  
      &         -wVel(i,j,kp1,bi,bj)*wFacKp  
      &        )*_rA(i,j,bi,bj)/deltaTmom  
370    
371             ENDDO  #ifdef ALLOW_DEBUG
372            ENDDO         IF ( debugLevel .GE. debLevB ) THEN
373           ENDDO          CALL DEBUG_STATS_RL(Nr,cg3d_b,'cg3d_b (SOLVE_FOR_PRESSURE)',
374         &                         myThid)
375  #ifdef ALLOW_OBCS         ENDIF
376           IF (useOBCS) THEN  #endif
377            DO k=1,Nr         IF ( DIFFERENT_MULTIPLE( diagFreq, myTime, deltaTClock) ) THEN
378            DO i=1,sNx          WRITE(sufx,'(I10.10)') myIter
379  C Northern boundary          CALL WRITE_FLD_XYZ_RL('cg3d_b.',sufx, cg3d_b, myIter,myThid )
           IF (OB_Jn(i,bi,bj).NE.0) THEN  
            cg3d_b(i,OB_Jn(i,bi,bj),k,bi,bj)=0.  
           ENDIF  
 C Southern boundary  
           IF (OB_Js(i,bi,bj).NE.0) THEN  
            cg3d_b(i,OB_Js(i,bi,bj),k,bi,bj)=0.  
           ENDIF  
           ENDDO  
           DO j=1,sNy  
 C Eastern boundary  
           IF (OB_Ie(j,bi,bj).NE.0) THEN  
            cg3d_b(OB_Ie(j,bi,bj),j,k,bi,bj)=0.  
           ENDIF  
 C Western boundary  
           IF (OB_Iw(j,bi,bj).NE.0) THEN  
            cg3d_b(OB_Iw(j,bi,bj),j,k,bi,bj)=0.  
           ENDIF  
           ENDDO  
           ENDDO  
          ENDIF  
 #endif /* ALLOW_OBCS */  
 C-    end bi,bj loops  
         ENDDO  
        ENDDO  
   
       firstResidual=0.  
       lastResidual=0.  
       numIters=cg3dMaxIters  
       CALL TIMER_START('CG3D   [SOLVE_FOR_PRESSURE]',myThid)  
       CALL CG3D(  
      U           cg3d_b,  
      U           phi_nh,  
      O           firstResidual,  
      O           lastResidual,  
      U           numIters,  
      I           myThid )  
       _EXCH_XYZ_R8(phi_nh, myThid )  
       CALL TIMER_STOP ('CG3D   [SOLVE_FOR_PRESSURE]',myThid)  
   
       IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,deltaTClock)  
      &   ) THEN  
        IF ( debugLevel .GE. debLevA ) THEN  
         _BEGIN_MASTER( myThid )  
         WRITE(msgBuf,'(A34,1PE24.14)') 'cg3d_init_res =',firstResidual  
         CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)  
         WRITE(msgBuf,'(A34,I6)') 'cg3d_iters =',numIters  
         CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)  
         WRITE(msgBuf,'(A34,1PE24.14)') 'cg3d_res =',lastResidual  
         CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)  
         _END_MASTER( myThid )  
380         ENDIF         ENDIF
       ENDIF  
381    
382  C--   Update surface pressure (account for NH-p @ surface level) and NH pressure:         firstResidual=0.
383        IF ( zeroPsNH ) THEN         lastResidual=0.
384         DO bj=myByLo(myThid),myByHi(myThid)         numIters=cg3dMaxIters
385          DO bi=myBxLo(myThid),myBxHi(myThid)         CALL TIMER_START('CG3D   [SOLVE_FOR_PRESSURE]',myThid)
386           CALL CG3D(
387           IF ( usingZCoords ) THEN       U            cg3d_b,
388  C-       Z coordinate: assume surface @ level k=1       U            phi_nh,
389            DO k=2,Nr       O            firstResidual,
390             DO j=1-OLy,sNy+OLy       O            lastResidual,
391              DO i=1-OLx,sNx+OLx       U            numIters,
392               phi_nh(i,j,k,bi,bj) = phi_nh(i,j,k,bi,bj)       I            myIter, myThid )
393       &                           - phi_nh(i,j,1,bi,bj)         _EXCH_XYZ_RL( phi_nh, myThid )
394              ENDDO         CALL TIMER_STOP ('CG3D   [SOLVE_FOR_PRESSURE]',myThid)
395             ENDDO  
396            ENDDO         IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,deltaTClock)
397            DO j=1-OLy,sNy+OLy       &    ) THEN
398             DO i=1-OLx,sNx+OLx          IF ( debugLevel .GE. debLevA ) THEN
399               etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)           _BEGIN_MASTER( myThid )
400       &                       *(cg2d_x(i,j,bi,bj) + phi_nh(i,j,1,bi,bj))           WRITE(msgBuf,'(A34,1PE24.14)') 'cg3d_init_res =',firstResidual
401               phi_nh(i,j,1,bi,bj) = 0.           CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
402             ENDDO           WRITE(msgBuf,'(A34,I6)') 'cg3d_iters =',numIters
403            ENDDO           CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
404           ELSE           WRITE(msgBuf,'(A34,1PE24.14)') 'cg3d_res =',lastResidual
405  C-       Other than Z coordinate: no assumption on surface level index           CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
406            DO j=1-OLy,sNy+OLy           _END_MASTER( myThid )
407             DO i=1-OLx,sNx+OLx          ENDIF
408              ks = ksurfC(i,j,bi,bj)         ENDIF
             IF ( ks.LE.Nr ) THEN  
              etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)  
      &                       *(cg2d_x(i,j,bi,bj) + phi_nh(i,j,ks,bi,bj))  
              DO k=Nr,1,-1  
               phi_nh(i,j,k,bi,bj) = phi_nh(i,j,k,bi,bj)  
      &                            - phi_nh(i,j,ks,bi,bj)  
              ENDDO  
             ENDIF  
            ENDDO  
           ENDDO  
          ENDIF  
409    
410          ENDDO  C--   Separate the Hydrostatic Surface Pressure adjusment (=> put it in dPhiNH)
411         ENDDO  C     from the Non-hydrostatic pressure (since cg3d_x contains both contribution)
412        ENDIF         IF ( nonHydrostatic .AND. exactConserv ) THEN
413            IF ( DIFFERENT_MULTIPLE( diagFreq, myTime, deltaTClock) ) THEN
414             WRITE(sufx,'(I10.10)') myIter
415             CALL WRITE_FLD_XYZ_RL('cg3d_x.',sufx, phi_nh, myIter,myThid )
416            ENDIF
417            CALL POST_CG3D(
418         I                  zeroPsNH, zeroMeanPnh,
419         I                  myTime, myIter, myThid )
420           ENDIF
421    
422        ENDIF        ENDIF
423  #endif /* ALLOW_NONHYDROSTATIC */  #endif /* ALLOW_NONHYDROSTATIC */

Legend:
Removed from v.1.64  
changed lines
  Added in v.1.74

  ViewVC Help
Powered by ViewVC 1.1.22