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

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

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


Revision 1.12 - (show annotations) (download)
Sun Aug 24 21:38:18 2008 UTC (15 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61f, checkpoint61n, checkpoint61q, checkpoint61e, checkpoint61g, checkpoint61d, checkpoint61c, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61t, checkpoint61r, checkpoint61s, checkpoint61p
Changes since 1.11: +36 -24 lines
add mass source/sink of fluid in continuity eq. ; need to store addMass
 in pickup file for restart.

1 C $Header: /u/gcmpack/MITgcm/model/src/integrate_for_w.F,v 1.11 2006/12/05 05:25:08 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: INTEGRATE_FOR_W
8 C !INTERFACE:
9 SUBROUTINE INTEGRATE_FOR_W(
10 I bi, bj, k, uFld, vFld, mFld,
11 O wFld,
12 I myThid )
13
14 C !DESCRIPTION: \bv
15 C *==========================================================*
16 C | SUBROUTINE INTEGRATE_FOR_W
17 C | o Integrate for vertical velocity.
18 C *==========================================================*
19 C \ev
20
21 C !USES:
22 IMPLICIT NONE
23 C == GLobal variables ==
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #include "PARAMS.h"
27 #include "GRID.h"
28 #include "SURFACE.h"
29
30 C !INPUT/OUTPUT PARAMETERS:
31 C == Routine arguments ==
32 C uFld, vFld :: Zonal and meridional flow
33 C mFld :: added mass
34 C wFld :: Vertical flow
35 INTEGER bi,bj,k
36 _RL uFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
37 _RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
38 c#ifdef ALLOW_ADDFLUID
39 _RL mFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
40 c#else
41 c _RL mFld (1)
42 c#endif
43 _RL wFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
44 INTEGER myThid
45
46 C !LOCAL VARIABLES:
47 C == Local variables ==
48 C uTrans, vTrans :: Temps. for volume transports
49 C conv2d :: horizontal transport convergence [m^3/s]
50 INTEGER i,j
51 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53 _RL conv2d(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54 CEOP
55
56 C-- Calculate velocity field "volume transports" through
57 C tracer cell faces (anelastic: scaled as a mass transport).
58 DO j=1,sNy+1
59 DO i=1,sNx+1
60 uTrans(i,j) = uFld(i,j,k,bi,bj)
61 & *_dyG(i,j,bi,bj)*deepFacC(k)*rhoFacC(k)
62 & *drF(k)*_hFacW(i,j,k,bi,bj)
63 vTrans(i,j) = vFld(i,j,k,bi,bj)
64 & *_dxG(i,j,bi,bj)*deepFacC(k)*rhoFacC(k)
65 & *drF(k)*_hFacS(i,j,k,bi,bj)
66 ENDDO
67 ENDDO
68 DO j=1,sNy
69 DO i=1,sNx
70 conv2d(i,j) = -( uTrans(i+1,j)-uTrans(i,j)
71 & +vTrans(i,j+1)-vTrans(i,j) )
72 ENDDO
73 ENDDO
74 #ifdef ALLOW_ADDFLUID
75 IF ( selectAddFluid.GE.1 ) THEN
76 DO j=1,sNy
77 DO i=1,sNx
78 conv2d(i,j) = conv2d(i,j)
79 & + mFld(i,j,k,bi,bj)*mass2rUnit
80 ENDDO
81 ENDDO
82 ENDIF
83 #endif /* ALLOW_ADDFLUID */
84
85 C-- Calculate vertical "volume transport" through face k
86 C between tracer cell k-1 & k
87 IF (rigidLid) THEN
88 C- o Rigid-Lid case: zero at lower and upper boundaries
89 IF (k.EQ.1) THEN
90 DO j=1,sNy
91 DO i=1,sNx
92 wFld(i,j,k,bi,bj) = 0.
93 ENDDO
94 ENDDO
95 ELSEIF (k.EQ.Nr) THEN
96 DO j=1,sNy
97 DO i=1,sNx
98 wFld(i,j,k,bi,bj) =
99 & conv2d(i,j)*recip_rA(i,j,bi,bj)
100 & *maskC(i,j,k,bi,bj)*maskC(i,j,k-1,bi,bj)
101 & *recip_deepFac2F(k)*recip_rhoFacF(k)
102 ENDDO
103 ENDDO
104 ELSE
105 DO j=1,sNy
106 DO i=1,sNx
107 wFld(i,j,k,bi,bj) =
108 & ( wFld(i,j,k+1,bi,bj)*deepFac2F(k+1)*rhoFacF(k+1)
109 & +conv2d(i,j)*recip_rA(i,j,bi,bj)
110 & )*maskC(i,j,k,bi,bj)*maskC(i,j,k-1,bi,bj)
111 & *recip_deepFac2F(k)*recip_rhoFacF(k)
112 ENDDO
113 ENDDO
114 ENDIF
115 #ifdef NONLIN_FRSURF
116 ELSEIF (select_rStar .NE. 0) THEN
117 # ifndef DISABLE_RSTAR_CODE
118 C- o rStar case: zero under-ground and at r_lower boundary
119 C can be non-zero at surface (useRealFreshWaterFlux).
120 C note: not implemented neither for anelastic nor deep-model.
121 IF (k.EQ.Nr) THEN
122 DO j=1,sNy
123 DO i=1,sNx
124 wFld(i,j,k,bi,bj) =
125 & ( conv2d(i,j)*recip_rA(i,j,bi,bj)
126 & -rStarDhCDt(i,j,bi,bj)*drF(k)*h0FacC(i,j,k,bi,bj)
127 & )*maskC(i,j,k,bi,bj)
128 ENDDO
129 ENDDO
130 ELSE
131 DO j=1,sNy
132 DO i=1,sNx
133 wFld(i,j,k,bi,bj) =
134 & ( wFld(i,j,k+1,bi,bj)
135 & +conv2d(i,j)*recip_rA(i,j,bi,bj)
136 & -rStarDhCDt(i,j,bi,bj)*drF(k)*h0FacC(i,j,k,bi,bj)
137 & )*maskC(i,j,k,bi,bj)
138 ENDDO
139 ENDDO
140 ENDIF
141 # endif /* DISABLE_RSTAR_CODE */
142 #endif /* NONLIN_FRSURF */
143 ELSE
144 C- o Free Surface case (r-Coordinate):
145 C non zero at surface ; zero under-ground and at r_lower boundary
146 IF (k.EQ.Nr) THEN
147 DO j=1,sNy
148 DO i=1,sNx
149 wFld(i,j,k,bi,bj) =
150 & conv2d(i,j)*recip_rA(i,j,bi,bj)
151 & *maskC(i,j,k,bi,bj)
152 & *recip_deepFac2F(k)*recip_rhoFacF(k)
153 ENDDO
154 ENDDO
155 ELSE
156 DO j=1,sNy
157 DO i=1,sNx
158 wFld(i,j,k,bi,bj) =
159 & ( wFld(i,j,k+1,bi,bj)*deepFac2F(k+1)*rhoFacF(k+1)
160 & +conv2d(i,j)*recip_rA(i,j,bi,bj)
161 & )*maskC(i,j,k,bi,bj)
162 & *recip_deepFac2F(k)*recip_rhoFacF(k)
163 ENDDO
164 ENDDO
165 ENDIF
166 C- endif - rigid-lid / Free-Surf.
167 ENDIF
168
169 RETURN
170 END

  ViewVC Help
Powered by ViewVC 1.1.22