/[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.10 - (show annotations) (download)
Tue Mar 14 17:47:25 2000 UTC (24 years, 2 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint28, checkpoint29, checkpoint25, checkpoint27, branch-atmos-merge-freeze, branch-atmos-merge-start, checkpoint26, branch-atmos-merge-shapiro, checkpoint33, checkpoint32, checkpoint31, checkpoint30, checkpoint34, branch-atmos-merge-zonalfilt, branch-atmos-merge-phase5, branch-atmos-merge-phase4, branch-atmos-merge-phase7, branch-atmos-merge-phase6, branch-atmos-merge-phase1, branch-atmos-merge-phase3, branch-atmos-merge-phase2
Branch point for: branch-atmos-merge
Changes since 1.9: +10 -9 lines
Various updates for OBCs and Non-hydrostatic routines.
 o OBCs now fits into time-stepping properly
 o div.G has been moved to solve_for_pressure()

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_div_ghat.F,v 1.9 1999/05/18 17:42:01 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=1,sNy
54 DO i=1,sNx
55 C Note: The source term containing cg2d_x and cg3d_x (at k=1)
56 C has been moved to solve_for_pressure.F for convenience.
57 cg2d_b(i,j,bi,bj) =
58 & freeSurfFac*_rA(i,j,bi,bj)*horiVertRatio*( 0.
59 #ifdef USE_NATURAL_BCS
60 & +EmPmR(I,J,bi,bj)/deltaTMom
61 #endif
62 & )
63 ENDDO
64 ENDDO
65 ENDIF
66
67 DO j=1,sNy
68 DO i=1,sNx+1
69 pf(i,j) = xA(i,j)*gUNm1(i,j,k,bi,bj) / deltaTmom
70 ENDDO
71 ENDDO
72 DO j=1,sNy
73 DO i=1,sNx
74 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
75 & pf(i+1,j)-pf(i,j)
76 ENDDO
77 ENDDO
78
79 #ifdef ALLOW_NONHYDROSTATIC
80 IF (nonHydrostatic) THEN
81 DO j=1,sNy
82 DO i=1,sNx
83 cg3d_b(i,j,k,bi,bj) = pf(i+1,j)-pf(i,j)
84 ENDDO
85 ENDDO
86 ENDIF
87 #endif
88
89 DO j=1,sNy+1
90 DO i=1,sNx
91 pf(i,j) = yA(i,j)*gVNm1(i,j,k,bi,bj) / deltatmom
92 ENDDO
93 ENDDO
94
95 DO j=1,sNy
96 DO i=1,sNx
97 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
98 & pf(i,j+1)-pf(i,j)
99 ENDDO
100 ENDDO
101
102 #ifdef ALLOW_NONHYDROSTATIC
103 IF (nonHydrostatic) THEN
104 DO j=1,sNy
105 DO i=1,sNx
106 cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj) +
107 & pf(i,j+1)-pf(i,j)
108 ENDDO
109 ENDDO
110 ENDIF
111 #endif
112
113 RETURN
114 END

  ViewVC Help
Powered by ViewVC 1.1.22