/[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.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 Clphachl
2     c $Header: /u/gcmpack/MITgcm_contrib/darwin/pkg/darwin/darwin_generate_phyto.F,v 1.13 2009/03/10 20:44:30 stephd Exp $
3     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     biovol(jp) = 1.25 _d -1 * factor**(jp-1)
84     autotrophy(jp)= 1.00 _d 0
85     use_NO3(jp) = 0
86     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     taxon_mu(jp) = 1.10 _d 0
97     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     biovol(jp) = 64.0 _d 0 * factor**(jp-10)
111     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     biovol(jp) = 8.0 _d 0 * factor**(jp-16)
120     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     c FRACTION GRAZED TO DOM
189     do io=1,iomax-iChl
190     p = darwin_random(myThid)
191     call invnormal(a,p,
192     & log10(a_beta_graz(io)),log10(ae_beta_graz(io))*error)
193     call invnormal(b,p,b_beta_graz(io),be_beta_graz(io)*error)
194     beta_graz(io,jp) = 10. _d 0**a * biovol(jp) ** b
195     beta_graz(io,jp)=min(max(
196     & beta_graz(io,jp),0.1 _d 0),0.9 _d 0)
197     c FRACTION MORTALITY TO DOM
198     p = darwin_random(myThid)
199     call invnormal(a,p,
200     & log10(a_beta_mort(io)),log10(ae_beta_mort(io))*error)
201     call invnormal(b,p,b_beta_mort(io),be_beta_mort(io)*error)
202     beta_mort(io,jp)= 10. _d 0**a * biovol(jp) ** b
203     beta_mort(io,jp)=min(max(
204     & beta_mort(io,jp),0.1 _d 0),0.9 _d 0)
205     enddo
206     c GRAZING HALF-SATURATION
207     p = darwin_random(myThid)
208     call invnormal(a,p,
209     & log10(a_kg),log10(ae_kg)*error)
210     call invnormal(b,p,b_kg,be_kg*error)
211     kg(jp) = 10. _d 0**a * biovol(jp) ** b
212     c PHYTOPLANKTON SINKING
213     p = darwin_random(myThid)
214     call invnormal(a,p,
215     & log10(a_biosink),log10(ae_biosink)*error)
216     call invnormal(b,p,b_biosink,be_biosink*error)
217     if (pft(jp).eq.6) then
218     biosink(jp) = 0.0 _d 0 ! grazers don't sink
219     else
220     biosink(jp) = (10.0 _d 0**a) * biovol(jp) ** b
221     endif
222     c SWIMMING
223     p = darwin_random(myThid)
224     IF (a_bioswim.NE.0. _d 0) THEN
225     call invnormal(a,p,
226     & log10(a_bioswim),log10(ae_bioswim)*error)
227     call invnormal(b,p,b_bioswim,be_bioswim*error)
228     if (autotrophy(jp).eq.1) then
229     bioswim(jp) = 0.00 _d 0 ! only grazers can swim
230     else
231     bioswim(jp) =-(10.0 _d 0**a) * biovol(jp) ** b
232     endif
233     ELSE
234     bioswim(jp) = 0.00 _d 0
235     ENDIF
236     c MORTALITY
237     p = darwin_random(myThid)
238     call invnormal(a,p,
239     & log10(a_mort),log10(ae_mort)*error)
240     call invnormal(b,p,b_mort,be_mort*error)
241     kmort(jp) = 10. _d 0**a * biovol(jp) ** b
242     ! if (pft(jp).eq.6) then
243     ! kmort(jp) = kmort(jp) / 8.0 _d 0
244     ! endif
245     ! parameters relating to inorganic nutrients
246     do ii=1,iimax
247     c MAXIMUM NUTRIENT UPTAKE RATE
248     p = darwin_random(myThid)
249     call invnormal(a,p,
250     & log10(a_vmaxi(ii)),log10(ae_vmaxi(ii))*error)
251     call invnormal(b,p,b_vmaxi(ii),be_vmaxi(ii)*error)
252     if (ii.eq.iDIC) then
253     vmaxi(ii,jp)= 10. _d 0**a * biovol(jp) ** b
254     & * taxon_mu(jp)
255     else
256     vmaxi(ii,jp)= 10. _d 0**a * biovol(jp) ** b
257     & * autotrophy(jp)
258     p = darwin_random(myThid)
259     call invnormal(a,p,
260     & log10(a_kn(ii)),log10(ae_kn(ii))*error)
261     call invnormal(b,p,b_kn(ii),be_kn(ii)*error)
262     kn(ii,jp) = 10. _d 0**a * biovol(jp) ** b
263     ! * * autotrophy(jp)
264     endif
265     enddo
266     #ifdef SQUOTA
267     ! Silicate parameters to zero for non-diatoms
268     vmaxi(iSi,jp) = vmaxi(iSi,jp) * float(use_Si(jp))
269     #endif
270     c
271     if (use_NO3(jp).eq.0) then
272     ! prochlorocococcus can't use NO3
273     vmaxi(iNO3,jp) = 0.0 _d 0
274     ! but have higher NH4 affinity
275     vmaxi(iNH4,jp) = vmaxi(iNH4,jp) * 2.0 _d 0
276     endif
277     ! parameters relating to quota nutrients
278     do io=1,iomax-iChl
279     c EXCRETION
280     if ((io.eq.iCarb.or.io.eq.iNitr.or.io.eq.iPhos)
281     & .and.a_kexc(io).NE.0. _d 0
282     & .and.ae_kexc(io).NE.0. _d 0) then
283     p = darwin_random(myThid)
284     call invnormal(a,p,
285     & log10(a_kexc(io)),log10(ae_kexc(io))*error)
286     call invnormal(b,p,b_kexc(io),be_kexc(io)*error)
287     kexc(io,jp) = 10. _d 0**a * biovol(jp) ** b
288     else
289     kexc(io,jp) = 0. _d 0
290     endif
291     if (io.ne.iCarb) then
292     c MINIMUM QUOTA
293     p = darwin_random(myThid)
294     call invnormal(a,p,
295     & log10(a_qmin(io)),log10(ae_qmin(io))*error)
296     call invnormal(b,p,b_qmin(io),be_qmin(io)*error)
297     qmin(io,jp) = 10. _d 0**a * biovol(jp) ** b
298     c MAXIMUM QUOTA
299     p = darwin_random(myThid)
300     call invnormal(a,p,
301     & log10(a_qmax(io)),log10(ae_qmax(io))*error)
302     call invnormal(b,p,b_qmax(io),be_qmax(io)*error)
303     qmax(io,jp) = 10. _d 0**a * biovol(jp) ** b
304     endif
305     enddo
306     #ifdef SQUOTA
307     ! Silicate parameters to zero for non-diatoms
308     qmin(iSili,jp) = qmin(iSili,jp) * float(use_Si(jp))
309     qmax(iSili,jp) = qmax(iSili,jp) * float(use_Si(jp))
310     #endif
311     c Zooplankton have approximately Redfieldian N:C ratio
312     if (pft(jp).eq.6) then
313     qmin(iNitr,jp) = 0.0755 _d 0
314     qmax(iNitr,jp) = 0.1510 _d 0
315     endif
316     c PREFERENCE FUNCTION
317     ! assign grazing preference according to predator/prey radius ratio
318     do jp2=1,npmax ! jp2 denotes prey
319     if (heterotrophy(jp).gt.0. _d 0.and.pft(jp2).ne.6) then
320     prd_pry = biovol(jp) / biovol(jp2)
321     graz_pref(jp,jp2) =
322     #ifdef SWITCH3
323     ! lower preference for larger P
324     ! & 1.0 _d 0
325     & biovol(jp2)**(-0.16 _d 0)
326     #else
327     & exp(-(log(prd_pry/pp_opt(jp))**2) / (2*pp_sig(jp)**2))
328     & / pp_sig(jp)/2. _d 0
329     #endif
330     c
331     if (graz_pref(jp,jp2).lt.1. _d -4) then
332     graz_pref(jp,jp2)=0. _d 0
333     endif
334     assim_graz(jp,jp2) = ass_eff
335     else
336     graz_pref(jp,jp2) = 0. _d 0
337     endif
338     enddo
339     c
340     c..........................................................
341     c generate phyto Temperature Function parameters
342     c.......................................................
343     phytoTempCoeff(jp) = tempcoeff1
344     phytoTempExp1(jp) = tempcoeff3
345     phytoTempExp2(jp) = tempcoeff2_small
346     & + (tempcoeff2_big-tempcoeff2_small)
347     & * float(jp-1)/npmaxm1
348     phytoTempOptimum(jp) = 2. _d 0
349     phytoDecayPower(jp) = tempdecay
350    
351     c..........................................................
352     enddo
353    
354    
355     RETURN
356     END
357     #endif /*ALLOW_QUOTA*/
358     #endif /*ALLOW_DARWIN*/
359     #endif /*ALLOW_PTRACERS*/
360    
361     c ===========================================================

  ViewVC Help
Powered by ViewVC 1.1.22