source: branches/2016/dev_v3.20_2016_platelet/SOURCES/source_3.20/bio.com @ 26

Last change on this file since 26 was 6, checked in by vancop, 8 years ago

initial import of v3.20 /Users/ioulianikolskaia/Boulot/CODES/LIM1D/ARCHIVE/TMP/LIM1D_v3.20/

File size: 14.0 KB
Line 
1!
2!               COMMONS FOR SEA ICE BIOGEOCHEMISTRY
3!               ===================================
4!
5!
6! z_i_bio       : vertical coordinate of the middle of bio-layers
7! deltaz_i_bio  : thickness of the bio-layers
8! c_i_bio       : concentration of tracers in the brines
9! cbu_i_bio     : bulk concentration of tracers in the ice
10! cbub_i_bio    : concentration of tracers in bubbles for bulk ice
11! f_bub         : Gas flux to the atmosphere due to gas bubbles
12! t_i_bio       : temperature in the ice, interpolated on the bio grid
13! s_i_bio       : salinity in the ice, interpolated on the bio grid
14! e_i_bio       : relative brine volume, interpolated on the bio grid
15! c_w_bio       : concentration of tracer in seawater
16
17      REAL(8), DIMENSION(nlay_bio) ::
18     &   z_i_bio,
19     &   deltaz_i_bio,
20     &   t_i_bio,
21     &   s_i_bio,
22     &   e_i_bio,
23     &   diff_br_bio
24
25      REAL(8), DIMENSION(0:nlay_bio) ::
26     &   zb_i_bio
27
28      REAL(8), DIMENSION(ntra_bio_max) ::
29     &   cbu_i_nml,
30     &   c_w_bio,
31     &   ct_i_bio,
32     &   ch_bo_bio,
33     &   ch_si_bio,
34     &   c_s_bio,
35     &   f_su_tra,
36     &   f_bo_tra,
37     &   f_bogr,
38     &   f_sigr,
39     &   fcb,
40     &   fcbp,
41     &   fcsi,
42     &   fcbm,
43     &   fcsu,
44     &   fcb_max,
45     &   fgas,
46     &   gas_trvel,
47     &   f_bub,
48     &   dmol_gas,
49     &   mixr_gas
50
51      INTEGER, DIMENSION(ntra_bio_max) ::
52     &   nn_init      !: switch for init ( 0=from code, 1=conc. conserved, 2=stock conserved, 3=read profile )
53
54      INTEGER ::
55     &   jn_dsi,      !: tracer number for dsi
56     &   jn_din,      !:  ...
57     &   jn_dip,      !:  ...
58     &   jn_aoc,      !:  ...
59     &   jn_eoc,      !:  ...
60     &   jn_dic,      !:  ...
61     &   jn_alk,      !:  ...
62     &   jn_ika,      !:  ...
63     &   jn_oxy,      !:  ...
64     &   jn_arg,      !:  ...
65     &   jn_pco,      !:  ...
66     &   jn_car,      !:  ...
67     &   jn_co2,      !:  ...
68     &   jn_cal
69
70      REAL(8), DIMENSION(ntra_bio_max,nlay_bio) ::
71     &   c_i_bio,
72     &   cbu_i_bio,
73     &   cbub_i_bio,
74     &   c_gtot_i,
75     &   pc_sat,
76     &   diag_divf_bio,
77     &   csat_gas,
78     &   sol_gas
79
80      REAL(8), DIMENSION(ntra_bio_max,0:nlay_bio) ::
81     &   fdiff
82
83      COMMON /bioarrays/
84     &   z_i_bio,
85     &   zb_i_bio,
86     &   deltaz_i_bio,
87     &   t_i_bio,
88     &   s_i_bio,
89     &   e_i_bio,
90     &   diff_br_bio,
91     &   ct_i_bio,
92     &   cbu_i_nml,
93     &   c_w_bio,
94     &   ch_bo_bio,
95     &   ch_si_bio,
96     &   c_s_bio,
97     &   f_su_tra,
98     &   f_bo_tra,
99     &   f_bogr,
100     &   f_sigr,
101     &   fcb,
102     &   fcbp,
103     &   fcsi,
104     &   fcbm,
105     &   fcsu,
106     &   fcb_max,
107     &   fgas,
108     &   f_bub,
109     &   dmol_gas,
110     &   mixr_gas,
111     &   gas_trvel,
112     &   c_i_bio,
113     &   cbu_i_bio,
114     &   cbub_i_bio,
115     &   c_gtot_i,
116     &   pc_sat,
117     &   diag_divf_bio,
118     &   fdiff,
119     &   csat_gas,
120     &   sol_gas
121
122      COMMON /bioini/
123     &   nn_init                  !: type of initialization for bgc tracers
124
125      COMMON/biotrindex/
126     &   jn_dsi,      !: tracer number for dsi
127     &   jn_din,      !:  ...
128     &   jn_dip,      !:  ...
129     &   jn_aoc,      !:  ...
130     &   jn_eoc,      !:  ...
131     &   jn_dic,      !:  ...
132     &   jn_alk,      !:  ...
133     &   jn_ika,      !:  ...
134     &   jn_oxy,      !:  ...
135     &   jn_arg,      !:  ...
136     &   jn_pco,      !:  ...
137     &   jn_car,      !:  ...
138     &   jn_co2,      !:  ...
139     &   jn_cal
140
141      COMMON /biophyparams/
142     &   nn_bio_opt       ,       !: type of biological formulation
143     &   astar_alg        ,       !: specific absorption coeff (m-1 / (mg chla m-3))
144     &   fdet_alg         ,       !: fraction of detrital absorption compared to algal absorption
145     &   nn_phs           ,       !: type of photosynthesis
146     &   nn_lys           ,       !: type of lysis
147     &   nn_rem           ,       !: type of remineralization
148     &   pp_presc         ,       !: prescribed primary production
149     &   h_skel           ,       !: thickness of the biological layer ('SL' & 'BAL' only)
150     &   e_thr_bal        ,       !: thickness of the biological layer ('SL' & 'BAL' only)
151     &   h_bio            ,       !: thickness of the biological layer ('SL' & 'BAL' only)
152     &   brines_ar                !: brines aspect ratio (for gas exchange)
153
154      REAL(8), DIMENSION(ntra_bio_max) ::
155     &   mt_i_bio_init, mt_i_bio_final,
156     &   mt_w_bio_init, mt_w_bio_final,
157     &   mt_i_bio
158     
159      REAL(8), DIMENSION(ntra_bio_max) ::
160     &   mt_i_gas_init, mt_i_gas_final,
161     &   mt_i_gas
162
163      REAL(8), DIMENSION(ntra_bio_max) ::
164     &   mt_i_carb_init, mt_i_carb_final,
165     &   mt_i_carb
166
167      REAL(8), DIMENSION(ntra_bio_max,nlay_bio) ::
168     &   m_i_bio_init, m_i_bio_final
169
170
171      COMMON/bioconserv/
172     &   mt_i_bio_init, mt_i_bio_final,
173     &   mt_w_bio_init, mt_w_bio_final,     
174     &   mt_i_bio,
175     &   mt_i_gas_init, mt_i_gas_final,
176     &   mt_i_gas,
177     &   mt_i_carb_init, mt_i_carb_final,
178     &   mt_i_carb,
179     &   m_i_bio_init, m_i_bio_final
180
181      LOGICAL ::
182     &   flag_diff(ntra_bio_max)     , !: flag which describes diffusability of a tracer
183     &   flag_active(ntra_bio_max)   , !: describe whether a tracer is assumed active or not
184     &   flag_adsorb(ntra_bio_max)   , !: adsorbed or not ?
185     &   ln_trbo                 , !: activate tracer basal entrapment
186     &   ln_trsi                 , !: activate tracer surface entrapment
187     &   ln_trdiff               , !: activate tracer diffusion
188     &   ln_trremp               , !: activate tracer remapping
189     &   ln_lim_dsi              , !: activate DSi limitation
190     &   ln_lim_no3              , !: activate NO3 limitation
191     &   ln_lim_po4              , !: activate PO4 limitation
192     &   ln_lim_lig              , !: activate light limitation
193     &   ln_lim_tem              , !: activate temperature inhibition
194     &   ln_lim_sal              , !: activate brine salinity inhibition
195     &   ln_lys                  , !: activate lysis
196     &   ln_rem                  , !: activate remineralization
197     &   ln_syn                  , !: activate diatom synthesis
198     &   ln_bubform              , !: activate gas buble formation
199     &   ln_bubrise              , !: activate gas buble ascent
200     &   ln_gasflux              , !: activate gas flux to atm
201     &   ln_carbon               , !: activate carbon cycle
202     &   ln_ikaite                 !: activate CaCO3
203     
204      INTEGER(4) ::
205     &   nn_bio_opt              , !: type of biological model (0=NP, 1=NPD Redfield)
206     &   nn_diff(ntra_bio_max)   , !: switch for diffusion (0=no diffus, 1=diffus, 2=reset brine cc to zero)
207     &   nn_remp(ntra_bio_max)   , !: switch for remapping (0=no remap , 1=diffus. remap, 2=squeeze remap.)
208     &   nn_phs                  , !: switch for photosynthesis (1=Ek, 2=chl-C, 3=chl-C+T/S, 4=variable chl-C)
209     &   nn_lys                  , !: type of loss term (1=prescribed, 2=T-dependent)
210     &   nn_rem                  , !: type of remineralization (1=prescribed, 2=T-dependent)
211     &   nn_lim_sal              , !: switch for the type of brine salinity inhibition
212     &   ntra_bio                , !: maximum number of tracers
213     &   layer_00                , !: index of the first layer
214     &   nn_carbonate              !: type of carbonate constants (1=Roy, 2=mehrbach)
215
216      REAL(8) ::
217     &   bub_form_rate           ,
218     &   bub_diss_rate           ,
219     &   h_bl_gas                ,
220     &   e_thr_bubrise           ,
221     &   e_thr_gasflux           ,
222     &   sursat_gas              ,
223     &   caco3_time               
224
225      COMMON /bioswi/
226     &   flag_diff               ,
227     &   flag_active             ,
228     &   flag_adsorb             ,
229     &   ln_trbo                 ,
230     &   ln_trsi                 ,
231     &   ln_trdiff               ,
232     &   ln_trremp               ,
233     &   ln_lim_dsi              ,
234     &   ln_lim_no3              ,
235     &   ln_lim_po4              ,
236     &   ln_lim_lig              ,
237     &   ln_lim_tem              ,
238     &   ln_lim_sal              ,
239     &   ln_lys                  ,
240     &   ln_rem                  ,
241     &   ln_syn                  ,
242     &   nn_diff                 ,
243     &   nn_remp                 ,
244     &   nn_lim_sal              ,
245     &   ntra_bio                ,
246     &   layer_00                ,
247     &   nn_carbonate            ,
248     &   i_gasflux               ,
249     &   ln_bubform              ,
250     &   ln_bubrise              ,
251     &   ln_gasflux              ,
252     &   ln_carbon               ,
253     &   ln_ikaite               ,
254     &   bub_form_rate           ,
255     &   bub_diss_rate           ,
256     &   h_bl_gas                ,
257     &   e_thr_bubrise           ,
258     &   e_thr_gasflux           ,
259     &   sursat_gas              ,
260     &   caco3_time               
261
262      !-----------------------
263      ! Brine characteristics
264      !-----------------------
265      REAL(8), DIMENSION(nlay_bio) ::  ! Brine characteristics
266     &   tc_bio                  ,  ! Celsius temperature on the bio-grid
267     &   sbr_bio                 ,  ! brine salinity on the bio-grid
268     &   rhobr_bio                  ! brine density on the bio-grid
269
270      COMMON/biobrine/
271     &   tc_bio                  ,
272     &   sbr_bio                 ,
273     &   rhobr_bio                 
274
275      !---------------------
276      ! Carbonate chemistry
277      !---------------------
278      REAL(8), DIMENSION(nlay_bio) ::  ! Carbonate chemistry diagnostics
279     &   CO2aq                   , ! aqueous CO2, bulk concentration
280     &   CO32m                   , ! carbonate (CO32-), bulk concentration
281     &   hCO3m                   , ! bicarbonate (HCO3-), bulk concentration
282     &   pH                      , ! pH, brine
283     &   pCO2                      ! pCO2, brine
284
285      COMMON/biocarbchem/       
286     &   CO2aq                   , ! aqueous CO2, bulk concentration
287     &   CO32m                   , ! carbonate (CO32-), bulk concentration
288     &   hCO3m                   , ! bicarbonate (HCO3-), bulk concentration
289     &   pH                      , ! pH, brine
290     &   pCO2                      ! pCO2, brine
291
292      CHARACTER(len=64) ::
293     &   biotr_i_nam(ntra_bio_max)  , !:
294     &   biotr_i_typ(ntra_bio_max)    !:
295
296      CHARACTER(len=64) ::         
297     &   biotr_i_uni(ntra_bio_max)
298
299      CHARACTER(len=2) ::         
300     &   c_grid
301
302      CHARACTER(len=3) ::
303     &   c_read_name(ntra_bio_max),
304     &   c_nc_name(ntra_bio_max)
305         
306      COMMON /biochar/
307     &   biotr_i_nam,
308     &   biotr_i_typ,
309     &   biotr_i_uni,
310     &   c_grid,
311     &   c_read_name,
312     &   c_nc_name   
313
314      COMMON /biomass/
315     &   chla_i_bio(nlay_bio)     !: chlorophyll a concentration
316
317      REAL(8) ::
318     &   ika_rate(nlay_bio)      , !: CaCO3 precipitation / dissolution rate (mmol/m3/s)
319     &   ika_omega(nlay_bio)     , !: CACO3 saturation state (-)
320     &   syn_bio(nlay_bio)       , !: synthesis
321     &   lys_bio(nlay_bio)       , !: lysis
322     &   exu_bio(nlay_bio)       , !: exudation
323     &   rsp_bio(nlay_bio)       , !: respiration
324     &   rem_bio(nlay_bio)       , !: remineralization
325     &   lim_lig(nlay_bio)       , !: light limitation
326     &   lim_dsi(nlay_bio)       , !: DSi limitation
327     &   lim_no3(nlay_bio)       , !: NO3 limitation
328     &   lim_po4(nlay_bio)       , !: PO4 limitation
329     &   lim_tem(nlay_bio)       , !: temperature limitation
330     &   lim_sal(nlay_bio)       , !: salt limitation
331     &   chlC_bio(nlay_bio)        !: interactive chl-a / C ratio
332
333      COMMON /biosources/
334     &   ika_rate                , !:
335     &   ika_omega               , !:
336     &   syn_bio                 , !:
337     &   lys_bio                 , !:
338     &   exu_bio                 , !:
339     &   rsp_bio                 , !:
340     &   rem_bio                 , !:
341     &   lim_lig                 , !:
342     &   lim_dsi                 , !:
343     &   lim_no3                 , !:
344     &   lim_po4                 , !:
345     &   lim_tem                 , !:
346     &   lim_sal                 , !:
347     &   chlC_bio                  !:
348
349      COMMON /biorad/             
350     &   par_bio(nlay_bio)         !: Photosynthetically available radiation
351                                   !: (flux micromol quanta m-2 s-1)
352      !---------------------------------------
353      ! Constants and parameters of the model
354      !---------------------------------------
355      REAL(8) ::
356     &   mumax_bio               , !: maximum specific growth (s-1)
357     &   klys_bio                , !: autolysis rate (s-1)
358     &   ek_bio                  , !: light adaptation micrmol quanta m-2 s-1
359     &   alpha_bio               , !: photosynthetic efficiency (gC/gchla/s-1/(muE/m2/s))
360     &   khs_si_bio              , !: half sat for Si uptake (mmol m-3)
361     &   khs_n_bio               , !: half sat for N uptake (mmol m-3)
362     &   khs_p_bio               , !: half sat for P uptake (mmol m-3)
363     &   frem_bio                , !: fraction of Si loss that is remineralized (-)
364     &   krem_bio                , !: carbon remineralization time constant (s-1)
365     &   krsp_bio                , !: carbon respiration time constant
366     &   rg_bio                  , !: temperature coefficient for diatom synthesis (deg C-1)
367     &   rg_bac                  , !: temperature coefficient for bacterial processes (deg C-1)
368     &   lim_sal_wid             , !: width of the limitation function (case 4)
369     &   lim_sal_smax            , !: salinity at which limitation function is 1 (case 4)
370     &   chla_c                  , !: Chlorophyll-to-carbon ratio
371     &   Estar                   , !: PAR level of minimum Chl/C
372     &   si_c                    , !: Si cell quota in diatoms
373     &   no3_c                   , !: N cell quota in diatoms
374     &   po4_c                   , !: N cell quota in diatoms
375     &   oxy_c                   , !: Oxygen cell quota in diatoms
376     &   c_molar                   !: carbon molar mass
377
378      COMMON /bioparams/
379     &   mumax_bio, klys_bio, ek_bio, alpha_bio,
380     &   khs_si_bio, khs_n_bio, khs_p_bio, frem_bio,
381     &   krem_bio, krsp_bio,
382     &   rg_bio, rg_bac, chla_c, Estar, si_c, no3_c, po4_c, oxy_c,
383     &   lim_sal_wid, lim_sal_smax, c_molar
384
Note: See TracBrowser for help on using the repository browser.