/[MITgcm]/MITgcm/pkg/mom_vecinv/mom_vecinv.F
ViewVC logotype

Diff of /MITgcm/pkg/mom_vecinv/mom_vecinv.F

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

revision 1.29 by jmc, Fri Nov 5 18:39:15 2004 UTC revision 1.35 by baylor, Thu Mar 10 03:45:11 2005 UTC
# Line 7  C $Name$ Line 7  C $Name$
7       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,
8       I        dPhiHydX,dPhiHydY,KappaRU,KappaRV,       I        dPhiHydX,dPhiHydY,KappaRU,KappaRV,
9       U        fVerU, fVerV,       U        fVerU, fVerV,
10         O        guDiss, gvDiss,
11       I        myTime, myIter, myThid)       I        myTime, myIter, myThid)
12  C     /==========================================================\  C     /==========================================================\
13  C     | S/R MOM_VECINV                                           |  C     | S/R MOM_VECINV                                           |
# Line 39  C     == Global variables == Line 40  C     == Global variables ==
40  #endif  #endif
41    
42  C     == Routine arguments ==  C     == Routine arguments ==
43  C     fVerU   - Flux of momentum in the vertical  C     fVerU  :: Flux of momentum in the vertical direction, out of the upper
44  C     fVerV     direction out of the upper face of a cell K  C     fVerV  :: face of a cell K ( flux into the cell above ).
 C               ( flux into the cell above ).  
45  C     dPhiHydX,Y :: Gradient (X & Y dir.) of Hydrostatic Potential  C     dPhiHydX,Y :: Gradient (X & Y dir.) of Hydrostatic Potential
46    C     guDiss :: dissipation tendency (all explicit terms), u component
47    C     gvDiss :: dissipation tendency (all explicit terms), v component
48  C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation  C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
49  C                                      results will be set.  C                                      results will be set.
50  C     kUp, kDown                     - Index for upper and lower layers.  C     kUp, kDown                     - Index for upper and lower layers.
# Line 53  C     myThid - Instance number for this Line 55  C     myThid - Instance number for this
55        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
56        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
57        _RL fVerV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
58          _RL guDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59          _RL gvDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60        INTEGER kUp,kDown        INTEGER kUp,kDown
61        _RL     myTime        _RL     myTime
62        INTEGER myIter        INTEGER myIter
# Line 81  c     _RL      mT (1-OLx:sNx+OLx,1-OLy:s Line 85  c     _RL      mT (1-OLx:sNx+OLx,1-OLy:s
85        _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86        _RL dStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL dStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87        _RL zStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL zStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RL uDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL vDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
88  C     I,J,K - Loop counters  C     I,J,K - Loop counters
89        INTEGER i,j,k        INTEGER i,j,k
 C     rVelMaskOverride - Factor for imposing special surface boundary conditions  
 C                        ( set according to free-surface condition ).  
 C     hFacROpen        - Lopped cell factos used tohold fraction of open  
 C     hFacRClosed        and closed cell wall.  
       _RL  rVelMaskOverride  
90  C     xxxFac - On-off tracer parameters used for switching terms off.  C     xxxFac - On-off tracer parameters used for switching terms off.
91        _RL  ArDudrFac        _RL  ArDudrFac
92        _RL  phxFac        _RL  phxFac
# Line 97  c     _RL  mtFacU Line 94  c     _RL  mtFacU
94        _RL  ArDvdrFac        _RL  ArDvdrFac
95        _RL  phyFac        _RL  phyFac
96  c     _RL  mtFacV  c     _RL  mtFacV
       _RL wVelBottomOverride  
97        LOGICAL bottomDragTerms        LOGICAL bottomDragTerms
98        LOGICAL writeDiag        LOGICAL writeDiag
99        _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 118  C--   (at least in part) Line 114  C--   (at least in part)
114        fVerV(1,1,kUp) = fVerV(1,1,kUp)        fVerV(1,1,kUp) = fVerV(1,1,kUp)
115  #endif  #endif
116    
       rVelMaskOverride=1.  
       IF ( k .EQ. 1 ) rVelMaskOverride=freeSurfFac  
       wVelBottomOverride=1.  
       IF (k.EQ.Nr) wVelBottomOverride=0.  
