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

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

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


Revision 1.3 - (hide annotations) (download)
Wed Jun 12 17:53:27 2013 UTC (12 years, 1 month ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt64k_20130723, ctrb_darwin2_ckpt65j_20150225, ctrb_darwin2_ckpt65_20140718, ctrb_darwin2_ckpt64m_20130820, ctrb_darwin2_ckpt64r_20131210, 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_ckpt65g_20141120, ctrb_darwin2_ckpt65k_20150402, ctrb_darwin2_ckpt64w_20140502, ctrb_darwin2_ckpt64l_20130806, ctrb_darwin2_ckpt65f_20141014, ctrb_darwin2_ckpt64u_20140308, ctrb_darwin2_ckpt64j_20130704, ctrb_darwin2_ckpt65i_20150123, ctrb_darwin2_ckpt65a_20140728, ctrb_darwin2_ckpt65b_20140812, ctrb_darwin2_ckpt64p_20131118, ctrb_darwin2_ckpt64q_20131118, ctrb_darwin2_ckpt64p_20131024, ctrb_darwin2_ckpt65c_20140830, ctrb_darwin2_ckpt65h_20141217
Changes since 1.2: +3 -3 lines
fix bug in initialization of plankton volumes in quota package

1 benw 1.2 Clphactl
2 jahn 1.3 c $Header: /u/gcmpack/MITgcm_contrib/darwin2/pkg/quota/quota_generate_phyto.F,v 1.2 2012/07/02 09:50:41 benw Exp $
3 jahn 1.1 C $Name: $
4    
5     #include "CPP_OPTIONS.h"
6     #include "PTRACERS_OPTIONS.h"
7     #include "DARWIN_OPTIONS.h"
8    
9     #ifdef ALLOW_PTRACERS
10     #ifdef ALLOW_DARWIN
11     #ifdef ALLOW_QUOTA
12    
13     c ==========================================================
14     c SUBROUTINE QUOTA_GENERATE_PHYTO
15     c generate parameters for "Operational Taxonomic Units" of plankton (index jp)
16     c using an allometric approach
17     c
18     c Ben Ward 2009/10
19     c ==========================================================
20     SUBROUTINE QUOTA_GENERATE_PHYTO(myThid)
21    
22     implicit none
23     #include "EEPARAMS.h"
24     #include "DARWIN_PARAMS.h"
25     #include "QUOTA_SIZE.h"
26     #include "QUOTA.h"
27    
28     C !INPUT PARAMETERS: ===================================================
29     C myThid :: thread number
30     INTEGER myThid
31    
32     C === Functions ===
33     _RL DARWIN_RANDOM
34     EXTERNAL DARWIN_RANDOM
35     _RL DARWIN_RANDOM_NORMAL
36     EXTERNAL DARWIN_RANDOM_NORMAL
37    
38    
39     C !LOCAL VARIABLES:
40     C === Local variables ===
41     C msgBuf - Informational/error meesage buffer
42     CHARACTER*(MAX_LEN_MBUF) msgBuf
43    
44     _RL RandNo
45     _RL mortdays
46     _RL year
47     _RL month
48     _RL fiveday
49     _RL rtime
50     _RL standin
51     _RL tmpsrt
52     _RL tmpend
53     _RL tmprng
54     _RL iimaxm1
55     _RL npmaxm1
56     _RL komaxm1
57     _RL prd_pry
58     _RL factor
59     _RL taxon_mu(npmax)
60     _RL a,b,p,error
61     _RL heterotrophy(npmax)
62     INTEGER ii,io,jp,ko
63     INTEGER jp2,icount
64     INTEGER signvar
65     CEOP
66     c
67     standin=0. _d 0
68    
69     c each time generate another functional group add one to ngroups
70     ngroups = ngroups + 1
71    
72     iimaxm1 = float(iimax-1)
73     npmaxm1 = float(npmax-1)
74     komaxm1 = float(komax-1)
75     c
76     c..........................................................
77     c Generate plankton volumes and stochastic parameters
78     c..........................................................
79     factor = 2. _d 0
80     c Allocate Phytoplankton Taxa
81     c Prochloro
82     do jp=1,2
83 benw 1.2 biovol(jp) = 0.125 _d 0 * factor**(jp-1)
84 jahn 1.1 autotrophy(jp)= 1.00 _d 0
85 benw 1.2 use_NO3(jp) = 1
86 jahn 1.1 use_Si(jp) = 0
87     taxon_mu(jp) = 1.00 _d 0
88     pft(jp) = 1
89     enddo
90     c Synnecho
91     do jp=3,5
92     biovol(jp) = 0.50 _d 0 * factor**(jp-3)
93     autotrophy(jp)= 1.00 _d 0
94     use_NO3(jp) = 1
95     use_Si(jp) = 0
96 benw 1.2 taxon_mu(jp) = 1.40 _d 0
97 jahn 1.1 pft(jp) = 2
98     enddo
99     c Small Euk
100     do jp=6,9
101     biovol(jp) = 4.00 _d 0 * factor**(jp-6)
102     autotrophy(jp)= 1.0 _d 0
103     use_NO3(jp) = 1
104     use_Si(jp) = 0
105     taxon_mu(jp) = 2.10 _d 0
106     pft(jp) = 3
107     enddo
108     c Diatoms
109     do jp=10,15
110 jahn 1.3 biovol(jp) = 128.0 _d 0 * factor**(jp-10)
111 jahn 1.1 autotrophy(jp)= 1.0 _d 0
112     use_NO3(jp) = 1
113     use_Si(jp) = 0
114     taxon_mu(jp) = 3.8 _d 0
115     pft(jp) = 4
116     enddo
117     c Specialist grazers
118     do jp=16,16
119 jahn 1.3 biovol(jp) = 8.0 _d 0 * factor**(jp-16)
120 jahn 1.1 autotrophy(jp)= 0.00 _d 0
121     use_NO3(jp) = 0
122     use_Si(jp) = 0
123     taxon_mu(jp) = 0.00 _d 0
124     pft(jp) = 6
125     enddo
126     c
127     do jp=1,16
128     heterotrophy(jp)=1.0 _d 0 - autotrophy(jp)
129     enddo
130     c
131     c ----------------------------------------------------------------------
132     c Allometry
133     #ifdef UNCERTAINTY
134     error = 1.0 _d 0
135     #else
136     error = 0.0 _d 0
137     ! set stdev of allometric parameters to zero
138     #endif
139     c ----------------------------------------------------------------------
140     do jp=1,npmax
141     ! parameters independent of nutrient element
142     c CARBON CONTENT
143     p = darwin_random(myThid)
144     call invnormal(a,p,
145     & log10(a_qcarbon),log10(ae_qcarbon)*error)
146     call invnormal(b,p,b_qcarbon,be_qcarbon*error)
147     qcarbon(jp) = 10. _d 0**a * biovol(jp) ** b
148     c INITIAL SLOPE P-I
149     p = darwin_random(myThid)
150     call invnormal(a,p,
151     & log10(a_alphachl),log10(ae_alphachl)*error)
152     call invnormal(b,p,b_alphachl,be_alphachl*error)
153     alphachl(jp) = 10. _d 0**a * biovol(jp) ** b
154     c RESPIRATION RATE
155     p = darwin_random(myThid)
156     IF (a_respir.NE.0. _d 0) THEN
157     call invnormal(a,p,
158     & log10(a_respir),log10(ae_respir)*error)
159     call invnormal(b,p,b_respir,be_respir*error)
160     respiration(jp) = 10. _d 0**a
161     & * (12. _d 9 * qcarbon(jp)) ** b
162     & / qcarbon(jp)
163     if (pft(jp).eq.6) then
164     respiration(jp) = respiration(jp) * 0.50 _d 0
165     endif
166     ELSE
167     respiration(jp) = 0.0 _d 0
168     ENDIF
169     c MAXIMUM GRAZING RATE
170     p = darwin_random(myThid)
171     call invnormal(a,p,
172     & log10(a_graz),log10(ae_graz)*error)
173     call invnormal(b,p,b_graz,be_graz*error)
174     graz(jp) = 10. _d 0**a * biovol(jp) ** b
175     & * heterotrophy(jp)
176     c GRAZING SIZE PREFERENCE RATIO
177     if (pft(jp).eq.5) then ! dinoflagellates prey upon similar sized plankton
178     pp_opt(jp) = 1.0 _d 0
179     else ! other types follow standard relationship
180     p = darwin_random(myThid)
181     call invnormal(a,p,
182     & log10(a_prdpry),log10(ae_prdpry)*error)
183     call invnormal(b,p,b_prdpry,be_prdpry*error)
184     pp_opt(jp) = 10. _d 0**a * biovol(jp) ** b
185     endif
186     c STANDARD DEVIATION OF SIZE PREFERENCE
187     pp_sig(jp) = 0.50 _d 0
188 benw 1.2 pp_sig(jp) = 1.00 _d 0
189 jahn 1.1 c FRACTION GRAZED TO DOM
190     do io=1,iomax-iChl
191 benw 1.2 ! p = darwin_random(myThid)
192     ! call invnormal(a,p,
193     ! & log10(a_beta_graz(io)),log10(ae_beta_graz(io))*error)
194     ! call invnormal(b,p,b_beta_graz(io),be_beta_graz(io)*error)
195     ! beta_graz(io,jp) = 10. _d 0**a * biovol(jp) ** b
196     ! beta_graz(io,jp)=min(max(
197     ! & beta_graz(io,jp),0.5 _d 0),0.9 _d 0)
198     if (pft(jp).lt.3) beta_graz(io,jp)=0.8
199     if (pft(jp).gt.2) beta_graz(io,jp)=0.5
200 jahn 1.1 c FRACTION MORTALITY TO DOM
201 benw 1.2 ! p = darwin_random(myThid)
202     ! call invnormal(a,p,
203     ! & log10(a_beta_mort(io)),log10(ae_beta_mort(io))*error)
204     ! call invnormal(b,p,b_beta_mort(io),be_beta_mort(io)*error)
205     ! beta_mort(io,jp)= 10. _d 0**a * biovol(jp) ** b
206     ! beta_mort(io,jp)=min(max(
207     ! & beta_mort(io,jp),0.5 _d 0),0.9 _d 0)
208     if (pft(jp).lt.3) beta_mort(io,jp)=0.8
209     if (pft(jp).gt.2) beta_mort(io,jp)=0.5
210 jahn 1.1 enddo
211     c GRAZING HALF-SATURATION
212     p = darwin_random(myThid)
213     call invnormal(a,p,
214     & log10(a_kg),log10(ae_kg)*error)
215     call invnormal(b,p,b_kg,be_kg*error)
216     kg(jp) = 10. _d 0**a * biovol(jp) ** b
217     c PHYTOPLANKTON SINKING
218     p = darwin_random(myThid)
219     call invnormal(a,p,
220     & log10(a_biosink),log10(ae_biosink)*error)
221     call invnormal(b,p,b_biosink,be_biosink*error)
222     if (pft(jp).eq.6) then
223     biosink(jp) = 0.0 _d 0 ! grazers don't sink
224     else
225     biosink(jp) = (10.0 _d 0**a) * biovol(jp) ** b
226     endif
227     c SWIMMING
228     p = darwin_random(myThid)
229     IF (a_bioswim.NE.0. _d 0) THEN
230     call invnormal(a,p,
231     & log10(a_bioswim),log10(ae_bioswim)*error)
232     call invnormal(b,p,b_bioswim,be_bioswim*error)
233     if (autotrophy(jp).eq.1) then
234     bioswim(jp) = 0.00 _d 0 ! only grazers can swim
235     else
236     bioswim(jp) =-(10.0 _d 0**a) * biovol(jp) ** b
237     endif
238     ELSE
239     bioswim(jp) = 0.00 _d 0
240     ENDIF
241     c MORTALITY
242 benw 1.2 ! constant background mortality
243     kmort(jp) = a_mort
244     if (pft(jp).eq.6) then
245     ! grazers have lower mortality
246     kmort(jp) = 1.00 _d 0 * a_mort
247     endif
248 jahn 1.1 ! parameters relating to inorganic nutrients
249     do ii=1,iimax
250     c MAXIMUM NUTRIENT UPTAKE RATE
251     p = darwin_random(myThid)
252     call invnormal(a,p,
253     & log10(a_vmaxi(ii)),log10(ae_vmaxi(ii))*error)
254     call invnormal(b,p,b_vmaxi(ii),be_vmaxi(ii)*error)
255     if (ii.eq.iDIC) then
256     vmaxi(ii,jp)= 10. _d 0**a * biovol(jp) ** b
257     & * taxon_mu(jp)
258     else
259     vmaxi(ii,jp)= 10. _d 0**a * biovol(jp) ** b
260     & * autotrophy(jp)
261     p = darwin_random(myThid)
262     call invnormal(a,p,
263     & log10(a_kn(ii)),log10(ae_kn(ii))*error)
264     call invnormal(b,p,b_kn(ii),be_kn(ii)*error)
265     kn(ii,jp) = 10. _d 0**a * biovol(jp) ** b
266     ! * * autotrophy(jp)
267     endif
268     enddo
269     #ifdef SQUOTA
270     ! Silicate parameters to zero for non-diatoms
271     vmaxi(iSi,jp) = vmaxi(iSi,jp) * float(use_Si(jp))
272     #endif
273     c
274     if (use_NO3(jp).eq.0) then
275     ! prochlorocococcus can't use NO3
276     vmaxi(iNO3,jp) = 0.0 _d 0
277     ! but have higher NH4 affinity
278     vmaxi(iNH4,jp) = vmaxi(iNH4,jp) * 2.0 _d 0
279     endif
280     ! parameters relating to quota nutrients
281     do io=1,iomax-iChl
282     c EXCRETION
283     if ((io.eq.iCarb.or.io.eq.iNitr.or.io.eq.iPhos)
284     & .and.a_kexc(io).NE.0. _d 0
285     & .and.ae_kexc(io).NE.0. _d 0) then
286     p = darwin_random(myThid)
287     call invnormal(a,p,
288     & log10(a_kexc(io)),log10(ae_kexc(io))*error)
289     call invnormal(b,p,b_kexc(io),be_kexc(io)*error)
290     kexc(io,jp) = 10. _d 0**a * biovol(jp) ** b
291     else
292     kexc(io,jp) = 0. _d 0
293     endif
294     if (io.ne.iCarb) then
295     c MINIMUM QUOTA
296     p = darwin_random(myThid)
297     call invnormal(a,p,
298     & log10(a_qmin(io)),log10(ae_qmin(io))*error)
299     call invnormal(b,p,b_qmin(io),be_qmin(io)*error)
300     qmin(io,jp) = 10. _d 0**a * biovol(jp) ** b
301     c MAXIMUM QUOTA
302     p = darwin_random(myThid)
303     call invnormal(a,p,
304     & log10(a_qmax(io)),log10(ae_qmax(io))*error)
305     call invnormal(b,p,b_qmax(io),be_qmax(io)*error)
306     qmax(io,jp) = 10. _d 0**a * biovol(jp) ** b
307     endif
308     enddo
309     #ifdef SQUOTA
310     ! Silicate parameters to zero for non-diatoms
311     qmin(iSili,jp) = qmin(iSili,jp) * float(use_Si(jp))
312     qmax(iSili,jp) = qmax(iSili,jp) * float(use_Si(jp))
313     #endif
314     c Zooplankton have approximately Redfieldian N:C ratio
315     if (pft(jp).eq.6) then
316     qmin(iNitr,jp) = 0.0755 _d 0
317     qmax(iNitr,jp) = 0.1510 _d 0
318     endif
319     c PREFERENCE FUNCTION
320     ! assign grazing preference according to predator/prey radius ratio
321     do jp2=1,npmax ! jp2 denotes prey
322     if (heterotrophy(jp).gt.0. _d 0.and.pft(jp2).ne.6) then
323     prd_pry = biovol(jp) / biovol(jp2)
324     graz_pref(jp,jp2) =
325     #ifdef SWITCH3
326     ! lower preference for larger P
327 benw 1.2 & 1.0 _d 0
328     ! & biovol(jp2)**(-0.16 _d 0)
329 jahn 1.1 #else
330     & exp(-(log(prd_pry/pp_opt(jp))**2) / (2*pp_sig(jp)**2))
331     & / pp_sig(jp)/2. _d 0
332     #endif
333 benw 1.2 ! ! reduce diatom palatability
334     ! if (pft(jp2).eq.5) then
335     ! graz_pref(jp,jp2) = graz_pref(jp,jp2) * 0.8
336     ! endif
337 jahn 1.1 if (graz_pref(jp,jp2).lt.1. _d -4) then
338     graz_pref(jp,jp2)=0. _d 0
339     endif
340     assim_graz(jp,jp2) = ass_eff
341     else
342     graz_pref(jp,jp2) = 0. _d 0
343     endif
344     enddo
345     c
346     c..........................................................
347     c generate phyto Temperature Function parameters
348     c.......................................................
349     phytoTempCoeff(jp) = tempcoeff1
350     phytoTempExp1(jp) = tempcoeff3
351     phytoTempExp2(jp) = tempcoeff2_small
352     & + (tempcoeff2_big-tempcoeff2_small)
353     & * float(jp-1)/npmaxm1
354     phytoTempOptimum(jp) = 2. _d 0
355     phytoDecayPower(jp) = tempdecay
356    
357     c..........................................................
358     enddo
359    
360    
361     RETURN
362     END
363     #endif /*ALLOW_QUOTA*/
364     #endif /*ALLOW_DARWIN*/
365     #endif /*ALLOW_PTRACERS*/
366    
367     c ===========================================================

  ViewVC Help
Powered by ViewVC 1.1.22