1 |
C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_diff_x.F,v 1.3 2001/09/21 13:11:43 adcroft Exp $ |
2 |
C $Name: $ |
3 |
|
4 |
#include "GAD_OPTIONS.h" |
5 |
|
6 |
CBOP |
7 |
C !ROUTINE: GAD_DIFF_X |
8 |
|
9 |
C !INTERFACE: ========================================================== |
10 |
SUBROUTINE GAD_DIFF_X( |
11 |
I bi,bj,k, |
12 |
I xA, diffKh, |
13 |
I tracer, |
14 |
O dfx, |
15 |
I myThid ) |
16 |
|
17 |
C !DESCRIPTION: |
18 |
C Calculates the area integrated zonal flux due to down-gradient diffusion |
19 |
C of a tracer: |
20 |
C \begin{equation*} |
21 |
C F^x_{diff} = - A^x \kappa_h \frac{1}{\Delta x_c} \delta_i \theta |
22 |
C \end{equation*} |
23 |
|
24 |
C !USES: =============================================================== |
25 |
IMPLICIT NONE |
26 |
#include "SIZE.h" |
27 |
#include "GRID.h" |
28 |
|
29 |
C !INPUT PARAMETERS: =================================================== |
30 |
C bi,bj :: tile indices |
31 |
C k :: vertical level |
32 |
C xA :: area of face at U points |
33 |
C diffKh :: horizontal diffusivity |
34 |
C tracer :: tracer field |
35 |
C myThid :: thread number |
36 |
INTEGER bi,bj,k |
37 |
_RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
38 |
_RL diffKh (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr) |
39 |
_RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
40 |
INTEGER myThid |
41 |
|
42 |
C !OUTPUT PARAMETERS: ================================================== |
43 |
C dfx :: zonal diffusive flux |
44 |
_RL dfx (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
45 |
|
46 |
C !LOCAL VARIABLES: ==================================================== |
47 |
C i,j :: loop indices |
48 |
INTEGER i,j |
49 |
CEOP |
50 |
|
51 |
C print *,'in gad_diff_x' |
52 |
DO j=1-Oly,sNy+Oly |
53 |
dfx(1-Olx,j)=0. |
54 |
DO i=1-Olx+1,sNx+Olx |
55 |
dfx(i,j) = -diffKh(i,j,k)*xA(i,j) |
56 |
& *_recip_dxC(i,j,bi,bj) |
57 |
& *(Tracer(i,j)-Tracer(i-1,j)) |
58 |
& *CosFacU(j,bi,bj) |
59 |
ENDDO |
60 |
ENDDO |
61 |
|
62 |
RETURN |
63 |
END |
64 |
c---------------------------------------------------------- |
65 |
SUBROUTINE CALC_MLD(bi,bj,diffkh3d_x,diffkh3d_y,myThid) |
66 |
implicit none |
67 |
|
68 |
#include "SIZE.h" |
69 |
#include "EEPARAMS.h" |
70 |
#include "PARAMS.h" |
71 |
#include "DYNVARS.h" |
72 |
#include "GRID.h" |
73 |
|
74 |
INTEGER bi,bj |
75 |
_RL diffkh3d_x (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr) |
76 |
_RL diffkh3d_y (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr) |
77 |
INTEGER myThid |
78 |
|
79 |
C !LOCAL VARIABLES: ==================================================== |
80 |
C i,j :: loop indices |
81 |
INTEGER i,j |
82 |
cjrs next |
83 |
_RL rhoK (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
84 |
_RL Khplus,gradij,gradim1,gradjm1,calc_grad |
85 |
real *8 khconst,khmin,khmax |
86 |
parameter ( khconst=5.d15 ) |
87 |
parameter ( khmin=1000.0 ) |
88 |
parameter ( khmax=40000.0 ) |
89 |
cjrs try constants 6e14, 3e15, 5e15, 10e15 |
90 |
|
91 |
c jrs next |
92 |
C print *,'in calc_mld for Khplus ' |
93 |
CALL FIND_RHO( |
94 |
& bi,bj,1-Olx,sNx+OLx,1-OLy,sNy+OLy,1,1, |
95 |
& theta,salt,rhoK,myThid) |
96 |
|
97 |
DO j=1-Oly,sNy+Oly |
98 |
DO i=1-Olx+1,sNx+Olx |
99 |
|
100 |
if (hfacc(i,j,1,bi,bj).ne.0) then |
101 |
gradij=calc_grad(i,j,bi,bj,rhoK) |
102 |
endif |
103 |
|
104 |
if ( (hfacc(i,j,1,bi,bj).ne.0).and. |
105 |
& (hfacc(i-1,j,1,bi,bj).ne.0) ) then |
106 |
gradim1=calc_grad(i-1,j,bi,bj,rhoK) |
107 |
if ((gradij.ne.0).and.(gradim1.ne.0)) then |
108 |
Khplus= khconst*(gradij+gradim1)/2 |
109 |
elseif (gradij.ne.0) then |
110 |
Khplus= khconst*gradij |
111 |
elseif (gradim1.ne.0) then |
112 |
Khplus= khconst*gradim1 |
113 |
else |
114 |
Khplus=0.d0 |
115 |
endif |
116 |
if (Khplus.lt.khmin) Khplus=khmin |
117 |
if (Khplus.gt.khmax) Khplus=khmax |
118 |
if (j.ge.43) Khplus=khmin |
119 |
diffkh3d_x(i,j,1)=Khplus |
120 |
c diffkh3d_x(i,j,2)=0.5*Khplus |
121 |
c diffkh3d_x(i,j,3)=0.2*Khplus |
122 |
C print *,'Khplus_x: ',i,j,Khplus |
123 |
|
124 |
else |
125 |
diffkh3d_x(i,j,1)=0.d0 |
126 |
endif |
127 |
|
128 |
if ( (hfacc(i,j,1,bi,bj).ne.0).and. |
129 |
& (hfacc(i,j-1,1,bi,bj).ne.0) ) then |
130 |
gradjm1=calc_grad(i,j-1,bi,bj,rhoK) |
131 |
if ((gradij.ne.0).and.(gradjm1.ne.0)) then |
132 |
Khplus= khconst*(gradij+gradjm1)/2 |
133 |
elseif (gradij.ne.0) then |
134 |
Khplus= khconst*gradij |
135 |
elseif (gradjm1.ne.0) then |
136 |
Khplus= khconst*gradjm1 |
137 |
else |
138 |
Khplus=0.d0 |
139 |
endif |
140 |
if (Khplus.lt.khmin) Khplus=khmin |
141 |
if (Khplus.gt.khmax) Khplus=khmax |
142 |
if (j.ge.43) Khplus=khmin |
143 |
diffkh3d_y(i,j,1)=Khplus |
144 |
c diffkh3d_y(i,j,2)=0.5*Khplus |
145 |
c diffkh3d_y(i,j,3)=0.2*Khplus |
146 |
C print *,'Khplus_y: ',i,j,Khplus |
147 |
|
148 |
else |
149 |
diffkh3d_y(i,j,1)=0.d0 |
150 |
endif |
151 |
|
152 |
ENDDO |
153 |
ENDDO |
154 |
|
155 |
return |
156 |
end |
157 |
c-------------------------------------------------- |
158 |
real*8 FUNCTION CALC_GRAD(i,j,bi,bj,rhoK) |
159 |
implicit none |
160 |
|
161 |
#include "SIZE.h" |
162 |
#include "EEPARAMS.h" |
163 |
#include "PARAMS.h" |
164 |
#include "GRID.h" |
165 |
|
166 |
INTEGER i,j,bi,bj |
167 |
_RL rhoK (1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
168 |
|
169 |
|
170 |
c Local variables |
171 |
integer xno,yno |
172 |
_RL xgrad,ygrad |
173 |
|
174 |
c print *,'entering calc_gradient...for ',i,j |
175 |
if (hfacC(i,j,1,bi,bj).eq.0) then |
176 |
calc_grad=0.d0 |
177 |
else |
178 |
xgrad=0.d0 |
179 |
xno=0 |
180 |
if (hfacC(i+1,j,1,bi,bj).ne.0) then |
181 |
xgrad= abs((rhoK(i+1,j)-rhoK(i,j))*_recip_dxC(i+1,j,bi,bj)) |
182 |
xno=1 |
183 |
c print *,'gradient with i+1: ',xgrad |
184 |
endif |
185 |
if (hfacC(i-1,j,1,bi,bj).ne.0) then |
186 |
xgrad= xgrad + |
187 |
& abs((rhoK(i,j)-rhoK(i-1,j))*_recip_dxC(i,j,bi,bj)) |
188 |
xno=xno+1 |
189 |
c print *,'gradient with i-1: ', |
190 |
c & abs((rhoK(i,j)-rhoK(i-1,j))*_recip_dxC(i,j,bi,bj)) |
191 |
endif |
192 |
|
193 |
ygrad=0.d0 |
194 |
yno=0 |
195 |
if (hfacC(i,j+1,1,bi,bj).ne.0) then |
196 |
ygrad= abs((rhoK(i,j+1)-rhoK(i,j))*_recip_dyC(i,j+1,bi,bj)) |
197 |
yno=1 |
198 |
endif |
199 |
if (hfacC(i,j-1,1,bi,bj).ne.0) then |
200 |
ygrad= ygrad + |
201 |
& abs((rhoK(i,j)-rhoK(i,j-1))*_recip_dyC(i,j,bi,bj)) |
202 |
yno=yno+1 |
203 |
endif |
204 |
|
205 |
if ((xno.ne.0).and.(yno.ne.0)) then |
206 |
calc_grad=(xgrad/xno)*(xgrad/xno) + |
207 |
& (ygrad/yno)*(ygrad/yno) |
208 |
elseif (xno.ne.0) then |
209 |
calc_grad= (xgrad/xno)*(xgrad/xno) |
210 |
else |
211 |
calc_grad= (ygrad/yno)*(ygrad/yno) |
212 |
endif |
213 |
endif |
214 |
|
215 |
return |
216 |
end |