117        writeDiag = DIFFERENT_MULTIPLE(diagFreq, myTime,        writeDiag = DIFFERENT_MULTIPLE(diagFreq, myTime,
118       &                                         myTime-deltaTClock)       &                                         myTime-deltaTClock)
119    
# Line 129  C--   (at least in part) Line 121  C--   (at least in part)
121        IF (useMNC .AND. snapshot_mnc .AND. writeDiag) THEN        IF (useMNC .AND. snapshot_mnc .AND. writeDiag) THEN
122          IF ((bi .EQ. 1).AND.(bj .EQ. 1).AND.(k .EQ. 1)) THEN          IF ((bi .EQ. 1).AND.(bj .EQ. 1).AND.(k .EQ. 1)) THEN
123            CALL MNC_CW_SET_UDIM('mom_vi', -1, myThid)            CALL MNC_CW_SET_UDIM('mom_vi', -1, myThid)
124            CALL MNC_CW_I_W_S('I','mom_vi',0,0,'iter',myIter,myThid)            CALL MNC_CW_I_W_S('I','mom_vi',0,0,'T',myIter,myThid)
125            CALL MNC_CW_SET_UDIM('mom_vi', 0, myThid)            CALL MNC_CW_SET_UDIM('mom_vi', 0, myThid)
126          ENDIF          ENDIF
127          DO i = 1,9          DO i = 1,9
# Line 143  C       write(*,*) 'offsets = ',(offsets Line 135  C       write(*,*) 'offsets = ',(offsets
135  C     Initialise intermediate terms  C     Initialise intermediate terms
136        DO J=1-OLy,sNy+OLy        DO J=1-OLy,sNy+OLy
137         DO I=1-OLx,sNx+OLx         DO I=1-OLx,sNx+OLx
138          vF(i,j)   = 0.          vF(i,j)    = 0.
139          vrF(i,j)  = 0.          vrF(i,j)   = 0.
140          uCf(i,j)   = 0.          uCf(i,j)   = 0.
141          vCf(i,j)   = 0.          vCf(i,j)   = 0.
142  c       mT(i,j)   = 0.  c       mT(i,j)    = 0.
143          del2u(i,j) = 0.          del2u(i,j) = 0.
144          del2v(i,j) = 0.          del2v(i,j) = 0.
145          dStar(i,j) = 0.          dStar(i,j) = 0.
146          zStar(i,j) = 0.          zStar(i,j) = 0.
147          uDiss(i,j) = 0.          guDiss(i,j)= 0.
148          vDiss(i,j) = 0.          gvDiss(i,j)= 0.
149          vort3(i,j) = 0.          vort3(i,j) = 0.
150          omega3(i,j) = 0.          omega3(i,j)= 0.
151          ke(i,j) = 0.          ke(i,j)    = 0.
152  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
153          strain(i,j)  = 0. _d 0          strain(i,j)  = 0. _d 0
154          tension(i,j) = 0. _d 0          tension(i,j) = 0. _d 0
# Line 214  c     CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFa Line 206  c     CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFa
206    
207        IF (momViscosity) THEN        IF (momViscosity) THEN
208  C      Calculate del^2 u and del^2 v for bi-harmonic term  C      Calculate del^2 u and del^2 v for bi-harmonic term
209         IF (viscA4.NE.0.         IF ( (viscA4.NE.0. .AND. no_slip_sides)
210         &     .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0.
211       &     .OR. viscA4Grid.NE.0.       &     .OR. viscA4Grid.NE.0.
212       &     .OR. viscC4leith.NE.0.       &     .OR. viscC4leith.NE.0.
213         &     .OR. viscC4leithD.NE.0.
214       &    ) THEN       &    ) THEN
215           CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,           CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,
216       O                      del2u,del2v,       O                      del2u,del2v,
# Line 231  C      in terms of vorticity and diverge Line 225  C      in terms of vorticity and diverge
225       &    .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0.       &    .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0.
226       &    .OR. viscAhGrid.NE.0. .OR. viscA4Grid.NE.0.       &    .OR. viscAhGrid.NE.0. .OR. viscA4Grid.NE.0.
227       &    .OR. viscC2leith.NE.0. .OR. viscC4leith.NE.0.       &    .OR. viscC2leith.NE.0. .OR. viscC4leith.NE.0.
228         &    .OR. viscC2leithD.NE.0. .OR. viscC4leithD.NE.0.
229       &    ) THEN       &    ) THEN
230           CALL MOM_VI_HDISSIP(bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar,           CALL MOM_VI_HDISSIP(bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar,
231       O                       uDiss,vDiss,       O                       guDiss,gvDiss,
232       &                       myThid)       &                       myThid)
233         ENDIF         ENDIF
234  C      or in terms of tension and strain  C      or in terms of tension and strain
235         IF (viscAstrain.NE.0. .OR. viscAtension.NE.0.) THEN         IF (viscAstrain.NE.0. .OR. viscAtension.NE.0.
236         O      .OR. viscC2smag.ne.0) THEN
237           CALL MOM_CALC_TENSION(bi,bj,k,uFld,vFld,           CALL MOM_CALC_TENSION(bi,bj,k,uFld,vFld,
238       O                         tension,       O                         tension,
239       I                         myThid)       I                         myThid)
# Line 246  C      or in terms of tension and strain Line 242  C      or in terms of tension and strain
242       I                        myThid)       I                        myThid)
243           CALL MOM_HDISSIP(bi,bj,k,           CALL MOM_HDISSIP(bi,bj,k,
244       I                    tension,strain,hFacZ,viscAtension,viscAstrain,       I                    tension,strain,hFacZ,viscAtension,viscAstrain,
245       O                    uDiss,vDiss,       O                    guDiss,gvDiss,
246       I                    myThid)       I                    myThid)
247         ENDIF         ENDIF
248        ENDIF        ENDIF
# Line 259  C---- Zonal momentum equation starts her Line 255  C---- Zonal momentum equation starts her
255  C--   Vertical flux (fVer is at upper face of "u" cell)  C--   Vertical flux (fVer is at upper face of "u" cell)
256    
257  C     Eddy component of vertical flux (interior component only) -> vrF  C     Eddy component of vertical flux (interior component only) -> vrF
258        IF (momViscosity.AND..NOT.implicitViscosity)        IF (momViscosity.AND..NOT.implicitViscosity) THEN
259       & CALL MOM_U_RVISCFLUX(bi,bj,k,uVel,KappaRU,vrF,myThid)         CALL MOM_U_RVISCFLUX(bi,bj,k,uVel,KappaRU,vrF,myThid)
260    
261  C     Combine fluxes  C     Combine fluxes
262        DO j=jMin,jMax         DO j=jMin,jMax
263         DO i=iMin,iMax          DO i=iMin,iMax
264          fVerU(i,j,kDown) = ArDudrFac*vrF(i,j)           fVerU(i,j,kDown) = ArDudrFac*vrF(i,j)
265            ENDDO
266         ENDDO         ENDDO
       ENDDO  
