1 |
C $Header$ |
2 |
C $Name$ |
3 |
|
4 |
#include "DARWIN_OPTIONS.h" |
5 |
|
6 |
CBOP |
7 |
C !ROUTINE: MONOD_RADTRANS_ITER |
8 |
|
9 |
C !INTERFACE: ========================================================== |
10 |
subroutine MONOD_RADTRANS_ITER( |
11 |
I H,rmud,Edsf,Essf,a_k,bt_k,bb_k,kmax,niter, |
12 |
O Edbot,Esbot,Eubot,Eutop, |
13 |
O tirrq,tirrwq, |
14 |
I myThid) |
15 |
|
16 |
C !DESCRIPTION: |
17 |
c |
18 |
c Model of irradiance in the water column. Accounts for three |
19 |
c irradiance streams: |
20 |
c |
21 |
c Edbot = direct downwelling irradiance in W/m2 per waveband |
22 |
c Esbot = diffuse downwelling irradiance in W/m2 per waveband |
23 |
c Eubot = diffuse upwelling irradiance in W/m2 per waveband |
24 |
c |
25 |
c Propagation is done in energy units, tests are done in quanta, |
26 |
c final is quanta for phytoplankton growth. |
27 |
c |
28 |
c The Ed equation is integrated exactly. |
29 |
c Es and Eu are first computed using a truncation to downward- |
30 |
c decreasing modes a la Aas that makes Es continuous. |
31 |
c Then niter alternating upward and downward integrations are performed, |
32 |
c each time using Es at the top and Eu at the bottom of each layer as a |
33 |
c boundary condition. The boundary condition in the deepest wet layer |
34 |
c is always downward-decreasing modes only. |
35 |
c During upward integrations, Eu is made continuous, during downward |
36 |
c integrations, Es. |
37 |
c At the end, Ed and Es are continuous, but Eu is so only approximately. |
38 |
c |
39 |
C !USES: =============================================================== |
40 |
IMPLICIT NONE |
41 |
#include "SIZE.h" /* Nr */ |
42 |
C#include "EEPARAMS.h" |
43 |
#include "MONOD_SIZE.h" |
44 |
#include "SPECTRAL_SIZE.h" /* tlam */ |
45 |
#include "SPECTRAL.h" /* WtouEin */ |
46 |
#include "WAVEBANDS_PARAMS.h" /* darwin_PAR_ilamLo/Hi |
47 |
darwin_radmodThresh |
48 |
darwin_rmus darwin_rmuu */ |
49 |
|
50 |
C !INPUT PARAMETERS: =================================================== |
51 |
C H :: layer thickness (including hFacC!) |
52 |
C rmud :: inv.cosine of direct (underwater solar) zenith angle |
53 |
C Edsf :: direct downwelling irradiance below surface per waveband |
54 |
C Essf :: diffuse downwelling irradiance below surface per waveband |
55 |
C a_k :: absorption coefficient per level and waveband (1/m) |
56 |
C bt_k :: total scattering coefficient per level and waveband (1/m) |
57 |
C = forward + back scattering coefficient |
58 |
C bb_k :: backscattering coefficient per level and waveband (1/m) |
59 |
C kmax :: maximum number of layers to compute |
60 |
C niter :: number of up-down iterations after initial Aas integration |
61 |
_RL H(Nr) |
62 |
_RL rmud |
63 |
_RL Edsf(tlam), Essf(tlam) |
64 |
_RL a_k(Nr,tlam), bt_k(Nr,tlam), bb_k(Nr,tlam) |
65 |
INTEGER kmax,niter |
66 |
INTEGER myThid |
67 |
|
68 |
C !OUTPUT PARAMETERS: ================================================== |
69 |
C Edbot :: direct downwelling irradiance at bottom of layer |
70 |
C Esbot :: diffuse downwelling irradiance at bottom of layer |
71 |
C Eubot :: diffuse upwelling irradiance at bottom of layer |
72 |
C tirrq :: total scalar irradiance at cell center (uEin/m2/s) |
73 |
C tirrwq :: total scalar irradiance at cell center per waveband |
74 |
_RL Edbot(tlam,Nr),Esbot(tlam,Nr),Eubot(tlam,Nr),Eutop(tlam,Nr) |
75 |
_RL tirrq(Nr) |
76 |
_RL tirrwq(tlam,Nr) |
77 |
|
78 |
#ifdef DAR_RADTRANS |
79 |
|
80 |
C !LOCAL VARIABLES: ==================================================== |
81 |
INTEGER k, nl, iter, kbot |
82 |
_RL Edtop(tlam,Nr),Estop(tlam,Nr) |
83 |
_RL Etopwq, Ebotwq |
84 |
_RL zd |
85 |
_RL rmus,rmuu |
86 |
|
87 |
C !LOCAL VARIABLES: ================================================ |
88 |
_RL cd,au,Bu,Cu |
89 |
_RL as,Bs,Cs,Bd,Fd |
90 |
_RL bquad,cquad,sqarg |
91 |
_RL a1,a2,denom |
92 |
_RL c1,c2,tmp,Esnew,Eunew |
93 |
_RL R2(Nr),R1(Nr),x(Nr),y(Nr) |
94 |
_RL expAddr(Nr),expAsdr(Nr),expmAudr(Nr),idenom(Nr) |
95 |
c |
96 |
_RL rbot, rd, ru |
97 |
data rbot /0.0/ !bottom reflectance (not used) |
98 |
data rd /1.5/ !these are taken from Ackleson, et al. 1994 (JGR) |
99 |
data ru /3.0/ |
100 |
CEOP |
101 |
rmus = darwin_rmus |
102 |
rmuu = darwin_rmuu |
103 |
|
104 |
c find deepest wet layer |
105 |
kbot = kmax |
106 |
DO WHILE (H(kbot).EQ.0 .AND. kbot.GT.1) |
107 |
kbot = kbot - 1 |
108 |
ENDDO |
109 |
|
110 |
DO nl = 1,tlam |
111 |
DO k=1,Nr |
112 |
Edtop(nl,k) = 0.0 |
113 |
Estop(nl,k) = 0.0 |
114 |
Eutop(nl,k) = 0.0 |
115 |
Edbot(nl,k) = 0.0 |
116 |
Esbot(nl,k) = 0.0 |
117 |
Eubot(nl,k) = 0.0 |
118 |
ENDDO |
119 |
IF (Edsf(nl) .GE. darwin_radmodThresh .OR. |
120 |
& Essf(nl) .GE. darwin_radmodThresh) THEN |
121 |
DO k=1,kbot |
122 |
zd = H(k) |
123 |
cd = (a_k(k,nl)+bt_k(k,nl))*rmud |
124 |
au = a_k(k,nl)*rmuu |
125 |
Bu = ru*bb_k(k,nl)*rmuu |
126 |
Cu = au+Bu |
127 |
as = a_k(k,nl)*rmus |
128 |
Bs = rd*bb_k(k,nl)*rmus |
129 |
Cs = as+Bs |
130 |
Bd = bb_k(k,nl)*rmud |
131 |
Fd = (bt_k(k,nl)-bb_k(k,nl))*rmud |
132 |
bquad = Cs - Cu |
133 |
cquad = Bs*Bu - Cs*Cu |
134 |
sqarg = bquad*bquad - 4.0*cquad |
135 |
a1 = 0.5*(-bquad + sqrt(sqarg)) |
136 |
a2 = 0.5*(-bquad - sqrt(sqarg)) ! K of Aas |
137 |
R1(k) = (a1+Cs)/Bu |
138 |
R2(k) = (a2+Cs)/Bu |
139 |
denom = (cd-Cs)*(cd+Cu) + Bs*Bu |
140 |
x(k) = -((cd+Cu)*Fd+Bu*Bd)/denom |
141 |
y(k) = (-Bs*Fd+(cd-Cs)*Bd)/denom |
142 |
expAddr(k) = exp(-cd*zd) |
143 |
expmAudr(k) = exp(-a1*zd) |
144 |
expAsdr(k) = exp(a2*zd) |
145 |
idenom(k) = 1./(R1(k)-R2(k)*expAsdr(k)*expmAudr(k)) |
146 |
ENDDO |
147 |
|
148 |
C integrate Ed equation first |
149 |
Edtop(nl,1) = Edsf(nl) |
150 |
DO k=1,kbot-1 |
151 |
Edbot(nl,k) = Edtop(nl,k)*expAddr(k) |
152 |
Edtop(nl,k+1) = Edbot(nl,k) |
153 |
ENDDO |
154 |
Edbot(nl,kbot) = Edtop(nl,kbot)*expAddr(kbot) |
155 |
|
156 |
C start with Aas solution (no increasing mode) |
157 |
Estop(nl,1) = Essf(nl) |
158 |
DO k=1,kbot-1 |
159 |
c2 = Estop(nl,k) - x(k)*Edtop(nl,k) |
160 |
Estop(nl,k+1) = MAX(0., c2*expAsdr(k) + x(k)*Edbot(nl,k)) |
161 |
Eubot(nl,k) = MAX(0., R2(k)*c2*expAsdr(k) + y(k)*Edbot(nl,k)) |
162 |
Eutop(nl,k) = R2(k)*c2 + y(k)*Edtop(nl,k) |
163 |
ENDDO |
164 |
C Aas b.c. in bottom layer |
165 |
c2 = Estop(nl,kbot) - x(kbot)*Edtop(nl,kbot) |
166 |
Eutop(nl,kbot) = R2(kbot)*c2 + y(kbot)*Edtop(nl,kbot) |
167 |
|
168 |
c improve solution iteratively |
169 |
DO iter=1,niter |
170 |
c bottom boundary condition |
171 |
Eubot(nl,kbot-1) = Eutop(nl,kbot) |
172 |
|
173 |
DO k=kbot-1,2,-1 |
174 |
c compute Eubot(k-1) from Estop(k) and Eubot(k) |
175 |
tmp = Estop(nl,k)-x(k)*Edtop(nl,k) |
176 |
c1 = (Eubot(nl,k)-R2(k)*expAsdr(k)*tmp-y(k)*Edbot(nl,k)) |
177 |
& *idenom(k) |
178 |
c2 = (R1(k)*tmp + y(k)*expmAudr(k)*Edbot(nl,k) |
179 |
& - expmAudr(k)*Eubot(nl,k))*idenom(k) |
180 |
Eunew = R2(k)*c2 + R1(k)*expmAudr(k)*c1 + y(k)*Edtop(nl,k) |
181 |
Eubot(nl,k-1) = MAX(0., Eunew) |
182 |
ENDDO |
183 |
DO k=1,kbot-1 |
184 |
c compute Estop(k+1) from Estop(k) and Eubot(k) |
185 |
tmp = Estop(nl,k) - x(k)*Edtop(nl,k) |
186 |
c1 = (Eubot(nl,k)-R2(k)*expAsdr(k)*tmp-y(k)*Edbot(nl,k)) |
187 |
& *idenom(k) |
188 |
c2 = (R1(k)*tmp + y(k)*expmAudr(k)*Edbot(nl,k) |
189 |
& - expmAudr(k)*Eubot(nl,k))*idenom(k) |
190 |
Esnew = expAsdr(k)*c2 + c1 + x(k)*Edbot(nl,k) |
191 |
Estop(nl,k+1) = MAX(0., Esnew) |
192 |
Eutop(nl,k) = R2(k)*c2+R1(k)*expmAudr(k)*c1+y(k)*Edtop(nl,k) |
193 |
ENDDO |
194 |
C Aas b.c. in bottom layer |
195 |
c2 = Estop(nl,kbot) - x(kbot)*Edtop(nl,kbot) |
196 |
Eutop(nl,kbot) = R2(kbot)*c2 + y(kbot)*Edtop(nl,kbot) |
197 |
C enddo iter |
198 |
ENDDO |
199 |
|
200 |
c compute missing fields |
201 |
C uses c2 from previous iteration! |
202 |
Esbot(nl,kbot) = c2*expAsdr(kbot) + x(kbot)*Edbot(nl,kbot) |
203 |
Eubot(nl,kbot) = R2(kbot)*c2*expAsdr(kbot) |
204 |
& + y(kbot)*Edbot(nl,kbot) |
205 |
|
206 |
C Es is continuous now (unless negative...) |
207 |
DO k=1,kbot-1 |
208 |
Esbot(nl,k) = Estop(nl,k+1) |
209 |
ENDDO |
210 |
C endif thresh |
211 |
ENDIF |
212 |
|
213 |
DO k = 1,Nr |
214 |
#ifdef DAR_RADTRANS_RMUS_PAR |
215 |
Etopwq = (Edtop(nl,k)+Estop(nl,k)+Eutop(nl,k))*WtouEins(nl) |
216 |
Ebotwq = (Edbot(nl,k)+Esbot(nl,k)+Eubot(nl,k))*WtouEins(nl) |
217 |
C interpolate and convert to scalar using rmus only!? |
218 |
tirrwq(nl,k) = sqrt(Etopwq*Ebotwq)*rmus |
219 |
#else |
220 |
C convert to scalar irradiance in quanta |
221 |
Etopwq = (rmud*Edtop(nl,k)+rmus*Estop(nl,k)+rmuu*Eutop(nl,k)) |
222 |
& *WtouEins(nl) |
223 |
Ebotwq = (rmud*Edbot(nl,k)+rmus*Esbot(nl,k)+rmuu*Eubot(nl,k)) |
224 |
& *WtouEins(nl) |
225 |
C and interpolate |
226 |
tirrwq(nl,k) = sqrt(Etopwq*Ebotwq) |
227 |
#endif |
228 |
ENDDO |
229 |
|
230 |
C enddo nl |
231 |
ENDDO |
232 |
|
233 |
DO k = 1,Nr |
234 |
C sum PAR range |
235 |
tirrq(k) = 0.0 |
236 |
DO nl = darwin_PAR_ilamLo,darwin_PAR_ilamHi |
237 |
tirrq(k) = tirrq(k) + tirrwq(nl,k) |
238 |
ENDDO |
239 |
ENDDO |
240 |
c |
241 |
#endif /* DAR_RADTRANS */ |
242 |
|
243 |
return |
244 |
end |
245 |
|