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

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

  ViewVC Help
Powered by ViewVC 1.1.22