/[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.3 by adcroft, Thu Sep 6 14:23:58 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, myIter, myThid)       I        myCurrentTime, myIter, myThid)
11  C     /==========================================================\  C     /==========================================================\
# 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)
# Line 274  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 293  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 357  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 376  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 492  C--   Bernoulli term Line 473  C--   Bernoulli term
473       &  DIFFERENT_MULTIPLE(diagFreq,myCurrentTime,       &  DIFFERENT_MULTIPLE(diagFreq,myCurrentTime,
474       &                     myCurrentTime-deltaTClock)       &                     myCurrentTime-deltaTClock)
475       & ) THEN       & ) THEN
        CALL WRITE_LOCAL_RL('Ph','I10',Nr,phi_hyd,bi,bj,1,myIter,myThid)  
476         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)
477         CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,myThid)         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)         CALL WRITE_LOCAL_RL('fV','I10',1,uCf,bi,bj,k,myIter,myThid)

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

  ViewVC Help
Powered by ViewVC 1.1.22