/[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.2 - (hide annotations) (download)
Mon Jul 2 09:55:36 2012 UTC (13 years ago) by benw
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt64k_20130723, ctrb_darwin2_ckpt65j_20150225, ctrb_darwin2_ckpt64h_20130528, ctrb_darwin2_ckpt65_20140718, ctrb_darwin2_ckpt64m_20130820, ctrb_darwin2_ckpt64r_20131210, ctrb_darwin2_ckpt64f_20130405, ctrb_darwin2_ckpt64a_20121116, ctrb_darwin2_ckpt64n_20130826, ctrb_darwin2_ckpt65e_20140929, ctrb_darwin2_ckpt64o_20131024, ctrb_darwin2_ckpt64v_20140411, ctrb_darwin2_ckpt64z_20140711, ctrb_darwin2_ckpt65l_20150504, ctrb_darwin2_ckpt64y_20140622, ctrb_darwin2_ckpt65d_20140915, ctrb_darwin2_ckpt64t_20140202, ctrb_darwin2_ckpt64i_20130622, ctrb_darwin2_ckpt64s_20140105, ctrb_darwin2_ckpt64x_20140524, ctrb_darwin2_ckpt64e_20130305, ctrb_darwin2_ckpt65g_20141120, ctrb_darwin2_ckpt63s_20120908, ctrb_darwin2_ckpt65k_20150402, ctrb_darwin2_ckpt64w_20140502, ctrb_darwin2_ckpt63r_20120817, ctrb_darwin2_ckpt64g_20130503, ctrb_darwin2_ckpt64l_20130806, ctrb_darwin2_ckpt65f_20141014, ctrb_darwin2_ckpt64c_20130120, ctrb_darwin2_ckpt64u_20140308, ctrb_darwin2_ckpt64j_20130704, ctrb_darwin2_ckpt65i_20150123, ctrb_darwin2_ckpt63p_20120707, ctrb_darwin2_ckpt65a_20140728, ctrb_darwin2_ckpt65b_20140812, ctrb_darwin2_ckpt64p_20131118, ctrb_darwin2_ckpt63q_20120731, ctrb_darwin2_ckpt64b_20121224, ctrb_darwin2_ckpt64d_20130219, ctrb_darwin2_ckpt64_20121012, ctrb_darwin2_ckpt64q_20131118, ctrb_darwin2_ckpt64p_20131024, ctrb_darwin2_ckpt65c_20140830, ctrb_darwin2_ckpt65h_20141217
Changes since 1.1: +21 -14 lines
Calculates N,Fe,I and T limitation factors

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

  ViewVC Help
Powered by ViewVC 1.1.22