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

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

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


Revision 1.9 - (show annotations) (download)
Tue May 18 17:42:01 1999 UTC (25 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint22, checkpoint23, checkpoint24
Changes since 1.8: +4 -6 lines
Deleted some erroneous comments.

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_div_ghat.F,v 1.8 1999/03/22 15:54:03 adcroft Exp $
2
3 #include "CPP_OPTIONS.h"
4
5 C /==========================================================\
6 C | S/R CALC_DIV_GHAT |
7 C | o Form the right hand-side of the surface pressure eqn. |
8 C |==========================================================|
9 C \==========================================================/
10 SUBROUTINE CALC_DIV_GHAT(
11 I bi,bj,iMin,iMax,jMin,jMax,
12 I K,
13 I xA,yA,
14 I myThid)
15
16 IMPLICIT NONE
17
18 C == Global variables ==
19 #include "SIZE.h"
20 #include "DYNVARS.h"
21 #include "FFIELDS.h"
22 #include "EEPARAMS.h"
23 #include "PARAMS.h"
24 #include "GRID.h"
25 #include "CG2D.h"
26 #ifdef ALLOW_NONHYDROSTATIC
27 #include "CG3D.h"
28 #endif
29
30 C == Routine arguments ==
31 C bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
32 C results will be set.
33 C k - Index of layer.
34 C xA, yA - Cell face areas
35 C myThid - Instance number for this innvocation of CALC_MOM_RHS
36 INTEGER bi,bj,iMin,iMax,jMin,jMax
37 INTEGER K
38 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
39 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
40 INTEGER myThid
41
42 C == Local variables ==
43 INTEGER i,j
44 _RL pf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45
46 C-- Pressure equation source term
47 C Term is the vertical integral of the divergence of the
48 C time tendency terms along with a relaxation term that
49 C pulls div(U) + dh/dt back toward zero.
50
51 IF ( k .EQ. Nr ) THEN
52 C Initialise source term on first pass
53 DO j=jMin,jMax
54 DO i=iMin,iMax
55 cg2d_b(i,j,bi,bj) =
56 & freeSurfFac*_rA(i,j,bi,bj)*horiVertRatio*(
57 & -cg2d_x(I,J,bi,bj)/deltaTMom/deltaTMom
58 #ifdef USE_NATURAL_BCS
59 & +EmPmR(I,J,bi,bj)/deltaTMom
60 #endif
61 & )
62 ENDDO
63 ENDDO
64 ENDIF
65
66 DO j=jMin,jMax
67 DO i=iMin,iMax
68 pf(i,j) = xA(i,j)*gUNm1(i,j,k,bi,bj) / deltaTmom
69 ENDDO
70 ENDDO
71 DO j=1,sNy
72 DO i=1,sNx
73 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
74 & pf(i+1,j)-pf(i,j)
75 ENDDO
76 ENDDO
77
78 #ifdef ALLOW_NONHYDROSTATIC
79 IF (nonHydrostatic) THEN
80 DO j=1,sNy
81 DO i=1,sNx
82 cg3d_b(i,j,k,bi,bj) = pf(i+1,j)-pf(i,j)
83 ENDDO
84 ENDDO
85 ENDIF
86 #endif
87
88 DO j=jMin,jMax
89 DO i=iMin,iMax
90 pf(i,j) = yA(i,j)*gVNm1(i,j,k,bi,bj) / deltatmom
91 ENDDO
92 ENDDO
93
94 DO j=1,sNy
95 DO i=1,sNx
96 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
97 & pf(i,j+1)-pf(i,j)
98 ENDDO
99 ENDDO
100
101 #ifdef ALLOW_NONHYDROSTATIC
102 IF (nonHydrostatic) THEN
103 DO j=1,sNy
104 DO i=1,sNx
105 cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj) +
106 & pf(i,j+1)-pf(i,j)
107 ENDDO
108 ENDDO
109 ENDIF
110 #endif
111
112 RETURN
113 END

  ViewVC Help
Powered by ViewVC 1.1.22