/[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.37 by jmc, Sat Apr 30 20:26:21 2005 UTC revision 1.43 by jmc, Sat Jul 30 22:05:36 2005 UTC
# Line 5  C $Name$ Line 5  C $Name$
5    
6        SUBROUTINE MOM_VECINV(        SUBROUTINE MOM_VECINV(
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        KappaRU, KappaRV,
9       U        fVerU, fVerV,       U        fVerU, fVerV,
10       O        guDiss, gvDiss,       O        guDiss, gvDiss,
11       I        myTime, myIter, myThid)       I        myTime, myIter, myThid)
# Line 42  C     == Global variables == Line 42  C     == Global variables ==
42  C     == Routine arguments ==  C     == Routine arguments ==
43  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
44  C     fVerV  :: face of a cell K ( flux into the cell above ).  C     fVerV  :: face of a cell K ( flux into the cell above ).
 C     dPhiHydX,Y :: Gradient (X & Y dir.) of Hydrostatic Potential  
45  C     guDiss :: dissipation tendency (all explicit terms), u component  C     guDiss :: dissipation tendency (all explicit terms), u component
46  C     gvDiss :: dissipation tendency (all explicit terms), v component  C     gvDiss :: dissipation tendency (all explicit terms), v component
47  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
48  C                                      results will be set.  C                                      results will be set.
49  C     kUp, kDown                     - Index for upper and lower layers.  C     kUp, kDown                     - Index for upper and lower layers.
50  C     myThid - Instance number for this innvocation of CALC_MOM_RHS  C     myThid - Instance number for this innvocation of CALC_MOM_RHS
       _RL dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
       _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
51        _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
52        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
53        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
# Line 66  C     myThid - Instance number for this Line 63  C     myThid - Instance number for this
63  #ifdef ALLOW_MOM_VECINV  #ifdef ALLOW_MOM_VECINV
64    
65  C     == Functions ==  C     == Functions ==
66        LOGICAL  DIFF_BASE_MULTIPLE        LOGICAL  DIFFERENT_MULTIPLE
67        EXTERNAL DIFF_BASE_MULTIPLE        EXTERNAL DIFFERENT_MULTIPLE
68    
69  C     == Local variables ==  C     == Local variables ==
70        _RL      vF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL      vF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 89  C     I,J,K - Loop counters Line 86  C     I,J,K - Loop counters
86        INTEGER i,j,k        INTEGER i,j,k
87  C     xxxFac - On-off tracer parameters used for switching terms off.  C     xxxFac - On-off tracer parameters used for switching terms off.
88        _RL  ArDudrFac        _RL  ArDudrFac
       _RL  phxFac  
89  c     _RL  mtFacU  c     _RL  mtFacU
90        _RL  ArDvdrFac        _RL  ArDvdrFac
       _RL  phyFac  
91  c     _RL  mtFacV  c     _RL  mtFacV
92        LOGICAL bottomDragTerms        LOGICAL bottomDragTerms
93        LOGICAL writeDiag        LOGICAL writeDiag
# Line 114  C--   (at least in part) Line 109  C--   (at least in part)
109        fVerV(1,1,kUp) = fVerV(1,1,kUp)        fVerV(1,1,kUp) = fVerV(1,1,kUp)
110  #endif  #endif
111    
112        writeDiag = DIFF_BASE_MULTIPLE(baseTime, diagFreq,        writeDiag = DIFFERENT_MULTIPLE(diagFreq, myTime, deltaTClock)
      &                               myTime, deltaTClock)  
113    
114  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
115        IF (useMNC .AND. snapshot_mnc .AND. writeDiag) THEN        IF (useMNC .AND. snapshot_mnc .AND. writeDiag) THEN
116          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
117            CALL MNC_CW_SET_UDIM('mom_vi', -1, myThid)            CALL MNC_CW_SET_UDIM('mom_vi', -1, myThid)
118            CALL MNC_CW_I_W_S('I','mom_vi',0,0,'T',myIter,myThid)            CALL MNC_CW_RL_W_S('D','mom_vi',0,0,'T',myTime,myThid)
119            CALL MNC_CW_SET_UDIM('mom_vi', 0, myThid)            CALL MNC_CW_SET_UDIM('mom_vi', 0, myThid)
120              CALL MNC_CW_I_W_S('I','mom_vi',0,0,'iter',myIter,myThid)
121          ENDIF          ENDIF
122          DO i = 1,9          DO i = 1,9
123            offsets(i) = 0            offsets(i) = 0
# Line 160  C--   Term by term tracer parmeters Line 155  C--   Term by term tracer parmeters
155  C     o U momentum equation  C     o U momentum equation
156        ArDudrFac    = vfFacMom*1.        ArDudrFac    = vfFacMom*1.
157  c     mTFacU       = mtFacMom*1.  c     mTFacU       = mtFacMom*1.
       phxFac       = pfFacMom*1.  
158  C     o V momentum equation  C     o V momentum equation
159        ArDvdrFac    = vfFacMom*1.        ArDvdrFac    = vfFacMom*1.
160  c     mTFacV       = mtFacMom*1.  c     mTFacV       = mtFacMom*1.
       phyFac       = pfFacMom*1.  
161    
162        IF (     no_slip_bottom        IF (     no_slip_bottom
163       &    .OR. bottomDragQuadratic.NE.0.       &    .OR. bottomDragQuadratic.NE.0.
# Line 174  c     mTFacV       = mtFacMom*1. Line 167  c     mTFacV       = mtFacMom*1.
167         bottomDragTerms=.FALSE.         bottomDragTerms=.FALSE.
168        ENDIF        ENDIF
169    
 C-- with stagger time stepping, grad Phi_Hyp is directly incoporated in TIMESTEP  
       IF (staggerTimeStep) THEN  
         phxFac = 0.  
         phyFac = 0.  
       ENDIF  
   
170  C--   Calculate open water fraction at vorticity points  C--   Calculate open water fraction at vorticity points
171        CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid)        CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid)
172    
# Line 256  C--   Vertical flux (fVer is at upper fa Line 243  C--   Vertical flux (fVer is at upper fa
243    
244  C     Eddy component of vertical flux (interior component only) -> vrF  C     Eddy component of vertical flux (interior component only) -> vrF
245        IF (momViscosity.AND..NOT.implicitViscosity) THEN        IF (momViscosity.AND..NOT.implicitViscosity) THEN
246         CALL MOM_U_RVISCFLUX(bi,bj,k,uVel,KappaRU,vrF,myThid)         IF ( k.LT.Nr ) THEN
247             CALL MOM_U_RVISCFLUX(bi,bj,k+1,uVel,KappaRU,vrF,myThid)
248           ENDIF
249    
250  C     Combine fluxes  C     Combine fluxes
251         DO j=jMin,jMax         DO j=jMin,jMax
# Line 272  C--   Tendency is minus divergence of th Line 261  C--   Tendency is minus divergence of th
261       &   -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)       &   -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)
262       &   *recip_rAw(i,j,bi,bj)       &   *recip_rAw(i,j,bi,bj)
263       &  *(       &  *(
264       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac       &    fVerU(i,j,kDown) - fVerU(i,j,kUp)
265       &   )       &   )*rkSign
266          ENDDO          ENDDO
267         ENDDO         ENDDO
268        ENDIF        ENDIF
# Line 316  C--   Vertical flux (fVer is at upper fa Line 305  C--   Vertical flux (fVer is at upper fa
305    
306  C     Eddy component of vertical flux (interior component only) -> vrF  C     Eddy component of vertical flux (interior component only) -> vrF
307        IF (momViscosity.AND..NOT.implicitViscosity) THEN        IF (momViscosity.AND..NOT.implicitViscosity) THEN
308         CALL MOM_V_RVISCFLUX(bi,bj,k,vVel,KappaRV,vrf,myThid)         IF ( k.LT.Nr ) THEN
309             CALL MOM_V_RVISCFLUX(bi,bj,k+1,vVel,KappaRV,vrF,myThid)
310           ENDIF
311    
312  C     Combine fluxes -> fVerV  C     Combine fluxes -> fVerV
313         DO j=jMin,jMax         DO j=jMin,jMax
# Line 332  C--   Tendency is minus divergence of th Line 323  C--   Tendency is minus divergence of th
323       &   -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)       &   -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)
324       &    *recip_rAs(i,j,bi,bj)       &    *recip_rAs(i,j,bi,bj)
325       &  *(       &  *(
326       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac       &    fVerV(i,j,kDown) - fVerV(i,j,kUp)
327       &   )       &   )*rkSign
328          ENDDO          ENDDO
329         ENDDO         ENDDO
330        ENDIF        ENDIF
# Line 387  C- jmc: change it to keep the Coriolis t Line 378  C- jmc: change it to keep the Coriolis t
378         ENDIF         ENDIF
379         DO j=jMin,jMax         DO j=jMin,jMax
380          DO i=iMin,iMax          DO i=iMin,iMax
381           gU(i,j,k,bi,bj) = uCf(i,j) - phxFac*dPhiHydX(i,j)           gU(i,j,k,bi,bj) = uCf(i,j)
382           gV(i,j,k,bi,bj) = vCf(i,j) - phyFac*dPhiHydY(i,j)           gV(i,j,k,bi,bj) = vCf(i,j)
383          ENDDO          ENDDO
384         ENDDO         ENDDO
385         IF ( writeDiag ) THEN         IF ( writeDiag ) THEN
# Line 408  C- jmc: change it to keep the Coriolis t Line 399  C- jmc: change it to keep the Coriolis t
399        ELSE        ELSE
400         DO j=jMin,jMax         DO j=jMin,jMax
401          DO i=iMin,iMax          DO i=iMin,iMax
402           gU(i,j,k,bi,bj) = -phxFac*dPhiHydX(i,j)           gU(i,j,k,bi,bj) = 0. _d 0
403           gV(i,j,k,bi,bj) = -phyFac*dPhiHydY(i,j)           gV(i,j,k,bi,bj) = 0. _d 0
404          ENDDO          ENDDO
405         ENDDO         ENDDO
406        ENDIF        ENDIF
407    
408        IF (momAdvection) THEN        IF (momAdvection) THEN
409  C--   Horizontal advection of relative vorticity  C--   Horizontal advection of relative (or absolute) vorticity
410         IF (useAbsVorticity) THEN         IF (highOrderVorticity.AND.useAbsVorticity) THEN
411            CALL MOM_VI_U_CORIOLIS_C4(bi,bj,k,vFld,omega3,r_hFacZ,
412         &                         uCf,myThid)
413           ELSEIF (highOrderVorticity) THEN
414            CALL MOM_VI_U_CORIOLIS_C4(bi,bj,k,vFld,vort3, r_hFacZ,
415         &                         uCf,myThid)
416           ELSEIF (useAbsVorticity) THEN
417          CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,hFacZ,r_hFacZ,          CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,hFacZ,r_hFacZ,
418       &                         uCf,myThid)       &                         uCf,myThid)
419         ELSE         ELSE
420          CALL MOM_VI_U_CORIOLIS(bi,bj,k,vFld,vort3,hFacZ,r_hFacZ,          CALL MOM_VI_U_CORIOLIS(bi,bj,k,vFld,vort3, hFacZ,r_hFacZ,
421       &                         uCf,myThid)       &                         uCf,myThid)
422         ENDIF         ENDIF
 c      CALL MOM_VI_U_CORIOLIS_C4(bi,bj,K,vFld,vort3,r_hFacZ,uCf,myThid)  
