/[MITgcm]/MITgcm_contrib/darwin2/pkg/monod/monod_init_fixed.F
ViewVC logotype

Annotation of /MITgcm_contrib/darwin2/pkg/monod/monod_init_fixed.F

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


Revision 1.6 - (hide annotations) (download)
Tue Jul 24 16:01:56 2012 UTC (12 years, 11 months ago) by stephd
Branch: MAIN
Changes since 1.5: +7 -1 lines
o new define ONLY_P_CYCLE, to run with reduced number ptracers to
  only look at Phosphorus cycle.
  ORDER: PO4, DOP, ZOO1P,..., ZOO(Nzmax)P, POP, Phy1,...,Phy(npmax), Dummy
   Dummy is initialized with zero, and stands in for all additional
   tracers in the code.

1 stephd 1.6 C $Header: /u/gcmpack/MITgcm_contrib/darwin2/pkg/monod/monod_init_fixed.F,v 1.5 2012/05/31 21:08:25 stephd Exp $
2 stephd 1.2 C $Name: $
3 jahn 1.1
4     #include "CPP_OPTIONS.h"
5     #include "PTRACERS_OPTIONS.h"
6     #include "DARWIN_OPTIONS.h"
7    
8     #ifdef ALLOW_PTRACERS
9     #ifdef ALLOW_MONOD
10    
11     c===============================================================================
12     C===============================================================================
13     CStartofinterface
14     SUBROUTINE MONOD_INIT_FIXED(myThid)
15     C =============== Global data ==========================================
16     C === Global variables ===
17     implicit none
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "PARAMS.h"
21     #include "GRID.h"
22     #include "DYNVARS.h"
23     #include "GCHEM.h"
24     #include "DARWIN_PARAMS.h"
25     #include "MONOD_SIZE.h"
26     #include "MONOD.h"
27     #include "DARWIN_FLUX.h"
28    
29     INTEGER myThid
30     C============== Local variables ============================================
31     C msgBuf - Informational/error meesage buffer
32     CHARACTER*(MAX_LEN_MBUF) msgBuf
33     _RL pday
34     INTEGER i,j,k,bi,bj,nz
35     INTEGER tmp
36     INTEGER prec
37     CHARACTER*(MAX_LEN_MBUF) fn
38     C /--------------------------------------------------------------\
39     C | initialise common block biochemical parameters |
40     C \--------------------------------------------------------------/
41    
42     WRITE(msgBuf,'(A)')
43     &'// ======================================================='
44     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
45     & SQUEEZE_RIGHT, myThid )
46     WRITE(msgBuf,'(A)') '// Darwin loading parameters'
47     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
48     & SQUEEZE_RIGHT, myThid )
49     WRITE(msgBuf,'(A)')
50     &'// ======================================================='
51     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
52     & SQUEEZE_RIGHT, myThid )
53    
54    
55     c ANNA set fixed params for WAVEBANDS
56     #ifdef WAVEBANDS
57     call wavebands_init_fixed(myThid)
58     #endif
59    
60     c c define 1 day in seconds
61     pday = 86400.0 _d 0
62    
63    
64     c attenuation coefficients
65     c ANNA only if not wavebands
66     #ifndef WAVEBANDS
67     k0= 4. _d -2 !atten coefficient water(m^-1)
68     #ifdef GEIDER
69     kc= 4. _d -2 !atten coefficient chl ((mmol chl/m3)-1)
70     #else
71     kc= 4. _d -2*16. _d 0*1. _d 0 !atten coefficient phy((uM m)-1)
72     #endif
73     #endif
74     c ANNA endif
75    
76    
77     c par parameters
78     parfrac= 0.4 _d 0 !fraction Qsw that is PAR
79     parconv= 1. _d 0/0.2174 _d 0 !conversion from W/m2 to uEin/m2/s
80     c for chl
81     chlpmax=40. _d 0 ! mg Chl/mmolP
82     chlpmin=16. _d 0 ! mg Chl/mmolP
83     istar=90. _d 0 ! w/m2
84     c iron related
85     alpfe= 0.04 _d 0 !solubility of Fe dust
86     scav= 0.4 _d 0/(360. _d 0*86400. _d 0) !iron chem scavenging rate (s-1)
87     ligand_tot=1. _d -3 !total ligand (uM)
88     ligand_stab=2. _d 5 !ligand stability rate ratio
89     freefemax = .4 _d -3 ! max free fe
90    
91     #ifdef IRON_SED_SOURCE
92     c iron sediment source
93     depthfesed=1000.0 _d 0 !depth above which to add sediment source
94     fesedflux =1.0 _d 0 * 1.0 _d -3 / (86400.0 _d 0) !iron flux (mmol/m2/s)
95     fesedflux_pcm =0.68 _d 0 * 1.0 _d -3 !iron flux (mmol/m3/s) per
96     c mmol POC/m3/s
97     #endif
98     #ifdef PART_SCAV
99     scav_rat=0.005 _d 0 /(86400.0 _d 0)
100     scav_inter=0.079 _d 0
101     scav_exp=0.58 _d 0
102     #endif
103    
104     c depth for denitrification to start
105     depthdenit=185.0 _d 0
106    
107     c critical oxygen for O2/NO3 remineralization
108     O2crit = 6.0 _d 0 !(Lipschultz et al 1990, DSR 37, 1513-1541)
109     c ratio of no3 to p in denitrification process
110     denit_np = 120.0 _d 0
111    
112     c
113     c oxidation rates for ammonium and nitrite
114     c i.e. Knita ... NH4 -> NO2
115     c i.e. Knitb ... NO2 -> NO3
116     Knita = 1.0 _d 0/(.50 _d 0*pday)
117     Knitb = 1.0 _d 0/(10.0 _d 0*pday)
118     c critical light level (muEin/m2/s) after which oxidation starts
119     PAR0 = 10. _d 0
120     c
121     #ifndef GEIDER
122     c set growth days ...small or big organism?
123     Smallgrow = .7 _d 0
124     Biggrow = .4 _d 0
125     Smallgrowrange = 0. _d 0
126     Biggrowrange = 0. _d 0
127     diaz_growfac = 2. _d 0
128     #endif
129     c set mort days ...small or big organism?
130     Smallmort = 10. _d 0
131     Bigmort = 10. _d 0
132     Smallmortrange = 0. _d 0
133     Bigmortrange = 0. _d 0
134     c set export fraction ...small or big organism?
135     Smallexport = 0.2 _d 0
136     Bigexport = 0.5 _d 0
137     c set sinking rates (m/s)... small or big organism?
138     SmallSink = 0.0 _d 0/pday
139     BigSink = 0.5 _d 0/pday !0.5 _d 0/pday
140     c set parameters for light function for phyto growth
141     #ifndef GEIDER
142     smallksatpar = 0.12 _d 0 ! 0.8 _d 0
143     smallksatparstd = 0.20 _d 0 ! 0.3 _d 0
144     smallkinhib = 6.0 _d 0 ! 2.0 _d 0
145     smallkinhibstd = 0.10 _d 0 ! 0.5 _d 0
146     Bigksatpar = 0.12 _d 0 ! 0.35 _d 0
147     Bigksatparstd = 0.06 _d 0 ! 0.1 _d 0
148     Bigkinhib = 1.0 _d 0 ! 0.5 _d 0
149     Bigkinhibstd = 0.05 _d 0 ! 0.1 _d 0
150     #endif
151     #ifdef GEIDER
152     c for Pcm -- should be growth rates, but using old variables
153     c note these are in terms of days - converted to 1/s later
154     Smallgrow = .7 _d 0
155     Biggrow = .4 _d 0
156     Smallgrowrange = 0. _d 0
157     Biggrowrange = 0. _d 0
158     diaz_growfac = 2. _d 0
159     c
160     smallchl2cmax = 0.2 _d 0 !mg Chl (mmol C)
161     smallchl2cmaxrange = 0.3 _d 0 !mg Chl (mmol C)
162     Bigchl2cmax = 0.5 _d 0 !mg Chl (mmol C)
163     Bigchl2cmaxrange = 0.3 _d 0 !mg Chl (mmol C)
164    
165     c ANNA_Q units for alpha are same as expected: mmol C (mg chla)-1 (uEin)-1 (m)2
166     c smallalphachl = 1. _d -6 !mmol C (uEin/m-2)-1 (mg Chl)-1
167     c smallalphachlrange = 1. _d -6 !mmol C (uEin/m-2)-1 (mg Chl)-1
168     c Bigalphachl = 6. _d -7 !mmol C (uEin/m-2)-1 (mg Chl)-1
169     c Bigalphachlrange = 4. _d -7 !mmol C (uEin/m-2)-1 (mg Chl)-1
170     c ANNA mQyield vals are from alphachl / aphy_chl which for now is 0.02
171     c ANNA ranges for mQyield are same as alphachl but reduced by factor 100
172     smallmQyield = 5. _d -5 !mmol C (uEin)-1
173     smallmQyieldrange = 1. _d -4 !mmol C (uEin)-1
174     BigmQyield = 3. _d -5 !mmol C (uEin)-1
175     BigmQyieldrange = 4. _d -5 !mmol C (uEin)-1
176    
177     c ANNA value of aphy_chl_ave = 0.02 - its the mean of all spectras used as input data
178     aphy_chl_ave = 0.02 _d 0 !m2 (mg chla)-1 (ie. x chla gives absorption m-1)
179    
180     c inhib for Prochl?
181     C inhibcoef_geid_val = 1.2 _d 0 !DUMMY VAL
182     inhibcoef_geid_val = 0 _d 0 !DUMMY VAL
183     #ifdef DYNAMIC_CHL
184     acclimtimescl = 1./(60. _d 0 *60. _d 0 *24. _d 0 * 20. _d 0)
185     #endif
186     #endif
187     c
188    
189     c set temperature function
190     tempcoeff1 = 1. _d 0/3. _d 0
191     tempcoeff2_small = 0.001 _d 0
192     tempcoeff2_big = 0.0003 _d 0
193     tempcoeff3 = 1.04 _d 0
194     tempmax = 30. _d 0 ! 32. _d 0
195     temprange = 32. _d 0 ! 30. _d 0
196     tempnorm = 0.3 _d 0 ! 1. _d 0
197     tempdecay = 4. _d 0
198     c set phosphate half stauration constants .. small or big organism
199     SmallPsat=0.015 _d 0
200     BigPsat=0.035 _d 0
201     ProcPsat=0.01 _d 0
202     UniDzPsat=0.012 _d 0
203     SmallPsatrange=0.02 _d 0
204     BigPsatrange=0.02 _d 0
205     ProcPsatrange=0.005 _d 0
206     UniDzPsatrange=0.02 _d 0
207     c set NH4/NO2 frac, so that NH4/NO2 can be preferred nitrogen source
208     ksatNH4fac=.50 _d 0
209     ksatNO2fac=1.0 _d 0
210     c set prochl lower half-sat (used only for mutants)
211     prochlPsat=.85 _d 0
212     c ammonia and nitrite inhibition
213     sig1 = 4.6 _d 0
214     sig2 = 4.6 _d 0
215     sig3 = 4.6 _d 0
216     ngrowfac = 1. _d 0
217     ilight = 2. _d 0
218     c set si half sat
219     val_ksatsi=1. _d 0
220     c set nutrient ratios for phyto
221     val_R_SiP_diatom=16.0 _d 0 ! 32 for Fanny's runs
222     val_R_NP=16.0 _d 0
223     val_RFeP=1.0 _d -3
224     val_R_NP_diaz=40.0 _d 0
225     val_RFeP_diaz=30.0 _d 0 * val_RFeP
226     val_R_PC=120.0 _d 0
227     val_R_PICPOC=0.8 _d 0
228     #ifdef OLD_GRAZE
229     c grazing hlaf saturation
230     kgrazesat = 0.1 _d 0
231     c set grazing rates .. small or big organism?
232     GrazeFast = 1.0 _d 0/(5.0 _d 0*pday)
233     GrazeSlow = 1.0 _d 0/(30.0 _d 0*pday)
234     c set grazing effeciency
235     GrazeEffsmall=0.6 _d 0
236     GrazeEffbig =0.2 _d 0
237     c set grazing of diatom factor
238     diatomgraz = 0.8 _d 0
239     coccograz = 0.7 _d 0
240     olargegraz = 0.9 _d 0
241     #else
242     c grazing hlaf saturation
243     c kgrazesat = 0.1 _d 0
244     kgrazesat = 0.1 _d 0
245     c phygrazmin = 1 _d -5
246     phygrazmin = 1 _d -10
247     c set grazing rates .. small or big organism?
248     c GrazeFast = 1.0 _d 0/(5.0 _d 0*pday)
249     GrazeFast = 1.0 _d 0/(2.0 _d 0*pday)
250     c GrazeSlow = 1.0 _d 0/(30.0 _d 0*pday)
251     GrazeSlow = 1.0 _d 0/(7.0 _d 0*pday)
252     c set grazing effeciency
253     GrazeEfflow= 0.2 _d 0
254     GrazeEffmod= 0.5 _d 0
255     GrazeEffhi = 0.7 _d 0
256     c set palatibility
257     palathi = 1.0 _d 0
258     palatlo = 0.2 _d 0
259     c set palatibilty diatom factor
260     diatomgraz = 0.7 _d 0
261     coccograz = 0.6 _d 0
262     olargegraz = 1.0 _d 0
263     c set faction graz to POM
264     ExGrazfracbig = 0.8 _d 0
265     ExGrazfracsmall = 0.8 _d 0
266 stephd 1.2 c grazing exponential 1= holling 2, 2=holling 3
267     hollexp=1.0 _d 0
268 jahn 1.1 #endif
269     c set zoo mortality
270     ZoomortSmall = 1.0 _d 0/(30.0 _d 0*pday)
271     ZoomortBig = 1.0 _d 0/(30.0 _d 0*pday)
272 stephd 1.3 ZoomortSmall2 = 0. _d 0
273     ZoomortBig2 = 0. _d 0
274 jahn 1.1 c set zoo exportfrac
275     ZooexfacSmall = 0.2 _d 0
276     ZooexfacBig = 0.7 _d 0
277     c minimum phyto (below which grazing and mortality doesn't happen)
278     c phymin = 1 _d -10
279     c phymin = 1 _d -50
280     phymin = 1 _d -20
281     c DOM remin rates
282     Kdop = 1.0 _d 0/(100.0 _d 0*pday)
283     Kdon = 1.0 _d 0/(100.0 _d 0*pday)
284     KdoFe = 1.0 _d 0/(100.0 _d 0*pday)
285     c Particulate detritus remin rates
286     c z* = wx_sink/Kremin_X
287     c for e-folding length scale, z* = 300 m
288     c choose Kremin_X = 1/30 day-1, wx_sink = 10 m day-1
289     Kpremin_P = 1.0 _d 0/(50.0 _d 0*pday)
290     Kpremin_N = Kpremin_P
291     Kpremin_Fe = Kpremin_P
292     Kpremin_Si = 1.0 _d 0/(300.0 _d 0*pday)
293     c sinking rate for particulate matter (m/s)
294     wp_sink = 10.0 _d 0/pday
295     wn_sink = wp_sink
296     wfe_sink = wp_sink
297     wsi_sink = wp_sink
298    
299     #ifdef ALLOW_CARBON
300     R_OP = 170 _d 0
301     Kdoc = 1.0 _d 0/(100.0 _d 0*pday)
302     Kpremin_C = 1.0 _d 0/(50.0 _d 0*pday)
303     Kdissc = 1.0 _d 0/(300.0 _d 0*pday)
304     wc_sink = wp_sink
305     wpic_sink = 15.0 _d 0/pday
306     permil = 1. _d 0 / 1024.5 _d 0
307     Pa2Atm = 1.01325 _d 5
308     #endif
309    
310 stephd 1.5 #ifdef ALLOW_CDOM
311     fraccdom=2. _d 0 / 100. _d 0
312     cdomdegrd= 1. _d 0 / (200 _d 0 *pday)
313     cdombleach = 1. _d 0 / (15 _d 0 *pday)
314     PARcdom = 20. _d 0
315     rnp_cdom = 16. _d 0
316     rfep_cdom = 1. _d -3
317     rcp_cdom = 120. _d 0
318     cdomcoeff = .1 _d -1 / 1.d -4
319     #endif
320    
321 jahn 1.1 C make sure we have reserved enough space in Ptracers
322     IF ( nCompZooMax .LT. 4 ) THEN
323     WRITE(msgBuf,'(A,A,I3)')
324     & 'MONOD_INIT_FIXED: ERROR: 4 zooplankton components, but ',
325     & 'nCompZooMax = ', nCompZooMax
326     CALL PRINT_ERROR( msgBuf , 1)
327     STOP 'ABNORMAL END: S/R MONOD_INIT_FIXED'
328     ENDIF
329     DO nz = 1,nzmax
330     iZooP (nz) = iZoo + (nz-1)*strideTypeZoo
331 stephd 1.6 #ifdef ONLY_P_CYCLE
332     iZooN (nz) = nptot
333     iZooFe(nz) = nptot
334     iZooSi(nz) = nptot
335     #else
336 jahn 1.1 iZooN (nz) = iZoo + 1*strideCompZoo + (nz-1)*strideTypeZoo
337     iZooFe(nz) = iZoo + 2*strideCompZoo + (nz-1)*strideTypeZoo
338     iZooSi(nz) = iZoo + 3*strideCompZoo + (nz-1)*strideTypeZoo
339 stephd 1.6 #endif
340 jahn 1.1 ENDDO
341     #ifdef ALLOW_CARBON
342     DO nz = 1,nzmax
343     iZooC (nz) = iZoC + (nz-1)
344     ENDDO
345     #endif
346    
347     #ifdef DAR_DIAG_DIVER
348     c only look at grid point with a minimum biomass
349     diver_thresh0=1 _d -12
350     c diver1 - if any type greater than
351     diver_thresh1=1 _d -8
352     c diver2 - if more than this proportion of total biomass
353     diver_thresh2=1 _d -3
354     c diver3 - fraction of biomass to count
355     diver_thresh3=.999 _d 0
356     c diver4 - fraction of maximum species
357     diver_thresh4=1 _d -5
358 jahn 1.4 c threshold on total biomass for contributing to Shannon and Simpson ind
359     c (these become large at very small biomass)
360     shannon_thresh = 1 _d -8 ! mmol P m-3
361 jahn 1.1 #endif
362    
363     c set up diagnostics
364     #ifdef ALLOW_MNC
365     IF ( useMNC ) THEN
366     CALL DARWIN_MNC_INIT( myThid )
367     #ifdef ALLOW_CARBON
368     CALL DIC_MNC_INIT( myThid )
369     #endif
370     ENDIF
371     #endif /* ALLOW_MNC */
372    
373     COJ set up diagnostics
374     #ifdef ALLOW_DIAGNOSTICS
375     IF ( useDIAGNOSTICS ) THEN
376     CALL MONOD_DIAGNOSTICS_INIT( myThid )
377     #ifdef ALLOW_CARBON
378     CALL DIC_DIAGNOSTICS_INIT( myThid )
379     #endif
380     ENDIF
381     #endif /* ALLOW_DIAGNOSTICS */
382     COJ
383    
384    
385    
386     RETURN
387     END
388     C============================================================================
389     #endif
390     #endif
391    

  ViewVC Help
Powered by ViewVC 1.1.22