267    
268  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes
269        DO j=2-Oly,sNy+Oly-1         DO j=2-Oly,sNy+Oly-1
270         DO i=2-Olx,sNx+Olx-1          DO i=2-Olx,sNx+Olx-1
271          gU(i,j,k,bi,bj) = uDiss(i,j)           guDiss(i,j) = guDiss(i,j)
272       &   -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)       &   -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)
273       &   *recip_rAw(i,j,bi,bj)       &   *recip_rAw(i,j,bi,bj)
274       &  *(       &  *(
275       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac
276       &   )       &   )
277       &  - phxFac*dPhiHydX(i,j)          ENDDO
278         ENDDO         ENDDO
279        ENDDO        ENDIF
280    
281  C-- No-slip and drag BCs appear as body forces in cell abutting topography  C-- No-slip and drag BCs appear as body forces in cell abutting topography
282        IF (momViscosity.AND.no_slip_sides) THEN        IF (momViscosity.AND.no_slip_sides) THEN
# Line 288  C-     No-slip BCs impose a drag at wall Line 284  C-     No-slip BCs impose a drag at wall
284         CALL MOM_U_SIDEDRAG(bi,bj,k,uFld,del2u,hFacZ,vF,myThid)         CALL MOM_U_SIDEDRAG(bi,bj,k,uFld,del2u,hFacZ,vF,myThid)
285         DO j=jMin,jMax         DO j=jMin,jMax
286          DO i=iMin,iMax          DO i=iMin,iMax
287           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+vF(i,j)           guDiss(i,j) = guDiss(i,j)+vF(i,j)
288          ENDDO          ENDDO
289         ENDDO         ENDDO
290        ENDIF        ENDIF
# Line 298  C-    No-slip BCs impose a drag at botto Line 294  C-    No-slip BCs impose a drag at botto
294         CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid)         CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid)
295         DO j=jMin,jMax         DO j=jMin,jMax
296          DO i=iMin,iMax          DO i=iMin,iMax
297           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+vF(i,j)           guDiss(i,j) = guDiss(i,j)+vF(i,j)
298          ENDDO          ENDDO
299         ENDDO         ENDDO
300        ENDIF        ENDIF
# Line 319  C---- Meridional momentum equation start Line 315  C---- Meridional momentum equation start
315  C--   Vertical flux (fVer is at upper face of "v" cell)  C--   Vertical flux (fVer is at upper face of "v" cell)
316    
317  C     Eddy component of vertical flux (interior component only) -> vrF  C     Eddy component of vertical flux (interior component only) -> vrF
318        IF (momViscosity.AND..NOT.implicitViscosity)        IF (momViscosity.AND..NOT.implicitViscosity) THEN
319       & CALL MOM_V_RVISCFLUX(bi,bj,k,vVel,KappaRV,vrf,myThid)         CALL MOM_V_RVISCFLUX(bi,bj,k,vVel,KappaRV,vrf,myThid)
320    
321  C     Combine fluxes -> fVerV  C     Combine fluxes -> fVerV
322        DO j=jMin,jMax         DO j=jMin,jMax
323         DO i=iMin,iMax          DO i=iMin,iMax
324          fVerV(i,j,kDown) = ArDvdrFac*vrF(i,j)           fVerV(i,j,kDown) = ArDvdrFac*vrF(i,j)
325            ENDDO
326         ENDDO         ENDDO
       ENDDO  
