/[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.10 - (hide annotations) (download)
Thu Aug 23 21:48:24 2012 UTC (12 years, 10 months ago) by jahn
Branch: MAIN
Changes since 1.9: +19 -8 lines
add Edstop timeave diagnostic, rename c1/2 to amp1/2

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

  ViewVC Help
Powered by ViewVC 1.1.22