/[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.3 - (hide annotations) (download)
Tue May 19 14:32:43 2015 UTC (10 years, 2 months ago) by benw
Branch: MAIN
Changes since 1.2: +91 -93 lines
Ben Ward - some superficial structural changes allowing runs with no pfts
         - more significant structural and parameter changes to follow later

1 benw 1.3 C $Header: /u/gcmpack/MITgcm_contrib/darwin2/pkg/quota/quota_plankton.F,v 1.2 2012/07/02 09:55:36 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     #ifdef FQUOTA
292     up_inorg(iNO3,jp) = up_inorg(iNO3,jp) * felimit(jp)
293     #endif
294     else ! if autotrophy(jp).eq.0
295     do ii=1,iimax
296     up_inorg(ii,jp) = 0. _d 0
297     enddo
298     endif ! autotrophy
299     enddo ! jp
300     c
301     c ****************************************************************
302     c ************* Photosynthetic Carbon Assimilation ***************
303     c ****************************************************************
304 benw 1.2 PP = 0.0 _d 0
305 jahn 1.1 call GEIDER98(
306     I PARlocal,
307     I biomass,
308     I qlimit,
309     #ifdef FQUOTA
310     I felimit,
311     #endif
312 benw 1.2 #ifdef QUOTA_DIAG_LIMIT
313     O Ilim,
314     #endif
315 jahn 1.1 U up_inorg,
316 benw 1.2 O PP,
317 jahn 1.1 I photo_Tempfunction,
318     O dchloro, ! chlorophyll synthesis rate
319     I myThid)
320     c
321     c ****************************************************************
322     c ********************* Heterotrophic Grazing ********************
323     c ****************************************************************
324     c PRE-ASSIMILATION grazing of type jpredator by type jprey
325     do jpred=1,npmax ! loop predators
326     if (autotrophy(jpred).lt.1. _d 0) then ! not for pure autotrophs
327 benw 1.3 food1 = 0.0 _d 0
328     food2 = 0.0 _d 0
329     do jprey=1,npmax ! sum all the prey carbon of predator, weighted by availability (preference)
330     if (graz_pref(jpred,jprey).gt.0.0 _d 0) then
331     food1 = food1
332     & + graz_pref(jpred,jprey)*biomass(iCarb,jprey)
333     #ifdef SWITCHING
334     food2 = food2
335     & + (graz_pref(jpred,jprey)*biomass(iCarb,jprey))**ns
336 jahn 1.1 #endif
337     endif
338     enddo
339     ! calculate grazing effort
340     if (food1.gt.0. _d 0) then
341 benw 1.3 refuge(jpred) = (1.0 _d 0 - exp(Lambda * food1))
342     tmp1 = activ_Tempfunction ! saturated grazing
343     & * food1 / (food1 + kg(jpred)) ! grazing effort
344     & * refuge(jpred) ! grazing refuge
345 jahn 1.1 else
346     tmp1 = 0. _d 0
347     endif
348     do jprey=1,npmax ! loop prey carbon consumption
349     if (food1.gt.0. _d 0) then
350     grazing(iCarb,jpred,jprey) ! d^-1
351 benw 1.3 & = tmp1 ! grazing effort
352     !#ifdef ONEGRAZER
353     ! & * graz(jprey) ! prey dependent maximum rate
354     !#else
355     & * graz(jpred) ! predator dependent maximum rate
356     !#endif
357     #ifdef SWITCHING
358     & *(graz_pref(jpred,jprey)*biomass(iCarb,jprey))**ns/food2
359 jahn 1.1 #else
360 benw 1.3 & * graz_pref(jpred,jprey)*biomass(iCarb,jprey) /food1
361 jahn 1.1 #endif
362     else
363     grazing(iCarb,jpred,jprey) = 0. _d 0
364     endif
365     ! other organic elements (+ chlorophyll) are grazed in stoichiometric relation to carbon
366     if (grazing(iCarb,jpred,jprey).gt.0. _d 0
367     & .and.biomass(iCarb,jprey).gt.0. _d 0) then
368     do io=2,iomax
369     grazing(io,jpred,jprey) = grazing(iCarb,jpred,jprey) ! uptake of prey carbon
370     & * biomass(io,jprey) ! *
371     & / biomass(iCarb,jprey) ! biomass ratio of prey
372     enddo
373     else
374     do io=1,iomax
375     grazing(io,jpred,jprey) = 0. _d 0
376     enddo
377     endif
378     enddo ! jprey
379     else ! if pure autotrophs (i.e. autotrophy(jpred).eq.1)
380     do io=1,iomax
381     do jprey=1,npmax
382     grazing(io,jpred,jprey) = 0. _d 0
383     enddo
384     enddo
385     endif
386     enddo ! jpred
387     c
388     c ************************************************************
389     c end evaluate biological process terms
390     c -----------------------------------------------------------------
391     c
392     c -----------------------------------------------------------------
393 benw 1.3 c evaluate vertical sink terms
394 jahn 1.1 c ************************************************************
395     c biosink is +ve downwards
396     c (upstream - downstream) * vertical velocity
397     c bvert is a gain term
398 benw 1.3
399     ! factors to avoid sinking into surface layer, or out of bottom
400     fSurf=float(1-surface)
401     fBott=float(1-bottom)
402     !
403 jahn 1.1 do io=1,iomax
404 benw 1.3 ! plankton sinking
405 jahn 1.1 do jp=1,npmax
406 benw 1.3 bvert(io,jp) = (fSurf*bioabove(io,jp)-fBott*biomass(io,jp))
407 jahn 1.1 & * biosink(jp) / dzlocal ! + sinking in - sinking out
408     enddo
409 benw 1.3 ! organic matter sinking
410 jahn 1.1 if (io.ne.iChlo) then
411 benw 1.3 pomsink(io) = (fSurf*orgabove(io,2)-fBott*orgmat(io,2))
412     & * orgsink(2) / dzlocal
413 jahn 1.1 endif
414     enddo
415     c ************************************************************
416     c end evaluate vertical sink terms
417     c -----------------------------------------------------------------
418     c
419     c -------------------------------------------------------------------
420     c calculate tendency terms (and some diagnostics)
421     c ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
422     c BIOMASS
423     c inorganic uptake
424     do jp=1,npmax
425     dbiomassdt(iCarb,jp) = biomass(iCarb,jp)*up_inorg(iDIC,jp)
426     dbiomassdt(iNitr,jp) = biomass(iCarb,jp)*up_inorg(iNO3,jp)
427     #ifdef NITRITE
428     & + biomass(iCarb,jp)*up_inorg(iNO2,jp)
429     #endif
430     #ifdef AMMON
431     & + biomass(iCarb,jp)*up_inorg(iNH4,jp)
432     #endif
433     #ifdef PQUOTA
434     dbiomassdt(iPhos,jp) = biomass(iCarb,jp)*up_inorg(iPO4,jp)
435     #endif
436     #ifdef SQUOTA
437     dbiomassdt(iSili,jp) = biomass(iCarb,jp)*up_inorg(iSi,jp)
438     #endif
439     #ifdef FQUOTA
440     dbiomassdt(iIron,jp) = biomass(iCarb,jp)*up_inorg(iFeT,jp)
441     #endif
442 benw 1.3 #ifdef QUOTA_DIAG_LIMIT
443     do io=1,iomax
444     AP(io,jp) = dbiomassdt(io,jp)
445     enddo
446     #endif
447 jahn 1.1 c
448     dbiomassdt(iChlo,jp) = dchloro(jp)
449     c
450     ! respiration
451     dbiomassdt(iCarb,jp) = dbiomassdt(iCarb,jp)
452     & - respiration(jp) * biomass(iCarb,jp)
453     & * activ_Tempfunction
454     c
455     c grazing uptake
456     do io=1,iomax
457 benw 1.3 #ifdef QUOTA_DIAG_LIMIT
458     HP(io,jp) = 0.0 _d 0
459     #endif
460 jahn 1.1 if (io.ne.iSili.and.io.ne.iChlo) then ! don't take up silicate or chlorophyll
461     c Grazing uptake of everything but silicate and chlorophyll
462     do jprey=1,npmax
463     dbiomassdt(io,jp) = dbiomassdt(io,jp)
464     & + biomass(iCarb,jp) ! carbon biomass of predator
465     & * grazing(io,jp,jprey)! * carbon specific rate
466 benw 1.3 & * assim_graz(jp,jprey) * q_reg(io,jp)
467     #ifdef QUOTA_DIAG_LIMIT
468     HP(io,jp) = HP(io,jp)
469     & + biomass(iCarb,jp) ! carbon biomass of predator
470     & * grazing(io,jp,jprey)! * carbon specific rate
471     & * assim_graz(jp,jprey) * q_reg(io,jp)
472     #endif
473 jahn 1.1 enddo ! jprey
474     c Exudation of elemental reservoirs
475 benw 1.3 if (io.ne.iChl.or.io.ne.iSili) then
476 jahn 1.1 dbiomassdt(io,jp) = dbiomassdt(io,jp)
477     & - kexc(io,jp) * biomass(io,jp)
478     endif
479     endif
480     !
481     ! calculate temperature adjusted mortality rates
482 benw 1.2 m_ref(jp) = kmort(jp) !* activ_Tempfunction
483 benw 1.3 #ifdef ALLOWPFT
484 benw 1.2 ! Z mortality is t dependent - a la Moore 2002
485 jahn 1.1 if (pft(jp).eq.6) then
486 benw 1.2 m_ref(jp) = kmort(jp) * activ_Tempfunction
487 jahn 1.1 endif
488 benw 1.3 #endif
489 jahn 1.1 !
490     ! Loss and sinking terms - include silicate and chlorophyll
491     dbiomassdt(io,jp) = dbiomassdt(io,jp)
492     & - biomass(io,jp)
493     & * m_ref(jp)
494     & + bvert(io,jp)
495     do jpred=1,npmax
496     ! - losses to other predators
497     dbiomassdt(io,jp) = dbiomassdt(io,jp)
498     & - biomass(iCarb,jpred) ! carbon biomass of predator
499     & * grazing(io,jpred,jp) ! * carbon specific rate
500     enddo ! jpred
501     enddo ! io
502     enddo ! jp
503     cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
504     c NUTRIENTS
505     ! uptake by phytoplankton
506     do ii=1,iimax
507     dnutrientdt(ii) = 0. _d 0
508     do jp=1,npmax
509     dnutrientdt(ii) = dnutrientdt(ii)
510     & - biomass(iCarb,jp)*up_inorg(ii,jp) ! - uptake of inorganic nutrients
511     enddo ! jp
512     enddo ! ii
513     c
514     ! remineralisation of organic matter
515     do ko=1,komax
516     dnutrientdt(iDIC) = dnutrientdt(iDIC)
517     & + orgmat(iCarb,ko) * remin(iCarb,ko)
518     & * activ_Tempfunction
519     #ifndef AMMON
520     dnutrientdt(iNO3) = dnutrientdt(iNO3)
521     & + orgmat(iNitr,ko) * remin(iNitr,ko) ! straight to NO3, if no NH4 ...
522     & * activ_Tempfunction
523     #else
524     dnutrientdt(iNH4) = dnutrientdt(iNH4)
525     & + orgmat(iNitr,ko) * remin(iNitr,ko) ! ... or to NH4
526     & * activ_Tempfunction
527     #endif
528     #ifdef PQUOTA
529     dnutrientdt(iPO4) = dnutrientdt(iPO4)
530     & + orgmat(iPhos,ko) * remin(iPhos,ko)
531     & * activ_Tempfunction
532     #endif
533     #ifdef SQUOTA
534     dnutrientdt(iSi) = dnutrientdt(iSi)
535     & + orgmat(iSili,ko) * remin(iSili,ko)
536     & * activ_Tempfunction
537     #endif
538     #ifdef FQUOTA
539     dnutrientdt(iFeT) = dnutrientdt(iFeT)
540     & + orgmat(iIron,ko) * remin(iIron,ko)
541     & * activ_Tempfunction
542     #endif
543     enddo !ko
544     #ifdef FQUOTA
545     dnutrientdt(iFeT) = dnutrientdt(iFeT)
546     & - scav * freefelocal ! scavenging of free iron
547     & + alpfe * inputFelocal/dzlocal ! atmospheric input
548     #endif
549    
550     ! respiration
551     do jp=1,npmax
552     dnutrientdt(iDIC) = dnutrientdt(iDIC)
553     & + respiration(jp) * biomass(iCarb,jp)
554     & * activ_Tempfunction
555     enddo
556    
557     ! oxidation of NH4 and NO2 compounds
558     #ifdef AMMON
559     dnutrientdt(iNH4) = dnutrientdt(iNH4)
560     & - amm2nrite * nutrient(iNH4) ! ammonium to (nitrite or nitrate)
561     #ifdef NITRITE
562     dnutrientdt(iNO2) = dnutrientdt(iNO2)
563     & + amm2nrite * nutrient(iNH4) ! nitrite from ammonium
564     & - nrite2nrate * nutrient(iNO2) ! nitrite to nitrate
565     dnutrientdt(iNO3) = dnutrientdt(iNO3)
566     & + nrite2nrate * nutrient(iNO2) ! nitrate from nitrite
567     #else
568     dnutrientdt(iNO3) = dnutrientdt(iNO3) ! or
569 benw 1.2 & + amm2nrite * nutrient(iNH4) ! nitrate from ammonium
570 jahn 1.1 #endif
571     #endif
572     c
573     c********************************************************************************
574     c organic matter
575     do io=1,iomax-iChl
576     dorgmatdt(io,1) = 0. _d 0 ! dissolved
577     dorgmatdt(io,2) = pomsink(io) ! particulate
578     do jp=1,npmax
579     ! mortality & excretion
580     dorgmatdt(io,1) = dorgmatdt(io,1)
581     & + biomass(io,jp)
582     & * m_ref(jp)
583     & * beta_mort(io,jp)
584     if (io.eq.iCarb.or.io.eq.iNitr.or.io.eq.iPhos) then
585     dorgmatdt(io,1) = dorgmatdt(io,1)
586     & + kexc(io,jp) * biomass(io,jp)
587     endif
588     dorgmatdt(io,2) = dorgmatdt(io,2)
589     & + biomass(io,jp)
590     & * m_ref(jp)
591 benw 1.3 & *(1. _d 0-beta_mort(io,jp))
592 jahn 1.1 do jprey=1,npmax
593     ! unassimilated grazing
594     dorgmatdt(io,1) = dorgmatdt(io,1)
595     & + biomass(iCarb,jp)
596     & * grazing(io,jp,jprey)
597 benw 1.3 & *(1. _d 0-assim_graz(jp,jprey)*q_reg(io,jp))
598 jahn 1.1 & * beta_graz(io,jprey)
599     dorgmatdt(io,2) = dorgmatdt(io,2)
600     & + biomass(iCarb,jp)
601     & * grazing(io,jp,jprey)
602 benw 1.3 & *(1. _d 0-assim_graz(jp,jprey)*q_reg(io,jp))
603     & *(1. _d 0-beta_graz(io,jprey))
604 jahn 1.1 enddo ! jprey
605     enddo ! jp
606     ! remineralisation of organic matter
607     do ko=1,komax
608     dorgmatdt(io,ko) = dorgmatdt(io,ko)
609     & - orgmat(io,ko) * remin(io,ko)
610     & * activ_Tempfunction
611     enddo ! ko
612     enddo ! io
613     c********************************************************************************
614     c -------------------------------------------------------------------
615     ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
616     c --------------------------------------------------------------------------
617     RETURN
618     END
619     #endif /*ALLOW_QUOTA*/
620     #endif /*ALLOW_DARWIN*/
621     #endif /*ALLOW_PTRACERS*/
622     c ==================================================================

  ViewVC Help
Powered by ViewVC 1.1.22