/[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.4 - (hide annotations) (download)
Tue May 19 15:23:46 2015 UTC (10 years, 2 months ago) by benw
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt65w_20160512, ctrb_darwin2_ckpt66g_20170424, ctrb_darwin2_ckpt66k_20171025, ctrb_darwin2_ckpt66n_20180118, ctrb_darwin2_ckpt65v_20160409, ctrb_darwin2_ckpt65s_20160114, ctrb_darwin2_ckpt66d_20170214, ctrb_darwin2_ckpt65m_20150615, ctrb_darwin2_ckpt65q_20151118, ctrb_darwin2_ckpt65o_20150914, ctrb_darwin2_ckpt65p_20151023, ctrb_darwin2_ckpt65z_20160929, ctrb_darwin2_ckpt65n_20150729, ctrb_darwin2_ckpt66h_20170602, ctrb_darwin2_ckpt65x_20160612, ctrb_darwin2_ckpt66f_20170407, ctrb_darwin2_ckpt66a_20161020, ctrb_darwin2_ckpt66b_20161219, ctrb_darwin2_ckpt66j_20170815, ctrb_darwin2_ckpt65y_20160801, ctrb_darwin2_ckpt66c_20170121, ctrb_darwin2_ckpt65t_20160221, ctrb_darwin2_ckpt66o_20180209, ctrb_darwin2_ckpt66e_20170314, ctrb_darwin2_ckpt65u_20160315, ctrb_darwin2_ckpt65r_20151221, ctrb_darwin2_ckpt66i_20170718, ctrb_darwin2_ckpt66l_20171025, ctrb_darwin2_ckpt66m_20171213, HEAD
Changes since 1.3: +6 -15 lines
Ben Ward - modifications to parameters and some structural changes
         - performs much better at OWS Mike

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

  ViewVC Help
Powered by ViewVC 1.1.22