423         DO j=jMin,jMax         DO j=jMin,jMax
424          DO i=iMin,iMax          DO i=iMin,iMax
425           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)
426          ENDDO          ENDDO
427         ENDDO         ENDDO
428         IF (useAbsVorticity) THEN         IF (highOrderVorticity.AND.useAbsVorticity) THEN
429            CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,omega3,r_hFacZ,
430         &                         vCf,myThid)
431           ELSEIF (highOrderVorticity) THEN
432            CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,vort3, r_hFacZ,
433         &                         vCf,myThid)
434           ELSEIF (useAbsVorticity) THEN
435          CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,hFacZ,r_hFacZ,          CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,hFacZ,r_hFacZ,
436       &                         vCf,myThid)       &                         vCf,myThid)
437         ELSE         ELSE
438          CALL MOM_VI_V_CORIOLIS(bi,bj,k,uFld,vort3,hFacZ,r_hFacZ,          CALL MOM_VI_V_CORIOLIS(bi,bj,k,uFld,vort3, hFacZ,r_hFacZ,
439       &                         vCf,myThid)       &                         vCf,myThid)
440         ENDIF         ENDIF
 c      CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,vort3,r_hFacZ,vCf,myThid)  
441         DO j=jMin,jMax         DO j=jMin,jMax
442          DO i=iMin,iMax          DO i=iMin,iMax
443           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 567  C--   Set du/dt & dv/dt on boundaries to Line 568  C--   Set du/dt & dv/dt on boundaries to
568          ENDIF          ENDIF
569  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
570        ENDIF        ENDIF
571          
572  #endif /* ALLOW_MOM_VECINV */  #endif /* ALLOW_MOM_VECINV */
573    
574        RETURN        RETURN

Legend:
Removed from v.1.37  
changed lines
  Added in v.1.43

  ViewVC Help
Powered by ViewVC 1.1.22