/[MITgcm]/MITgcm/model/src/calc_div_ghat.F
ViewVC logotype

Diff of /MITgcm/model/src/calc_div_ghat.F

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

revision 1.12 by jmc, Tue Feb 20 15:06:21 2001 UTC revision 1.13 by jmc, Tue Mar 6 16:51:02 2001 UTC
# Line 9  C     | o Form the right hand-side of th Line 9  C     | o Form the right hand-side of th
9  C     |==========================================================|  C     |==========================================================|
10  C     \==========================================================/  C     \==========================================================/
11        SUBROUTINE CALC_DIV_GHAT(        SUBROUTINE CALC_DIV_GHAT(
12       I        bi,bj,iMin,iMax,jMin,jMax,       I        bi,bj,iMin,iMax,jMin,jMax,K,
      I        K,  
13       I        xA,yA,       I        xA,yA,
14         U        cg2d_b,
15       I        myThid)       I        myThid)
16    
17        IMPLICIT NONE        IMPLICIT NONE
# Line 23  C     == Global variables == Line 23  C     == Global variables ==
23  #include "EEPARAMS.h"  #include "EEPARAMS.h"
24  #include "PARAMS.h"  #include "PARAMS.h"
25  #include "GRID.h"  #include "GRID.h"
 #include "CG2D.h"  
26  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
27  #include "CG3D.h"  #include "CG3D.h"
28  #endif  #endif
# Line 33  C     bi, bj, iMin, iMax, jMin, jMax - R Line 32  C     bi, bj, iMin, iMax, jMin, jMax - R
32  C                                      results will be set.  C                                      results will be set.
33  C     k                              - Index of layer.  C     k                              - Index of layer.
34  C     xA, yA                         - Cell face areas  C     xA, yA                         - Cell face areas
35  C     myThid - Instance number for this innvocation of CALC_MOM_RHS  C     cg2d_b - Conjugate Gradient 2-D solver : Right-hand side vector
36    C     myThid - Instance number for this call of CALC_DIV_GHAT
37        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
38        INTEGER K        INTEGER K
39        _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
40        _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41          _RL cg2d_b(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
42        INTEGER myThid        INTEGER myThid
43    
44  C     == Local variables ==  C     == Local variables ==
# Line 49  C     Term is the vertical integral of t Line 50  C     Term is the vertical integral of t
50  C     time tendency terms along with a relaxation term that  C     time tendency terms along with a relaxation term that
51  C     pulls div(U) + dh/dt back toward zero.  C     pulls div(U) + dh/dt back toward zero.
52    
       IF ( k .EQ. Nr ) THEN  
 C      Initialise source term on first pass  
        DO j=1,sNy  
         DO i=1,sNx  
 C Note: The source term containing cg2d_x and cg3d_x (at k=1)  
 C       has been moved to solve_for_pressure.F for convenience.  
          cg2d_b(i,j,bi,bj) = 0.  
 #ifdef USE_NATURAL_BCS  
      &     + freeSurfFac*_rA(i,j,bi,bj)*horiVertRatio*  
      &       EmPmR(I,J,bi,bj)/deltaTMom  
 #endif  
         ENDDO  
        ENDDO  
       ENDIF  
   
53        IF (implicDiv2Dflow.EQ.1.) then        IF (implicDiv2Dflow.EQ.1.) then
54  C     Fully Implicit treatment of the Barotropic Flow Divergence  C     Fully Implicit treatment of the Barotropic Flow Divergence
55          DO j=1,sNy          DO j=1,sNy

Legend:
Removed from v.1.12  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22