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

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

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


Revision 1.11 - (hide annotations) (download)
Sun Feb 4 14:38:45 2001 UTC (23 years, 3 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint35
Changes since 1.10: +2 -1 lines
Made sure each .F and .h file had
the CVS keywords Header and Name at its start.
Most had header but very few currently have Name, so
lots of changes!

1 cnh 1.11 C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_div_ghat.F,v 1.10 2000/03/14 17:47:25 adcroft Exp $
2     C $Name: $
3 cnh 1.1
4 cnh 1.6 #include "CPP_OPTIONS.h"
5 cnh 1.1
6     C /==========================================================\
7     C | S/R CALC_DIV_GHAT |
8     C | o Form the right hand-side of the surface pressure eqn. |
9 adcroft 1.9 C |==========================================================|
10 cnh 1.1 C \==========================================================/
11     SUBROUTINE CALC_DIV_GHAT(
12     I bi,bj,iMin,iMax,jMin,jMax,
13     I K,
14     I xA,yA,
15     I myThid)
16    
17     IMPLICIT NONE
18    
19     C == Global variables ==
20     #include "SIZE.h"
21     #include "DYNVARS.h"
22     #include "FFIELDS.h"
23     #include "EEPARAMS.h"
24     #include "PARAMS.h"
25     #include "GRID.h"
26     #include "CG2D.h"
27 adcroft 1.8 #ifdef ALLOW_NONHYDROSTATIC
28     #include "CG3D.h"
29     #endif
30 cnh 1.1
31     C == Routine arguments ==
32     C bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
33     C results will be set.
34 adcroft 1.9 C k - Index of layer.
35     C xA, yA - Cell face areas
36 cnh 1.1 C myThid - Instance number for this innvocation of CALC_MOM_RHS
37     INTEGER bi,bj,iMin,iMax,jMin,jMax
38     INTEGER K
39     _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
40     _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41     INTEGER myThid
42    
43     C == Local variables ==
44     INTEGER i,j
45     _RL pf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46    
47     C-- Pressure equation source term
48     C Term is the vertical integral of the divergence of the
49     C time tendency terms along with a relaxation term that
50     C pulls div(U) + dh/dt back toward zero.
51    
52 cnh 1.2 IF ( k .EQ. Nr ) THEN
53 cnh 1.1 C Initialise source term on first pass
54 adcroft 1.10 DO j=1,sNy
55     DO i=1,sNx
56     C Note: The source term containing cg2d_x and cg3d_x (at k=1)
57     C has been moved to solve_for_pressure.F for convenience.
58 cnh 1.1 cg2d_b(i,j,bi,bj) =
59 adcroft 1.10 & freeSurfFac*_rA(i,j,bi,bj)*horiVertRatio*( 0.
60 adcroft 1.7 #ifdef USE_NATURAL_BCS
61     & +EmPmR(I,J,bi,bj)/deltaTMom
62     #endif
63     & )
64 cnh 1.1 ENDDO
65     ENDDO
66     ENDIF
67    
68 adcroft 1.10 DO j=1,sNy
69     DO i=1,sNx+1
70 cnh 1.1 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 adcroft 1.8 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
76 cnh 1.1 & pf(i+1,j)-pf(i,j)
77     ENDDO
78     ENDDO
79    
80 adcroft 1.8 #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 adcroft 1.10 DO j=1,sNy+1
91     DO i=1,sNx
92 cnh 1.1 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 adcroft 1.8 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
99 cnh 1.1 & pf(i,j+1)-pf(i,j)
100     ENDDO
101     ENDDO
102 cnh 1.4
103 adcroft 1.8 #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 cnh 1.1
114     RETURN
115     END

  ViewVC Help
Powered by ViewVC 1.1.22