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

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

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


Revision 1.11 - (hide annotations) (download)
Thu Aug 23 21:49:33 2012 UTC (12 years, 10 months ago) by jahn
Branch: MAIN
Changes since 1.10: +34 -5 lines
add direct radtrans solver

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

  ViewVC Help
Powered by ViewVC 1.1.22