/[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.4 - (show annotations) (download)
Tue Sep 8 01:37:49 1998 UTC (25 years, 8 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint15, checkpoint14
Changes since 1.3: +15 -1 lines
Consistent isomorphism changes

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_div_ghat.F,v 1.3 1998/09/07 15:36:24 cnh Exp $
2
3 #include "CPP_EEOPTIONS.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
26 C == Routine arguments ==
27 C pH - Hydrostatic pressure
28 C bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
29 C results will be set.
30 C kUp, kDown, kM1 - Index for upper and lower layers.
31 C myThid - Instance number for this innvocation of CALC_MOM_RHS
32 INTEGER bi,bj,iMin,iMax,jMin,jMax
33 INTEGER K
34 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
35 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
36 INTEGER myThid
37
38 C == Local variables ==
39 INTEGER i,j
40 _RL pf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41
42 CcnhDEbugStarts
43 INTEGER i1, j1
44 CcnhDebugEnds
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 C cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
56 C & -freeSurfFac*_rA(i,j,bi,bj)*
57 C & cg2d_x(I ,J ,bi,bj)/deltaTMom/deltaTMom
58 cg2d_b(i,j,bi,bj) =
59 & -freeSurfFac*_rA(i,j,bi,bj)*horiVertRatio*
60 & cg2d_x(I ,J ,bi,bj)/deltaTMom/deltaTMom
61 ENDDO
62 ENDDO
63 ENDIF
64
65 DO j=jMin,jMax
66 DO i=iMin,iMax
67 pf(i,j) = xA(i,j)*gUNm1(i,j,k,bi,bj) / deltaTmom
68 ENDDO
69 ENDDO
70 DO j=1,sNy
71 DO i=1,sNx
72 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
73 & pf(i+1,j)-pf(i,j)
74 ENDDO
75 ENDDO
76
77 DO j=jMin,jMax
78 DO i=iMin,iMax
79 pf(i,j) = yA(i,j)*gVNm1(i,j,k,bi,bj) / deltatmom
80 ENDDO
81 ENDDO
82
83 DO j=1,sNy
84 DO i=1,sNx
85 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
86 & pf(i,j+1)-pf(i,j)
87 ENDDO
88 ENDDO
89
90 CcnhDebugSTarts
91 C IF ( K .EQ. 10 .OR. K .EQ. 1 ) THEN
92 C i1 = 54
93 C j1 = 26
94 C WRITE(0,*) ' @ I = ', i1, ' , J = ', j1, ' K = ', K
95 C WRITE(0,*) ' cg2d_b = ', cg2d_b(i1,j1,bi,bj)
96 C ENDIF
97 CcnhDebugEnds
98
99
100 RETURN
101 END

  ViewVC Help
Powered by ViewVC 1.1.22