/[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.14 by ljmc, Mon Jun 25 20:38:15 2001 UTC revision 1.18 by jmc, Thu Apr 17 13:40:06 2003 UTC
# Line 2  C $Header$ Line 2  C $Header$
2  C $Name$  C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5  #undef ALLOW_ZONAL_FILT  CBOP
6  #undef ALLOW_SHAP_FILT  C     !ROUTINE: CALC_DIV_GHAT
7    C     !INTERFACE:
8  C     /==========================================================\        SUBROUTINE CALC_DIV_GHAT(
 C     | S/R CALC_DIV_GHAT                                        |  
 C     | o Form the right hand-side of the surface pressure eqn.  |  
 C     |==========================================================|  
 C     \==========================================================/  
       SUBROUTINE CALC_DIV_GHAT(  
9       I        bi,bj,iMin,iMax,jMin,jMax,K,       I        bi,bj,iMin,iMax,jMin,jMax,K,
10       I        xA,yA,       I        xA,yA,
11       U        cg2d_b,       U        cg2d_b,
12       I        myThid)       I        myThid)
13    C     !DESCRIPTION: \bv
14    C     *==========================================================*
15    C     | S/R CALC_DIV_GHAT                                        
16    C     | o Form the right hand-side of the surface pressure eqn.  
17    C     *==========================================================*
18    C     | Right hand side of pressure equation is divergence
19    C     | of veclocity tendency (GHAT) term along with a relaxation
20    C     | term equal to the barotropic flow field divergence.
21    C     *==========================================================*
22    C     \ev
23    
24    C     !USES:
25        IMPLICIT NONE        IMPLICIT NONE
   
26  C     == Global variables ==  C     == Global variables ==
27  #include "SIZE.h"  #include "SIZE.h"
28  #include "DYNVARS.h"  #include "DYNVARS.h"
# Line 25  C     == Global variables == Line 30  C     == Global variables ==
30  #include "EEPARAMS.h"  #include "EEPARAMS.h"
31  #include "PARAMS.h"  #include "PARAMS.h"
32  #include "GRID.h"  #include "GRID.h"
33  #ifdef ALLOW_NONHYDROSTATIC  #include "SOLVE_FOR_PRESSURE3D.h"
 #include "CG3D.h"  
 #endif  
34    
35    C     !INPUT/OUTPUT PARAMETERS:
36  C     == Routine arguments ==  C     == Routine arguments ==
37  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
38  C                                      results will be set.  C                                      results will be set.
# Line 43  C     myThid - Instance number for this Line 47  C     myThid - Instance number for this
47        _RL cg2d_b(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RL cg2d_b(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
48        INTEGER myThid        INTEGER myThid
49    
50    C     !LOCAL VARIABLES:
51  C     == Local variables ==  C     == Local variables ==
52    C     i,j :: Loop counters
53    C     pf  :: Intermediate array for building RHS source term.
54        INTEGER i,j        INTEGER i,j
55        _RL pf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL pf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56    CEOP
57    
58  C--   Pressure equation source term  C--   Pressure equation source term
59  C     Term is the vertical integral of the divergence of the  C     Term is the vertical integral of the divergence of the
60  C     time tendency terms along with a relaxation term that  C     time tendency terms along with a relaxation term that
61  C     pulls div(U) + dh/dt back toward zero.  C     pulls div(U) + dh/dt back toward zero.
62    
63        IF (implicDiv2Dflow.EQ.1.) then        IF (implicDiv2Dflow.EQ.1.) THEN
64  C     Fully Implicit treatment of the Barotropic Flow Divergence  C     Fully Implicit treatment of the Barotropic Flow Divergence
65          DO j=1,sNy          DO j=1,sNy
66           DO i=1,sNx+1           DO i=1,sNx+1
67            pf(i,j) = xA(i,j)*gUNm1(i,j,k,bi,bj) / deltaTmom            pf(i,j) = xA(i,j)*gU(i,j,k,bi,bj) / deltaTmom
68             ENDDO
69            ENDDO
70          ELSEIF (exactConserv) THEN
71    c     ELSEIF (nonlinFreeSurf.GT.0) THEN
72    C     Implicit treatment of the Barotropic Flow Divergence
73            DO j=1,sNy
74             DO i=1,sNx+1
75              pf(i,j) = implicDiv2Dflow
76         &             *xA(i,j)*gU(i,j,k,bi,bj) / deltaTmom
77           ENDDO           ENDDO
78          ENDDO          ENDDO
79        ELSE        ELSE
80  C     Explicit+Implicit part of the Barotropic Flow Divergence  C     Explicit+Implicit part of the Barotropic Flow Divergence
81  C      => Filtering of uVel,vVel is necessary  C      => Filtering of uVel,vVel is necessary
82  #ifdef ALLOW_ZONAL_FILT  C-- Now the filter are applied in the_correction_step().
83          IF (zonal_filt_lat.LT.90.) THEN  C   We have left this code here to indicate where the filters used to be
84            CALL ZONAL_FILTER(  C   in the algorithm before JMC moved them to after the pressure solver.
85       &      uVel, hFacW, 1-1, sNy+1, k, k, bi, bj, 1, myThid)  C-
86            CALL ZONAL_FILTER(  C#ifdef ALLOW_ZONAL_FILT
87       &      vVel, hFacS, 1-1, sNy+1, k, k, bi, bj, 2, myThid)  C        IF (zonal_filt_lat.LT.90.) THEN
88          ENDIF  C          CALL ZONAL_FILTER(
89  #endif  C     &      uVel, hFacW, 1-1, sNy+1, k, k, bi, bj, 1, myThid)
90    C          CALL ZONAL_FILTER(
91    C     &      vVel, hFacS, 1-1, sNy+1, k, k, bi, bj, 2, myThid)
92    C        ENDIF
93    C#endif
94          DO j=1,sNy          DO j=1,sNy
95           DO i=1,sNx+1           DO i=1,sNx+1
96            pf(i,j) = ( implicDiv2Dflow * gUNm1(i,j,k,bi,bj)            pf(i,j) = ( implicDiv2Dflow * gU(i,j,k,bi,bj)
97       &          + (1.-implicDiv2Dflow) * uVel(i,j,k,bi,bj)       &          + (1.-implicDiv2Dflow) * uVel(i,j,k,bi,bj)
98       &               ) * xA(i,j) / deltaTmom       &               ) * xA(i,j) / deltaTmom
99           ENDDO           ENDDO
# Line 95  C      => Filtering of uVel,vVel is nece Line 116  C      => Filtering of uVel,vVel is nece
116        ENDIF        ENDIF
117  #endif  #endif
118    
119        IF (implicDiv2Dflow.EQ.1.) then        IF (implicDiv2Dflow.EQ.1.) THEN
120  C     Fully Implicit treatment of the Barotropic Flow Divergence  C     Fully Implicit treatment of the Barotropic Flow Divergence
121          DO j=1,sNy+1          DO j=1,sNy+1
122           DO i=1,sNx           DO i=1,sNx
123            pf(i,j) = yA(i,j)*gVNm1(i,j,k,bi,bj) / deltatmom            pf(i,j) = yA(i,j)*gV(i,j,k,bi,bj) / deltatmom
124             ENDDO
125            ENDDO
126          ELSEIF (exactConserv) THEN
127    c     ELSEIF (nonlinFreeSurf.GT.0) THEN
128    C     Implicit treatment of the Barotropic Flow Divergence
129            DO j=1,sNy+1
130             DO i=1,sNx
131              pf(i,j) = implicDiv2Dflow
132         &             *yA(i,j)*gV(i,j,k,bi,bj) / deltatmom
133           ENDDO           ENDDO
134          ENDDO          ENDDO
135        ELSE        ELSE
136  C     Explicit+Implicit part of the Barotropic Flow Divergence  C     Explicit+Implicit part of the Barotropic Flow Divergence
137          DO j=1,sNy+1          DO j=1,sNy+1
138           DO i=1,sNx           DO i=1,sNx
139            pf(i,j) = ( implicDiv2Dflow * gVNm1(i,j,k,bi,bj)            pf(i,j) = ( implicDiv2Dflow * gV(i,j,k,bi,bj)
140       &          + (1.-implicDiv2Dflow) * vVel(i,j,k,bi,bj)       &          + (1.-implicDiv2Dflow) * vVel(i,j,k,bi,bj)
141       &               ) * yA(i,j) / deltaTmom       &               ) * yA(i,j) / deltaTmom
142           ENDDO           ENDDO

Legend:
Removed from v.1.14  
changed lines
  Added in v.1.18

  ViewVC Help
Powered by ViewVC 1.1.22