/[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.1 by adcroft, Thu Aug 16 17:16:03 2001 UTC revision 1.4 by jmc, Sat Feb 8 02:10:57 2003 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        phi_hyd,KappaRU,KappaRV,       I        dPhiHydX,dPhiHydY,KappaRU,KappaRV,
9       U        fVerU, fVerV,       U        fVerU, fVerV,
10       I        myCurrentTime, myThid)       I        myCurrentTime, myIter, myThid)
11  C     /==========================================================\  C     /==========================================================\
12  C     | S/R MOM_VECINV                                           |  C     | S/R MOM_VECINV                                           |
13  C     | o Form the right hand-side of the momentum equation.     |  C     | o Form the right hand-side of the momentum equation.     |
# Line 36  C     == Routine arguments == Line 36  C     == Routine arguments ==
36  C     fVerU   - Flux of momentum in the vertical  C     fVerU   - Flux of momentum in the vertical
37  C     fVerV     direction out of the upper face of a cell K  C     fVerV     direction out of the upper face of a cell K
38  C               ( flux into the cell above ).  C               ( flux into the cell above ).
39  C     phi_hyd - Hydrostatic pressure  C     dPhiHydX,Y :: Gradient (X & Y dir.) of Hydrostatic Potential
40  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
41  C                                      results will be set.  C                                      results will be set.
42  C     kUp, kDown                     - Index for upper and lower layers.  C     kUp, kDown                     - Index for upper and lower layers.
43  C     myThid - Instance number for this innvocation of CALC_MOM_RHS  C     myThid - Instance number for this innvocation of CALC_MOM_RHS
44        _RL phi_hyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
45          _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
46        _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
47        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
48        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
49        _RL fVerV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
50        INTEGER kUp,kDown        INTEGER kUp,kDown
       INTEGER myThid  
