1 |
jahn |
1.1 |
C $Header$ |
2 |
|
|
C $Name$ |
3 |
|
|
|
4 |
|
|
#include "DARWIN_OPTIONS.h" |
5 |
|
|
|
6 |
|
|
CBOP |
7 |
|
|
C !ROUTINE: DARWIN_READPARMS |
8 |
|
|
|
9 |
|
|
C !INTERFACE: ========================================================== |
10 |
|
|
SUBROUTINE DARWIN_READPARMS( myThid ) |
11 |
|
|
|
12 |
|
|
C !DESCRIPTION: |
13 |
|
|
C Initialize DARWIN parameters, read in data.darwin |
14 |
|
|
|
15 |
|
|
C !USES: =============================================================== |
16 |
|
|
IMPLICIT NONE |
17 |
|
|
#include "SIZE.h" |
18 |
|
|
#include "EEPARAMS.h" |
19 |
|
|
#include "PARAMS.h" |
20 |
|
|
#include "GCHEM.h" |
21 |
|
|
#include "DARWIN_SIZE.h" |
22 |
|
|
#include "DARWIN_IO.h" |
23 |
|
|
#include "DARWIN_PARAMS.h" |
24 |
|
|
#ifdef WAVEBANDS |
25 |
|
|
#include "SPECTRAL_SIZE.h" |
26 |
|
|
#include "SPECTRAL.h" |
27 |
|
|
#include "WAVEBANDS_PARAMS.h" |
28 |
|
|
#endif |
29 |
|
|
|
30 |
|
|
C !INPUT PARAMETERS: =================================================== |
31 |
|
|
C myThid :: thread number |
32 |
|
|
INTEGER myThid |
33 |
|
|
|
34 |
|
|
C !OUTPUT PARAMETERS: ================================================== |
35 |
|
|
C none |
36 |
|
|
|
37 |
|
|
#ifdef ALLOW_DARWIN |
38 |
|
|
|
39 |
|
|
C !LOCAL VARIABLES: ==================================================== |
40 |
|
|
C iUnit :: unit number for I/O |
41 |
|
|
C msgBuf :: message buffer |
42 |
|
|
INTEGER iUnit,errIO |
43 |
|
|
CHARACTER*(MAX_LEN_MBUF) msgBuf |
44 |
|
|
#if defined(WAVEBANDS) || defined(OASIM) |
45 |
|
|
INTEGER ilam,i |
46 |
|
|
_RL planck, c, hc, oavo, hcoavo, rlamm |
47 |
|
|
#endif |
48 |
|
|
CEOP |
49 |
|
|
|
50 |
|
|
NAMELIST /DARWIN_FORCING/ |
51 |
|
|
& darwin_iceFile, |
52 |
|
|
& darwin_ironFile, |
53 |
|
|
& darwin_PARFile, |
54 |
|
|
& darwin_nutWVelFile, |
55 |
|
|
& darwin_PO4_relaxFile, darwin_NO3_relaxFile, |
56 |
|
|
& darwin_FeT_relaxFile, darwin_Si_relaxFile, |
57 |
|
|
& darwin_PO4_fluxFile, darwin_NO3_fluxFile, |
58 |
|
|
& darwin_FeT_fluxFile, darwin_Si_fluxFile, |
59 |
|
|
& darwin_waterabsorbFile, darwin_phytoabsorbFile, |
60 |
|
|
& darwin_surfacespecFile, darwin_acdomFile, |
61 |
|
|
& darwin_particleabsorbFile, |
62 |
|
|
#ifdef OASIM |
63 |
|
|
& darwin_oasim_edFile, darwin_oasim_esFile, |
64 |
|
|
#endif |
65 |
|
|
& darwin_relaxscale, |
66 |
|
|
& darwin_ForcingPeriod, darwin_ForcingCycle, |
67 |
|
|
#ifdef ALLOW_PAR_DAY |
68 |
|
|
& darwin_PARavPeriod, |
69 |
|
|
#endif |
70 |
|
|
& darwin_seed |
71 |
|
|
|
72 |
|
|
#if defined(WAVEBANDS) || defined(OASIM) |
73 |
|
|
NAMELIST /DARWIN_SPECTRAL_PARM/ |
74 |
|
|
& darwin_waves |
75 |
|
|
#ifdef WAVEBANDS |
76 |
|
|
#ifdef DAR_CALC_ACDOM |
77 |
|
|
& ,darwin_Sdom |
78 |
|
|
#endif |
79 |
|
|
#ifdef DAR_DIAG_ACDOM |
80 |
|
|
& ,darwin_diag_acdom_ilam |
81 |
|
|
#endif |
82 |
|
|
#ifdef DAR_RADTRANS |
83 |
|
|
& ,darwin_PAR_ilamLo |
84 |
|
|
& ,darwin_PAR_ilamHi |
85 |
|
|
& ,darwin_radmodThresh |
86 |
|
|
& ,darwin_Dmax |
87 |
|
|
& ,darwin_rmus |
88 |
|
|
& ,darwin_rmuu |
89 |
|
|
& ,darwin_bbw |
90 |
|
|
& ,darwin_bbphy |
91 |
|
|
& ,darwin_bbmin |
92 |
|
|
& ,darwin_radtrans_kmax |
93 |
|
|
& ,darwin_radtrans_niter |
94 |
|
|
& ,darwin_part_size_P |
95 |
|
|
#endif |
96 |
|
|
#endif /* WAVEBANDS */ |
97 |
|
|
#endif /* WAVEBANDS || OASIM */ |
98 |
|
|
|
99 |
|
|
#ifdef DAR_DIAG_CHL |
100 |
|
|
NAMELIST /DARWIN_CHL/ |
101 |
|
|
& Geider_Bigalphachl, Geider_smallalphachl, |
102 |
|
|
& Geider_Bigchl2cmax, Geider_smallchl2cmax, |
103 |
|
|
& Geider_Bigchl2cmin, |
104 |
|
|
& Doney_Bmin, Doney_Bmax, Doney_PARstar, |
105 |
|
|
& Cloern_A, Cloern_B, Cloern_C, Cloern_chl2cmin |
106 |
|
|
#endif |
107 |
|
|
|
108 |
|
|
#ifdef ALLOW_CARBON |
109 |
|
|
NAMELIST /DIC_FORCING/ |
110 |
|
|
& DIC_windFile, DIC_atmospFile, |
111 |
|
|
& dic_pCO2, dic_int1, dic_int2, dic_int3, dic_int4 |
112 |
|
|
#endif |
113 |
|
|
|
114 |
|
|
C Set defaults values for parameters in DARWIN_IO.h |
115 |
|
|
darwin_iceFile=' ' |
116 |
|
|
darwin_ironFile=' ' |
117 |
|
|
darwin_PARFile=' ' |
118 |
|
|
darwin_nutWVelFile=' ' |
119 |
|
|
darwin_PO4_relaxFile=' ' |
120 |
|
|
darwin_NO3_relaxFile=' ' |
121 |
|
|
darwin_FeT_relaxFile=' ' |
122 |
|
|
darwin_Si_relaxFile=' ' |
123 |
|
|
darwin_PO4_fluxFile=' ' |
124 |
|
|
darwin_NO3_fluxFile=' ' |
125 |
|
|
darwin_FeT_fluxFile=' ' |
126 |
|
|
darwin_Si_fluxFile=' ' |
127 |
|
|
darwin_waterabsorbFile=' ' |
128 |
|
|
darwin_phytoabsorbFile=' ' |
129 |
|
|
darwin_particleabsorbFile=' ' |
130 |
|
|
darwin_surfacespecFile=' ' |
131 |
|
|
darwin_acdomFile=' ' |
132 |
|
|
darwin_oasim_edFile=' ' |
133 |
|
|
darwin_oasim_esFile=' ' |
134 |
|
|
darwin_relaxscale=0. _d 0 |
135 |
|
|
darwin_seed=0 |
136 |
|
|
c default periodic forcing to same as for GCHEM |
137 |
|
|
darwin_forcingPeriod=gchem_ForcingPeriod |
138 |
|
|
darwin_forcingCycle=gchem_ForcingCycle |
139 |
|
|
|
140 |
|
|
#ifdef ALLOW_CARBON |
141 |
|
|
DIC_windFile = ' ' |
142 |
|
|
DIC_atmospFile= ' ' |
143 |
|
|
dic_int1 = 0 |
144 |
|
|
dic_int2 = 0 |
145 |
|
|
dic_int3 = 0 |
146 |
|
|
dic_int4 = 0 |
147 |
|
|
dic_pCO2 = 0. _d 0 |
148 |
|
|
#endif |
149 |
|
|
|
150 |
|
|
#ifdef ALLOW_PAR_DAY |
151 |
|
|
darwin_PARavPeriod=86400. _d 0 |
152 |
|
|
#endif |
153 |
|
|
|
154 |
|
|
#if defined(WAVEBANDS) || defined(OASIM) |
155 |
|
|
DO ilam=1,tlam |
156 |
|
|
darwin_waves(ilam) = 0 |
157 |
|
|
ENDDO |
158 |
|
|
IF (tlam.EQ.13) THEN |
159 |
|
|
darwin_waves(1) = 400 |
160 |
|
|
darwin_waves(2) = 425 |
161 |
|
|
darwin_waves(3) = 450 |
162 |
|
|
darwin_waves(4) = 475 |
163 |
|
|
darwin_waves(5) = 500 |
164 |
|
|
darwin_waves(6) = 525 |
165 |
|
|
darwin_waves(7) = 550 |
166 |
|
|
darwin_waves(8) = 575 |
167 |
|
|
darwin_waves(9) = 600 |
168 |
|
|
darwin_waves(10) = 625 |
169 |
|
|
darwin_waves(11) = 650 |
170 |
|
|
darwin_waves(12) = 675 |
171 |
|
|
darwin_waves(13) = 700 |
172 |
|
|
ENDIF |
173 |
|
|
#endif |
174 |
|
|
|
175 |
|
|
#ifdef WAVEBANDS |
176 |
|
|
#ifdef DAR_CALC_ACDOM |
177 |
|
|
darwin_Sdom = 0.014 _d 0 |
178 |
|
|
#endif |
179 |
|
|
#ifdef DAR_DIAG_ACDOM |
180 |
|
|
c value >= 100 will be converted to index in wavebands_init_fixed |
181 |
|
|
darwin_diag_acdom_ilam = 450 |
182 |
|
|
#endif |
183 |
|
|
#ifdef DAR_RADTRANS |
184 |
|
|
darwin_PAR_ilamLo = 1 |
185 |
|
|
darwin_PAR_ilamHi = tlam |
186 |
|
|
darwin_radmodThresh = 1 _d -4 |
187 |
|
|
darwin_Dmax = 500 _d 0 |
188 |
|
|
darwin_rmus = 1.0/0.83 _d 0 |
189 |
|
|
darwin_rmuu = 1.0/0.4 _d 0 |
190 |
|
|
darwin_bbmin = 0.0002 _d 0 |
191 |
|
|
darwin_bbw = 0.5 _d 0 |
192 |
|
|
do i=1,tnabp |
193 |
|
|
darwin_bbphy(i) = 0 _d 0 |
194 |
|
|
enddo |
195 |
|
|
darwin_radtrans_kmax = Nr |
196 |
|
|
darwin_radtrans_niter = 1 |
197 |
|
|
darwin_part_size_P = 1 _d -15 ! mmol P per particle |
198 |
|
|
#endif |
199 |
|
|
#endif /* WAVEBANDS */ |
200 |
|
|
|
201 |
|
|
C Open and read the data.darwin file |
202 |
|
|
_BEGIN_MASTER(myThid) |
203 |
|
|
WRITE(msgBuf,'(A)') ' DARWIN_READPARMS: opening data.darwin' |
204 |
|
|
CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, |
205 |
|
|
& SQUEEZE_RIGHT , 1) |
206 |
|
|
CALL OPEN_COPY_DATA_FILE( |
207 |
|
|
I 'data.darwin', 'DARWIN_READPARAMS', |
208 |
|
|
O iUnit, |
209 |
|
|
I myThid ) |
210 |
|
|
READ(UNIT=iUnit,NML=DARWIN_FORCING) |
211 |
|
|
#ifdef ALLOW_PAR_DAY |
212 |
|
|
darwin_PARnav = NINT(darwin_PARavPeriod*nsubtime/dTtracerLev(1)) |
213 |
|
|
#endif |
214 |
|
|
|
215 |
|
|
#ifdef DAR_DIAG_CHL |
216 |
|
|
C default values |
217 |
|
|
C Geider: chl:c = max(chl2cmin, chl2cmax/(1+(chl2cmax*alphachl*PARday)/(2*Pcm))) |
218 |
|
|
C Pcm = mu*limit*phytoTempFunction |
219 |
|
|
Geider_smallalphachl = 2. _d -6 ! mmol C (mg Chl)-1 m2 (uEin)-1 |
220 |
|
|
Geider_Bigalphachl = 1. _d -6 ! mmol C (mg Chl)-1 m2 (uEin)-1 |
221 |
|
|
Geider_smallchl2cmax = 0.35 _d 0 ! mg Chl (mmol C)-1 |
222 |
|
|
Geider_Bigchl2cmax = 0.65 _d 0 ! mg Chl (mmol C)-1 |
223 |
|
|
Geider_smallchl2cmin = 0.003 _d 0 * 12. _d 0 ! mg Chl a/mmol C |
224 |
|
|
Geider_Bigchl2cmin = 0.003 _d 0 * 12. _d 0 ! mg Chl a/mmol C |
225 |
|
|
|
226 |
|
|
C Doney: chl:c = (Bmax - (Bmax-Bmin)*MIN(1,PARday/PARstar))*limit |
227 |
|
|
Doney_Bmax = 12. _d 0 / 37. _d 0 ! mg Chl a/mmol C |
228 |
|
|
Doney_Bmin = 12. _d 0 / 90. _d 0 ! mg Chl a/mmol C |
229 |
|
|
Doney_PARstar = 90. _d 0 / 0.2174 _d 0 ! uEin/m2/s |
230 |
|
|
|
231 |
|
|
C Cloern: chl:c = chl2cmin + A*exp(B*T)*exp(-C*PARday)*limit |
232 |
|
|
Cloern_chl2cmin = 0.003 _d 0 * 12. _d 0 ! mg Chl a/mmol C |
233 |
|
|
Cloern_A = 0.0154 _d 0 * 12. _d 0 ! mg Chl a/mmol C |
234 |
|
|
Cloern_B = 0.050 _d 0 ! (degree C)^{-1} |
235 |
|
|
Cloern_C = 0.059 _d 0 * 86400. _d 0 / 1. _d 6 ! m^2 s/uEin |
236 |
|
|
|
237 |
|
|
READ(UNIT=iUnit,NML=DARWIN_CHL) |
238 |
|
|
#endif /* DAR_DIAG_CHL */ |
239 |
|
|
|
240 |
|
|
#ifdef ALLOW_CARBON |
241 |
|
|
READ(UNIT=iUnit,NML=DIC_FORCING) |
242 |
|
|
#endif |
243 |
|
|
|
244 |
|
|
#ifdef DAR_RADTRANS |
245 |
|
|
#ifndef DAR_NONSPECTRAL_BACKSCATTERING_RATIO |
246 |
|
|
DO i=1,tnabp |
247 |
|
|
IF ( darwin_bbphy(i) .NE. 0 _d 0 ) THEN |
248 |
|
|
WRITE(msgBuf,'(2A)') 'S/R DARWIN_READPARMS:', |
249 |
|
|
& 'darwin_bbphy is obsolete.' |
250 |
|
|
CALL PRINT_ERROR( msgBuf , 1) |
251 |
|
|
WRITE(msgBuf,'(2A)') 'S/R DARWIN_READPARMS:', |
252 |
|
|
& 'Backscattering coefficients are now read from' |
253 |
|
|
CALL PRINT_ERROR( msgBuf , 1) |
254 |
|
|
WRITE(msgBuf,'(2A)') 'S/R DARWIN_READPARMS:', |
255 |
|
|
& 'darwin_phytoabsorbFile.' |
256 |
|
|
CALL PRINT_ERROR( msgBuf , 1) |
257 |
|
|
ENDIF |
258 |
|
|
ENDDO |
259 |
|
|
#endif |
260 |
|
|
#endif |
261 |
|
|
|
262 |
|
|
#if defined(WAVEBANDS) || defined(OASIM) |
263 |
|
|
READ(UNIT=iUnit,NML=DARWIN_SPECTRAL_PARM,IOSTAT=errIO) |
264 |
|
|
IF ( errIO .LT. 0 ) THEN |
265 |
|
|
WRITE(msgBuf,'(A)') |
266 |
|
|
& 'S/R DARWIN_READPARMS' |
267 |
|
|
CALL PRINT_ERROR( msgBuf , 1) |
268 |
|
|
WRITE(msgBuf,'(A)') |
269 |
|
|
& 'Error reading darwin package' |
270 |
|
|
CALL PRINT_ERROR( msgBuf , 1) |
271 |
|
|
WRITE(msgBuf,'(A)') |
272 |
|
|
& 'parameter file "data.darwin"' |
273 |
|
|
CALL PRINT_ERROR( msgBuf , 1) |
274 |
|
|
WRITE(msgBuf,'(A)') |
275 |
|
|
& 'Problem in namelist DARWIN_SPECTRAL_PARM' |
276 |
|
|
CALL PRINT_ERROR( msgBuf , 1) |
277 |
|
|
STOP 'ABNORMAL END: S/R DARWIN_READPARMS' |
278 |
|
|
ENDIF |
279 |
|
|
#endif |
280 |
|
|
|
281 |
|
|
WRITE(msgBuf,'(A)') |
282 |
|
|
& ' DARWIN_READPARMS: finished reading data.darwin' |
283 |
|
|
CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, |
284 |
|
|
& SQUEEZE_RIGHT , 1) |
285 |
|
|
|
286 |
|
|
C Close the open data file |
287 |
|
|
CLOSE(iUnit) |
288 |
|
|
|
289 |
|
|
#if defined(WAVEBANDS) || defined(OASIM) |
290 |
|
|
c Quanta conversion |
291 |
|
|
planck = 6.6256 _d -34 !Plancks constant J sec |
292 |
|
|
c = 2.998 _d 8 !speed of light m/sec |
293 |
|
|
hc = 1.0/(planck*c) |
294 |
|
|
oavo = 1.0/6.023 _d 23 ! 1/Avogadros number |
295 |
|
|
hcoavo = hc*oavo |
296 |
|
|
do ilam = 1,tlam |
297 |
|
|
rlamm = darwin_waves(ilam)*1 _d -9 !lambda in m |
298 |
|
|
WtouEins(ilam) = 1 _d 6*rlamm*hcoavo !Watts to uEin/s conversion |
299 |
|
|
enddo |
300 |
|
|
#endif |
301 |
|
|
|
302 |
|
|
C-- Print a summary of parameter values: |
303 |
|
|
iUnit = standardMessageUnit |
304 |
|
|
WRITE(msgBuf,'(A)') '// ===================================' |
305 |
|
|
CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid ) |
306 |
|
|
WRITE(msgBuf,'(A)') '// darwin parameters ' |
307 |
|
|
CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid ) |
308 |
|
|
WRITE(msgBuf,'(A)') '// ===================================' |
309 |
|
|
CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid ) |
310 |
|
|
CALL WRITE_0D_I( darwin_seed, INDEX_NONE, |
311 |
|
|
& 'darwin_seed =', |
312 |
|
|
& ' /* seed for random number generator */') |
313 |
|
|
|
314 |
|
|
WRITE(msgBuf,'(A)') ' -----------------------------------' |
315 |
|
|
CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid ) |
316 |
|
|
|
317 |
|
|
#if defined(WAVEBANDS) || defined(OASIM) |
318 |
|
|
CALL WRITE_1D_I( darwin_waves, tlam, 0, |
319 |
|
|
& 'darwin_waves =', |
320 |
|
|
&' /* "central" wavelengths of wavebands */') |
321 |
|
|
#endif |
322 |
|
|
#ifdef WAVEBANDS |
323 |
|
|
#ifdef DAR_CALC_ACDOM |
324 |
|
|
CALL WRITE_0D_RL( darwin_Sdom, INDEX_NONE, |
325 |
|
|
& 'darwin_Sdom =', |
326 |
|
|
&' /* spectral slope for aCDOM */') |
327 |
|
|
#endif |
328 |
|
|
#ifdef DAR_DIAG_ACDOM |
329 |
|
|
CALL WRITE_0D_I( darwin_diag_acdom_ilam, INDEX_NONE, |
330 |
|
|
& 'darwin_diag_acdom_ilam =', |
331 |
|
|
&' /* waveband to use for aCDOM diagnostic */') |
332 |
|
|
#endif |
333 |
|
|
#ifdef DAR_RADTRANS |
334 |
|
|
CALL WRITE_0D_I( darwin_PAR_ilamLo, INDEX_NONE, |
335 |
|
|
& 'darwin_PAR_ilamLo =', |
336 |
|
|
&' /* waveband index of PAR lower bound */') |
337 |
|
|
CALL WRITE_0D_I( darwin_PAR_ilamHi, INDEX_NONE, |
338 |
|
|
& 'darwin_PAR_ilamHi =', |
339 |
|
|
&' /* waveband index of PAR upper bound */') |
340 |
|
|
CALL WRITE_0D_RL( darwin_radmodThresh, INDEX_NONE, |
341 |
|
|
& 'darwin_radmodThresh =', |
342 |
|
|
&' /* threshold for calling radmod (W/m2/waveband) */') |
343 |
|
|
CALL WRITE_0D_RL( darwin_Dmax, INDEX_NONE, |
344 |
|
|
& 'darwin_Dmax =', |
345 |
|
|
&' /* depth at which Ed is assumed zero */') |
346 |
|
|
CALL WRITE_0D_RL( darwin_rmus, INDEX_NONE, |
347 |
|
|
& 'darwin_rmus =', |
348 |
|
|
&' /* inverse average cosine of downward diffuse irradiance */') |
349 |
|
|
CALL WRITE_0D_RL( darwin_rmuu, INDEX_NONE, |
350 |
|
|
& 'darwin_rmuu =', |
351 |
|
|
&' /* inverse average cosine of upward diffuse irradiance */') |
352 |
|
|
CALL WRITE_0D_RL( darwin_bbw, INDEX_NONE, |
353 |
|
|
& 'darwin_bbw =', |
354 |
|
|
&' /* backscattering to forward scattering ratio for water */') |
355 |
|
|
CALL WRITE_0D_RL( darwin_bbmin, INDEX_NONE, |
356 |
|
|
& 'darwin_bbmin =', |
357 |
|
|
&' /* minimum backscattering coefficient (1/m) */') |
358 |
|
|
CALL WRITE_1D_RL( darwin_bbphy, tnabp, 0, |
359 |
|
|
& 'darwin_bbphy =', |
360 |
|
|
&' /* backscattering to forward scattering ratio for phyto */') |
361 |
|
|
CALL WRITE_0D_I( darwin_radtrans_kmax, INDEX_NONE, |
362 |
|
|
& 'darwin_radtrans_kmax =', |
363 |
|
|
&' /* deepest level in which to compute irradiances */') |
364 |
|
|
CALL WRITE_0D_I( darwin_radtrans_niter, INDEX_NONE, |
365 |
|
|
& 'darwin_radtrans_niter =', |
366 |
|
|
&' /* number of "radtrans improvement" iterations */') |
367 |
|
|
#endif /* DAR_RADTRANS */ |
368 |
|
|
#endif /* WAVEBANDS */ |
369 |
|
|
|
370 |
|
|
WRITE(msgBuf,'(A)') ' ===================================' |
371 |
|
|
CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid ) |
372 |
|
|
|
373 |
|
|
_END_MASTER(myThid) |
374 |
|
|
|
375 |
|
|
C Everyone else must wait for the parameters to be loaded |
376 |
|
|
_BARRIER |
377 |
|
|
|
378 |
|
|
#endif /* ALLOW_DARWIN */ |
379 |
|
|
|
380 |
|
|
RETURN |
381 |
|
|
END |