/[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.20 by jmc, Tue Apr 6 00:31:54 2004 UTC revision 1.21 by jmc, Thu Feb 23 20:55:48 2006 UTC
# Line 7  CBOP Line 7  CBOP
7  C     !ROUTINE: CALC_DIV_GHAT  C     !ROUTINE: CALC_DIV_GHAT
8  C     !INTERFACE:  C     !INTERFACE:
9        SUBROUTINE CALC_DIV_GHAT(        SUBROUTINE CALC_DIV_GHAT(
10       I        bi,bj,iMin,iMax,jMin,jMax,K,       I        bi,bj,iMin,iMax,jMin,jMax,k,
11       I        xA,yA,       I        xA,yA,
12       U        cg2d_b,       U        cg2d_b,
13       I        myThid)       I        myThid)
14  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
15  C     *==========================================================*  C     *==========================================================*
16  C     | S/R CALC_DIV_GHAT                                          C     | S/R CALC_DIV_GHAT
17  C     | o Form the right hand-side of the surface pressure eqn.    C     | o Form the right hand-side of the surface pressure eqn.
18  C     *==========================================================*  C     *==========================================================*
19  C     | Right hand side of pressure equation is divergence  C     | Right hand side of pressure equation is divergence
20  C     | of veclocity tendency (GHAT) term along with a relaxation  C     | of veclocity tendency (GHAT) term along with a relaxation
# Line 34  C     == Global variables == Line 34  C     == Global variables ==
34    
35  C     !INPUT/OUTPUT PARAMETERS:  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  :: tile indices
38  C                                      results will be set.  C     iMin, iMax, jMin, jMax :: Range of points for which calculation
39  C     k                              - Index of layer.  C                               results will be set.
40  C     xA, yA                         - Cell face areas  C     k       :: Index of layer.
41  C     cg2d_b - Conjugate Gradient 2-D solver : Right-hand side vector  C     xA, yA  :: Cell face areas
42  C     myThid - Instance number for this call of CALC_DIV_GHAT  C     cg2d_b  :: Conjugate Gradient 2-D solver : Right-hand side vector
43        INTEGER bi,bj,iMin,iMax,jMin,jMax  C     myThid  :: Instance number for this call of CALC_DIV_GHAT
44        INTEGER K        INTEGER bi,bj, iMin,iMax,jMin,jMax
45          INTEGER k
46        _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
47        _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48        _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)
# Line 56  C     pf  :: Intermediate array for buil Line 57  C     pf  :: Intermediate array for buil
57  CEOP  CEOP
58    
59  C--   Pressure equation source term  C--   Pressure equation source term
60  C     Term is the vertical integral of the divergence of the  C     Term is the vertical integral of the divergence of the
61  C     time tendency terms along with a relaxation term that  C     time tendency terms along with a relaxation term that
62  C     pulls div(U) + dh/dt back toward zero.  C     pulls div(U) + dh/dt back toward zero.
63    
# Line 72  c     ELSEIF (nonlinFreeSurf.GT.0) THEN Line 73  c     ELSEIF (nonlinFreeSurf.GT.0) THEN
73  C     Implicit treatment of the Barotropic Flow Divergence  C     Implicit treatment of the Barotropic Flow Divergence
74          DO j=1,sNy          DO j=1,sNy
75           DO i=1,sNx+1           DO i=1,sNx+1
76            pf(i,j) = implicDiv2Dflow            pf(i,j) = implicDiv2Dflow
77       &             *xA(i,j)*gU(i,j,k,bi,bj) / deltaTmom       &             *xA(i,j)*gU(i,j,k,bi,bj) / deltaTmom
78           ENDDO           ENDDO
79          ENDDO          ENDDO
# Line 81  C     Explicit+Implicit part of the Baro Line 82  C     Explicit+Implicit part of the Baro
82  C      => Filtering of uVel,vVel is necessary  C      => Filtering of uVel,vVel is necessary
83  C-- Now the filter are applied in the_correction_step().  C-- Now the filter are applied in the_correction_step().
84  C   We have left this code here to indicate where the filters used to be  C   We have left this code here to indicate where the filters used to be
85  C   in the algorithm before JMC moved them to after the pressure solver.  C   in the algorithm before JMC moved them to after the pressure solver.
86  C-  C-
87  C#ifdef ALLOW_ZONAL_FILT  C#ifdef ALLOW_ZONAL_FILT
88  C        IF (zonal_filt_lat.LT.90.) THEN  C        IF (zonal_filt_lat.LT.90.) THEN
# Line 107  C#endif Line 108  C#endif
108        ENDDO        ENDDO
109    
110  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
111        IF (nonHydrostatic) THEN        IF (use3Dsolver) THEN
112         DO j=1,sNy         DO j=1,sNy
113          DO i=1,sNx          DO i=1,sNx
114           cg3d_b(i,j,k,bi,bj) = pf(i+1,j)-pf(i,j)           cg3d_b(i,j,k,bi,bj) = pf(i+1,j)-pf(i,j)
# Line 150  C     Explicit+Implicit part of the Baro Line 151  C     Explicit+Implicit part of the Baro
151        ENDDO        ENDDO
152    
153  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
154        IF (nonHydrostatic) THEN        IF (use3Dsolver) THEN
155         DO j=1,sNy         DO j=1,sNy
156          DO i=1,sNx          DO i=1,sNx
157           cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj) +           cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj) +

Legend:
Removed from v.1.20  
changed lines
  Added in v.1.21

  ViewVC Help
Powered by ViewVC 1.1.22