/[MITgcm]/MITgcm_contrib/darwin2/pkg/monod/monod_forcing.F
ViewVC logotype

Contents of /MITgcm_contrib/darwin2/pkg/monod/monod_forcing.F

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


Revision 1.9 - (show annotations) (download)
Mon Jul 30 15:21:51 2012 UTC (13 years ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt63r_20120817, ctrb_darwin2_ckpt63q_20120731
Changes since 1.8: +17 -1 lines
add timeave diagnostics rmud and c1,c2 for irradiance amplitudes

1 C $Header: /u/gcmpack/MITgcm_contrib/darwin2/pkg/monod/monod_forcing.F,v 1.8 2012/06/30 19:23:04 jahn Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5 #include "PTRACERS_OPTIONS.h"
6 #include "DARWIN_OPTIONS.h"
7
8 #ifdef ALLOW_PTRACERS
9 #ifdef ALLOW_MONOD
10
11 c=============================================================
12 c subroutine MONOD_forcing
13 c step forward bio-chemical tracers in time
14 C==============================================================
15 SUBROUTINE MONOD_FORCING(
16 U Ptr,
17 I bi,bj,imin,imax,jmin,jmax,
18 I myTime,myIter,myThid)
19 #include "SIZE.h"
20 #include "EEPARAMS.h"
21 #include "PARAMS.h"
22 #include "GRID.h"
23 #include "DYNVARS.h"
24 c for Qsw and/or surfaceForcingT
25 c choice which field to take pCO2 from for pCO2limit
26 c this assumes we use Ttendency from offline
27 #include "FFIELDS.h"
28 #ifdef ALLOW_LONGSTEP
29 #include "LONGSTEP.h"
30 #endif
31 #include "PTRACERS_SIZE.h"
32 #include "PTRACERS_PARAMS.h"
33 #include "GCHEM.h"
34 #include "MONOD_SIZE.h"
35 #include "MONOD.h"
36 #include "DARWIN_IO.h"
37 #include "DARWIN_FLUX.h"
38 #include "MONOD_FIELDS.h"
39
40 c ANNA include wavebands_params.h
41 #ifdef WAVEBANDS
42 #include "SPECTRAL_SIZE.h"
43 #include "SPECTRAL.h"
44 #include "WAVEBANDS_PARAMS.h"
45 #endif
46
47
48 C === Global variables ===
49 c tracers
50 _RL Ptr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy,nDarwin)
51 INTEGER bi,bj,imin,imax,jmin,jmax
52 INTEGER myIter
53 _RL myTime
54 INTEGER myThid
55
56 C !FUNCTIONS:
57 C == Functions ==
58 #ifdef ALLOW_PAR_DAY
59 LOGICAL DIFF_PHASE_MULTIPLE
60 EXTERNAL DIFF_PHASE_MULTIPLE
61 #endif
62
63 C============== Local variables ============================================
64 c plankton arrays
65 _RL ZooP(nzmax)
66 _RL ZooN(nzmax)
67 _RL ZooFe(nzmax)
68 _RL ZooSi(nzmax)
69 _RL Phy(npmax)
70 _RL Phy_k(npmax,Nr)
71 _RL Phyup(npmax)
72 _RL part_k(Nr)
73 #ifdef ALLOW_CDOM
74 _RL cdom_k(Nr)
75 #endif
76 c iron partitioning
77 _RL freefe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
78 c some working variables
79 _RL sumpy
80 _RL sumpyup
81 c light variables
82 _RL PAR(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
83 _RL sfac(1-OLy:sNy+OLy)
84 _RL atten,lite
85 _RL newtime ! for sub-timestepping
86 _RL runtim ! time from tracer initialization
87
88
89 c ANNA define variables for wavebands
90 #ifdef WAVEBANDS
91 integer ilam
92 _RL PARw_k(tlam,Nr)
93 _RL PARwup(tlam)
94 _RL acdom_k(Nr,tlam)
95 #ifdef DAR_RADTRANS
96 integer iday,iyr,imon,isec,lp,wd,mydate(4)
97 _RL Edwsf(tlam),Eswsf(tlam)
98 _RL Edz(tlam,Nr),Esz(tlam,Nr),Euz(tlam,Nr),Eutop(tlam,Nr)
99 _RL tirrq(nr)
100 _RL tirrwq(tlam,nr)
101 _RL c1(tlam,nr), c2(tlam,nr)
102 _RL solz
103 _RL rmud
104 _RL actot,bctot,bbctot
105 _RL apart_k(Nr,tlam),bpart_k(Nr,tlam),bbpart_k(Nr,tlam)
106 _RL bt_k(Nr,tlam), bb_k(Nr,tlam)
107 #else
108 _RL PARwdn(tlam)
109 #endif
110 C always need for diagnostics
111 _RL a_k(Nr,tlam)
112 #endif /* WAVEBANDS */
113
114
115 #ifdef DAR_DIAG_DIVER
116 _RL Diver1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
117 _RL Diver2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
118 _RL Diver3(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
119 _RL Diver4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
120 _RL Shannon(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
121 _RL Simpson(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
122
123 _RL tmpphy(npmax)
124 _RL totphy, biotot, maxphy, phymax
125 #endif
126
127 #ifdef GEIDER
128 _RL phychl(npmax)
129 _RL phychl_k(npmax,Nr)
130 #ifdef DYNAMIC_CHL
131 _RL dphychl(npmax)
132 _RL chlup(npmax)
133 #endif
134 #endif
135 #ifdef ALLOW_CDOM
136 _RL cdoml
137 _RL dcdoml
138 #endif
139
140 #ifdef ALLOW_DIAGNOSTICS
141 COJ for diagnostics
142 _RL PParr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
143 _RL Nfixarr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
144 c ANNA_TAVE
145 #ifdef WAVES_DIAG_PCHL
146 _RL Pchlarr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,npmax)
147 #endif
148 c ANNA end TAVE
149 #ifdef DAR_DIAG_RSTAR
150 _RL Rstararr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,npmax)
151 #endif
152 #ifdef ALLOW_DIAZ
153 #ifdef DAR_DIAG_NFIXP
154 _RL NfixParr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,npmax)
155 #endif
156 #endif
157 #endif
158
159
160 _RL totphyC
161 #ifdef ALLOW_PAR_DAY
162 LOGICAL itistime
163 INTEGER PARiprev, PARiaccum, iperiod, nav
164 _RL phase
165 _RL dtsubtime
166 #endif
167 #ifdef DAR_DIAG_CHL
168 _RL ChlGeiderlocal, ChlDoneylocal, ChlCloernlocal
169 #ifdef ALLOW_DIAGNOSTICS
170 _RL GeiderChlarr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
171 _RL GeiderChl2Carr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
172 _RL DoneyChlarr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
173 _RL DoneyChl2Carr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
174 _RL CloernChlarr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
175 _RL CloernChl2Carr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
176 #endif
177 #endif
178 c
179 _RL freefu
180 _RL inputFel
181
182 c some local variables
183 _RL PO4l
184 _RL NO3l
185 _RL FeTl
186 _RL Sil
187 _RL DOPl
188 _RL DONl
189 _RL DOFel
190 _RL POPl
191 _RL PONl
192 _RL POFel
193 _RL PSil
194 _RL POPupl
195 _RL PONupl
196 _RL POFeupl
197 _RL PSiupl
198 _RL Tlocal
199 _RL Slocal
200 _RL pCO2local
201 _RL Qswlocal
202 _RL NH4l
203 _RL NO2l
204 _RL PARl
205 _RL dzlocal
206 _RL dz_k(Nr)
207 _RL dtplankton
208 _RL bottom
209 _RL PP
210 _RL Nfix
211 _RL denit
212 _RL Chl
213 _RL Rstarl(npmax)
214 _RL RNstarl(npmax)
215 #ifdef DAR_DIAG_GROW
216 _RL Growl(npmax)
217 _RL Growsql(npmax)
218 #endif
219 #ifdef ALLOW_DIAZ
220 #ifdef DAR_DIAG_NFIXP
221 _RL NfixPl(npmax)
222 #endif
223 #endif
224
225 c local tendencies
226 _RL dphy(npmax)
227 _RL dzoop(nzmax)
228 _RL dzoon(nzmax)
229 _RL dzoofe(nzmax)
230 _RL dzoosi(nzmax)
231 _RL dPO4l
232 _RL dNO3l
233 _RL dFeTl
234 _RL dSil
235 _RL dDOPl
236 _RL dDONl
237 _RL dDOFel
238 _RL dPOPl
239 _RL dPONl
240 _RL dPOFel
241 _RL dPSil
242 _RL dNH4l
243 _RL dNO2l
244
245 #ifdef ALLOW_CARBON
246 _RL dicl
247 _RL docl
248 _RL pocl
249 _RL picl
250 _RL alkl
251 _RL o2l
252 _RL ZooCl(nzmax)
253 _RL pocupl
254 _RL picupl
255 c tendencies
256 _RL ddicl
257 _RL ddocl
258 _RL dpocl
259 _RL dpicl
260 _RL dalkl
261 _RL do2l
262 _RL dZooCl(nzmax)
263 c air-sea fluxes
264 _RL flxCO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
265 _RL flxALK(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
266 _RL flxO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
267 #endif
268
269 _RL tot_Nfix
270
271 _RL tmp
272
273 _RL phytmp, chltmp
274
275 INTEGER i,j,k,it, ktmp
276 INTEGER np, nz, np2, npsave
277 INTEGER debug
278 CHARACTER*8 diagname
279
280 c
281 c
282 c
283 DO j=1-OLy,sNy+OLy
284 DO i=1-OLx,sNx+OLx
285 do k=1,Nr
286 freefe(i,j,k)=0. _d 0
287 PAR(i,j,k) = 0. _d 0
288 #ifdef DAR_DIAG_DIVER
289 Diver1(i,j,k)=0. _d 0
290 Diver2(i,j,k)=0. _d 0
291 Diver3(i,j,k)=0. _d 0
292 Diver4(i,j,k)=0. _d 0
293 Shannon(i,j,k)=0. _d 0
294 Simpson(i,j,k)=1. _d 0
295 #endif
296
297 #ifdef ALLOW_DIAGNOSTICS
298 COJ for diagnostics
299 PParr(i,j,k) = 0. _d 0
300 Nfixarr(i,j,k) = 0. _d 0
301 #ifdef DAR_DIAG_CHL
302 GeiderChlarr(i,j,k) = 0. _d 0
303 GeiderChl2Carr(i,j,k) = 0. _d 0
304 DoneyChlarr(i,j,k) = 0. _d 0
305 DoneyChl2Carr(i,j,k) = 0. _d 0
306 CloernChlarr(i,j,k) = 0. _d 0
307 CloernChl2Carr(i,j,k) = 0. _d 0
308 #endif
309 c ANNA_TAVE
310 #ifdef WAVES_DIAG_PCHL
311 DO np=1,npmax
312 Pchlarr(i,j,k,np) = 0. _d 0
313 ENDDO
314 #endif
315 c ANNA end TAVE
316 #ifdef DAR_DIAG_RSTAR
317 DO np=1,npmax
318 Rstararr(i,j,k,np) = 0. _d 0
319 ENDDO
320 #endif
321 COJ
322 #ifdef ALLOW_DIAZ
323 #ifdef DAR_DIAG_NFIXP
324 DO np=1,npmax
325 NfixParr(i,j,k,np) = 0. _d 0
326 ENDDO
327 #endif
328 #endif
329 #endif
330 enddo
331 ENDDO
332 ENDDO
333 c
334 c bio-chemical time loop
335 c--------------------------------------------------
336 DO it=1,nsubtime
337 c -------------------------------------------------
338 tot_Nfix=0. _d 0
339 COJ cannot use dfloat because of adjoint
340 COJ division will be double precision anyway because of dTtracerLev
341 newtime=myTime-dTtracerLev(1)+
342 & float(it)*dTtracerLev(1)/float(nsubtime)
343 c print*,'it ',it,newtime,nsubtime,myTime
344 runtim=myTime-float(PTRACERS_Iter0)*dTtracerLev(1)
345
346 c determine iron partitioning - solve for free iron
347 c ---------------------------
348 call darwin_fe_chem(bi,bj,iMin,iMax,jMin,jMax,
349 & Ptr(1-OLx,1-OLy,1,bi,bj,iFeT), freefe,
350 & myIter, mythid)
351 c --------------------------
352 #ifdef ALLOW_CARBON
353 c air-sea flux and dilution of CO2
354 call dic_surfforcing(Ptr(1-OLx,1-OLy,1,bi,bj,iDIC),
355 & Ptr(1-OLx,1-OLy,1,bi,bj,iALK),
356 & Ptr(1-OLx,1-OLy,1,bi,bj,iPO4),
357 & Ptr(1-OLx,1-OLy,1,bi,bj,iSi),
358 & flxCO2,
359 & bi,bj,imin,imax,jmin,jmax,
360 & myIter,myTime,myThid)
361 c air-sea flux of O2
362 call dic_o2_surfforcing(Ptr(1-OLx,1-OLy,1,bi,bj,iO2),
363 & flxO2,
364 & bi,bj,imin,imax,jmin,jmax,
365 & myIter,myTime,myThid)
366 c dilusion of alkalinity
367 call dic_alk_surfforcing(Ptr(1-OLx,1-OLy,1,bi,bj,iALK),
368 & flxALK,
369 & bi,bj,imin,imax,jmin,jmax,
370 & myIter,myTime,myThid)
371 #endif
372
373
374 c find light in each grid cell
375 c ---------------------------
376 c determine incident light
377 #ifndef READ_PAR
378 #ifndef USE_QSW
379 DO j=1-OLy,sNy+OLy
380 sfac(j)=0. _d 0
381 ENDDO
382 call darwin_insol(newTime,sfac,bj)
383 #endif /* not USE_QSW */
384 #endif /* not READ_PAR */
385
386 #ifdef ALLOW_PAR_DAY
387 C find out which slot of PARday has previous day's average
388 dtsubtime = dTtracerLev(1)/float(nsubtime)
389 C running index of averaging period
390 C myTime has already been incremented in this iteration,
391 C go back half a substep to avoid roundoff problems
392 iperiod = FLOOR((newtime-0.5 _d 0*dtsubtime)
393 & /darwin_PARavPeriod)
394 C 0 -> 1, 1->2, 2->0, ...
395 PARiprev = MOD(iperiod, 2) + 1
396
397 #ifdef ALLOW_DIAGNOSTICS
398 C always fill; this will be the same during PARavPeriod, but this
399 C way it won't blow up for weird diagnostics periods.
400 C we fill before updating, so the diag is the one used in this time
401 C step
402 CALL DIAGNOSTICS_FILL(
403 & PARday(1-Olx,1-Oly,1,bi,bj,PARiprev),'PARday ',
404 & 0,Nr,2,bi,bj,myThid )
405 #endif
406 #endif /* ALLOW_PAR_DAY */
407
408 #ifdef DAR_RADTRANS
409 #ifndef DAR_RADTRANS_USE_MODEL_CALENDAR
410 #ifdef ALLOW_CAL
411 C get current date and time of day: iyr/imon/iday+isec
412 CALL CAL_GETDATE( myIter, newtime, mydate, mythid )
413 CALL CAL_CONVDATE( mydate,iyr,imon,iday,isec,lp,wd,mythid )
414 #else
415 STOP 'need cal package or DAR_RADTRANS_USE_MODEL_CALENDAR'
416 #endif
417 #endif
418 #endif
419
420 C.................................................................
421 C.................................................................
422
423
424 C ========================== i,j loops =================================
425 DO j=1,sNy
426 DO i=1,sNx
427
428 c ------------ these are convenient ------------------------------------
429 DO k=1,Nr
430 part_k(k) = max(Ptr(i,j,k,bi,bj,iPOP),0. _d 0)
431 #ifdef ALLOW_CDOM
432 cdom_k(k) = max(Ptr(i,j,k,bi,bj,iCDOM),0. _d 0)
433 #endif
434 DO np = 1,npmax
435 Phy_k(np,k) = max(Ptr(i,j,k,bi,bj,iPhy+np-1),0. _d 0)
436 #ifdef GEIDER
437 #ifdef DYNAMIC_CHL
438 phychl_k(np,k) = max(Ptr(i,j,k,bi,bj,iChl+np-1),0. _d 0)
439 #else
440 phychl_k(np,k) = max(Chl_phy(i,j,k,bi,bj,np), 0. _d 0)
441 #endif
442 #endif
443 ENDDO
444 ENDDO
445
446 c ------------ GET CDOM_k FOR WAVEBANDS_3D and RADTRANS ----------------
447 #ifdef WAVEBANDS
448 #if defined(DAR_CALC_ACDOM) || defined(DAR_RADTRANS)
449 #ifdef ALLOW_CDOM
450 call MONOD_ACDOM(cdom_k,
451 O acdom_k,
452 I myThid)
453 #else
454 call MONOD_ACDOM(phychl_k,aphy_chl,aw,
455 O acdom_k,
456 I myThid)
457 #endif
458 #else
459 DO k=1,Nr
460 DO ilam = 1,tlam
461 acdom_k(k,ilam) = acdom(ilam)
462 ENDDO
463 ENDDO
464 #endif /* DAR_CALC_ACDOM or DAR_RADTRANS */
465 #endif /* WAVEBANDS */
466
467 c ------------ GET INCIDENT NON-SPECTRAL LIGHT -------------------------
468 #if !(defined(WAVEBANDS) && defined(OASIM))
469 #ifdef READ_PAR
470
471 lite = sur_par(i,j,bi,bj)
472
473 #else /* not READ_PAR */
474 #ifdef USE_QSW
475
476 #ifdef ALLOW_LONGSTEP
477 Qswlocal=LS_Qsw(i,j,bi,bj)
478 #else
479 Qswlocal=Qsw(i,j,bi,bj)
480 #endif
481 lite = -parfrac*Qswlocal*parconv*maskC(i,j,1,bi,bj)
482
483 #else /* not USE_QSW */
484
485 lite = sfac(j)*maskC(i,j,1,bi,bj)/86400*1 _d 6
486
487 #endif /* not USE_QSW */
488 #endif /* not READ_PAR */
489
490 c take ice coverage into account
491 c unless already done in seaice package
492 #if !(defined (ALLOW_SEAICE) && defined (USE_QSW))
493 lite = lite*(1. _d 0-fice(i,j,bi,bj))
494 #endif
495 #endif /* not(WAVEBANDS and OASIM) */
496
497 c ------------ LIGHT ATTENUATION: --------------------------------------
498 #ifndef WAVEBANDS
499 c ------------ SINGLE-BAND ATTENUATION ---------------------------------
500 atten=0. _d 0
501 do k=1,Nr
502 if (HFacC(i,j,k,bi,bj).gt.0. _d 0) then
503 sumpyup = sumpy
504 sumpy = 0. _d 0
505 do np=1,npmax
506 #ifdef GEIDER
507 sumpy = sumpy + phychl_k(np,k)
508 #else
509 sumpy = sumpy + Phy_k(np,k)
510 #endif
511 enddo
512 atten= atten + (k0 + kc*sumpy)*5. _d -1*drF(k)
513 if (k.gt.1)then
514 atten = atten + (k0+kc*sumpyup)*5. _d -1*drF(k-1)
515 endif
516 PAR(i,j,k) = lite*exp(-atten)
517 endif
518 enddo
519
520 #else /* WAVEBANDS */
521 #ifndef DAR_RADTRANS
522 c ------------ WAVEBANDS W/O RADTRANS ----------------------------------
523 do ilam = 1,tlam
524 #ifdef OASIM
525 c add direct and diffuse, convert to uEin/m2/s/nm
526 PARwup(ilam) = WtouEins(ilam)*(oasim_ed(i,j,ilam,bi,bj)+
527 & oasim_es(i,j,ilam,bi,bj))
528 c and take ice fraction into account
529 c PARwup(ilam) = PARwup(ilam)*(1 _d 0 - fice(i,j,bi,bj))
530 #else
531 c sf is per nm; convert to per waveband
532 PARwup(ilam) = wb_width(ilam)*sf(ilam)*lite
533 #endif
534 enddo
535
536 do k=1,Nr
537 if (HFacC(i,j,k,bi,bj).gt.0. _d 0) then
538 do ilam = 1,tlam
539 sumpy = 0.
540 do np = 1,npmax
541 c get total attenuation (absorption) by phyto at each wavelength
542 sumpy = sumpy + (phychl_k(np,k)*aphy_chl(np,ilam))
543 enddo
544 c for diagnostic
545 a_k(k,ilam) = aw(ilam) + sumpy + acdom_k(k,ilam)
546 atten = a_k(k,ilam)*drF(k)
547 PARwdn(ilam) = PARwup(ilam)*exp(-atten)
548 enddo
549
550 c find for the midpoint of the gridcell (gridcell mean)
551 do ilam = 1,tlam
552 C PARw_k(ilam,k)=exp((log(PARwup(ilam))+log(PARwdn(ilam)))*0.5)
553 PARw_k(ilam,k)=sqrt(PARwup(ilam)*PARwdn(ilam))
554 enddo
555
556 c cycle
557 do ilam=1,tlam
558 PARwup(ilam) = PARwdn(ilam)
559 enddo
560 else
561 do ilam=1,tlam
562 PARw_k(ilam,k) = 0. _d 0
563 enddo
564 endif
565
566 c sum wavebands for total PAR at the mid point of the gridcell (PARl)
567 PAR(i,j,k) = 0.
568 do ilam = 1,tlam
569 PAR(i,j,k) = PAR(i,j,k) + PARw_k(ilam,k)
570 enddo
571 enddo
572
573 #else /* DAR_RADTRANS */
574 c ------------ FULL RADIATIVE TRANSFER CODE ----------------------------
575 do ilam = 1,tlam
576 Edwsf(ilam) = oasim_ed(i,j,ilam,bi,bj)
577 Eswsf(ilam) = oasim_es(i,j,ilam,bi,bj)
578 enddo
579
580 #ifdef DAR_RADTRANS_USE_MODEL_CALENDAR
581 C simplified solar zenith angle for 360-day year and daily averaged light
582 C cos(solz) is average over daylight period
583 call darwin_solz360(newtime, YC(i,j,bi,bj),
584 O solz)
585
586 #else /* not DAR_RADTRANS_USE_MODEL_CALENDAR */
587 C use calendar date for full solar zenith angle computation
588 C oj: average light effective at noon?
589 solz = 0.0 _d 0
590 isec = 12*3600
591 call radtrans_sfcsolz(rad,iyr,imon,iday,isec,
592 I XC(i,j,bi,bj),YC(i,j,bi,bj),
593 O solz)
594 #endif /* not DAR_RADTRANS_USE_MODEL_CALENDAR */
595
596 c have Ed,Es below surface - no need for this adjustment on Ed Es for surface affects
597 c do ilam=1,tlam
598 c rod(ilam) = 0.0 _d 0
599 c ros(ilam) = 0.0 _d 0
600 c enddo
601
602 c compute 1/cos(zenith) for direct light below surface
603 call radtrans_sfcrmud(rad,solz,
604 O rmud)
605
606 C compute absorption/scattering coefficients for radtrans
607 DO k=1,Nr
608 dz_k(k) = drF(k)*HFacC(i,j,k,bi,bj)
609 DO ilam = 1,tlam
610 c absorption by phyto
611 actot = 0.0
612 bctot = 0.0
613 bbctot = 0.0
614 DO np = 1,npmax
615 actot = actot + phychl_k(np,k)*aphy_chl(np,ilam)
616 bctot = bctot + phychl_k(np,k)*bphy_chl(np,ilam)
617 bbctot = bbctot + phychl_k(np,k)*bbphy_chl(np,ilam)
618 ENDDO
619 c particulate
620 apart_k(k,ilam) = part_k(k)*apart_P(ilam)
621 bpart_k(k,ilam) = part_k(k)*bpart_P(ilam)
622 bbpart_k(k,ilam) = part_k(k)*bbpart_P(ilam)
623 c add water and CDOM
624 a_k(k,ilam) = aw(ilam)+acdom_k(k,ilam)+actot+apart_k(k,ilam)
625 bt_k(k,ilam) = bw(ilam) + bctot + bpart_k(k,ilam)
626 bb_k(k,ilam) = darwin_bbw*bw(ilam)+bbctot+bbpart_k(k,ilam)
627 bb_k(k,ilam) = MAX(darwin_bbmin, bb_k(k,ilam))
628 ENDDO
629 ENDDO
630
631 #ifdef DAR_RADTRANS_ITERATIVE
632 call MONOD_RADTRANS_ITER(
633 I dz_k,rmud,Edwsf,Eswsf,a_k,bt_k,bb_k,
634 I darwin_radtrans_kmax,darwin_radtrans_niter,
635 O Edz,Esz,Euz,Eutop,
636 O tirrq,tirrwq,
637 O c1,c2,
638 I myThid)
639 #else
640 c dzlocal ?????
641 call MONOD_RADTRANS(
642 I drF,rmud,Edwsf,Eswsf,a_k,bt_k,bb_k,
643 O Edz,Esz,Euz,Eutop,
644 O tirrq,tirrwq,
645 I myThid)
646 #endif
647 c
648 c uses chl from prev timestep (as wavebands does)
649 c keep like this in case need to consider upwelling irradiance as affecting the grid box above
650 c will pass to plankton: PARw only, but will be for this timestep for RT and prev timestep for WAVBANDS
651 c
652 c now copy
653 DO k=1,Nr
654 PAR(i,j,k) = tirrq(k)
655 DO ilam = 1,tlam
656 PARw_k(ilam,k) = tirrwq(ilam,k)
657 ENDDO
658 ENDDO
659 #endif /* DAR_RADTRANS */
660
661 c oj: ???
662 c so PARw and PARwup from WAVEBANDS_1D are from previous timestep (attenuation done in plankton)
663 c but PARw and PARwup from WAVEBANDS_3D and RADTRANS are for the current timestep
664
665 #endif /* WAVEBANDS */
666
667 C ============================ k loop ==================================
668 c for each layer ...
669 do k= 1, NR
670 if (HFacC(i,j,k,bi,bj).gt.0. _d 0) then
671
672 c make sure we only deal with positive definite numbers
673 c brute force...
674 po4l = max(Ptr(i,j,k,bi,bj,iPO4 ),0. _d 0)
675 no3l = max(Ptr(i,j,k,bi,bj,iNO3 ),0. _d 0)
676 fetl = max(Ptr(i,j,k,bi,bj,iFeT ),0. _d 0)
677 sil = max(Ptr(i,j,k,bi,bj,iSi ),0. _d 0)
678 dopl = max(Ptr(i,j,k,bi,bj,iDOP ),0. _d 0)
679 donl = max(Ptr(i,j,k,bi,bj,iDON ),0. _d 0)
680 dofel = max(Ptr(i,j,k,bi,bj,iDOFe ),0. _d 0)
681 DO nz = 1,nzmax
682 ZooP(nz) = max(Ptr(i,j,k,bi,bj,iZooP (nz)),0. _d 0)
683 ZooN(nz) = max(Ptr(i,j,k,bi,bj,iZooN (nz)),0. _d 0)
684 ZooFe(nz) = max(Ptr(i,j,k,bi,bj,iZooFe(nz)),0. _d 0)
685 ZooSi(nz) = max(Ptr(i,j,k,bi,bj,iZooSi(nz)),0. _d 0)
686 ENDDO
687 popl = max(Ptr(i,j,k,bi,bj,iPOP ),0. _d 0)
688 ponl = max(Ptr(i,j,k,bi,bj,iPON ),0. _d 0)
689 pofel = max(Ptr(i,j,k,bi,bj,iPOFe ),0. _d 0)
690 psil = max(Ptr(i,j,k,bi,bj,iPOSi ),0. _d 0)
691 NH4l = max(Ptr(i,j,k,bi,bj,iNH4 ),0. _d 0)
692 NO2l = max(Ptr(i,j,k,bi,bj,iNO2 ),0. _d 0)
693 #ifdef ALLOW_CDOM
694 cdoml = max(Ptr(i,j,k,bi,bj,iCDOM ),0. _d 0)
695 #endif
696 #ifdef ALLOW_CARBON
697 dicl = max(Ptr(i,j,k,bi,bj,iDIC ),0. _d 0)
698 docl = max(Ptr(i,j,k,bi,bj,iDOC ),0. _d 0)
699 pocl = max(Ptr(i,j,k,bi,bj,iPOC ),0. _d 0)
700 picl = max(Ptr(i,j,k,bi,bj,iPIC ),0. _d 0)
701 alkl = max(Ptr(i,j,k,bi,bj,iALK ),0. _d 0)
702 o2l = max(Ptr(i,j,k,bi,bj,iO2 ),0. _d 0)
703 DO nz = 1,nzmax
704 ZooCl(nz) = max(Ptr(i,j,k,bi,bj,iZooC (nz)),0. _d 0)
705 ENDDO
706 #endif
707
708 totphyC = 0. _d 0
709 DO np=1,npmax
710 totphyC = totphyC + R_PC(np)*Ptr(i,j,k,bi,bj,iPhy+np-1)
711 ENDDO
712
713 DO np = 1,npmax
714 Phy(np) = Phy_k(np,k)
715 #ifdef GEIDER
716 phychl(np) = phychl_k(np,k)
717 #endif
718 ENDDO
719
720 #ifdef DAR_DIAG_DIVER
721 Diver1(i,j,k)=0. _d 0
722 Diver2(i,j,k)=0. _d 0
723 Diver3(i,j,k)=0. _d 0
724 Diver4(i,j,k)=0. _d 0
725 totphy=0. _d 0
726 do np=1,npmax
727 totphy=totphy + Phy(np)
728 tmpphy(np)=Phy(np)
729 enddo
730 if (totphy.gt.diver_thresh0) then
731 do np=1,npmax
732 c simple threshhold
733 if (Phy(np).gt.diver_thresh1) then
734 Diver1(i,j,k)=Diver1(i,j,k)+1. _d 0
735 endif
736 c proportion of total biomass
737 if (Phy(np)/totphy.gt.diver_thresh2) then
738 Diver2(i,j,k)=Diver2(i,j,k)+1. _d 0
739 endif
740 enddo
741 c majority of biomass by finding rank order
742 biotot=0. _d 0
743 do np2=1,npmax
744 phymax=0. _d 0
745 do np=1,npmax
746 if (tmpphy(np).gt.phymax) then
747 phymax=tmpphy(np)
748 npsave=np
749 endif
750 enddo
751 if (biotot.lt.totphy*diver_thresh3) then
752 Diver3(i,j,k)=Diver3(i,j,k)+1. _d 0
753 endif
754 biotot=biotot+tmpphy(npsave)
755 tmpphy(npsave)=0. _d 0
756 if (np2.eq.1) then
757 maxphy=phymax
758 endif
759 enddo
760 c ratio of maximum species
761 do np=1,npmax
762 if (Phy(np).gt.diver_thresh4*maxphy) then
763 Diver4(i,j,k)=Diver4(i,j,k)+1. _d 0
764 endif
765 enddo
766 c totphy > thresh0
767 endif
768 c Shannon and Simpson indices
769 Shannon(i,j,k) = 0. _d 0
770 c note: minimal valid value is 1, but we set to zero below threshold
771 Simpson(i,j,k) = 0. _d 0
772 if (totphy.gt.shannon_thresh) then
773 do np=1,npmax
774 if (Phy(np) .gt. 0. _d 0) then
775 tmpphy(np) = Phy(np)/totphy
776 Shannon(i,j,k)=Shannon(i,j,k)+tmpphy(np)*LOG(tmpphy(np))
777 Simpson(i,j,k)=Simpson(i,j,k)+tmpphy(np)*tmpphy(np)
778 endif
779 enddo
780 Shannon(i,j,k) = -Shannon(i,j,k)
781 Simpson(i,j,k) = 1./Simpson(i,j,k)
782 endif
783 #endif
784
785 c..........................................................
786 c find local light
787 c..........................................................
788
789 PARl = PAR(i,j,k)
790 c..........................................................
791
792 c for explicit sinking of particulate matter and phytoplankton
793 if (k.eq.1) then
794 popupl =0. _d 0
795 ponupl =0. _d 0
796 pofeupl = 0. _d 0
797 psiupl = 0. _d 0
798 do np=1,npmax
799 Phyup(np)=0. _d 0
800 #ifdef DYNAMIC_CHL
801 chlup(np)=0. _d 0
802 #endif
803 enddo
804 #ifdef ALLOW_CARBON
805 pocupl = 0. _d 0
806 picupl = 0. _d 0
807 #endif
808 endif
809
810 #ifdef ALLOW_LONGSTEP
811 Tlocal = LS_theta(i,j,k,bi,bj)
812 Slocal = LS_salt(i,j,k,bi,bj)
813 #else
814 Tlocal = theta(i,j,k,bi,bj)
815 Slocal = salt(i,j,k,bi,bj)
816 #endif
817
818 c choice where to get pCO2 from
819 c taking from igsm dic run - fed through Tflux array
820 c pCO2local=surfaceForcingT(i,j,bi,bj)
821 c or from darwin carbon module
822 #ifdef ALLOW_CARBON
823 pCO2local=pCO2(i,j,bi,bj)
824 #else
825 pCO2local=280. _d -6
826 #endif
827
828 freefu = max(freefe(i,j,k),0. _d 0)
829 if (k.eq.1) then
830 inputFel = inputFe(i,j,bi,bj)
831 else
832 inputFel = 0. _d 0
833 endif
834
835 dzlocal = drF(k)*HFacC(i,j,k,bi,bj)
836 c set bottom=1.0 if the layer below is not ocean
837 ktmp=min(nR,k+1)
838 if(hFacC(i,j,ktmp,bi,bj).eq.0. _d 0.or.k.eq.Nr) then
839 bottom = 1.0 _d 0
840 else
841 bottom = 0.0 _d 0
842 endif
843
844 c set tendencies to 0
845 do np=1,npmax
846 dphy(np)=0. _d 0
847 enddo
848 do nz=1,nzmax
849 dzoop(nz)=0. _d 0
850 dzoon(nz)=0. _d 0
851 dzoofe(nz)=0. _d 0
852 dzoosi(nz)=0. _d 0
853 enddo
854 dPO4l=0. _d 0
855 dNO3l=0. _d 0
856 dFeTl=0. _d 0
857 dSil=0. _d 0
858 dDOPl=0. _d 0
859 dDONl=0. _d 0
860 dDOFel=0. _d 0
861 dPOPl=0. _d 0
862 dPONl=0. _d 0
863 dPOFel=0. _d 0
864 dPSil=0. _d 0
865 dNH4l=0. _d 0
866 dNO2l=0. _d 0
867 #ifdef DYNAMIC_CHL
868 do np=1,npmax
869 dphychl(np)=0. _d 0
870 enddo
871 #endif
872 #ifdef ALLOW_CDOM
873 dcdoml=0. _d 0
874 #endif
875 #ifdef ALLOW_CARBON
876 ddicl=0. _d 0
877 ddocl=0. _d 0
878 dpocl=0. _d 0
879 dpicl=0. _d 0
880 dalkl=0. _d 0
881 do2l=0. _d 0
882 do nz=1,nzmax
883 dzoocl(nz)=0. _d 0
884 enddo
885 #endif
886 c set other arguments to zero
887 PP=0. _d 0
888 Nfix=0. _d 0
889 denit=0. _d 0
890 do np=1,npmax
891 Rstarl(np)=0. _d 0
892 RNstarl(np)=0. _d 0
893 #ifdef DAR_DIAG_GROW
894 Growl(np)=0. _d 0
895 Growsql(np)=0. _d 0
896 #endif
897 #ifdef ALLOW_DIAZ
898 #ifdef DAR_DIAG_NFIXP
899 NfixPl(np)=0. _d 0
900 #endif
901 #endif
902 enddo
903
904
905 debug=0
906 c if (i.eq.20.and.j.eq.20.and.k.eq.1) debug=8
907 c if (i.eq.10.and.j.eq.10.and.k.eq.1) debug=100
908 c if (i.eq.1.and.j.eq.10.and.k.eq.1) debug=10
909 c if (i.eq.1.and.j.eq.1.and.k.eq.10) debug=14
910
911 if (debug.eq.7) print*,'PO4, DOP, POP, ZooP',
912 & PO4l, DOPl, POPl, zooP
913 if (debug.eq.7) print*,'NO3, NO2, NH4, DON, PON, ZooN',
914 & NO3l,NO2l,NH4l, DONl, PONl, ZooN
915 if (debug.eq.7) print*,'FeT, DOFe, POFe, Zoofe',
916 & FeTl, DOFel, POFel, zooFe
917 if (debug.eq.7) print*,'Si, Psi, zooSi',
918 & Sil, PSil, zooSi
919 if (debug.eq.7) print*,'Total Phy', sumpy, PARl, lite
920 if (debug.eq.7) print*,'Phy', Phy
921
922 if (debug.eq.8) print*,'k, PARl, inputFel, dzlocal',
923 & PARl, inputFel, dzlocal
924
925 c if (NO3l.eq.0. _d 0.or.NO2l.eq.0. _d 0
926 c & .or.NH4l.eq.0. _d 0) then
927 c print*,'QQ N zeros',i,j,k,NO3l,NO2l,NH4l
928 c endif
929
930
931 c ANNA pass extra variables if WAVEBANDS
932 CALL MONOD_PLANKTON(
933 U Phy,
934 I zooP, zooN, zooFe, zooSi,
935 O PP, Chl, Nfix, denit,
936 I PO4l, NO3l, FeTl, Sil,
937 I NO2l, NH4l,
938 I DOPl, DONl, DOFel,
939 I POPl, PONl, POFel, PSil,
940 I phyup, popupl, ponupl,
941 I pofeupl, psiupl,
942 I PARl,
943 I Tlocal, Slocal,
944 I pCO2local,
945 I freefu, inputFel,
946 I bottom, dzlocal,
947 O Rstarl, RNstarl,
948 #ifdef DAR_DIAG_GROW
949 O Growl, Growsql,
950 #endif
951 #ifdef ALLOW_DIAZ
952 #ifdef DAR_DIAG_NFIXP
953 O NfixPl,
954 #endif
955 #endif
956 O dphy, dzooP, dzooN, dzooFe,
957 O dzooSi,
958 O dPO4l, dNO3l, dFeTl, dSil,
959 O dNH4l, dNO2l,
960 O dDOPl, dDONl, dDOFel,
961 O dPOPl, dPONl, dPOFel, dPSil,
962 #ifdef ALLOW_CARBON
963 I dicl, docl, pocl, picl,
964 I alkl, o2l, zoocl,
965 I pocupl, picupl,
966 O ddicl, ddocl, dpocl, dpicl,
967 O dalkl, do2l, dzoocl,
968 #endif
969 #ifdef GEIDER
970 O phychl,
971 #ifdef DYNAMIC_CHL
972 I dphychl,
973 I chlup,
974 #endif
975 #ifdef ALLOW_CDOM
976 O dcdoml,
977 I cdoml,
978 #endif
979 #ifdef WAVEBANDS
980 I PARw_k(1,k),
981 #endif
982 #endif
983 #ifdef ALLOW_PAR_DAY
984 I PARday(i,j,k,bi,bj,PARiprev),
985 #endif
986 #ifdef DAR_DIAG_CHL
987 O ChlGeiderlocal, ChlDoneylocal,
988 O ChlCloernlocal,
989 #endif
990 I debug,
991 I runtim,
992 I MyThid)
993
994 c
995 c if (i.eq.1.and.k.eq.1.and.j.eq.5) then
996 c print*,i,j,k
997 c print*,'NO3,No2,NH4', NO3l, NO2l, NH4l
998 c print*,'dNO3 etc',dNO3l,dNH4l, dNO2l
999 c print*,'PO4',PO4l,dPO4l
1000 c endif
1001 c
1002 #ifdef IRON_SED_SOURCE
1003 c only above minimum depth (continental shelf)
1004 if (rF(k).gt.-depthfesed) then
1005 c only if bottom layer
1006 if (bottom.eq.1.0 _d 0) then
1007 #ifdef IRON_SED_SOURCE_VARIABLE
1008 c calculate sink of POP into bottom layer
1009 tmp=(wp_sink*POPupl)/(dzlocal)
1010 c convert to dPOCl
1011 dFetl=dFetl+fesedflux_pcm*(tmp*106. _d 0)
1012 #else
1013 dFetl=dFetl+fesedflux/
1014 & (drF(k)*hFacC(i,j,k,bi,bj))
1015 #endif
1016 endif
1017 endif
1018 #endif
1019
1020
1021 popupl = POPl
1022 ponupl = PONl
1023 pofeupl = POFel
1024 psiupl = PSil
1025 do np=1,npmax
1026 Phyup(np) = Phy(np)
1027 #ifdef DYNAMIC_CHL
1028 chlup(np) = phychl(np)
1029 #endif
1030 enddo
1031
1032
1033 c
1034 #ifdef ALLOW_CARBON
1035 pocupl = POCl
1036 picupl = PICl
1037 c include surface forcing
1038 if (k.eq.1) then
1039 ddicl = ddicl + flxCO2(i,j)
1040 dalkl = dalkl + flxALK(i,j)
1041 do2l = do2l + flxO2(i,j)
1042 endif
1043 #endif
1044 c
1045 #ifdef CONS_SUPP
1046 c only works for two layer model
1047 if (k.eq.2) then
1048 dpo4l=0. _d 0
1049 dno3l=0. _d 0
1050 dfetl=0. _d 0
1051 dsil=0. _d 0
1052 endif
1053 #endif
1054 #ifdef RELAX_NUTS
1055 #ifdef DENIT_RELAX
1056 if (rF(k).lt.-depthdenit) then
1057 if (darwin_relaxscale.gt.0. _d 0) then
1058 IF ( darwin_NO3_RelaxFile .NE. ' ' ) THEN
1059 c Fanny's formulation
1060 tmp=(Ptr(i,j,k,bi,bj,iNO3 )-no3_obs(i,j,k,bi,bj))
1061 if (tmp.gt.0. _d 0) then
1062 dno3l=dno3l-(tmp/
1063 & darwin_relaxscale)
1064 denit=tmp/
1065 & darwin_relaxscale
1066 else
1067 denit=0. _d 0
1068 endif
1069 c --- end fanny's formulation
1070 ENDIF
1071 c steph's alternative
1072 c tmp=(Ptr(i,j,k,bi,bj,iNO3 )-
1073 c & 16. _d 0 * Ptr(i,j,k,bi,bj,iPO4 ))
1074 c if (tmp.gt.0. _d 0) then
1075 c dno3l=dno3l-(tmp/
1076 c & darwin_relaxscale)
1077 c denit=tmp/
1078 c & darwin_relaxscale
1079 c else
1080 c denit=0. _d 0
1081 c endif
1082 c ---- end steph's alternative
1083 endif
1084 endif
1085 #else
1086 if (darwin_relaxscale.gt.0. _d 0) then
1087 IF ( darwin_PO4_RelaxFile .NE. ' ' ) THEN
1088 tmp=(Ptr(i,j,k,bi,bj,iPO4 )-po4_obs(i,j,k,bi,bj))
1089 if (tmp.lt.0. _d 0) then
1090 dpo4l=dpo4l-(tmp/
1091 & darwin_relaxscale)
1092 endif
1093 ENDIF
1094 IF ( darwin_NO3_RelaxFile .NE. ' ' ) THEN
1095 tmp=(Ptr(i,j,k,bi,bj,iNO3 )-no3_obs(i,j,k,bi,bj))
1096 if (tmp.lt.0. _d 0) then
1097 dno3l=dno3l-(tmp/
1098 & darwin_relaxscale)
1099 endif
1100 ENDIF
1101 IF ( darwin_Fet_RelaxFile .NE. ' ' ) THEN
1102 tmp=(Ptr(i,j,k,bi,bj,iFeT )-fet_obs(i,j,k,bi,bj))
1103 if (tmp.lt.0. _d 0) then
1104 dfetl=dfetl-(tmp/
1105 & darwin_relaxscale)
1106 endif
1107 ENDIF
1108 IF ( darwin_Si_RelaxFile .NE. ' ' ) THEN
1109 tmp=( Ptr(i,j,k,bi,bj,iSi )-si_obs(i,j,k,bi,bj))
1110 if (tmp.lt.0. _d 0) then
1111 dsil=dsil-(tmp/
1112 & darwin_relaxscale)
1113 endif
1114 ENDIF
1115 endif
1116 #endif
1117 #endif
1118 #ifdef FLUX_NUTS
1119 dpo4l=dpo4l+po4_flx(i,j,k,bi,bj)
1120 dno3l=dno3l+no3_flx(i,j,k,bi,bj)
1121 dfetl=dfetl+fet_flx(i,j,k,bi,bj)
1122 dsil=dsil+si_flx(i,j,k,bi,bj)
1123 #endif
1124 c
1125 c now update main tracer arrays
1126 dtplankton = PTRACERS_dTLev(k)/float(nsubtime)
1127 Ptr(i,j,k,bi,bj,iPO4 ) = Ptr(i,j,k,bi,bj,iPO4) +
1128 & dtplankton*dpo4l
1129 Ptr(i,j,k,bi,bj,iNO3 ) = Ptr(i,j,k,bi,bj,iNO3) +
1130 & dtplankton*dno3l
1131 Ptr(i,j,k,bi,bj,iFeT ) = Ptr(i,j,k,bi,bj,iFeT) +
1132 & dtplankton*dfetl
1133 Ptr(i,j,k,bi,bj,iSi ) = Ptr(i,j,k,bi,bj,iSi ) +
1134 & dtplankton*dsil
1135 Ptr(i,j,k,bi,bj,iDOP ) = Ptr(i,j,k,bi,bj,iDOP) +
1136 & dtplankton*ddopl
1137 Ptr(i,j,k,bi,bj,iDON ) = Ptr(i,j,k,bi,bj,iDON) +
1138 & dtplankton*ddonl
1139 Ptr(i,j,k,bi,bj,iDOFe) = Ptr(i,j,k,bi,bj,iDOFe) +
1140 & dtplankton*ddofel
1141 Ptr(i,j,k,bi,bj,iPOP ) = Ptr(i,j,k,bi,bj,iPOP ) +
1142 & dtplankton*dpopl
1143 Ptr(i,j,k,bi,bj,iPON ) = Ptr(i,j,k,bi,bj,iPON ) +
1144 & dtplankton*dponl
1145 Ptr(i,j,k,bi,bj,iPOFe) = Ptr(i,j,k,bi,bj,iPOFe) +
1146 & dtplankton*dpofel
1147 Ptr(i,j,k,bi,bj,iPOSi) = Ptr(i,j,k,bi,bj,iPOSi) +
1148 & dtplankton*dpsil
1149 Ptr(i,j,k,bi,bj,iNH4 ) = Ptr(i,j,k,bi,bj,iNH4 ) +
1150 & dtplankton*dnh4l
1151 Ptr(i,j,k,bi,bj,iNO2 ) = Ptr(i,j,k,bi,bj,iNO2 ) +
1152 & dtplankton*dno2l
1153 DO nz = 1,nzmax
1154 Ptr(i,j,k,bi,bj,iZooP (nz)) = Ptr(i,j,k,bi,bj,iZooP (nz)) +
1155 & dtplankton*dzoop (nz)
1156 Ptr(i,j,k,bi,bj,iZooN (nz)) = Ptr(i,j,k,bi,bj,iZooN (nz)) +
1157 & dtplankton*dzoon (nz)
1158 Ptr(i,j,k,bi,bj,iZooFe(nz)) = Ptr(i,j,k,bi,bj,iZooFe(nz)) +
1159 & dtplankton*dzoofe(nz)
1160 Ptr(i,j,k,bi,bj,iZooSi(nz)) = Ptr(i,j,k,bi,bj,iZooSi(nz)) +
1161 & dtplankton*dzoosi(nz)
1162 ENDDO
1163 DO np = 1,npmax
1164 Ptr(i,j,k,bi,bj,iPhy+np-1) = Ptr(i,j,k,bi,bj,iPhy+np-1) +
1165 & dtplankton*dPhy(np)
1166 #ifdef GEIDER
1167 #ifdef DYNAMIC_CHL
1168 if (np.eq.1) Chl=0. _d 0
1169 Ptr(i,j,k,bi,bj,iChl+np-1) = Ptr(i,j,k,bi,bj,iChl+np-1) +
1170 & dtplankton*dphychl(np)
1171 c chltmp=Ptr(i,j,k,bi,bj,iChl+np-1)
1172 c phytmp=Ptr(i,j,k,bi,bj,iPhy+np-1)
1173 c Ptr(i,j,k,bi,bj,iChl+np-1)=
1174 c & max(chltmp,phytmp*R_PC(np)*chl2cmin(np))
1175 c if (np.eq.1.and.i.eq.1.and.j.eq.1.and.k.eq.1)
1176 c & print*,chltmp,phytmp,phytmp*R_PC(np)*chl2cmin(np),
1177 c & phytmp*R_PC(np)*chl2cmax(np)
1178 c in darwin_plankton this is stored for previous timestep. Reset here.
1179 Chl=Chl+Ptr(i,j,k,bi,bj,iChl+np-1)
1180 #else
1181 Chl_phy(i,j,k,bi,bj,np)=phychl(np)
1182 #endif
1183 #endif
1184 ENDDO
1185 #ifdef ALLOW_CDOM
1186 Ptr(i,j,k,bi,bj,iCDOM ) = Ptr(i,j,k,bi,bj,iCDOM ) +
1187 & dtplankton*dcdoml
1188 #endif
1189 #ifdef ALLOW_CARBON
1190 Ptr(i,j,k,bi,bj,iDIC ) = Ptr(i,j,k,bi,bj,iDIC ) +
1191 & dtplankton*ddicl
1192 Ptr(i,j,k,bi,bj,iDOC ) = Ptr(i,j,k,bi,bj,iDOC ) +
1193 & dtplankton*ddocl
1194 Ptr(i,j,k,bi,bj,iPOC ) = Ptr(i,j,k,bi,bj,iPOC ) +
1195 & dtplankton*dpocl
1196 Ptr(i,j,k,bi,bj,iPIC ) = Ptr(i,j,k,bi,bj,iPIC ) +
1197 & dtplankton*dpicl
1198 Ptr(i,j,k,bi,bj,iALK ) = Ptr(i,j,k,bi,bj,iALK ) +
1199 & dtplankton*dalkl
1200 Ptr(i,j,k,bi,bj,iO2 ) = Ptr(i,j,k,bi,bj,iO2 ) +
1201 & dtplankton*do2l
1202 DO nz = 1,nzmax
1203 Ptr(i,j,k,bi,bj,iZooC (nz)) = Ptr(i,j,k,bi,bj,iZooC (nz)) +
1204 & dtplankton*dzoocl (nz)
1205 ENDDO
1206 #endif
1207 c
1208 #ifdef ALLOW_MUTANTS
1209 cQQQQTEST
1210 if (debug.eq.11) then
1211 if (k.lt.8) then
1212 do np=1,60
1213 if(mod(np,4).eq. 1. _d 0)then
1214 np2=np+1
1215 np4=np+3
1216
1217 Coj: couldn't test this part after change Phynp -> Ptr(...,iPhy+np-1)
1218 Coj: used to be many copies of this:
1219 C if (dPhy(2).gt.dPhy(4).and.dPhy(4).gt.0. _d 0) then
1220 C print*,'QQQ dphy2 > dphy4',i,j,k,Phy2(i,j,k),
1221 C & Phy4(i,j,k), dPhy(2), dPhy(4)
1222 C endif
1223 C if (Phy2(i,j,k).gt.Phy4(i,j,k).and.
1224 C & Phy4(i,j,k).gt.0. _d 0) then
1225 C print*,'QQ phy02 > phy04',i,j,k,Phy2(i,j,k),
1226 C & Phy4(i,j,k), dPhy(2), dPhy(4)
1227 C endif
1228
1229 if (dPhy(np2).gt.dPhy(np4).and.dPhy(np4).gt.0. _d 0) then
1230 print*,'QQQ dphy',np2,' > dphy',np4,i,j,k,Phy2(i,j,k),
1231 & Ptr(i,j,k,bi,bj,iPhy+np4-1), dPhy(2), dPhy(4)
1232 endif
1233 if (Ptr(i,j,k,bi,bj,iphy+np2-1).gt.Ptr(i,j,k,bi,bj,iPhy+np4-1)
1234 & .and. Ptr(i,j,k,bi,bj,iPhy+np4-1).gt.0. _d 0) then
1235 print*,'QQ phy',np2,' > ',np4,i,j,k,
1236 & Ptr(i,j,k,bi,bj,iPhy+np2-1),
1237 & Ptr(i,j,k,bi,bj,iPhy+np4-1), dPhy(2), dPhy(4)
1238 endif
1239
1240 endif
1241 enddo ! np
1242 endif ! k
1243 endif
1244 #endif
1245
1246 #ifdef ALLOW_DIAGNOSTICS
1247 COJ for diagnostics
1248 PParr(i,j,k) = PP
1249 Nfixarr(i,j,k) = Nfix
1250 c ANNA_TAVE
1251 #ifdef WAVES_DIAG_PCHL
1252 DO np = 1,npmax
1253 Pchlarr(i,j,k,np) = phychl(np)
1254 ENDDO
1255 #endif
1256 c ANNA end TAVE
1257 #ifdef DAR_DIAG_RSTAR
1258 DO np = 1,npmax
1259 Rstararr(i,j,k,np) = Rstarl(np)
1260 ENDDO
1261 #endif
1262 #ifdef ALLOW_DIAZ
1263 #ifdef DAR_DIAG_NFIXP
1264 DO np = 1,npmax
1265 NfixParr(i,j,k,np) = NfixPl(np)
1266 ENDDO
1267 #endif
1268 #endif
1269 #ifdef DAR_DIAG_CHL
1270 GeiderChlarr(i,j,k) = ChlGeiderlocal
1271 DoneyChlarr(i,j,k) = ChlDoneylocal
1272 CloernChlarr(i,j,k) = ChlCloernlocal
1273 IF (totphyC .NE. 0. _d 0) THEN
1274 GeiderChl2Carr(i,j,k) = ChlGeiderlocal/totphyC
1275 DoneyChl2Carr(i,j,k) = ChlDoneylocal/totphyC
1276 CloernChl2Carr(i,j,k) = ChlCloernlocal/totphyC
1277 ELSE
1278 GeiderChl2Carr(i,j,k) = 0. _d 0
1279 DoneyChl2Carr(i,j,k) = 0. _d 0
1280 CloernChl2Carr(i,j,k) = 0. _d 0
1281 ENDIF
1282 #endif
1283 COJ
1284 #endif /* ALLOW_DIAGNOSTICS */
1285
1286 c total fixation (NOTE - STILL NEEDS GLOB SUM)
1287 tot_Nfix=tot_Nfix+
1288 & Nfix*rA(i,j,bi,bj)*rF(k)*hFacC(i,j,k,bi,bj)
1289
1290 #ifdef ALLOW_TIMEAVE
1291 c save averages
1292 c Phygrow1ave(i,j,k,bi,bj)=Phygrow1ave(i,j,k,bi,bj)+
1293 c & mu1*py1*deltaTclock
1294 c & /float(nsubtime)
1295 c Phygrow2ave(i,j,k,bi,bj)=Phygrow2ave(i,j,k,bi,bj)+
1296 c & mu2*py2*deltaTclock
1297 c & /float(nsubtime)
1298 c Zoograzave(i,j,k,bi,bj)=Zoograzave(i,j,k,bi,bj)+
1299 c & (gampn1*graz1*zo +gampn2*graz2*zo)*
1300 c & deltaTclock/float(nsubtime)
1301 #ifdef GEIDER
1302 Chlave(i,j,k,bi,bj)=Chlave(i,j,k,bi,bj)+
1303 & Chl*dtplankton
1304 #endif
1305 PARave(i,j,k,bi,bj)=PARave(i,j,k,bi,bj)+
1306 & PARl*dtplankton
1307 PPave(i,j,k,bi,bj)=PPave(i,j,k,bi,bj)+
1308 & PP*dtplankton
1309 Nfixave(i,j,k,bi,bj)=Nfixave(i,j,k,bi,bj)+
1310 & Nfix*dtplankton
1311 Denitave(i,j,k,bi,bj)=Denitave(i,j,k,bi,bj)+
1312 & denit*dtplankton
1313 #ifdef WAVES_DIAG_PCHL
1314 do np=1,npmax
1315 Pchlave(i,j,k,bi,bj,np)=Pchlave(i,j,k,bi,bj,np)+
1316 & phychl(np)*dtplankton
1317 enddo
1318 #endif
1319 #ifdef DAR_DIAG_ACDOM
1320 c print*,'acdom',k,acdom_k(k,darwin_diag_acdom_ilam)
1321 aCDOMave(i,j,k,bi,bj)=aCDOMave(i,j,k,bi,bj)+
1322 & acdom_k(k,darwin_diag_acdom_ilam)*dtplankton
1323 #endif
1324 #ifdef DAR_DIAG_IRR
1325 do ilam = 1,tlam
1326 if (k.EQ.1) then
1327 Edave(i,j,k,bi,bj,ilam)=Edave(i,j,k,bi,bj,ilam)+
1328 & Edwsf(ilam)*dtplankton
1329 Esave(i,j,k,bi,bj,ilam)=Esave(i,j,k,bi,bj,ilam)+
1330 & Eswsf(ilam)*dtplankton
1331 Coj no Eu at surface (yet)
1332 else
1333 Edave(i,j,k,bi,bj,ilam)=Edave(i,j,k,bi,bj,ilam)+
1334 & Edz(ilam,k-1)*dtplankton
1335 Esave(i,j,k,bi,bj,ilam)=Esave(i,j,k,bi,bj,ilam)+
1336 & Esz(ilam,k-1)*dtplankton
1337 Euave(i,j,k,bi,bj,ilam)=Euave(i,j,k,bi,bj,ilam)+
1338 & Euz(ilam,k-1)*dtplankton
1339 endif
1340 Eutave(i,j,k,bi,bj,ilam)=Eutave(i,j,k,bi,bj,ilam)+
1341 & Eutop(ilam,k)*dtplankton
1342 enddo
1343 #endif
1344 #ifdef DAR_DIAG_IRR_AMPS
1345 do ilam = 1,tlam
1346 c1ave(i,j,k,bi,bj,ilam)=c1ave(i,j,k,bi,bj,ilam)+
1347 & c1(ilam,k)*dtplankton
1348 c2ave(i,j,k,bi,bj,ilam)=c2ave(i,j,k,bi,bj,ilam)+
1349 & c2(ilam,k)*dtplankton
1350 enddo
1351 #endif
1352 #ifdef DAR_DIAG_ABSORP
1353 do ilam = 1,tlam
1354 aave(i,j,k,bi,bj,ilam)=aave(i,j,k,bi,bj,ilam)+
1355 & a_k(k,ilam)*dtplankton
1356 enddo
1357 #endif
1358 #ifdef DAR_DIAG_SCATTER
1359 do ilam = 1,tlam
1360 btave(i,j,k,bi,bj,ilam)=btave(i,j,k,bi,bj,ilam)+
1361 & bt_k(k,ilam)*dtplankton
1362 bbave(i,j,k,bi,bj,ilam)=bbave(i,j,k,bi,bj,ilam)+
1363 & bb_k(k,ilam)*dtplankton
1364 enddo
1365 #endif
1366 #ifdef DAR_DIAG_PART_SCATTER
1367 do ilam = 1,tlam
1368 apartave(i,j,k,bi,bj,ilam)=apartave(i,j,k,bi,bj,ilam)+
1369 & apart_k(k,ilam)*dtplankton
1370 btpartave(i,j,k,bi,bj,ilam)=btpartave(i,j,k,bi,bj,ilam)+
1371 & bpart_k(k,ilam)*dtplankton
1372 bbpartave(i,j,k,bi,bj,ilam)=bbpartave(i,j,k,bi,bj,ilam)+
1373 & bbpart_k(k,ilam)*dtplankton
1374 enddo
1375 #endif
1376 #ifdef DAR_RADTRANS
1377 if (k.eq.1) then
1378 rmudave(i,j,bi,bj)=rmudave(i,j,bi,bj)+
1379 & rmud*dtplankton
1380 endif
1381 #endif
1382 #ifdef DAR_DIAG_RSTAR
1383 do np=1,npmax
1384 Rstarave(i,j,k,bi,bj,np)=Rstarave(i,j,k,bi,bj,np)+
1385 & Rstarl(np)*dtplankton
1386 RNstarave(i,j,k,bi,bj,np)=RNstarave(i,j,k,bi,bj,np)+
1387 & RNstarl(np)*dtplankton
1388 enddo
1389 #endif
1390 #ifdef DAR_DIAG_DIVER
1391 Diver1ave(i,j,k,bi,bj)=Diver1ave(i,j,k,bi,bj)+
1392 & Diver1(i,j,k)*dtplankton
1393 Diver2ave(i,j,k,bi,bj)=Diver2ave(i,j,k,bi,bj)+
1394 & Diver2(i,j,k)*dtplankton
1395 Diver3ave(i,j,k,bi,bj)=Diver3ave(i,j,k,bi,bj)+
1396 & Diver3(i,j,k)*dtplankton
1397 Diver4ave(i,j,k,bi,bj)=Diver4ave(i,j,k,bi,bj)+
1398 & Diver4(i,j,k)*dtplankton
1399 #endif
1400 #ifdef DAR_DIAG_GROW
1401 do np=1,npmax
1402 Growave(i,j,k,bi,bj,np)=Growave(i,j,k,bi,bj,np)+
1403 & Growl(np)*dtplankton
1404 Growsqave(i,j,k,bi,bj,np)=Growsqave(i,j,k,bi,bj,np)+
1405 & Growsql(np)*dtplankton
1406 enddo
1407 #endif
1408
1409 #ifdef ALLOW_DIAZ
1410 #ifdef DAR_DIAG_NFIXP
1411 do np=1,npmax
1412 NfixPave(i,j,k,bi,bj,np)=NfixPave(i,j,k,bi,bj,np)+
1413 & NfixPl(np)*dtplankton
1414 enddo
1415 #endif
1416 #endif
1417 #endif
1418
1419 #ifdef ALLOW_CARBON
1420 if (k.eq.1) then
1421 SURave(i,j,bi,bj) =SURave(i,j,bi,bj)+
1422 & flxCO2(i,j)*dtplankton
1423 SURCave(i,j,bi,bj) =SURCave(i,j,bi,bj)+
1424 & FluxCO2(i,j,bi,bj)*dtplankton
1425 SUROave(i,j,bi,bj) =SUROave(i,j,bi,bj)+
1426 & flxO2(i,j)*dtplankton
1427 pCO2ave(i,j,bi,bj) =pCO2ave(i,j,bi,bj)+
1428 & pCO2(i,j,bi,bj)*dtplankton
1429 pHave(i,j,bi,bj) =pHave(i,j,bi,bj)+
1430 & pH(i,j,bi,bj)*dtplankton
1431 endif
1432 #endif
1433 endif
1434 c end if hFac>0
1435
1436 enddo ! k
1437 c end layer loop
1438 c
1439
1440 ENDDO ! i
1441 ENDDO ! j
1442
1443 #ifdef ALLOW_PAR_DAY
1444 C 1 <-> 2
1445 PARiaccum = 3 - PARiprev
1446
1447 DO k=1,nR
1448 DO j=1,sNy
1449 DO i=1,sNx
1450 PARday(i,j,k,bi,bj,PARiaccum) =
1451 & PARday(i,j,k,bi,bj,PARiaccum) + PAR(i,j,k)
1452 ENDDO
1453 ENDDO
1454 ENDDO
1455
1456 phase = 0. _d 0
1457 itistime = DIFF_PHASE_MULTIPLE( phase, darwin_PARavPeriod,
1458 & newtime, dtsubtime)
1459
1460 IF ( itistime ) THEN
1461 C compute average
1462 nav = darwin_PARnav
1463 IF (newtime - baseTime .LT. darwin_PARavPeriod) THEN
1464 C incomplete period at beginning of run
1465 nav = NINT((newtime-baseTime)/dtsubtime)
1466 ENDIF
1467 DO k=1,nR
1468 DO j=1,sNy
1469 DO i=1,sNx
1470 PARday(i,j,k,bi,bj,PARiaccum) =
1471 & PARday(i,j,k,bi,bj,PARiaccum) / nav
1472 ENDDO
1473 ENDDO
1474 ENDDO
1475 C reset the other slot for averaging
1476 DO k=1,nR
1477 DO j=1,sNy
1478 DO i=1,sNx
1479 PARday(i,j,k,bi,bj,PARiprev) = 0. _d 0
1480 ENDDO
1481 ENDDO
1482 ENDDO
1483 ENDIF
1484 C itistime
1485 #endif
1486
1487 COJ fill diagnostics
1488 #ifdef ALLOW_DIAGNOSTICS
1489 IF ( useDiagnostics ) THEN
1490 diagname = ' '
1491 WRITE(diagname,'(A8)') 'PAR '
1492 CALL DIAGNOSTICS_FILL( PAR(1-Olx,1-Oly,1), diagname,
1493 & 0,Nr,2,bi,bj,myThid )
1494 WRITE(diagname,'(A8)') 'PP '
1495 CALL DIAGNOSTICS_FILL( PParr(1-Olx,1-Oly,1), diagname,
1496 & 0,Nr,2,bi,bj,myThid )
1497 WRITE(diagname,'(A8)') 'Nfix '
1498 CALL DIAGNOSTICS_FILL( Nfixarr(1-Olx,1-Oly,1), diagname,
1499 & 0,Nr,2,bi,bj,myThid )
1500 c ANNA_TAVE
1501 #ifdef WAVES_DIAG_PCHL
1502 DO np=1,MIN(99,npmax)
1503 WRITE(diagname,'(A5,I2.2,A1)') 'Pchl',np,' '
1504 CALL DIAGNOSTICS_FILL( Pchlarr(1-Olx,1-Oly,1,np), diagname,
1505 & 0,Nr,2,bi,bj,myThid )
1506 ENDDO
1507 #endif
1508 c ANNA end TAVE
1509 #ifdef DAR_DIAG_RSTAR
1510 DO np=1,MIN(99,npmax)
1511 WRITE(diagname,'(A5,I2.2,A1)') 'Rstar',np,' '
1512 CALL DIAGNOSTICS_FILL( Rstararr(1-Olx,1-Oly,1,np), diagname,
1513 & 0,Nr,2,bi,bj,myThid )
1514 ENDDO
1515 #endif
1516 #ifdef DAR_DIAG_DIVER
1517 WRITE(diagname,'(A8)') 'Diver1 '
1518 CALL DIAGNOSTICS_FILL( Diver1(1-Olx,1-Oly,1), diagname,
1519 & 0,Nr,2,bi,bj,myThid )
1520 WRITE(diagname,'(A8)') 'Diver2 '
1521 CALL DIAGNOSTICS_FILL( Diver2(1-Olx,1-Oly,1), diagname,
1522 & 0,Nr,2,bi,bj,myThid )
1523 WRITE(diagname,'(A8)') 'Diver3 '
1524 CALL DIAGNOSTICS_FILL( Diver3(1-Olx,1-Oly,1), diagname,
1525 & 0,Nr,2,bi,bj,myThid )
1526 WRITE(diagname,'(A8)') 'Diver4 '
1527 CALL DIAGNOSTICS_FILL( Diver4(1-Olx,1-Oly,1), diagname,
1528 & 0,Nr,2,bi,bj,myThid )
1529 WRITE(diagname,'(A8)') 'Shannon '
1530 CALL DIAGNOSTICS_FILL( Shannon(1-Olx,1-Oly,1), diagname,
1531 & 0,Nr,2,bi,bj,myThid )
1532 WRITE(diagname,'(A8)') 'Simpson '
1533 CALL DIAGNOSTICS_FILL( Simpson(1-Olx,1-Oly,1), diagname,
1534 & 0,Nr,2,bi,bj,myThid )
1535 #endif
1536 #ifdef ALLOW_DIAZ
1537 #ifdef DAR_DIAG_NFIXP
1538 DO np=1,MIN(99,npmax)
1539 WRITE(diagname,'(A5,I2.2,A1)') 'NfixP',np,' '
1540 CALL DIAGNOSTICS_FILL( NfixParr(1-Olx,1-Oly,1,np), diagname,
1541 & 0,Nr,2,bi,bj,myThid )
1542 ENDDO
1543 #endif
1544 #endif
1545 #ifdef DAR_DIAG_CHL
1546 CALL DIAGNOSTICS_FILL( GeiderChlarr(1-Olx,1-Oly,1), 'ChlGeide',
1547 & 0,Nr,2,bi,bj,myThid )
1548 CALL DIAGNOSTICS_FILL( GeiderChl2Carr(1-Olx,1-Oly,1),'Chl2CGei',
1549 & 0,Nr,2,bi,bj,myThid )
1550 CALL DIAGNOSTICS_FILL( DoneyChlarr(1-Olx,1-Oly,1), 'ChlDoney',
1551 & 0,Nr,2,bi,bj,myThid )
1552 CALL DIAGNOSTICS_FILL( DoneyChl2Carr(1-Olx,1-Oly,1), 'Chl2CDon',
1553 & 0,Nr,2,bi,bj,myThid )
1554 CALL DIAGNOSTICS_FILL( CloernChlarr(1-Olx,1-Oly,1), 'ChlCloer',
1555 & 0,Nr,2,bi,bj,myThid )
1556 CALL DIAGNOSTICS_FILL( CloernChl2Carr(1-Olx,1-Oly,1),'Chl2CClo',
1557 & 0,Nr,2,bi,bj,myThid )
1558 #endif
1559 #ifdef ALLOW_CARBON
1560 CALL DIAGNOSTICS_FILL( flxCO2(1-Olx,1-Oly), 'DICTFLX ',
1561 & 0,1,2,bi,bj,myThid )
1562 CALL DIAGNOSTICS_FILL( FluxCO2(1-Olx,1-Oly,bi,bj), 'DICCFLX ',
1563 & 0,1,2,bi,bj,myThid )
1564 CALL DIAGNOSTICS_FILL( flxO2(1-Olx,1-Oly), 'DICOFLX ',
1565 & 0,1,2,bi,bj,myThid )
1566 CALL DIAGNOSTICS_FILL( pCO2(1-Olx,1-Oly,bi,bj), 'DICPCO2 ',
1567 & 0,1,2,bi,bj,myThid )
1568 CALL DIAGNOSTICS_FILL( pH(1-Olx,1-Oly,bi,bj), 'DICPHAV ',
1569 & 0,1,2,bi,bj,myThid )
1570 #endif /* ALLOW_CARBON */
1571 ENDIF
1572 #endif /* ALLOW_DIAGNOSTICS */
1573 COJ
1574
1575 c determine iron partitioning - solve for free iron
1576 call darwin_fe_chem(bi,bj,iMin,iMax,jMin,jMax,
1577 & Ptr(1-OLx,1-OLy,1,bi,bj,iFeT), freefe,
1578 & myIter, mythid)
1579 c
1580 #ifdef ALLOW_TIMEAVE
1581 c save averages
1582 do k=1,nR
1583 dar_timeave(bi,bj,k)=dar_timeave(bi,bj,k)
1584 & +dtplankton
1585 #ifdef ALLOW_CARBON
1586 dic_timeave(bi,bj,k)=dic_timeave(bi,bj,k)
1587 & +dtplankton
1588 #endif
1589 enddo
1590 #endif
1591 c
1592 c -----------------------------------------------------
1593 ENDDO ! it
1594 c -----------------------------------------------------
1595 c end of bio-chemical time loop
1596 c
1597 RETURN
1598 END
1599 #endif /*MONOD*/
1600 #endif /*ALLOW_PTRACERS*/
1601
1602 C============================================================================

  ViewVC Help
Powered by ViewVC 1.1.22