/[MITgcm]/MITgcm_contrib/dcarroll/highres_darwin/code/darwin_generate_phyto.F
ViewVC logotype

Annotation of /MITgcm_contrib/dcarroll/highres_darwin/code/darwin_generate_phyto.F

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


Revision 1.1 - (hide annotations) (download)
Sun Sep 22 21:23:46 2019 UTC (5 years, 10 months ago) by dcarroll
Branch: MAIN
CVS Tags: HEAD
Initial check in of high resolution Darwin simulation code

1 dcarroll 1.1 C $Header: /u/gcmpack/MITgcm_contrib/ecco_darwin/v4_llc270/code_darwin/darwin_generate_phyto.F,v 1.2 2019/03/21 06:02:45 dimitri Exp $
2     C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5     #include "PTRACERS_OPTIONS.h"
6     #include "DARWIN_OPTIONS.h"
7    
8     #ifdef ALLOW_PTRACERS
9     #ifdef ALLOW_DARWIN
10    
11     c ==========================================================
12     c SUBROUTINE DARWIN_GENERATE_PHYTO
13     c generate parameters for "functional group" of phyto (index np)
14     c using a "Monte Carlo" approach
15     c Mick Follows, Scott Grant Fall/Winter 2005
16     c Stephanie Dutkiewicz Spring/Summer 2005
17     c Anna Hickman Summer 2008
18     c TWO_SPECIES_SETUP
19     c 1=large, 2=small
20     c NINE_SPECIES_SETUP
21     c 1=diatom, 2=other large, 3=syn, 4=hl pro, 5=ll pro, 6=trich,
22     c 7=uni diaz, 8=small euk, 9=cocco
23     c ==========================================================
24     SUBROUTINE DARWIN_GENERATE_PHYTO(myThid, np)
25    
26     implicit none
27     #include "EEPARAMS.h"
28     #include "DARWIN_SIZE.h"
29     #include "DARWIN_PARAMS.h"
30     #include "DARWIN.h"
31    
32    
33     c ANNA define WAVEBANDS variables
34     #ifdef WAVEBANDS
35     #include "SPECTRAL_SIZE.h"
36     #include "WAVEBANDS_PARAMS.h"
37     #endif
38    
39    
40    
41     C !INPUT PARAMETERS: ===================================================
42     C myThid :: thread number
43     INTEGER myThid
44    
45     C === Functions ===
46     _RL DARWIN_RANDOM
47     EXTERNAL DARWIN_RANDOM
48     _RL DARWIN_RANDOM_NORMAL
49     EXTERNAL DARWIN_RANDOM_NORMAL
50    
51     C !LOCAL VARIABLES:
52     C === Local variables ===
53     C msgBuf - Informational/error meesage buffer
54     CHARACTER*(MAX_LEN_MBUF) msgBuf
55    
56     _RL RandNo
57     _RL growthdays
58     _RL mortdays
59     _RL pday
60     _RL year
61     _RL month
62     _RL fiveday
63     _RL rtime
64     _RL standin
65     _RL dm
66     _RL volp
67     _RL PI
68     INTEGER np
69     INTEGER nz
70     INTEGER signvar
71     PARAMETER ( PI = 3.14159265358979323844D0 )
72    
73     CEOP
74     c
75     standin=0. _d 0
76    
77     c length of day (seconds)
78     pday = 86400.0 _d 0
79    
80     c each time generate another functional group add one to ngroups
81     ngroups = ngroups + 1
82    
83     c RANDOM NUMBERS
84     c phyto either "small" (physize(np)=0.0) or "big" (physize(np)=1.0)
85     c at this point independent of whether diatom or coccolithophor or not
86     RandNo = darwin_random(myThid)
87     if(RandNo .gt. 0.500 _d 0)then
88     physize(np) = 1.0 _d 0
89     else
90     physize(np) = 0.0 _d 0
91     end if
92     #ifdef TWO_SPECIES_SETUP
93     if (np.eq.1) physize(np) = 1.0 _d 0
94     if (np.eq.2) physize(np) = 0.0 _d 0
95     #endif
96     #ifdef NINE_SPECIES_SETUP
97     if (np.lt.3.or.np.eq.6.or.np.eq.9) then
98     physize(np) = 1.0 _d 0
99     else
100     physize(np) = 0.0 _d 0
101     end if
102     #endif
103    
104     c size of phytoplankton
105     if(physize(np).eq. 1.0 _d 0)then
106     dm = 10. _d 0 ! diameter (micrometer)
107     else
108     dm = 1. _d 0 ! diameter (micrometer)
109     end if
110     c phytoplankton volume in micrometers cubed
111     volp=4. _d 0/3. _d 0 *PI*(dm/2. _d 0)**3 _d 0
112     c
113     c common block variables (in m and m3)
114     phyto_esd(np)=dm* 1. _d -6
115     phyto_vol(np)=volp* 1. _d -18
116     c
117     c phyto either diatoms (diacoc=1.0) and use silica or cocolithophor
118     c (diacoc=2.0) and produce PIC or neither (diacoc=0.0)
119     c if they are large
120     if (physize(np).eq.1.0 _d 0) then
121     RandNo = darwin_random(myThid)
122     if(RandNo .gt. 0.500 _d 0)then
123     diacoc(np) = 1.0 _d 0
124     else
125     diacoc(np) = 0.0 _d 0
126     end if
127     c if(RandNo .gt. 0.670 _d 0)then
128     c diacoc(np) = 1.0 _d 0
129     c endif
130     c if(RandNo .gt. 0.330 _d 0 .and. RandNo. le. 0.67 _d 0)then
131     c diacoc(np) = 2.0 _d 0
132     c endif
133     c if (RandNo .le. 0.330 _d 0) then
134     c diacoc(np) = 0.0 _d 0
135     c endif
136     else
137     diacoc(np) = 0.0 _d 0
138     endif
139     #ifdef TWO_SPECIES_SETUP
140     diacoc(np) = 0.0 _d 0
141     #endif
142     #ifdef NINE_SPECIES_SETUP
143     if (np.eq.1) then
144     diacoc(np) = 1.0 _d 0
145     else
146     diacoc(np) = 0.0 _d 0
147     endif
148     if (np.eq.9) then
149     diacoc(np) = 2.0 _d 0
150     endif
151     #endif
152     c TEST ...........................................
153     c diacoc(np) = 0.0 _d 0
154     c write(msgBuf,'(A,I4,A)')
155     c & 'generate Phyto: np = ',np,' FIXED - no DIAZO'
156     c CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
157     c & SQUEEZE_RIGHT , mythid)
158     c TEST ...........................................
159    
160    
161    
162     c phyto either diazotrophs (diazotroph=1.0) or not (diazotroph=0.0)
163     RandNo = darwin_random(myThid)
164     if(RandNo .gt. 0.6700 _d 0)then
165     diazotroph(np) = 1.0 _d 0
166     else
167     diazotroph(np) = 0.0 _d 0
168     end if
169     c TEST ...........................................
170     #ifndef ALLOW_DIAZ
171     diazotroph(np) = 0.0 _d 0
172     write(msgBuf,'(A,I4,A)')
173     & 'generate Phyto: np = ',np,' FIXED - no DIAZO'
174     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
175     & SQUEEZE_RIGHT , mythid)
176     #endif
177     c TEST ...........................................
178     #ifdef TWO_SPECIES_SETUP
179     diazotroph(np) = 0.0 _d 0
180     #endif
181     #ifdef NINE_SPECIES_SETUP
182     if (np.gt.5.and.np.lt.8) then
183     diazotroph(np) = 1.0 _d 0
184     else
185     diazotroph(np) = 0.0 _d 0
186     end if
187     #endif
188    
189    
190     c growth rates
191     RandNo = darwin_random(myThid)
192     c big/small phyto growth rates..
193     if(physize(np) .eq. 1.0 _d 0)then
194     growthdays = Biggrow +Randno*Biggrowrange
195     else
196     growthdays = Smallgrow +RandNo*Smallgrowrange
197     end if
198     c but diazotrophs always slower due to energetics
199     if(diazotroph(np) .eq. 1.0 _d 0) then
200     growthdays = growthdays * diaz_growfac
201     endif
202     #ifdef TWO_SPECIES_SETUP
203     if(physize(np) .eq. 1.0 _d 0)then
204     growthdays = Biggrow
205     else
206     growthdays = Smallgrow
207     end if
208     #endif
209     #ifdef NINE_SPECIES_SETUP
210     if(physize(np) .eq. 1.0 _d 0)then
211     growthdays = Biggrow
212     else
213     growthdays = Smallgrow
214     end if
215     c but diazotrophs always slower due to energetics
216     if(diazotroph(np) .eq. 1.0 _d 0) then
217     growthdays = growthdays * diaz_growfac
218     endif
219     c cocco have slower growth than other large
220     if (diacoc(np).eq.2. _d 0) then
221     growthdays= growthdays * 1.3 _d 0
222     endif
223     c diatom has faster thatn other large
224     if (diacoc(np).eq.1. _d 0) then
225     growthdays= growthdays * 1. _d 0 ! 0.95 _d 0
226     endif
227     #endif
228     c now convert to a growth rate
229     if (growthdays.gt.0. _d 0) then
230     mu(np) = 1.0 _d 0/(growthdays*pday)
231     else
232     mu(np) = 0. _d 0
233     endif
234    
235     c mortality and export fraction rates
236     RandNo = darwin_random(myThid)
237     c big/small phyto mortality rates..
238     if(physize(np) .eq. 1.0 _d 0)then
239     mortdays = Bigmort +Randno*Bigmortrange
240     ExportFracP(np)=Bigexport
241     else
242     mortdays = Smallmort +RandNo*Smallmortrange
243     ExportFracP(np)=Smallexport
244     end if
245     #ifdef TWO_SPECIES_SETUP
246     if(physize(np) .eq. 1.0 _d 0)then
247     mortdays = Bigmort
248     else
249     mortdays = Smallmort
250     end if
251     #endif
252     #ifdef NINE_SPECIES_SETUP
253     if(physize(np) .eq. 1.0 _d 0)then
254     mortdays = Bigmort
255     else
256     mortdays = Smallmort
257     end if
258     #endif
259    
260     c now convert to a mortality rate
261     if (mortdays.gt.0. _d 0) then
262     mortphy(np) = 1.0 _d 0/(mortdays*pday)
263     else
264     mortphy(np) = 0. _d 0
265     endif
266    
267    
268    
269     c nutrient source
270     if(diazotroph(np) .ne. 1.0 _d 0)then
271     RandNo = darwin_random(myThid)
272     if (physize(np).eq.1.0 _d 0) then
273     nsource(np) = 3
274     else
275     if(RandNo .gt. 0.670 _d 0)then
276     nsource(np) = 1
277     elseif(RandNo .lt. 0.33 _d 0)then
278     nsource(np) = 2
279     else
280     nsource(np) = 3
281     endif
282     c ANNA shift bias away from pros. Now equal chance of being HL, LL, Syn, Euk.
283     c ANNA i.e. now 50% chance of being Pro (nsource 1 or 2, with 50% change of each being HL)
284     c ANNA i.e. and 50% chance of being non-Pro (nsource 3, with 50% chance of non-pro being Syn)
285     c if(RandNo .gt. 0.50 _d 0)then
286     c nsource(np) = 3
287     c elseif(RandNo .lt. 0.25 _d 0)then
288     c nsource(np) = 2
289     c else
290     c nsource(np) = 1
291     c endif
292     endif
293     else
294     nsource(np) = 0
295     end if
296     #ifdef TWO_SPECIES_SETUP
297     nsource(np) = 3
298     #endif
299     #ifdef NINE_SPECIES_SETUP
300     if (np.lt.4) then
301     nsource(np) = 3
302     end if
303     nsource(4)=2
304     nsource(5)=1
305     if (np.gt.5.and.np.lt.8) then
306     nsource(np) = 0
307     end if
308     if (np.gt.7) then
309     nsource(np) = 3
310     end if
311     #endif
312    
313     c.....................................................
314     c ANNA make selections for WAVEBANDS
315     c.....................................................
316     #ifdef WAVEBANDS
317     c for now, choice of four absorption spectra types
318     c pros get either 'HL' or 'LL'
319     c small others get 'syn' or 'euk'
320     c large get 'euk'
321     c each 'type', once assigned, gets given actual values in wavebands_init_vari.F
322    
323     c ANNA_Q could use tricho abs and scattering spectra (Subramanian et al. 1999)
324     c ANNA_Q think diaz is turned off for now
325     c Diaz will be 0 if not defined, and will have nsource = 0.
326     if (tnabp.eq.4) then
327     if (nsource(np).eq.0) then !if diazotroph
328     if (physize(np).eq.1.0d0) then !if BIG
329     ap_type(np) = 1 !euk (assume diatom association)
330     else !or
331     ap_type(np) = 2 !syn (for now - tricho has billins)
332     end if
333     end if
334    
335     RandNo = darwin_random(myThid)
336     if (nsource(np).eq.3) then !if all three sources (NO3)
337     if (physize(np).eq.1.0d0) then !if BIG
338     ap_type(np) = 1 !euk
339     else !if SMALL
340     if (RandNo.gt.0.500d0) then
341     ap_type(np) = 1 !euk
342     else !or
343     ap_type(np) = 2 !Syn
344     end if
345     end if
346     endif
347    
348     RandNo = darwin_random(myThid)
349     if (nsource(np).eq.2) then !if NH4 only
350     if (RandNo.gt.0.500d0) then
351     ap_type(np) = 3 !Pro HL
352     else !or
353     ap_type(np) = 4 !Pro LL
354     end if
355     end if
356    
357     RandNo = darwin_random(myThid)
358     if (nsource(np).eq.1) then !if NH4 & NO2
359     if (RandNo.gt.0.500d0) then
360     ap_type(np) = 3 !Pro HL
361     else !or
362     ap_type(np) = 4 !Pro LL
363     end if
364     end if
365     endif
366     c
367     if (tnabp.eq.12) then
368     if (nsource(np).eq.0) then !if diazotroph
369     if (physize(np).eq.1.0d0) then !if BIG
370     if (diacoc(np).eq.1.0d0) then
371     ap_type(np) = 5 !diatom association
372     endif
373     if (diacoc(np).eq.0.0d0) then
374     ap_type(np) = 7 !tricho
375     endif
376     if (diacoc(np).eq.2.0d0) then
377     ap_type(np) = 6 !coccolithopher(?)
378     endif
379     else !or
380     ap_type(np) = 1 !unicellular (whould be 8 -
381     !but currently zero)
382     end if
383     end if
384    
385     RandNo = darwin_random(myThid)
386     if (nsource(np).eq.3) then !if all three sources (NO3)
387     if (physize(np).eq.1.0d0) then !if BIG
388     if (diacoc(np).eq.1.0d0) then
389     ap_type(np) = 5 !diatom
390     endif
391     if (diacoc(np).eq.0.0d0) then
392     ap_type(np) = 9 !Lg Euk
393     endif
394     if (diacoc(np).eq.2.0d0) then
395     ap_type(np) = 6 !coccolithopher
396     endif
397     else !if SMALL
398     if (RandNo.gt.0.500d0) then
399     ap_type(np) = 1 !euk
400     else !or
401     ap_type(np) = 2 !Syn
402     end if
403     end if
404     endif
405     endif
406    
407     #ifdef TWO_SPECIES_SETUP
408     if (np.eq.1) ap_type(np) = 10
409     if (np.eq.2) ap_type(np) = 10
410     #endif
411     #ifdef NINE_SPECIES_SETUP
412     if (np.eq.1) ap_type(np) = 5
413     if (np.eq.2) ap_type(np) = 9
414     if (np.eq.3) ap_type(np) = 2
415     if (np.eq.4) ap_type(np) = 3
416     if (np.eq.5) ap_type(np) = 4
417     if (np.eq.6) ap_type(np) = 7
418     if (np.eq.7) ap_type(np) = 8
419     if (np.eq.8) ap_type(np) = 1
420     if (np.eq.9) ap_type(np) = 6
421     ap_type(np) = 10
422     #endif
423    
424    
425     #else
426     c ANNA number of RandNo's carreid out MUST MATCH regardless of wavebands or not.
427     C ANNA the number of RandNo statements here MUST MATCH the number done above
428    
429     c RandNo = darwin_random(myThid)
430     c RandNo = darwin_random(myThid)
431     c RandNo = darwin_random(myThid)
432    
433     #endif
434     c ANNA endif
435    
436    
437     c..........................................................
438     c generate phyto Temperature Function parameters
439     c.......................................................
440     phytoTempCoeff(np) = tempcoeff1
441     phytoTempExp1(np) = tempcoeff3
442     if(physize(np) .eq. 1.0 _d 0)then
443     phytoTempExp2(np) = tempcoeff2_big
444     else
445     phytoTempExp2(np) = tempcoeff2_small
446     endif
447    
448     RandNo = darwin_random(myThid)
449     #ifdef TEMP_RANGE
450     cswd phytoTempOptimum(np) = 30.0 _d 0 - RandNo*28.0 _d 0
451     phytoTempOptimum(np) = tempmax - RandNo*temprange
452     phytoDecayPower(np) = tempdecay
453     #else
454     phytoTempOptimum(np) = 0. _d 0
455     phytoDecayPower(np) = 0. _d 0
456     #endif
457    
458     write(msgBuf,'(A,I4,A,1P1G24.15E3)')
459     & 'generate Phyto: np = ',np,' Topt =',
460     & phytoTempOptimum(np)
461     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
462     & SQUEEZE_RIGHT , mythid)
463    
464     c ...............................................
465     write(msgBuf,'(A,I4,A,1P1G24.15E3)')
466     & 'generate Phyto: np = ',np,' growthdays =', growthdays
467     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
468     & SQUEEZE_RIGHT , mythid)
469     c ...............................................
470    
471     c stoichiometric ratios for each functional group of phyto
472     c relative to phosphorus - the base currency nutrient
473     c set Si:P
474     if(diacoc(np) .eq. 1.0 _d 0)then
475     R_SiP(np) = val_R_SiP_diatom
476     else
477     R_SiP(np) = 0.0 _d 0
478     end if
479     if(diacoc(np) .eq. 2.0 _d 0)then
480     R_PICPOC(np) = val_R_PICPOC
481     else
482     R_PICPOC(np) = 0.0 _d 0
483     end if
484     cswd %%%%%%%%%%% OCMIP STYLE for other phyto (not diatom or prochl)
485     if (np.eq.2.or.np.eq.3.or.np.eq.8) then
486     R_PICPOC(np) = 0.041886 _d 0
487     cBX GF optizm run ag4 R_PICPOC(np) = 0.133 _d 0
488     endif
489     c set N:P and iron requirement according to diazotroph status
490     if(diazotroph(np) .eq. 1.0 _d 0)then
491     R_NP(np) = val_R_NP_diaz
492     R_FeP(np) = val_RFeP_diaz
493     else
494     R_NP(np) = val_R_NP
495     R_FeP(np) = val_RFeP
496     end if
497     c set C:P ratio
498     R_PC(np) = val_R_PC
499     c set sinking rates according to allometry
500     if(physize(np) .eq. 1.0 _d 0)then
501     wsink(np) = BigSink
502     else
503     wsink(np) = SmallSink
504     end if
505     c half-saturation coeffs
506    
507     RandNo = darwin_random(myThid)
508     if(physize(np) .eq. 1.0 _d 0)then
509     ksatPO4(np) = BigPsat + RandNo*BigPsatrange
510     else
511     c ksatPO4(np) = SmallPsat + RandNo*SmallPsatrange
512     c if (nsource(np).lt.3) then
513     c ksatPO4(np) = ksatPO4(np)*prochlPsat
514     c endif
515     if (nsource(np).eq.3) then
516     ksatPO4(np) = SmallPsat + RandNo*SmallPsatrange
517     endif
518     if (nsource(np).eq..0) then
519     c ksatPO4(np) = SmallPsat + RandNo*SmallPsatrange
520     ksatPO4(np) = UniDzPsat + RandNo*UniDzPsatrange
521     endif
522     if (nsource(np).eq.2.or.nsource(np).eq.1) then
523     ksatPO4(np) = ProcPsat + RandNo*ProcPsatrange
524     endif
525     endif
526     #ifdef TWO_SPECIES_SETUP
527     if(physize(np) .eq. 1.0 _d 0)then
528     ksatPO4(np) = BigPsat
529     else
530     ksatPO4(np) = SmallPsat
531     endif
532     #endif
533     #ifdef NINE_SPECIES_SETUP
534     if(physize(np) .eq. 1.0 _d 0)then
535     ksatPO4(np) = BigPsat
536     else
537     ksatPO4(np) = SmallPsat
538     endif
539     if (nsource(np).eq.2.or.nsource(np).eq.1) then
540     ksatPO4(np) = ProcPsat
541     endif
542     if (diacoc(np) .eq. 2.0 _d 0) then
543     ksatPO4(np) = ksatPO4(np)/1.2 _d 0
544     endif
545     #endif
546    
547     ksatNO3(np) = ksatPO4(np)*R_NP(np)
548     ksatNO2(np) = ksatNO3(np)*ksatNO2fac
549     c Made ksatNH4 smaller since it is the preferred source
550     ksatNH4(np) = ksatNO3(np)*ksatNH4fac
551     ksatFeT(np) = ksatPO4(np)*R_FeP(np)
552     ksatSi(np) = val_ksatsi
553    
554     #ifndef GEIDER
555     cNEW Light parameters:
556     c ksatPAR {0.1 - 1.3}
557     c 0.35=Av High Light Adapted, 0.8=Av Low Light Adapted
558     c kinhib {0.0 - 3.0}
559     c 0.5 =Av High Light Adapted, 2.0=Av Low Light Adapted
560     c High Light Groups for Large size:
561     if(physize(np) .eq. 1.0 _d 0)then
562     RandNo = darwin_random_normal(myThid)
563     ksatPAR(np) = abs(Bigksatpar+Bigksatparstd*RandNo)
564    
565     RandNo = darwin_random_normal(myThid)
566     kinhib(np) = abs(Bigkinhib+Bigkinhibstd*RandNo)
567     else
568     c QQ remove someday
569     RandNo = darwin_random(myThid)
570     c Low Light Groups for Small size:
571     RandNo = darwin_random_normal(myThid)
572     ksatPAR(np) = abs(smallksatpar+smallksatparstd*RandNo)
573    
574     RandNo = darwin_random_normal(myThid)
575     kinhib(np) = abs(smallkinhib+smallkinhibstd*RandNo)
576     endif
577     #ifdef TWO_SPECIES_SETUP
578     if(physize(np) .eq. 1.0 _d 0)then
579     ksatPAR(np) = abs(Bigksatpar)
580     kinhib(np) = abs(Bigkinhib)
581     else
582     ksatPAR(np) = abs(smallksatpar)
583     kinhib(np) = abs(smallkinhib)
584     endif
585     #endif
586     #ifdef NINE_SPECIES_SETUP
587     if(physize(np) .eq. 1.0 _d 0)then
588     ksatPAR(np) = abs(Bigksatpar)
589     kinhib(np) = abs(Bigkinhib)
590     else
591     ksatPAR(np) = abs(smallksatpar)
592     kinhib(np) = abs(smallkinhib)
593     endif
594     if (np.eq.5) then
595     kinhib(np) = 6.0 _d 0
596     endif
597     if (np.eq.9) then
598     kinhib(np) = 0.5 _d 0
599     endif
600     #endif
601     write(msgBuf,'(A,I4,A,1P1G24.15E3)')
602     & 'generate Phyto: np = ',np,' ksatPAR =', ksatPAR(np)
603     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
604     & SQUEEZE_RIGHT , mythid)
605     write(msgBuf,'(A,I4,A,1P1G24.15E3)')
606     & 'generate Phyto: np = ',np,' kinhib =', kinhib(np)
607     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
608     & SQUEEZE_RIGHT , mythid)
609     #endif
610    
611     #ifdef GEIDER
612     RandNo = darwin_random(myThid)
613     c big/small phyto growth rates..
614     if(physize(np) .eq. 1.0 _d 0)then
615     growthdays = Biggrow +Randno*Biggrowrange
616     else
617     growthdays = Smallgrow +RandNo*Smallgrowrange
618     end if
619     c but diazotrophs always slower due to energetics
620     if(diazotroph(np) .eq. 1.0 _d 0) then
621     growthdays = growthdays * diaz_growfac
622     endif
623     c cocco have slower growth than diatom
624     if (diacoc(np).eq.2. _d 0) then
625     growthdays= growthdays * 1.3 _d 0
626     endif
627     #ifdef TWO_SPECIES_SETUP
628     if(physize(np) .eq. 1.0 _d 0)then
629     growthdays = Biggrow
630     else
631     growthdays = Smallgrow
632     end if
633     #endif
634     #ifdef NINE_SPECIES_SETUP
635     if(physize(np) .eq. 1.0 _d 0)then
636     growthdays = Biggrow
637     else
638     growthdays = Smallgrow
639     end if
640     c but diazotrophs always slower due to energetics
641     if(diazotroph(np) .eq. 1.0 _d 0) then
642     growthdays = growthdays * diaz_growfac
643     endif
644     c cocco have slower growth than other large
645     if (diacoc(np).eq.2. _d 0) then
646     growthdays= growthdays * 1.3 _d 0
647     endif
648     c diatom has faster thatn other large
649     if (diacoc(np).eq.1. _d 0) then
650     growthdays= growthdays * 1.0 _d 0 ! 0.95 _d 0
651     endif
652     #endif
653     c now convert to a growth rate
654     if (growthdays.gt.0. _d 0) then
655     pcmax(np) = 1.0 _d 0/(growthdays*pday)
656     else
657     pcmax(np) = 0. _d 0
658     endif
659     c
660     c photo-inhibition
661     #ifdef WAVEBANDS
662     c only LL Pro are inhibited
663     if (ap_type(np).eq.4) then
664     inhibcoef_geid(np) = inhibcoef_geid_val
665     else
666     inhibcoef_geid(np) = 0. _d 0
667     endif
668     #else
669     c no inhibition
670     if(physize(np) .eq. 1.0 _d 0)then
671     inhibcoef_geid(np) = 0. _d 0
672     else
673     inhibcoef_geid(np) = 0. _d 0 !inhibcoef_geid_val
674     endif
675     #endif
676     c
677     RandNo = darwin_random(myThid)
678    
679     c big/small phyto PI slope (chl specific)
680     c if(physize(np) .eq. 1.0 _d 0)then
681     c alphachl(np) = Bigalphachl +Randno*Bigalphachlrange
682     c else
683     c alphachl(np) = Smallalphachl +RandNo*Smallalphachlrange
684     c end if
685    
686     c ANNA gieder via mQyield instead of alpha
687     c big/small phyto Maximum Quantum Yield
688     if(physize(np) .eq. 1.0 _d 0)then
689     mQyield(np) = BigmQyield +Randno*BigmQyieldrange
690     else
691     mQyield(np) = SmallmQyield +RandNo*SmallmQyieldrange
692     end if
693     #ifdef TWO_SPECIES_SETUP
694     if(physize(np) .eq. 1.0 _d 0)then
695     mQyield(np) = BigmQyield
696     else
697     mQyield(np) = SmallmQyield
698     end if
699     #endif
700     #ifdef NINE_SPECIES_SETUP
701     if(physize(np) .eq. 1.0 _d 0)then
702     mQyield(np) = BigmQyield
703     else
704     mQyield(np) = SmallmQyield
705     end if
706     #endif
707     #ifdef WAVEBANDS
708     c ANNA for wavebands only, re-set mQyield to be constant for all np's
709     c ANNA i.e. let alpha vary only with aphy_chl_ps
710     c ANNA value is mean of vals for big and small.
711     mQyield(np) = 4.0 _d -5
712     #endif
713    
714     RandNo = darwin_random(myThid)
715     c big/small phyto C:Chl max
716     if(physize(np) .eq. 1.0 _d 0)then
717     chl2cmax(np) = Bigchl2cmax +Randno*Bigchl2cmaxrange
718     else
719     chl2cmax(np) = Smallchl2cmax +RandNo*Smallchl2cmaxrange
720     end if
721     #ifdef TWO_SPECIES_SETUP
722     if(physize(np) .eq. 1.0 _d 0)then
723     chl2cmax(np) = Bigchl2cmax
724     else
725     chl2cmax(np) = Smallchl2cmax
726     end if
727     #endif
728     #ifdef NINE_SPECIES_SETUP
729     if(physize(np) .eq. 1.0 _d 0)then
730     chl2cmax(np) = Bigchl2cmax
731     else
732     chl2cmax(np) = Smallchl2cmax
733     end if
734     #endif
735     c ANNA chl2cmin added
736     c chl2cmin(np) = 0.003 _d 0 * 12. _d 0 ! mg Chl a/mmol C
737    
738     write(msgBuf,'(A,I4,A,1P1G24.15E3)')
739     & 'generate Phyto: np = ',np,' pcmax =', pcmax(np)
740     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
741     & SQUEEZE_RIGHT , mythid)
742     c write(msgBuf,'(A,I4,A,1P1G24.15E3)')
743     c & 'generate Phyto: np = ',np,' alphachl =', alphachl(np)
744     c ANNA CHANGED TO MQYIELD from ALPHACHL
745     c ANNA STEPH msgBuf changed for mQyield?
746     write(msgBuf,'(A,I4,A,1P1G24.15E3)')
747     & 'generate Phyto: np = ',np,' mQyield =', mQyield(np)
748     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
749     & SQUEEZE_RIGHT , mythid)
750     write(msgBuf,'(A,I4,A,1P1G24.15E3)')
751     & 'generate Phyto: np = ',np,' chl2cmax =', chl2cmax(np)
752     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
753     & SQUEEZE_RIGHT , mythid)
754     #endif
755    
756     #ifdef DAR_DIAG_CHL
757     if(physize(np) .eq. 1.0 _d 0)then
758     Geider_alphachl(np) = Geider_Bigalphachl
759     Geider_chl2cmax(np) = Geider_Bigchl2cmax
760     Geider_chl2cmin(np) = Geider_Bigchl2cmin
761     else
762     Geider_alphachl(np) = Geider_smallalphachl
763     Geider_chl2cmax(np) = Geider_smallchl2cmax
764     Geider_chl2cmin(np) = Geider_smallchl2cmin
765     end if
766    
767     write(msgBuf,'(A,I4,A,1P1G24.15E3)')
768     & 'generate Phyto: np = ',np,' Geider_alphachl =',
769     & Geider_alphachl(np)
770     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
771     & SQUEEZE_RIGHT , mythid)
772     write(msgBuf,'(A,I4,A,1P1G24.15E3)')
773     & 'generate Phyto: np = ',np,' Geider_chl2cmax =',
774     & Geider_chl2cmax(np)
775     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
776     & SQUEEZE_RIGHT , mythid)
777     #endif
778    
779     RETURN
780     END
781     #endif /*DARWIN*/
782     #endif /*ALLOW_PTRACERS*/
783    
784     c ===========================================================

  ViewVC Help
Powered by ViewVC 1.1.22