/[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.2 by cnh, Sat Aug 22 17:51:07 1998 UTC revision 1.13 by jmc, Tue Mar 6 16:51:02 2001 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_EEOPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6  C     /==========================================================\  C     /==========================================================\
7  C     | S/R CALC_DIV_GHAT                                        |  C     | S/R CALC_DIV_GHAT                                        |
8  C     | o Form the right hand-side of the surface pressure eqn.  |  C     | o Form the right hand-side of the surface pressure eqn.  |
9    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 21  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"
26  #include "CG2D.h"  #ifdef ALLOW_NONHYDROSTATIC
27    #include "CG3D.h"
28    #endif
29    
30  C     == Routine arguments ==  C     == Routine arguments ==
 C     pH - Hydrostatic pressure  
31  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
32  C                                      results will be set.  C                                      results will be set.
33  C     kUp, kDown, kM1                - Index for upper and lower layers.  C     k                              - Index of layer.
34  C     myThid - Instance number for this innvocation of CALC_MOM_RHS  C     xA, yA                         - Cell face areas
35    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 44  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    
53        IF ( k .EQ. Nr ) THEN        IF (implicDiv2Dflow.EQ.1.) then
54  C      Initialise source term on first pass  C     Fully Implicit treatment of the Barotropic Flow Divergence
55         DO j=jMin,jMax          DO j=1,sNy
56          DO i=iMin,iMax           DO i=1,sNx+1
57  C        cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)            pf(i,j) = xA(i,j)*gUNm1(i,j,k,bi,bj) / deltaTmom
58  C    &    -freeSurfFac*_rA(i,j,bi,bj)*           ENDDO
59  C    &     cg2d_x(I  ,J  ,bi,bj)/deltaTMom/deltaTMom          ENDDO
60           cg2d_b(i,j,bi,bj) =        ELSE
61       &    -freeSurfFac*_rA(i,j,bi,bj)*  C     Explicit+Implicit part of the Barotropic Flow Divergence
62       &     cg2d_x(I  ,J  ,bi,bj)/deltaTMom/deltaTMom  C      => Filtering of uVel,vVel is necessary
63    #ifdef ALLOW_ZONAL_FILT
64            IF (zonal_filt_lat.LT.90.) THEN
65              CALL ZONAL_FILTER(
66         &      uVel, hFacW, 1-1, sNy+1, k, k, bi, bj, 1, myThid)
67              CALL ZONAL_FILTER(
68         &      vVel, hFacS, 1-1, sNy+1, k, k, bi, bj, 2, myThid)
69            ENDIF
70    #endif
71            DO j=1,sNy
72             DO i=1,sNx+1
73              pf(i,j) = ( implicDiv2Dflow * gUNm1(i,j,k,bi,bj)
74         &          + (1.-implicDiv2Dflow) * uVel(i,j,k,bi,bj)
75         &               ) * xA(i,j) / deltaTmom
76             ENDDO
77          ENDDO          ENDDO
        ENDDO  
78        ENDIF        ENDIF
   
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         pf(i,j) = xA(i,j)*gUNm1(i,j,k,bi,bj) / deltaTmom  
        ENDDO  
       ENDDO  
79        DO j=1,sNy        DO j=1,sNy
80         DO i=1,sNx         DO i=1,sNx
81          cg2d_b(i,j,bi,bj) =  cg2d_b(i,j,bi,bj) +          cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
82       &   pf(i+1,j)-pf(i,j)       &   pf(i+1,j)-pf(i,j)
83         ENDDO         ENDDO
84        ENDDO        ENDDO
85    
86        DO j=jMin,jMax  #ifdef ALLOW_NONHYDROSTATIC
87         DO i=iMin,iMax        IF (nonHydrostatic) THEN
88          pf(i,j) = yA(i,j)*gVNm1(i,j,k,bi,bj) / deltatmom         DO j=1,sNy
89            DO i=1,sNx
90             cg3d_b(i,j,k,bi,bj) = pf(i+1,j)-pf(i,j)
91            ENDDO
92         ENDDO         ENDDO
93        ENDDO        ENDIF
94    #endif
95    
96          IF (implicDiv2Dflow.EQ.1.) then
97    C     Fully Implicit treatment of the Barotropic Flow Divergence
98            DO j=1,sNy+1
99             DO i=1,sNx
100              pf(i,j) = yA(i,j)*gVNm1(i,j,k,bi,bj) / deltatmom
101             ENDDO
102            ENDDO
103          ELSE
104    C     Explicit+Implicit part of the Barotropic Flow Divergence
105            DO j=1,sNy+1
106             DO i=1,sNx
107              pf(i,j) = ( implicDiv2Dflow * gVNm1(i,j,k,bi,bj)
108         &          + (1.-implicDiv2Dflow) * vVel(i,j,k,bi,bj)
109         &               ) * yA(i,j) / deltaTmom
110             ENDDO
111            ENDDO
112          ENDIF
113        DO j=1,sNy        DO j=1,sNy
114         DO i=1,sNx         DO i=1,sNx
115          cg2d_b(i,j,bi,bj) =  cg2d_b(i,j,bi,bj) +          cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
116       &   pf(i,j+1)-pf(i,j)       &   pf(i,j+1)-pf(i,j)
117         ENDDO         ENDDO
118        ENDDO        ENDDO
119    
120    #ifdef ALLOW_NONHYDROSTATIC
121          IF (nonHydrostatic) THEN
122           DO j=1,sNy
123            DO i=1,sNx
124             cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj) +
125         &    pf(i,j+1)-pf(i,j)
126            ENDDO
127           ENDDO
128          ENDIF
129    #endif
130    
131        RETURN        RETURN
132        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22