327    
328  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes
329        DO j=jMin,jMax         DO j=jMin,jMax
330         DO i=iMin,iMax          DO i=iMin,iMax
331          gV(i,j,k,bi,bj) = vDiss(i,j)           gvDiss(i,j) = gvDiss(i,j)
332       &   -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)       &   -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)
333       &    *recip_rAs(i,j,bi,bj)       &    *recip_rAs(i,j,bi,bj)
334       &  *(       &  *(
335       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac
336       &   )       &   )
337       &  - phyFac*dPhiHydY(i,j)          ENDDO
338         ENDDO         ENDDO
339        ENDDO        ENDIF
340    
341  C-- No-slip and drag BCs appear as body forces in cell abutting topography  C-- No-slip and drag BCs appear as body forces in cell abutting topography
342        IF (momViscosity.AND.no_slip_sides) THEN        IF (momViscosity.AND.no_slip_sides) THEN
# Line 348  C-     No-slip BCs impose a drag at wall Line 344  C-     No-slip BCs impose a drag at wall
344         CALL MOM_V_SIDEDRAG(bi,bj,k,vFld,del2v,hFacZ,vF,myThid)         CALL MOM_V_SIDEDRAG(bi,bj,k,vFld,del2v,hFacZ,vF,myThid)
345         DO j=jMin,jMax         DO j=jMin,jMax
346          DO i=iMin,iMax          DO i=iMin,iMax
347           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j)           gvDiss(i,j) = gvDiss(i,j)+vF(i,j)
348          ENDDO          ENDDO
349         ENDDO         ENDDO
350        ENDIF        ENDIF
# Line 357  C-    No-slip BCs impose a drag at botto Line 353  C-    No-slip BCs impose a drag at botto
353         CALL MOM_V_BOTTOMDRAG(bi,bj,k,vFld,KE,KappaRV,vF,myThid)         CALL MOM_V_BOTTOMDRAG(bi,bj,k,vFld,KE,KappaRV,vF,myThid)
354         DO j=jMin,jMax         DO j=jMin,jMax
355          DO i=iMin,iMax          DO i=iMin,iMax
356           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j)           gvDiss(i,j) = gvDiss(i,j)+vF(i,j)
357          ENDDO          ENDDO
358         ENDDO         ENDDO
359        ENDIF        ENDIF
# Line 380  C--   Horizontal Coriolis terms Line 376  C--   Horizontal Coriolis terms
376       &                      uCf,vCf,myThid)       &                      uCf,vCf,myThid)
377         DO j=jMin,jMax         DO j=jMin,jMax
378          DO i=iMin,iMax          DO i=iMin,iMax
379           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)           gU(i,j,k,bi,bj) = uCf(i,j) - phxFac*dPhiHydX(i,j)
380           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)           gV(i,j,k,bi,bj) = vCf(i,j) - phyFac*dPhiHydY(i,j)
381          ENDDO          ENDDO
382         ENDDO         ENDDO
383         IF ( writeDiag ) THEN         IF ( writeDiag ) THEN
# Line 398  C--   Horizontal Coriolis terms Line 394  C--   Horizontal Coriolis terms
394           ENDIF           ENDIF
395  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
396         ENDIF         ENDIF
397          ELSE
398           DO j=jMin,jMax
399            DO i=iMin,iMax
400             gU(i,j,k,bi,bj) = -phxFac*dPhiHydX(i,j)
401             gV(i,j,k,bi,bj) = -phyFac*dPhiHydY(i,j)
402            ENDDO
403           ENDDO
404        ENDIF        ENDIF
405    
406        IF (momAdvection) THEN        IF (momAdvection) THEN
# Line 445  c      CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K Line 448  c      CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K
448         ENDIF         ENDIF
449    
450  #ifdef ALLOW_TIMEAVE  #ifdef ALLOW_TIMEAVE
451  #ifndef HRCUBE  #ifndef MINIMAL_TAVE_OUTPUT
452         IF (taveFreq.GT.0.) THEN         IF (taveFreq.GT.0.) THEN
453           CALL TIMEAVE_CUMUL_1K1T(uZetatave,vCf,deltaTClock,           CALL TIMEAVE_CUMUL_1K1T(uZetatave,vCf,deltaTClock,
454       &                           Nr, k, bi, bj, myThid)       &                           Nr, k, bi, bj, myThid)
455           CALL TIMEAVE_CUMUL_1K1T(vZetatave,uCf,deltaTClock,           CALL TIMEAVE_CUMUL_1K1T(vZetatave,uCf,deltaTClock,
456       &                           Nr, k, bi, bj, myThid)       &                           Nr, k, bi, bj, myThid)
457         ENDIF         ENDIF
458  #endif /* ndef HRCUBE */  #endif /* ndef MINIMAL_TAVE_OUTPUT */
459  #endif /* ALLOW_TIMEAVE */  #endif /* ALLOW_TIMEAVE */
460    
461  C--   Vertical shear terms (-w*du/dr & -w*dv/dr)  C--   Vertical shear terms (-w*du/dr & -w*dv/dr)
# Line 516  C--   Set du/dt & dv/dt on boundaries to Line 519  C--   Set du/dt & dv/dt on boundaries to
519       &   .AND. nPx.EQ.1 .AND. nPy.EQ.1       &   .AND. nPx.EQ.1 .AND. nPy.EQ.1
520       &   .AND. useCubedSphereExchange ) THEN       &   .AND. useCubedSphereExchange ) THEN
521          CALL DEBUG_CS_CORNER_UV( ' uDiss,vDiss from MOM_VECINV',          CALL DEBUG_CS_CORNER_UV( ' uDiss,vDiss from MOM_VECINV',
522       &             uDiss,vDiss, k, standardMessageUnit,bi,bj,myThid )       &             guDiss,gvDiss, k, standardMessageUnit,bi,bj,myThid )
523        ENDIF        ENDIF
524  #endif /* ALLOW_DEBUG */  #endif /* ALLOW_DEBUG */
525    
# Line 525  C--   Set du/dt & dv/dt on boundaries to Line 528  C--   Set du/dt & dv/dt on boundaries to
528            CALL WRITE_LOCAL_RL('Ds','I10',1,strain,bi,bj,k,myIter,myThid)            CALL WRITE_LOCAL_RL('Ds','I10',1,strain,bi,bj,k,myIter,myThid)
529            CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,            CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,
530       &         myThid)       &         myThid)
531            CALL WRITE_LOCAL_RL('Du','I10',1,uDiss,bi,bj,k,myIter,myThid)            CALL WRITE_LOCAL_RL('Du','I10',1,guDiss,bi,bj,k,myIter,myThid)
532            CALL WRITE_LOCAL_RL('Dv','I10',1,vDiss,bi,bj,k,myIter,myThid)            CALL WRITE_LOCAL_RL('Dv','I10',1,gvDiss,bi,bj,k,myIter,myThid)
533            CALL WRITE_LOCAL_RL('Z3','I10',1,vort3,bi,bj,k,myIter,myThid)            CALL WRITE_LOCAL_RL('Z3','I10',1,vort3,bi,bj,k,myIter,myThid)
534            CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid)            CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid)
535            CALL WRITE_LOCAL_RL('KE','I10',1,KE,bi,bj,k,myIter,myThid)            CALL WRITE_LOCAL_RL('KE','I10',1,KE,bi,bj,k,myIter,myThid)
# Line 538  C--   Set du/dt & dv/dt on boundaries to Line 541  C--   Set du/dt & dv/dt on boundaries to
541       &          offsets, myThid)       &          offsets, myThid)
542            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Dt',tension,            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Dt',tension,
543       &          offsets, myThid)       &          offsets, myThid)
544            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Du',uDiss,            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Du',guDiss,
545       &          offsets, myThid)       &          offsets, myThid)
546            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Dv',vDiss,            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Dv',gvDiss,
547       &          offsets, myThid)       &          offsets, myThid)
548            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Z3',vort3,            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Z3',vort3,
549       &          offsets, myThid)       &          offsets, myThid)

Legend:
Removed from v.1.29  
changed lines
  Added in v.1.35

  ViewVC Help
Powered by ViewVC 1.1.22