1 |
jscott |
1.2 |
C $Header: /u/gcmpack/MITgcm/model/src/calc_gs.F,v 1.50 2009/02/13 21:56:48 heimbach Exp $ |
2 |
jscott |
1.1 |
C $Name: $ |
3 |
jscott |
1.2 |
C inserted mods in 1.51 7/10/09 |
4 |
jscott |
1.1 |
|
5 |
|
|
#include "PACKAGES_CONFIG.h" |
6 |
|
|
#include "CPP_OPTIONS.h" |
7 |
|
|
|
8 |
|
|
CBOP |
9 |
|
|
C !ROUTINE: CALC_GS |
10 |
|
|
C !INTERFACE: |
11 |
|
|
SUBROUTINE CALC_GS( |
12 |
|
|
I bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown, |
13 |
|
|
I xA, yA, maskUp, uFld, vFld, wFld, |
14 |
|
|
I uTrans, vTrans, rTrans, rTransKp1, |
15 |
|
|
I KappaRS, diffKh3d_x, diffKh3d_y, |
16 |
|
|
U fVerS, |
17 |
|
|
I myTime,myIter,myThid ) |
18 |
|
|
C !DESCRIPTION: \bv |
19 |
|
|
C *==========================================================* |
20 |
|
|
C | SUBROUTINE CALC_GS |
21 |
|
|
C | o Calculate the salt tendency terms. |
22 |
|
|
C *==========================================================* |
23 |
|
|
C | A procedure called EXTERNAL_FORCING_S is called from |
24 |
|
|
C | here. These procedures can be used to add per problem |
25 |
|
|
C | E-P flux source terms. |
26 |
|
|
C | Note: Although it is slightly counter-intuitive the |
27 |
|
|
C | EXTERNAL_FORCING routine is not the place to put |
28 |
|
|
C | file I/O. Instead files that are required to |
29 |
|
|
C | calculate the external source terms are generally |
30 |
|
|
C | read during the model main loop. This makes the |
31 |
|
|
C | logisitics of multi-processing simpler and also |
32 |
|
|
C | makes the adjoint generation simpler. It also |
33 |
|
|
C | allows for I/O to overlap computation where that |
34 |
|
|
C | is supported by hardware. |
35 |
|
|
C | Aside from the problem specific term the code here |
36 |
|
|
C | forms the tendency terms due to advection and mixing |
37 |
|
|
C | The baseline implementation here uses a centered |
38 |
|
|
C | difference form for the advection term and a tensorial |
39 |
|
|
C | divergence of a flux form for the diffusive term. The |
40 |
|
|
C | diffusive term is formulated so that isopycnal mixing and |
41 |
|
|
C | GM-style subgrid-scale terms can be incorporated b simply |
42 |
|
|
C | setting the diffusion tensor terms appropriately. |
43 |
|
|
C *==========================================================* |
44 |
|
|
C \ev |
45 |
|
|
|
46 |
|
|
C !USES: |
47 |
|
|
IMPLICIT NONE |
48 |
|
|
C == GLobal variables == |
49 |
|
|
#include "SIZE.h" |
50 |
|
|
#include "DYNVARS.h" |
51 |
|
|
#include "EEPARAMS.h" |
52 |
|
|
#include "PARAMS.h" |
53 |
jscott |
1.2 |
#include "RESTART.h" |
54 |
jscott |
1.1 |
#ifdef ALLOW_GENERIC_ADVDIFF |
55 |
|
|
#include "GAD.h" |
56 |
|
|
#endif |
57 |
|
|
#ifdef ALLOW_AUTODIFF_TAMC |
58 |
|
|
# include "tamc.h" |
59 |
|
|
# include "tamc_keys.h" |
60 |
|
|
#endif |
61 |
|
|
|
62 |
|
|
C !INPUT/OUTPUT PARAMETERS: |
63 |
|
|
C == Routine arguments == |
64 |
|
|
C bi, bj, :: tile indices |
65 |
|
|
C iMin,iMax, jMin,jMax :: Range of points for which calculation |
66 |
|
|
C results will be set. |
67 |
|
|
C k :: vertical index |
68 |
|
|
C kM1 :: =k-1 for k>1, =1 for k=1 |
69 |
|
|
C kUp :: index into 2 1/2D array, toggles between 1|2 |
70 |
|
|
C kDown :: index into 2 1/2D array, toggles between 2|1 |
71 |
|
|
C xA :: Tracer cell face area normal to X |
72 |
|
|
C yA :: Tracer cell face area normal to X |
73 |
|
|
C maskUp :: Land mask used to denote base of the domain. |
74 |
|
|
C uFld,vFld :: Local copy of horizontal velocity field |
75 |
|
|
C wFld :: Local copy of vertical velocity field |
76 |
|
|
C uTrans :: Zonal volume transport through cell face |
77 |
|
|
C vTrans :: Meridional volume transport through cell face |
78 |
|
|
C rTrans :: Vertical volume transport at interface k |
79 |
|
|
C rTransKp1 :: Vertical volume transport at inteface k+1 |
80 |
|
|
C KappaRS :: Vertical diffusion for Salinity |
81 |
|
|
C fVerS :: Flux of salt (S) in the vertical direction |
82 |
|
|
C at the upper(U) and lower(D) faces of a cell. |
83 |
|
|
C myTime :: current time |
84 |
|
|
C myIter :: current iteration number |
85 |
|
|
C myThid :: my Thread Id. number |
86 |
|
|
|
87 |
|
|
INTEGER bi,bj,iMin,iMax,jMin,jMax |
88 |
|
|
INTEGER k,kUp,kDown,kM1 |
89 |
|
|
_RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
90 |
|
|
_RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
91 |
|
|
_RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
92 |
|
|
_RL uFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
93 |
|
|
_RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
94 |
|
|
_RL wFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
95 |
|
|
_RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
96 |
|
|
_RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
97 |
|
|
_RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
98 |
|
|
_RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
99 |
|
|
_RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
100 |
|
|
_RL diffKh3d_x(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr) |
101 |
|
|
_RL diffKh3d_y(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr) |
102 |
|
|
_RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2) |
103 |
|
|
_RL myTime |
104 |
|
|
INTEGER myIter |
105 |
|
|
INTEGER myThid |
106 |
|
|
CEOP |
107 |
|
|
|
108 |
|
|
#ifdef ALLOW_GENERIC_ADVDIFF |
109 |
|
|
C === Local variables === |
110 |
|
|
LOGICAL calcAdvection |
111 |
|
|
INTEGER iterNb |
112 |
|
|
#ifdef ALLOW_ADAMSBASHFORTH_3 |
113 |
|
|
INTEGER m1, m2 |
114 |
|
|
#endif |
115 |
|
|
|
116 |
|
|
#ifdef ALLOW_AUTODIFF_TAMC |
117 |
|
|
act1 = bi - myBxLo(myThid) |
118 |
|
|
max1 = myBxHi(myThid) - myBxLo(myThid) + 1 |
119 |
|
|
act2 = bj - myByLo(myThid) |
120 |
|
|
max2 = myByHi(myThid) - myByLo(myThid) + 1 |
121 |
|
|
act3 = myThid - 1 |
122 |
|
|
max3 = nTx*nTy |
123 |
|
|
act4 = ikey_dynamics - 1 |
124 |
|
|
itdkey = (act1 + 1) + act2*max1 |
125 |
|
|
& + act3*max1*max2 |
126 |
|
|
& + act4*max1*max2*max3 |
127 |
|
|
kkey = (itdkey-1)*Nr + k |
128 |
|
|
#endif /* ALLOW_AUTODIFF_TAMC */ |
129 |
|
|
|
130 |
|
|
#ifdef ALLOW_AUTODIFF_TAMC |
131 |
|
|
C-- only the kUp part of fverS is set in this subroutine |
132 |
|
|
C-- the kDown is still required |
133 |
|
|
fVerS(1,1,kDown) = fVerS(1,1,kDown) |
134 |
|
|
# ifdef NONLIN_FRSURF |
135 |
|
|
CADJ STORE fVerS(:,:,:) = |
136 |
jscott |
1.2 |
CADJ & comlev1_bibj_k, key=kkey, byte=isbyte, |
137 |
|
|
CADJ & kind = isbyte |
138 |
|
|
CADJ STORE gsNm1(:,:,k,bi,bj) = |
139 |
|
|
CADJ & comlev1_bibj_k, key=kkey, byte=isbyte, |
140 |
|
|
CADJ & kind = isbyte |
141 |
jscott |
1.1 |
# endif |
142 |
|
|
#endif |
143 |
|
|
|
144 |
|
|
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
145 |
|
|
|
146 |
|
|
calcAdvection = saltAdvection .AND. .NOT.saltMultiDimAdvec |
147 |
|
|
iterNb = myIter |
148 |
|
|
IF (staggerTimeStep) iterNb = myIter - 1 |
149 |
|
|
|
150 |
|
|
#ifdef ALLOW_ADAMSBASHFORTH_3 |
151 |
|
|
m1 = 1 + MOD(iterNb+1,2) |
152 |
|
|
m2 = 1 + MOD( iterNb ,2) |
153 |
|
|
CALL GAD_CALC_RHS( |
154 |
|
|
I bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown, |
155 |
|
|
I xA, yA, maskUp, uFld, vFld, wFld, |
156 |
|
|
I uTrans, vTrans, rTrans, rTransKp1, |
157 |
|
|
I diffKhS, diffK4S, KappaRS, |
158 |
jscott |
1.2 |
I gsNm(1-Olx,1-Oly,1,1,1,m2), salt, dTtracerLev, |
159 |
jscott |
1.1 |
I GAD_SALINITY, saltAdvScheme, saltVertAdvScheme, |
160 |
|
|
I calcAdvection, saltImplVertAdv, AdamsBashforth_S, |
161 |
jscott |
1.2 |
I useGMRedi, useKPP, |
162 |
jscott |
1.1 |
U fVerS, gS, |
163 |
|
|
I myTime, myIter, myThid ) |
164 |
|
|
#else /* ALLOW_ADAMSBASHFORTH_3 */ |
165 |
|
|
CALL GAD_CALC_RHS_RAF( |
166 |
|
|
I bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown, |
167 |
|
|
I xA, yA, maskUp, uFld, vFld, wFld, |
168 |
|
|
I uTrans, vTrans, rTrans, rTransKp1, |
169 |
|
|
I diffKh3d_x, diffKh3d_y, |
170 |
jscott |
1.2 |
I diffK4S, KappaRS, gsNm1, salt, dTtracerLev, |
171 |
jscott |
1.1 |
I GAD_SALINITY, saltAdvScheme, saltVertAdvScheme, |
172 |
|
|
I calcAdvection, saltImplVertAdv, AdamsBashforth_S, |
173 |
jscott |
1.2 |
I useGMRedi, useKPP, |
174 |
jscott |
1.1 |
U fVerS, gS, |
175 |
|
|
I myTime, myIter, myThid ) |
176 |
|
|
#endif /* ALLOW_ADAMSBASHFORTH_3 */ |
177 |
|
|
|
178 |
|
|
C-- External salinity forcing term(s) inside Adams-Bashforth: |
179 |
|
|
IF ( saltForcing .AND. tracForcingOutAB.NE.1 ) |
180 |
|
|
& CALL EXTERNAL_FORCING_S( |
181 |
|
|
I iMin,iMax,jMin,jMax,bi,bj,k, |
182 |
|
|
I myTime,myThid) |
183 |
|
|
|
184 |
|
|
IF ( AdamsBashforthGs ) THEN |
185 |
|
|
#ifdef ALLOW_ADAMSBASHFORTH_3 |
186 |
|
|
CALL ADAMS_BASHFORTH3( |
187 |
|
|
I bi, bj, k, |
188 |
|
|
U gS, gsNm, |
189 |
|
|
I saltStartAB, iterNb, myThid ) |
190 |
|
|
#else |
191 |
|
|
CALL ADAMS_BASHFORTH2( |
192 |
|
|
I bi, bj, k, |
193 |
|
|
U gS, gsNm1, |
194 |
jscott |
1.2 |
I saltStartAB, iterNb, myThid ) |
195 |
jscott |
1.1 |
#endif |
196 |
|
|
ENDIF |
197 |
|
|
|
198 |
|
|
C-- External salinity forcing term(s) outside Adams-Bashforth: |
199 |
|
|
IF ( saltForcing .AND. tracForcingOutAB.EQ.1 ) |
200 |
|
|
& CALL EXTERNAL_FORCING_S( |
201 |
|
|
I iMin,iMax,jMin,jMax,bi,bj,k, |
202 |
|
|
I myTime,myThid) |
203 |
|
|
|
204 |
|
|
#ifdef NONLIN_FRSURF |
205 |
|
|
IF (nonlinFreeSurf.GT.0) THEN |
206 |
|
|
CALL FREESURF_RESCALE_G( |
207 |
|
|
I bi, bj, k, |
208 |
|
|
U gS, |
209 |
|
|
I myThid ) |
210 |
|
|
IF ( AdamsBashforthGs ) THEN |
211 |
|
|
#ifdef ALLOW_ADAMSBASHFORTH_3 |
212 |
|
|
CALL FREESURF_RESCALE_G( |
213 |
|
|
I bi, bj, k, |
214 |
|
|
U gsNm(1-OLx,1-OLy,1,1,1,1), |
215 |
|
|
I myThid ) |
216 |
|
|
CALL FREESURF_RESCALE_G( |
217 |
|
|
I bi, bj, k, |
218 |
|
|
U gsNm(1-OLx,1-OLy,1,1,1,2), |
219 |
|
|
I myThid ) |
220 |
|
|
#else |
221 |
|
|
CALL FREESURF_RESCALE_G( |
222 |
|
|
I bi, bj, k, |
223 |
|
|
U gsNm1, |
224 |
|
|
I myThid ) |
225 |
|
|
#endif |
226 |
|
|
ENDIF |
227 |
|
|
ENDIF |
228 |
|
|
#endif /* NONLIN_FRSURF */ |
229 |
|
|
|
230 |
|
|
#endif /* ALLOW_GENERIC_ADVDIFF */ |
231 |
|
|
|
232 |
|
|
RETURN |
233 |
|
|
END |