/[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.76 by jmc, Sat Jan 3 23:58:53 2015 UTC revision 1.81 by jmc, Sat Apr 29 16:11:38 2017 UTC
# Line 59  C     bi,bj   :: current tile indices Line 59  C     bi,bj   :: current tile indices
59  C     k       :: current vertical level  C     k       :: current vertical level
60  C     iMin,iMax,jMin,jMax :: loop ranges  C     iMin,iMax,jMin,jMax :: loop ranges
61  C     fVerU   :: Flux of momentum in the vertical direction, out of the upper  C     fVerU   :: Flux of momentum in the vertical direction, out of the upper
62  C     fVerV   :: face of a cell K ( flux into the cell above ).  C     fVerV   :: face of a cell k ( flux into the cell above ).
63  C     fVerUkm :: vertical viscous flux of U, interface above (k-1/2)  C     fVerUkm :: vertical viscous flux of U, interface above (k-1/2)
64  C     fVerVkm :: vertical viscous flux of V, interface above (k-1/2)  C     fVerVkm :: vertical viscous flux of V, interface above (k-1/2)
65  C     fVerUkp :: vertical viscous flux of U, interface below (k+1/2)  C     fVerUkp :: vertical viscous flux of U, interface below (k+1/2)
# Line 138  C     xxxFac :: On-off tracer parameters Line 138  C     xxxFac :: On-off tracer parameters
138  #ifdef ALLOW_AUTODIFF  #ifdef ALLOW_AUTODIFF
139  C--   only the kDown part of fverU/V is set in this subroutine  C--   only the kDown part of fverU/V is set in this subroutine
140  C--   the kUp is still required  C--   the kUp is still required
141  C--   In the case of mom_fluxform Kup is set as well  C--   In the case of mom_fluxform kUp is set as well
142  C--   (at least in part)  C--   (at least in part)
143        fVerUkm(1,1) = fVerUkm(1,1)        fVerUkm(1,1) = fVerUkm(1,1)
144        fVerVkm(1,1) = fVerVkm(1,1)        fVerVkm(1,1) = fVerVkm(1,1)
# Line 229  C       vorticity at a no-slip boundary Line 229  C       vorticity at a no-slip boundary
229          sideMaskFac = 0. _d 0          sideMaskFac = 0. _d 0
230        ENDIF        ENDIF
231    
232        IF (     no_slip_bottom        IF ( selectImplicitDrag.EQ.0 .AND.
233         &      (  no_slip_bottom
234       &    .OR. selectBotDragQuadr.GE.0       &    .OR. selectBotDragQuadr.GE.0
235       &    .OR. bottomDragLinear.NE.0.) THEN       &    .OR. bottomDragLinear.NE.0. ) ) THEN
236         bottomDragTerms=.TRUE.         bottomDragTerms=.TRUE.
237        ELSE        ELSE
238         bottomDragTerms=.FALSE.         bottomDragTerms=.FALSE.
# Line 248  C     Make local copies of horizontal fl Line 249  C     Make local copies of horizontal fl
249         ENDDO         ENDDO
250        ENDDO        ENDDO
251    
252    #ifdef ALLOW_AUTODIFF_TAMC
253    CADJ STORE ufld(:,:) =
254    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
255    CADJ STORE vfld(:,:) =
256    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
257    CADJ STORE hFacZ(:,:) =
258    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
259    CADJ STORE r_hFacZ(:,:) =
260    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
261    CADJ STORE fverukm(:,:) =
262    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
263    CADJ STORE fvervkm(:,:) =
264    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
265    #endif
266    
267  C note (jmc) : Dissipation and Vort3 advection do not necesary  C note (jmc) : Dissipation and Vort3 advection do not necesary
268  C              use the same maskZ (and hFacZ)  => needs 2 call(s)  C              use the same maskZ (and hFacZ)  => needs 2 call(s)
269  c     CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFacZ,r_hFacZ,myThid)  c     CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFacZ,r_hFacZ,myThid)
# Line 256  c     CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFa Line 272  c     CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFa
272    
273        CALL MOM_CALC_RELVORT3(bi,bj,k,uFld,vFld,hFacZ,vort3,myThid)        CALL MOM_CALC_RELVORT3(bi,bj,k,uFld,vFld,hFacZ,vort3,myThid)
274    
275    #ifdef ALLOW_AUTODIFF_TAMC
276    CADJ STORE ke(:,:) =
277    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
278    CADJ STORE vort3(:,:) =
279    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
280    CADJ STORE vort3bc(:,:) =
281    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
282    #endif
283    
284  C-    mask vort3 and account for no-slip / free-slip BC in vort3BC:  C-    mask vort3 and account for no-slip / free-slip BC in vort3BC:
285        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
286         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
# Line 267  C-    mask vort3 and account for no-slip Line 292  C-    mask vort3 and account for no-slip
292         ENDDO         ENDDO
293        ENDDO        ENDDO
294    
295    #ifdef ALLOW_AUTODIFF_TAMC
296    CADJ STORE vort3(:,:) =
297    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
298    CADJ STORE vort3bc(:,:) =
299    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
300    #endif
301    
302        IF (momViscosity) THEN        IF (momViscosity) THEN
303  C--    For viscous term, compute horizontal divergence, tension & strain  C--    For viscous term, compute horizontal divergence, tension & strain
304  C      and mask relative vorticity (free-slip case):  C      and mask relative vorticity (free-slip case):
# Line 288  C      and mask relative vorticity (free Line 320  C      and mask relative vorticity (free
320         ENDIF         ENDIF
321  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
322    
323    #ifdef ALLOW_AUTODIFF_TAMC
324    CADJ STORE h0FacZ(:,:) =
325    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
326    CADJ STORE hFacZ(:,:) =
327    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
328    #endif
329    
330         CALL MOM_CALC_HDIV(bi,bj,k,2,uFld,vFld,hDiv,myThid)         CALL MOM_CALC_HDIV(bi,bj,k,2,uFld,vFld,hDiv,myThid)
331    
332         IF ( useVariableVisc .OR. useStrainTensionVisc ) THEN         IF ( useVariableVisc .OR. useStrainTensionVisc ) THEN
# Line 305  C-    mask strain and account for no-sli Line 344  C-    mask strain and account for no-sli
344          ENDDO          ENDDO
345         ENDIF         ENDIF
346    
347    #ifdef ALLOW_AUTODIFF_TAMC
348    CADJ STORE hdiv(:,:) =
349    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
350    CADJ STORE tension(:,:) =
351    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
352    CADJ STORE strain(:,:) =
353    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
354    CADJ STORE strainbc(:,:) =
355    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
356    #endif
357    
358  C--    Calculate Lateral Viscosities  C--    Calculate Lateral Viscosities
359         DO j=1-OLy,sNy+OLy         DO j=1-OLy,sNy+OLy
360          DO i=1-OLx,sNx+OLx          DO i=1-OLx,sNx+OLx
# Line 322  C-     uses vort3BC & strainBC which acc Line 372  C-     uses vort3BC & strainBC which acc
372       I            myThid )       I            myThid )
373         ENDIF         ENDIF
374    
375    #ifdef ALLOW_AUTODIFF_TAMC
376    CADJ STORE viscAh_Z(:,:) =
377    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
378    CADJ STORE viscAh_D(:,:) =
379    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
380    CADJ STORE viscA4_Z(:,:) =
381    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
382    CADJ STORE viscA4_D(:,:) =
383    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
384    #endif
385    
386    #ifdef ALLOW_AUTODIFF_TAMC
387    CADJ STORE hDiv(:,:) =
388    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
389    CADJ STORE vort3(:,:) =
390    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
391    CADJ STORE hFacZ(:,:) =
392    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
393    #endif
394    
395  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
396         IF (useBiharmonicVisc) THEN         IF (useBiharmonicVisc) THEN
397           CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,           CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,
398       O                      del2u,del2v,       O                      del2u,del2v,
399       I                      myThid)       I                      myThid)
400    #ifdef ALLOW_AUTODIFF_TAMC
401    CADJ STORE del2u(:,:) =
402    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
403    CADJ STORE del2v(:,:) =
404    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
405    #endif
406           CALL MOM_CALC_HDIV(bi,bj,k,2,del2u,del2v,dStar,myThid)           CALL MOM_CALC_HDIV(bi,bj,k,2,del2u,del2v,dStar,myThid)
407           CALL MOM_CALC_RELVORT3(bi,bj,k,           CALL MOM_CALC_RELVORT3(bi,bj,k,
408       &                          del2u,del2v,hFacZ,zStar,myThid)       &                          del2u,del2v,hFacZ,zStar,myThid)
409         ENDIF         ENDIF
410    
411    #ifdef ALLOW_AUTODIFF_TAMC
412    CADJ STORE del2u(:,:) =
413    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
414    CADJ STORE del2v(:,:) =
415    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
416    CADJ STORE dStar(:,:) =
417    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
418    CADJ STORE zStar(:,:) =
419    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
420    #endif
421    
422  C---   Calculate dissipation terms for U and V equations  C---   Calculate dissipation terms for U and V equations
423    
424  C-     in terms of tension and strain  C-     in terms of tension and strain
# Line 365  C     Combine fluxes Line 452  C     Combine fluxes
452           fVerUkp(i,j) = ArDudrFac*vrF(i,j)           fVerUkp(i,j) = ArDudrFac*vrF(i,j)
453          ENDDO          ENDDO
454         ENDDO         ENDDO
455    
456    #ifdef ALLOW_AUTODIFF_TAMC
457    CADJ STORE fVerUkp(:,:) =
458    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
459    #endif
460    
461  C--   Tendency is minus divergence of the fluxes  C--   Tendency is minus divergence of the fluxes
462    C     vert.visc.flx is scaled by deepFac2F (deep-atmos) and rhoFac (anelastic)
463         DO j=jMin,jMax         DO j=jMin,jMax
464          DO i=iMin,iMax          DO i=iMin,iMax
465           guDiss(i,j) = guDiss(i,j)           guDiss(i,j) = guDiss(i,j)
466       &   -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)       &   -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)
467       &   *recip_rAw(i,j,bi,bj)       &   *recip_rAw(i,j,bi,bj)
468       &   *( fVerUkp(i,j) - fVerUkm(i,j) )*rkSign       &   *( fVerUkp(i,j) - fVerUkm(i,j) )*rkSign
469         &   *recip_deepFac2C(k)*recip_rhoFacC(k)
470          ENDDO          ENDDO
471         ENDDO         ENDDO
472        ENDIF        ENDIF
# Line 430  C     Combine fluxes -> fVerV Line 525  C     Combine fluxes -> fVerV
525           fVerVkp(i,j) = ArDvdrFac*vrF(i,j)           fVerVkp(i,j) = ArDvdrFac*vrF(i,j)
526          ENDDO          ENDDO
527         ENDDO         ENDDO
528    #ifdef ALLOW_AUTODIFF_TAMC
529    CADJ STORE fVerVkp(:,:) =
530    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
531    #endif
532  C--   Tendency is minus divergence of the fluxes  C--   Tendency is minus divergence of the fluxes
533    C     vert.visc.flx is scaled by deepFac2F (deep-atmos) and rhoFac (anelastic)
534         DO j=jMin,jMax         DO j=jMin,jMax
535          DO i=iMin,iMax          DO i=iMin,iMax
536           gvDiss(i,j) = gvDiss(i,j)           gvDiss(i,j) = gvDiss(i,j)
537       &   -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)       &   -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)
538       &   *recip_rAs(i,j,bi,bj)       &   *recip_rAs(i,j,bi,bj)
539       &   *( fVerVkp(i,j) - fVerVkm(i,j) )*rkSign       &   *( fVerVkp(i,j) - fVerVkm(i,j) )*rkSign
540         &   *recip_deepFac2C(k)*recip_rhoFacC(k)
541          ENDDO          ENDDO
542         ENDDO         ENDDO
543        ENDIF        ENDIF
# Line 496  C-    calculate absolute vorticity Line 597  C-    calculate absolute vorticity
597        IF (useAbsVorticity)        IF (useAbsVorticity)
598       &  CALL MOM_CALC_ABSVORT3(bi,bj,k,vort3,omega3,myThid)       &  CALL MOM_CALC_ABSVORT3(bi,bj,k,vort3,omega3,myThid)
599    
600    #ifdef ALLOW_AUTODIFF_TAMC
601    CADJ STORE omega3(:,:) =
602    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
603    #endif
604    
605  C--   Horizontal Coriolis terms  C--   Horizontal Coriolis terms
606  c     IF (useCoriolis .AND. .NOT.useCDscheme  c     IF (useCoriolis .AND. .NOT.useCDscheme
607  c    &    .AND. .NOT. useAbsVorticity) THEN  c    &    .AND. .NOT. useAbsVorticity) THEN
# Line 504  C- jmc: change it to keep the Coriolis t Line 610  C- jmc: change it to keep the Coriolis t
610       &     .NOT.( useCDscheme .OR. useAbsVorticity.AND.momAdvection )       &     .NOT.( useCDscheme .OR. useAbsVorticity.AND.momAdvection )
611       &   ) THEN       &   ) THEN
612         IF (useAbsVorticity) THEN         IF (useAbsVorticity) THEN
613          CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,hFacZ,r_hFacZ,          CALL MOM_VI_U_CORIOLIS(bi,bj,k,selectVortScheme,useJamartMomAdv,
614         &                         vFld,omega3,hFacZ,r_hFacZ,
615       &                         uCf,myThid)       &                         uCf,myThid)
616          CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,hFacZ,r_hFacZ,          CALL MOM_VI_V_CORIOLIS(bi,bj,k,selectVortScheme,useJamartMomAdv,
617         &                         uFld,omega3,hFacZ,r_hFacZ,
618       &                         vCf,myThid)       &                         vCf,myThid)
619         ELSE         ELSE
620          CALL MOM_VI_CORIOLIS(bi,bj,k,uFld,vFld,hFacZ,r_hFacZ,          CALL MOM_VI_CORIOLIS(bi,bj,k,uFld,vFld,hFacZ,r_hFacZ,
# Line 547  C- jmc: change it to keep the Coriolis t Line 655  C- jmc: change it to keep the Coriolis t
655         ENDDO         ENDDO
656        ENDIF        ENDIF
657    
658    #ifdef ALLOW_AUTODIFF_TAMC
659    CADJ STORE ucf(:,:) =
660    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
661    CADJ STORE vcf(:,:) =
662    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
663    #endif
664    
665        IF (momAdvection) THEN        IF (momAdvection) THEN
666  C--   Horizontal advection of relative (or absolute) vorticity  C--   Horizontal advection of relative (or absolute) vorticity
667         IF ( (highOrderVorticity.OR.upwindVorticity)         IF ( (highOrderVorticity.OR.upwindVorticity)
668       &     .AND.useAbsVorticity ) THEN       &     .AND.useAbsVorticity ) THEN
669          CALL MOM_VI_U_CORIOLIS_C4(bi,bj,k,vFld,omega3,r_hFacZ,          CALL MOM_VI_U_CORIOLIS_C4(bi,bj,k,selectVortScheme,
670         &                         highOrderVorticity,upwindVorticity,
671         &                         vFld,omega3,r_hFacZ,
672       &                         uCf,myThid)       &                         uCf,myThid)
673         ELSEIF ( (highOrderVorticity.OR.upwindVorticity) ) THEN         ELSEIF ( (highOrderVorticity.OR.upwindVorticity) ) THEN
674          CALL MOM_VI_U_CORIOLIS_C4(bi,bj,k,vFld,vort3, r_hFacZ,          CALL MOM_VI_U_CORIOLIS_C4(bi,bj,k,selectVortScheme,
675         &                         highOrderVorticity, upwindVorticity,
676         &                         vFld,vort3, r_hFacZ,
677       &                         uCf,myThid)       &                         uCf,myThid)
678         ELSEIF ( useAbsVorticity ) THEN         ELSEIF ( useAbsVorticity ) THEN
679          CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,hFacZ,r_hFacZ,          CALL MOM_VI_U_CORIOLIS(bi,bj,k,selectVortScheme,useJamartMomAdv,
680         &                         vFld,omega3,hFacZ,r_hFacZ,
681       &                         uCf,myThid)       &                         uCf,myThid)
682         ELSE         ELSE
683          CALL MOM_VI_U_CORIOLIS(bi,bj,k,vFld,vort3, hFacZ,r_hFacZ,          CALL MOM_VI_U_CORIOLIS(bi,bj,k,selectVortScheme,useJamartMomAdv,
684         &                         vFld,vort3, hFacZ,r_hFacZ,
685       &                         uCf,myThid)       &                         uCf,myThid)
686         ENDIF         ENDIF
687         DO j=jMin,jMax         DO j=jMin,jMax
# Line 570  C--   Horizontal advection of relative ( Line 691  C--   Horizontal advection of relative (
691         ENDDO         ENDDO
692         IF ( (highOrderVorticity.OR.upwindVorticity)         IF ( (highOrderVorticity.OR.upwindVorticity)
693       &     .AND.useAbsVorticity ) THEN       &     .AND.useAbsVorticity ) THEN
694          CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,omega3,r_hFacZ,          CALL MOM_VI_V_CORIOLIS_C4(bi,bj,k,selectVortScheme,
695         &                         highOrderVorticity, upwindVorticity,
696         &                         uFld,omega3,r_hFacZ,
697       &                         vCf,myThid)       &                         vCf,myThid)
698         ELSEIF ( (highOrderVorticity.OR.upwindVorticity) ) THEN         ELSEIF ( (highOrderVorticity.OR.upwindVorticity) ) THEN
699          CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,vort3, r_hFacZ,          CALL MOM_VI_V_CORIOLIS_C4(bi,bj,k,selectVortScheme,
700         &                         highOrderVorticity, upwindVorticity,
701         &                         uFld,vort3, r_hFacZ,
702       &                         vCf,myThid)       &                         vCf,myThid)
703         ELSEIF ( useAbsVorticity ) THEN         ELSEIF ( useAbsVorticity ) THEN
704          CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,hFacZ,r_hFacZ,          CALL MOM_VI_V_CORIOLIS(bi,bj,k,selectVortScheme,useJamartMomAdv,
705         &                         uFld,omega3,hFacZ,r_hFacZ,
706       &                         vCf,myThid)       &                         vCf,myThid)
707         ELSE         ELSE
708          CALL MOM_VI_V_CORIOLIS(bi,bj,k,uFld,vort3, hFacZ,r_hFacZ,          CALL MOM_VI_V_CORIOLIS(bi,bj,k,selectVortScheme,useJamartMomAdv,
709         &                         uFld,vort3, hFacZ,r_hFacZ,
710       &                         vCf,myThid)       &                         vCf,myThid)
711         ENDIF         ENDIF
712         DO j=jMin,jMax         DO j=jMin,jMax
# Line 588  C--   Horizontal advection of relative ( Line 715  C--   Horizontal advection of relative (
715          ENDDO          ENDDO
716         ENDDO         ENDDO
717    
718    #ifdef ALLOW_AUTODIFF_TAMC
719    CADJ STORE ucf(:,:) =
720    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
721    CADJ STORE vcf(:,:) =
722    CADJ &     comlev1_bibj_k, key = imomkey, byte = isbyte
723    #endif
724    
725         IF ( writeDiag ) THEN         IF ( writeDiag ) THEN
726           IF (snapshot_mdsio) THEN           IF (snapshot_mdsio) THEN
727             CALL WRITE_LOCAL_RL('zV','I10',1,uCf,bi,bj,k,myIter,myThid)             CALL WRITE_LOCAL_RL('zV','I10',1,uCf,bi,bj,k,myIter,myThid)
# Line 620  C--   Horizontal advection of relative ( Line 754  C--   Horizontal advection of relative (
754    
755  C--   Vertical shear terms (-w*du/dr & -w*dv/dr)  C--   Vertical shear terms (-w*du/dr & -w*dv/dr)
756         IF ( .NOT. momImplVertAdv ) THEN         IF ( .NOT. momImplVertAdv ) THEN
757          CALL MOM_VI_U_VERTSHEAR(bi,bj,K,uVel,wVel,uCf,myThid)          CALL MOM_VI_U_VERTSHEAR(bi,bj,k,uVel,wVel,uCf,myThid)
758          DO j=jMin,jMax          DO j=jMin,jMax
759           DO i=iMin,iMax           DO i=iMin,iMax
760            gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)            gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
761           ENDDO           ENDDO
762          ENDDO          ENDDO
763          CALL MOM_VI_V_VERTSHEAR(bi,bj,K,vVel,wVel,vCf,myThid)          CALL MOM_VI_V_VERTSHEAR(bi,bj,k,vVel,wVel,vCf,myThid)
764          DO j=jMin,jMax          DO j=jMin,jMax
765           DO i=iMin,iMax           DO i=iMin,iMax
766            gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)            gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
# Line 641  C--   Vertical shear terms (-w*du/dr & - Line 775  C--   Vertical shear terms (-w*du/dr & -
775         ENDIF         ENDIF
776    
777  C--   Bernoulli term  C--   Bernoulli term
778         CALL MOM_VI_U_GRAD_KE(bi,bj,K,KE,uCf,myThid)         CALL MOM_VI_U_GRAD_KE(bi,bj,k,KE,uCf,myThid)
779         DO j=jMin,jMax         DO j=jMin,jMax
780          DO i=iMin,iMax          DO i=iMin,iMax
781           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
782          ENDDO          ENDDO
783         ENDDO         ENDDO
784         CALL MOM_VI_V_GRAD_KE(bi,bj,K,KE,vCf,myThid)         CALL MOM_VI_V_GRAD_KE(bi,bj,k,KE,vCf,myThid)
785         DO j=jMin,jMax         DO j=jMin,jMax
786          DO i=iMin,iMax          DO i=iMin,iMax
787           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)

Legend:
Removed from v.1.76  
changed lines
  Added in v.1.81

  ViewVC Help
Powered by ViewVC 1.1.22