/[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.8 - (show annotations) (download)
Mon Mar 22 15:54:03 1999 UTC (25 years, 2 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint20, checkpoint21
Changes since 1.7: +26 -3 lines
Modifications for non-hydrostatic ability + updates for open-boundaries.

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

  ViewVC Help
Powered by ViewVC 1.1.22