51        _RL     myCurrentTime        _RL     myCurrentTime
52          INTEGER myIter
53          INTEGER myThid
54        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
55    
56    C     == Functions ==
57          LOGICAL  DIFFERENT_MULTIPLE
58          EXTERNAL DIFFERENT_MULTIPLE
59    
60  C     == Local variables ==  C     == Local variables ==
61        _RL      aF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL      aF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
62        _RL      vF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL      vF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 61  C     == Local variables == Line 67  C     == Local variables ==
67        _RL      pF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL      pF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
68        _RL del2u(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL del2u(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
69        _RL del2v(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL del2v(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70          _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71          _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72        _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73        _RS r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74        _RS xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 222  C     Calculate velocity field "volume t Line 230  C     Calculate velocity field "volume t
230    
231        IF (momViscosity) THEN        IF (momViscosity) THEN
232  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
233         CALL MOM_VI_DEL2UV(         IF (viscA4.NE.0.) THEN
234       I                    bi,bj,k,hDiv,vort3,hFacZ,           CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,
235       O                    del2u,del2v,       O                      del2u,del2v,
236       &                    myThid)       &                      myThid)
237         CALL MOM_VI_CALC_HDIV(bi,bj,k,del2u,del2v,dStar,myThid)           CALL MOM_VI_CALC_HDIV(bi,bj,k,del2u,del2v,dStar,myThid)
238         CALL MOM_VI_CALC_RELVORT3(bi,bj,k,del2u,del2v,hFacZ,zStar,myThid)           CALL MOM_VI_CALC_RELVORT3(
239         &                         bi,bj,k,del2u,del2v,hFacZ,zStar,myThid)
240           ENDIF
241  C      Calculate dissipation terms for U and V equations  C      Calculate dissipation terms for U and V equations
242         CALL MOM_VI_HDISSIP(  C      in terms of vorticity and divergence
243       I                     bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar,         IF (viscAh.NE.0. .OR. viscA4.NE.0.) THEN
244       O                     uDiss,vDiss,           CALL MOM_VI_HDISSIP(bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar,
245       &                     myThid)       O                       uDiss,vDiss,
246         &                       myThid)
247           ENDIF
248    C      or in terms of tension and strain
249           IF (viscAstrain.NE.0. .OR. viscAtension.NE.0.) THEN
250             CALL MOM_CALC_TENSION(bi,bj,k,uFld,vFld,
251         O                         tension,
252         I                         myThid)
253             CALL MOM_CALC_STRAIN(bi,bj,k,uFld,vFld,hFacZ,
254         O                        strain,
255         I                        myThid)
256             CALL MOM_HDISSIP(bi,bj,k,
257         I                    tension,strain,hFacZ,viscAtension,viscAstrain,
258         O                    uDiss,vDiss,
259         I                    myThid)
260           ENDIF
261        ENDIF        ENDIF
262    
263  C---- Zonal momentum equation starts here  C---- Zonal momentum equation starts here
# Line 250  C     Combine fluxes Line 275  C     Combine fluxes
275         ENDDO         ENDDO
276        ENDDO        ENDDO
277    
 C---  Hydrostatic term ( -1/rhoConst . dphi/dx )  
       IF (momPressureForcing) THEN  
        DO j=1-Olx,sNy+Oly  
         DO i=2-Olx,sNx+Olx  
          pf(i,j) = - _recip_dxC(i,j,bi,bj)  
      &    *(phi_hyd(i,j,k)-phi_hyd(i-1,j,k))  
         ENDDO  
        ENDDO  
       ENDIF  
   
278  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term
279        DO j=2-Oly,sNy+Oly-1        DO j=2-Oly,sNy+Oly-1
280         DO i=2-Olx,sNx+Olx-1         DO i=2-Olx,sNx+Olx-1
# Line 269  C--   Tendency is minus divergence of th Line 284  C--   Tendency is minus divergence of th
284       &  *(       &  *(
285       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac
286       &   )       &   )
287       & _PHM( +phxFac * pf(i,j) )       &  - phxFac*dPhiHydX(i,j)
288         ENDDO         ENDDO
289        ENDDO        ENDDO
290    
# Line 333  C     Combine fluxes -> fVerV Line 348  C     Combine fluxes -> fVerV
348         ENDDO         ENDDO
349        ENDDO        ENDDO
350    
 C---  Hydorstatic term (-1/rhoConst . dphi/dy )  
       IF (momPressureForcing) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          pF(i,j) = -_recip_dyC(i,j,bi,bj)  
      &    *(phi_hyd(i,j,k)-phi_hyd(i,j-1,k))  
         ENDDO  
        ENDDO  
       ENDIF  
   
351  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term
352        DO j=jMin,jMax        DO j=jMin,jMax
353         DO i=iMin,iMax         DO i=iMin,iMax
# Line 352  C--   Tendency is minus divergence of th Line 357  C--   Tendency is minus divergence of th
357       &  *(       &  *(
358       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac
359       &   )       &   )
360       & _PHM( +phyFac*pf(i,j) )       &  - phyFac*dPhiHydY(i,j)
361         ENDDO         ENDDO
362        ENDDO        ENDDO
363    
# Line 464  C--   Bernoulli term Line 469  C--   Bernoulli term
469        ENDDO        ENDDO
470        ENDIF        ENDIF
471    
472          IF (
473         &  DIFFERENT_MULTIPLE(diagFreq,myCurrentTime,
474         &                     myCurrentTime-deltaTClock)
475         & ) THEN
476           CALL WRITE_LOCAL_RL('Ds','I10',1,strain,bi,bj,k,myIter,myThid)
477           CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,myThid)
478           CALL WRITE_LOCAL_RL('fV','I10',1,uCf,bi,bj,k,myIter,myThid)
479           CALL WRITE_LOCAL_RL('fU','I10',1,vCf,bi,bj,k,myIter,myThid)
480           CALL WRITE_LOCAL_RL('Du','I10',1,uDiss,bi,bj,k,myIter,myThid)
481           CALL WRITE_LOCAL_RL('Dv','I10',1,vDiss,bi,bj,k,myIter,myThid)
482           CALL WRITE_LOCAL_RL('Z3','I10',1,vort3,bi,bj,k,myIter,myThid)
483           CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid)
484           CALL WRITE_LOCAL_RL('KE','I10',1,KE,bi,bj,k,myIter,myThid)
485           CALL WRITE_LOCAL_RL('D','I10',1,hdiv,bi,bj,k,myIter,myThid)
486          ENDIF
487    
488        RETURN        RETURN
489        END        END

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.4

  ViewVC Help
Powered by ViewVC 1.1.22