/[MITgcm]/MITgcm_contrib/darwin2/pkg/quota/quota_plankton.F
ViewVC logotype

Annotation of /MITgcm_contrib/darwin2/pkg/quota/quota_plankton.F

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


Revision 1.1 - (hide annotations) (download)
Wed Apr 13 18:56:26 2011 UTC (14 years, 3 months ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt63l_20120405, ctrb_darwin2_ckpt62v_20110413, ctrb_darwin2_ckpt63f_20111201, ctrb_darwin2_ckpt62y_20110526, ctrb_darwin2_ckpt62x_20110513, ctrb_darwin2_ckpt62w_20110426, ctrb_darwin2_ckpt63o_20120629, ctrb_darwin2_ckpt63c_20111011, ctrb_darwin2_ckpt63i_20120124, ctrb_darwin2_ckpt63m_20120506, ctrb_darwin2_ckpt63e_20111107, ctrb_darwin2_ckpt63b_20110830, ctrb_darwin2_ckpt63j_20120217, ctrb_darwin2_ckpt63g_20111220, ctrb_darwin2_ckpt63a_20110804, ctrb_darwin2_ckpt63h_20111230, ctrb_darwin2_ckpt63d_20111107, ctrb_darwin2_ckpt63_20110728, ctrb_darwin2_baseline, ctrb_darwin2_ckpt63n_20120604, ctrb_darwin2_ckpt63k_20120317, ctrb_darwin2_ckpt62z_20110622
darwin2 initial checkin

1 jahn 1.1 C $Header: /u/gcmpack/MITgcm_contrib/darwin/pkg/darwin/darwin_plankton.F,v 1.1y 2009/04/01 14:32:12 jahn Exp $
2     C $Name: $
3     #include "CPP_OPTIONS.h"
4     #include "PTRACERS_OPTIONS.h"
5     #include "DARWIN_OPTIONS.h"
6    
7     #ifdef ALLOW_PTRACERS
8     #ifdef ALLOW_DARWIN
9     #ifdef ALLOW_QUOTA
10    
11     c ====================================================================
12     c SUBROUTINE QUOTA_PLANKTON
13     c 0. New version for mixotrophic QUOTA model
14     c
15     c 1. Local ecological interactions for models with many phytoplankton
16     c "functional groups"
17     c 2. Timestep plankton and nutrients locally
18     c 3. Same equations for DOM and POM
19     c 4. Remineralization of detritus also determined in routine
20     c 5. Sinking particles and plankton
21     c 6. NOT in this routine: iron chemistry
22     c
23     c Mick Follows, Scott Grant, Fall/Winter 2005
24     c Stephanie Dutkiewicz Spring/Summer 2006
25     c Ben Ward, 2009/10
26     c
27     c - Dropped in initial quota version...
28     c - R* diagnostics (#define DAR_DIAG_RSTAR)
29     c - diazotrophy (#define ALLOW_DIAZ)
30     c - mutation code (#define ALLOW_MUTANTS)
31     c - new nitrogen limiting scheme (#undef OLD_NSCHEME)
32     c - diversity diagnostics
33     c - waveband dependence of light attenuation and absorption
34     c ====================================================================
35    
36     SUBROUTINE QUOTA_PLANKTON(
37     I biomass, orgmat, nutrient,
38     O PP,
39     I bioabove, biobelow,
40     I orgabove,
41     #ifdef FQUOTA
42     I freefelocal, inputFelocal,
43     #endif
44     I PARlocal, Tlocal, Slocal,
45     I bottom, surface, dzlocal,
46     O dbiomassdt,dorgmatdt, dnutrientdt,
47     I debug,
48     I runtim,
49     I MyThid)
50    
51    
52     implicit none
53     #include "SIZE.h"
54     #include "EEPARAMS.h"
55     #include "DARWIN_PARAMS.h"
56     #include "QUOTA_SIZE.h"
57     #include "QUOTA.h"
58    
59     C !INPUT PARAMETERS: ===================================================
60     C myThid :: thread number
61     INTEGER myThid
62     CEOP
63     c === GLOBAL VARIABLES =====================
64     c iimax = no of nutrient species (1=Carbon,2=Nitrate, ...)
65     c npmax = no of plankton species
66     c komax = no of organic matter classes
67     c biomass = plankton biomass (auto/mixo/hetero)
68     c x_num = cell density
69     c quota = (average) cell quota
70     c nutrient = ambient inorganic nutrient concntration
71     c orgmat = organic matter biomass (dissolved and particulate)
72     _RL biomass(iomax,npmax)
73     _RL nutrient(iimax)
74     _RL orgmat(iomax-iChl,komax)
75     _RL quota(iomax-iChl,npmax)
76     _RL PP
77     _RL bioabove(iomax,npmax)
78     _RL biobelow(iomax,npmax)
79     _RL orgabove(iomax-iChl,komax)
80     #ifdef FQUOTA
81     _RL freefelocal
82     _RL inputFelocal
83     #endif
84     _RL m_ref(npmax)
85     _RL PARlocal
86     _RL Tlocal
87     _RL Slocal
88     INTEGER bottom
89     INTEGER surface
90     _RL dzlocal
91     INTEGER debug
92     _RL dbiomassdt(iomax,npmax)
93     _RL dchloro(npmax)
94     _RL dnutrientdt(iimax)
95     _RL dorgmatdt(iomax-iChl,komax)
96     #ifdef ALLOW_PAR_DAY
97     _RL PARdaylocal
98     #endif
99     _RL runtim
100    
101     c LOCAL VARIABLES
102     c -------------------------------------------------------------
103    
104     c WORKING VARIABLES
105     c ii = nutrient element index
106     integer ii,io
107     c jp = plankton index
108     integer jp,jp2
109     c ko = organic matter index
110     integer ko
111     c 'spare' indices
112     integer ii2, ko2
113     integer jpred, jprey
114     integer iin
115     c variables for plankton growth rate limitation
116     _RL limit
117     _RL qlimit(npmax)
118     #ifdef FQUOTA
119     _RL felimit(npmax)
120     #endif
121     c plankton specific nutrient limitation terms
122     _RL qreg(iomax,npmax)
123     _RL qregmax
124     c photosynthesis light limitation term
125     _RL ilimit(npmax)
126     c temperature limitation terms
127     _RL photo_Tempfunction
128     _RL activ_Tempfunction
129     c uptake of inorganic nutrients
130     _RL up_inorg(iimax,npmax)
131     c plankton grazing rates
132     _RL grazing(iomax,npmax,npmax)
133     _RL food1,food2
134     _RL Psum,Zsum,Jsum
135     _RL biomass2(npmax)
136     c plankton respiration rates (carbon only)
137     _RL C_resp(npmax)
138     c varible for mimumum phyto
139     _RL biomassmin(npmax)
140     c variables for remineralization of organic matter
141     c
142     c variables for sinking/swimming
143     _RL bvert(iomax,npmax)
144     _RL pomsink(iomax-iChl)
145     c variables for sums of plankton and organic matter
146     _RL totplankton(iomax)
147     _RL totorgmat(iomax-iChl)
148     c ?
149     _RL facpz
150     _RL kpar, kinh
151     _RL tmpr,tmpz, tmpgrow, tmp1, tmp2
152     integer ITEST
153     c
154     c *****************************************************************
155     c ******************** Evaluate Quota Status **********************
156     c *****************************************************************
157     c qlimit --> Function of most limiting nutrient
158     c 1 = replete, 0 = no C assimilation
159     c N,Si - linear from quota
160     c P & Fe - Droop from quota
161     c
162     c qreg --> individual nutrient status for uptake regualtion
163     c 0 = quota full, 1 = quota empty
164     c linear for all elements (not needed for Si)
165     c qreg(C) = inverse of qreg for most limiting element
166     c
167     do jp = 1,npmax
168     c set diagnostic to zero
169     qlimit(jp) = 1. _d 0
170     qreg(iCarb,jp) = 1. _d 0
171     c
172     do io = 2,iomax-iChl ! skip carbon index; quota = X:C biomass ratio
173     c quota = nutrient biomass to carbon biomass ratio
174     if (biomass(iCarb,jp).gt.0. _d 0) then
175     quota(io,jp) = biomass(io,jp) / biomass(iCarb,jp)
176     else
177     quota(io,jp) = 0. _d 0
178     endif
179     c limit ranges from 1 to 0 between qmin and qmax
180     if (quota(io,jp).le.qmin(io,jp)) then ! if quota empty...
181     limit = 0. _d 0
182     qreg(io,jp) = 1. _d 0
183     elseif (quota(io,jp).ge.qmax(io,jp)) then ! if quota full...
184     limit = 1. _d 0
185     qreg(io,jp) = 0. _d 0
186     else ! if quota somewhere in between...
187     if (io.eq.iNitr.or.io.eq.iSili) then ! linear
188     limit = (quota(io,jp) - qmin(io,jp))
189     & / ( qmax(io,jp) - qmin(io,jp))
190     else ! normalised Droop
191     limit = (1. _d 0 - qmin(io,jp)/quota(io,jp))
192     & / (1. _d 0 - qmin(io,jp)/qmax(io,jp) )
193     endif
194     ! regulation term is always linear
195     qreg(io,jp) = (qmax(io,jp) - quota(io,jp))
196     & / (qmax(io,jp) - qmin(io,jp) )
197     endif
198     #ifdef FQUOTA
199     if (io.eq.iIron) then
200     felimit(jp) = limit
201     limit = 1. _d 0
202     endif
203     #endif
204     #ifdef SQUOTA
205     ! non-diatoms are not Si limited
206     if (io.eq.iSili.and.use_Si(jp).eq.0) then
207     limit = 1. _d 0
208     qreg(iSili,jp) = 0. _d 0
209     biomass(iSili,jp) = 0. _d 0
210     bioabove(iSili,jp)= 0. _d 0
211     biobelow(iSili,jp)= 0. _d 0
212     quota(iSili,jp) = 0. _d 0
213     endif
214     #endif
215     qlimit(jp) = min(qlimit(jp),limit)
216     qreg(iCarb,jp) = min(qreg(iCarb,jp),1. _d 0 - qreg(io,jp))
217     enddo ! io
218     if (autotrophy(jp).eq. 0. _d 0) then
219     biomass(iChlo,jp) = 0. _d 0 ! pure heterotroph, so chl is zero
220     bioabove(iChlo,jp) = 0. _d 0
221     biobelow(iChlo,jp) = 0. _d 0
222     endif
223     enddo ! jp
224     c
225     c ****************************************************************
226     c * Determine temperature Dependent Growth function for Plankton *
227     c ****************************************************************
228     call quota_tempfunc(
229     I Tlocal,
230     O photo_Tempfunction,
231     O activ_Tempfunction,
232     I myThid)
233     c
234     c *****************************************************************
235     c ******************** Resource Acquisition ***********************
236     c *****************************************************************
237     do jp=1,npmax
238     if (autotrophy(jp).gt.0.0 _d 0) then
239     do ii=2,iimax ! not carbon...
240     if (ii.eq.iNO3.or.ii.eq.iNO2.or.ii.eq.iNH4) io=iNitr
241     if (ii.eq.iPO4) io=iPhos
242     if (ii.eq.iFeT) io=iIron
243     if (ii.eq.iSi) io=iSili
244     c C-specific nutrient uptake, modulated by quota fullness and temperature
245     if (nutrient(ii).gt.0. _d 0) then
246     up_inorg(ii,jp) = vmaxi(ii,jp) ! maximum uptake rate
247     & * nutrient(ii)/(nutrient(ii)+kn(ii,jp)) ! ambient nutrients
248     & * qreg(io,jp) ! quota satiation
249     & * activ_Tempfunction ! temperature effects
250     #ifdef AMMON
251     c apply ammonium inhibition to NO3 and NO2
252     if (ii.eq.iNO3.or.ii.eq.iNO2) then
253     up_inorg(ii,jp) = up_inorg(ii,jp)
254     & * exp(-amminhib*nutrient(iNH4))
255     endif
256     #endif
257     else
258     up_inorg(ii,jp) = 0. _d 0
259     endif
260     enddo ! ii
261     #ifdef FQUOTA
262     up_inorg(iNO3,jp) = up_inorg(iNO3,jp) * felimit(jp)
263     #endif
264     else ! if autotrophy(jp).eq.0
265     do ii=1,iimax
266     up_inorg(ii,jp) = 0. _d 0
267     enddo
268     endif ! autotrophy
269     enddo ! jp
270     c
271     c ****************************************************************
272     c ************* Photosynthetic Carbon Assimilation ***************
273     c ****************************************************************
274     call GEIDER98(
275     I PARlocal,
276     I biomass,
277     I qlimit,
278     #ifdef FQUOTA
279     I felimit,
280     #endif
281     U up_inorg,
282     I photo_Tempfunction,
283     O dchloro, ! chlorophyll synthesis rate
284     I myThid)
285     c
286     c ****************************************************************
287     c ********************* Heterotrophic Grazing ********************
288     c ****************************************************************
289     c PRE-ASSIMILATION grazing of type jpredator by type jprey
290     do jpred=1,npmax ! loop predators
291     if (autotrophy(jpred).lt.1. _d 0) then ! not for pure autotrophs
292     food1 = 0. _d 0
293     #ifdef SWITCH3
294     food2 = 0. _d 0
295     #else
296     Psum = 0. _d 0
297     Zsum = 0. _d 0
298     #endif
299     do jprey=1,npmax ! sum all the prey carbon of predator, weighted by preference
300     food1 = food1
301     & + graz_pref(jpred,jprey) * biomass(iCarb,jprey)
302     #ifdef SWITCH3
303     food2 = food2
304     & + graz_pref(jpred,jprey) * biomass(iCarb,jprey)
305     & * graz_pref(jpred,jprey) * biomass(iCarb,jprey)
306     #else
307     if (pft(jprey).ne.6) then
308     Psum = Psum
309     & + graz_pref(jpred,jprey)
310     & * biomass(iCarb,jprey) * biomass(iCarb,jprey)
311     else
312     Zsum = Zsum
313     & + graz_pref(jpred,jprey)
314     & * biomass(iCarb,jprey) * biomass(iCarb,jprey)
315     endif
316     #endif
317     enddo
318     ! calculate grazing effort
319     if (food1.gt.0. _d 0) then
320     tmp1 = graz(jpred) * activ_Tempfunction ! saturated grazing
321     & * food1 / (food1+kg(jpred)) ! grazing effort
322     & * (1.0 _d 0 - exp(-1. _d 0 * food1))
323     else
324     tmp1 = 0. _d 0
325     endif
326     do jprey=1,npmax ! loop prey carbon consumption
327     #ifdef SWITCH3
328     if (food1.gt.0. _d 0) then
329     tmp2=food2
330     #else
331     if (food1.gt.0. _d 0 .and.(Psum+Zsum).gt.0) then
332     tmp2=food1
333     if (pft(jprey).ne.6) then
334     Jsum = Psum
335     else
336     Jsum = Zsum
337     endif
338     #endif
339     grazing(iCarb,jpred,jprey) ! d^-1
340     #ifndef SWITCH3
341     & = Jsum / (Psum+Zsum)
342     #else
343     & = graz_pref(jpred,jprey) * biomass(iCarb,jprey)
344     #endif
345     & * graz_pref(jpred,jprey) * biomass(iCarb,jprey)
346     & / tmp2
347     & * tmp1
348     else
349     grazing(iCarb,jpred,jprey) = 0. _d 0
350     endif
351     ! other organic elements (+ chlorophyll) are grazed in stoichiometric relation to carbon
352     if (grazing(iCarb,jpred,jprey).gt.0. _d 0
353     & .and.biomass(iCarb,jprey).gt.0. _d 0) then
354     do io=2,iomax
355     grazing(io,jpred,jprey) = grazing(iCarb,jpred,jprey) ! uptake of prey carbon
356     & * biomass(io,jprey) ! *
357     & / biomass(iCarb,jprey) ! biomass ratio of prey
358     enddo
359     else
360     do io=1,iomax
361     grazing(io,jpred,jprey) = 0. _d 0
362     enddo
363     endif
364     enddo ! jprey
365     else ! if pure autotrophs (i.e. autotrophy(jpred).eq.1)
366     do io=1,iomax
367     do jprey=1,npmax
368     grazing(io,jpred,jprey) = 0. _d 0
369     enddo
370     enddo
371     endif
372     enddo ! jpred
373     c
374     c ************************************************************
375     c end evaluate biological process terms
376     c -----------------------------------------------------------------
377     c
378     c -----------------------------------------------------------------
379     c evaluate vertical sink and swim terms
380     c ************************************************************
381     c biosink is +ve downwards
382     c bioswim is -ve upwards
383     c (upstream - downstream) * vertical velocity
384     c bvert is a gain term
385     do io=1,iomax
386     do jp=1,npmax
387     if (surface.eq.1) then ! surface
388     bvert(io,jp) =(-biomass(io,jp))
389     & * biosink(jp) / dzlocal ! - sinking out
390     & +(-biobelow(io,jp))
391     & * bioswim(jp) / dzlocal ! - swimming in (-ve)
392     elseif (bottom.eq.1) then ! bottom
393     bvert(io,jp) = bioabove(io,jp)
394     & * biosink(jp) / dzlocal ! + sinking in
395     & + biomass(io,jp)
396     & * bioswim(jp) / dzlocal ! + swimming out (-ve)
397     else ! in between
398     bvert(io,jp) = (bioabove(io,jp)-biomass(io,jp))
399     & * biosink(jp) / dzlocal ! + sinking in - sinking out
400     & + (biomass(io,jp)-biobelow(io,jp))
401     & * bioswim(jp) / dzlocal ! + swimming out (-ve) - swimming in (-ve)
402     endif
403     enddo
404     if (io.ne.iChlo) then
405     if (surface.eq.1) then ! surface
406     pomsink(io) =(-orgmat(io,2))
407     & * orgsink(2) / dzlocal
408     elseif (bottom.eq.1) then ! bottom
409     pomsink(io) = orgabove(io,2)
410     & * orgsink(2) / dzlocal
411     else ! in between
412     pomsink(io) = (orgabove(io,2)-orgmat(io,2))
413     & * orgsink(2) / dzlocal
414     endif
415     endif
416     enddo
417     c ************************************************************
418     c end evaluate vertical sink terms
419     c -----------------------------------------------------------------
420     c
421     c -------------------------------------------------------------------
422     c calculate tendency terms (and some diagnostics)
423     c ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
424     c BIOMASS
425     c inorganic uptake
426     do jp=1,npmax
427     dbiomassdt(iCarb,jp) = biomass(iCarb,jp)*up_inorg(iDIC,jp)
428     dbiomassdt(iNitr,jp) = biomass(iCarb,jp)*up_inorg(iNO3,jp)
429     #ifdef NITRITE
430     & + biomass(iCarb,jp)*up_inorg(iNO2,jp)
431     #endif
432     #ifdef AMMON
433     & + biomass(iCarb,jp)*up_inorg(iNH4,jp)
434     #endif
435     #ifdef PQUOTA
436     dbiomassdt(iPhos,jp) = biomass(iCarb,jp)*up_inorg(iPO4,jp)
437     #endif
438     #ifdef SQUOTA
439     dbiomassdt(iSili,jp) = biomass(iCarb,jp)*up_inorg(iSi,jp)
440     #endif
441     #ifdef FQUOTA
442     dbiomassdt(iIron,jp) = biomass(iCarb,jp)*up_inorg(iFeT,jp)
443     #endif
444     c
445     dbiomassdt(iChlo,jp) = dchloro(jp)
446     c
447     ! respiration
448     dbiomassdt(iCarb,jp) = dbiomassdt(iCarb,jp)
449     & - respiration(jp) * biomass(iCarb,jp)
450     & * activ_Tempfunction
451     c
452     c grazing uptake
453     do io=1,iomax
454     if (io.ne.iSili.and.io.ne.iChlo) then ! don't take up silicate or chlorophyll
455     c Grazing uptake of everything but silicate and chlorophyll
456     do jprey=1,npmax
457     dbiomassdt(io,jp) = dbiomassdt(io,jp)
458     & + biomass(iCarb,jp) ! carbon biomass of predator
459     & * grazing(io,jp,jprey)! * carbon specific rate
460     & * assim_graz(jp,jprey) * qreg(io,jp)
461     enddo ! jprey
462     c Exudation of elemental reservoirs
463     if (io.eq.iCarb.or.io.eq.iNitr.or.io.eq.iPhos) then
464     dbiomassdt(io,jp) = dbiomassdt(io,jp)
465     & - kexc(io,jp) * biomass(io,jp)
466     endif
467     endif
468     !
469     ! calculate temperature adjusted mortality rates
470     m_ref(jp) = kmort(jp) ! linear
471     ! quadratic Z mortality
472     if (pft(jp).eq.6) then
473     m_ref(jp) = kmort(jp) * 0.5 _d 0 ! linear
474     ! & + kmort(jp) * 0.25 _d 0 * biomass(iCarb,jp) ! quadratic
475     endif
476     m_ref(jp) = m_ref(jp) * activ_Tempfunction
477     !
478     ! Loss and sinking terms - include silicate and chlorophyll
479     dbiomassdt(io,jp) = dbiomassdt(io,jp)
480     & - biomass(io,jp)
481     & * m_ref(jp)
482     & + bvert(io,jp)
483     do jpred=1,npmax
484     ! - losses to other predators
485     dbiomassdt(io,jp) = dbiomassdt(io,jp)
486     & - biomass(iCarb,jpred) ! carbon biomass of predator
487     & * grazing(io,jpred,jp) ! * carbon specific rate
488     enddo ! jpred
489     enddo ! io
490     enddo ! jp
491     cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
492     c NUTRIENTS
493     ! uptake by phytoplankton
494     do ii=1,iimax
495     dnutrientdt(ii) = 0. _d 0
496     do jp=1,npmax
497     dnutrientdt(ii) = dnutrientdt(ii)
498     & - biomass(iCarb,jp)*up_inorg(ii,jp) ! - uptake of inorganic nutrients
499     enddo ! jp
500     enddo ! ii
501     c
502     ! remineralisation of organic matter
503     do ko=1,komax
504     dnutrientdt(iDIC) = dnutrientdt(iDIC)
505     & + orgmat(iCarb,ko) * remin(iCarb,ko)
506     & * activ_Tempfunction
507     #ifndef AMMON
508     dnutrientdt(iNO3) = dnutrientdt(iNO3)
509     & + orgmat(iNitr,ko) * remin(iNitr,ko) ! straight to NO3, if no NH4 ...
510     & * activ_Tempfunction
511     #else
512     dnutrientdt(iNH4) = dnutrientdt(iNH4)
513     & + orgmat(iNitr,ko) * remin(iNitr,ko) ! ... or to NH4
514     & * activ_Tempfunction
515     #endif
516     #ifdef PQUOTA
517     dnutrientdt(iPO4) = dnutrientdt(iPO4)
518     & + orgmat(iPhos,ko) * remin(iPhos,ko)
519     & * activ_Tempfunction
520     #endif
521     #ifdef SQUOTA
522     dnutrientdt(iSi) = dnutrientdt(iSi)
523     & + orgmat(iSili,ko) * remin(iSili,ko)
524     & * activ_Tempfunction
525     #endif
526     #ifdef FQUOTA
527     dnutrientdt(iFeT) = dnutrientdt(iFeT)
528     & + orgmat(iIron,ko) * remin(iIron,ko)
529     & * activ_Tempfunction
530     #endif
531     enddo !ko
532     #ifdef FQUOTA
533     dnutrientdt(iFeT) = dnutrientdt(iFeT)
534     & - scav * freefelocal ! scavenging of free iron
535     & + alpfe * inputFelocal/dzlocal ! atmospheric input
536     #endif
537    
538     ! respiration
539     do jp=1,npmax
540     dnutrientdt(iDIC) = dnutrientdt(iDIC)
541     & + respiration(jp) * biomass(iCarb,jp)
542     & * activ_Tempfunction
543     enddo
544    
545     ! oxidation of NH4 and NO2 compounds
546     #ifdef AMMON
547     dnutrientdt(iNH4) = dnutrientdt(iNH4)
548     & - amm2nrite * nutrient(iNH4) ! ammonium to (nitrite or nitrate)
549     #ifdef NITRITE
550     dnutrientdt(iNO2) = dnutrientdt(iNO2)
551     & + amm2nrite * nutrient(iNH4) ! nitrite from ammonium
552     & - nrite2nrate * nutrient(iNO2) ! nitrite to nitrate
553     dnutrientdt(iNO3) = dnutrientdt(iNO3)
554     & + nrite2nrate * nutrient(iNO2) ! nitrate from nitrite
555     #else
556     dnutrientdt(iNO3) = dnutrientdt(iNO3) ! or
557     & + amm2nrate * nutrient(iNH4) ! nitrate from ammonium
558     #endif
559     #endif
560     c
561     c********************************************************************************
562     c organic matter
563     do io=1,iomax-iChl
564     dorgmatdt(io,1) = 0. _d 0 ! dissolved
565     dorgmatdt(io,2) = pomsink(io) ! particulate
566     do jp=1,npmax
567     ! mortality & excretion
568     dorgmatdt(io,1) = dorgmatdt(io,1)
569     & + biomass(io,jp)
570     & * m_ref(jp)
571     & * beta_mort(io,jp)
572     if (io.eq.iCarb.or.io.eq.iNitr.or.io.eq.iPhos) then
573     dorgmatdt(io,1) = dorgmatdt(io,1)
574     & + kexc(io,jp) * biomass(io,jp)
575     endif
576     dorgmatdt(io,2) = dorgmatdt(io,2)
577     & + biomass(io,jp)
578     & * m_ref(jp)
579     & * (1. _d 0 - beta_mort(io,jp))
580     do jprey=1,npmax
581     ! unassimilated grazing
582     dorgmatdt(io,1) = dorgmatdt(io,1)
583     & + biomass(iCarb,jp)
584     & * grazing(io,jp,jprey)
585     & * (1. _d 0-assim_graz(jp,jprey)*qreg(io,jp))
586     & * beta_graz(io,jprey)
587     dorgmatdt(io,2) = dorgmatdt(io,2)
588     & + biomass(iCarb,jp)
589     & * grazing(io,jp,jprey)
590     & * (1. _d 0-assim_graz(jp,jprey)*qreg(io,jp))
591     & * (1. _d 0 - beta_graz(io,jprey))
592     enddo ! jprey
593     enddo ! jp
594     ! remineralisation of organic matter
595     do ko=1,komax
596     dorgmatdt(io,ko) = dorgmatdt(io,ko)
597     & - orgmat(io,ko) * remin(io,ko)
598     & * activ_Tempfunction
599     enddo ! ko
600     enddo ! io
601     c********************************************************************************
602     c Uptake diagnostics
603     PP=0. _d 0
604     do jp=1,npmax
605     if (pft(jp).ne.6) then
606     PP = PP + biomass(iCarb,jp) * up_inorg(iCarb,jp) * 86400. _d 0
607     endif
608     enddo
609     c -------------------------------------------------------------------
610     ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
611     c --------------------------------------------------------------------------
612     RETURN
613     END
614     #endif /*ALLOW_QUOTA*/
615     #endif /*ALLOW_DARWIN*/
616     #endif /*ALLOW_PTRACERS*/
617     c ==================================================================

  ViewVC Help
Powered by ViewVC 1.1.22