/[MITgcm]/MITgcm/pkg/bling/bling_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/bling/bling_readparms.F

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


Revision 1.11 - (show annotations) (download)
Wed Aug 9 15:23:39 2017 UTC (6 years, 8 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, HEAD
Changes since 1.10: +6 -2 lines
replace CLOSE(nmlfileUnit) with CLOSE(nmlfileUnit,STATUS='DELETE') to remove
scratchfiles after closing, except for SINGLE_DISK_IO, when everything
stays the same

1 C $Header: /u/gcmpack/MITgcm/pkg/bling/bling_readparms.F,v 1.10 2017/03/16 17:03:26 mmazloff Exp $
2 C $Name: BASE $
3
4 #include "BLING_OPTIONS.h"
5 #ifdef ALLOW_EXF
6 # include "EXF_OPTIONS.h"
7 #endif
8
9 CBOP
10 SUBROUTINE BLING_READPARMS( myThid )
11
12 C *========================================================*
13 C | subroutine bling_readparms
14 C | o Initialise and read parameters for BLING model
15 C *========================================================*
16
17 implicit none
18
19 C === Global variables ===
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #ifdef USE_EXFCO2
24 # ifdef USE_EXF_INTERPOLATION
25 # ifdef ALLOW_EXCH2
26 # include "W2_EXCH2_SIZE.h"
27 # include "W2_EXCH2_TOPOLOGY.h"
28 # endif /* ALLOW_EXCH2 */
29 # include "SET_GRID.h"
30 # endif /* USE_EXF_INTERPOLATION */
31 # include "EXF_PARAM.h"
32 # include "EXF_CONSTANTS.h"
33 #endif /* USE_EXFCO2 */
34 #include "BLING_VARS.h"
35
36 C === Routine arguments ===
37 C myThid :: My Thread Id. number
38 INTEGER myThid
39 CEOP
40
41 #ifdef ALLOW_BLING
42
43 C === Local variables ===
44 C msgBuf :: Informational/error message buffer
45 C errCount :: error counter
46 C iUnit :: Work variable for IO unit number
47 CHARACTER*(MAX_LEN_MBUF) msgBuf
48 INTEGER errCount
49 INTEGER iUnit
50
51 C ==========================================================
52 C Abiotic parameters
53 C ==========================================================
54
55 NAMELIST /ABIOTIC_PARMS/
56 & permil, Pa2Atm
57
58 C ==========================================================
59 C BLING parameters
60 C ==========================================================
61
62 NAMELIST /BIOTIC_PARMS/
63 & pivotal,
64 & Pc_0,
65 & Pc_0_diaz,
66 & lambda_0,
67 & chl_min,
68 & CtoN,
69 & NO3toN,
70 & HtoC,
71 & O2toN,
72 & CatoN,
73 & masstoN,
74 & alpha_photo,
75 & theta_Fe_max_hi,
76 & theta_Fe_max_lo,
77 & gamma_irr_mem,
78 & gamma_DON,
79 & gamma_DOP,
80 & gamma_POM,
81 & k_Fe,
82 & k_Fe_diaz,
83 & k_O2,
84 & k_NO3,
85 & k_PO4,
86 & k_PtoN,
87 & k_FetoN,
88 & kFe_eq_lig_max,
89 & kFe_eq_lig_min,
90 & kFe_eq_lig_Femin,
91 & kFe_eq_lig_irr,
92 & kFe_org,
93 & kFe_inorg,
94 & PtoN_min,
95 & PtoN_max,
96 & FetoN_min,
97 & FetoN_max,
98 & FetoC_sed,
99 & remin_min,
100 & oxic_min,
101 & ligand,
102 & kappa_eppley,
103 & kappa_eppley_diaz,
104 & kappa_remin,
105 & ca_remin_depth,
106 & phi_DOM,
107 & phi_sm,
108 & phi_lg,
109 & phi_dvm,
110 & sigma_dvm,
111 & wsink0z,
112 & wsink0,
113 & wsinkacc,
114 & parfrac,
115 & alpfe,
116 & k0,
117 & epsln
118
119 C ==========================================================
120 C BLING forcing
121 C ==========================================================
122
123 NAMELIST /BLING_FORCING/
124 & bling_windFile, bling_atmospFile, bling_iceFile,
125 & bling_ironFile, bling_silicaFile,
126 & bling_psmFile, bling_plgFile, bling_PdiazFile,
127 & bling_forcingPeriod, bling_forcingCycle,
128 & bling_pCO2, river_conc_trac,
129 & bling_Pc_2dFile, bling_Pc_2d_diazFile,
130 & bling_alpha_photo2dFile,bling_phi_DOM2dFile,
131 & bling_k_Fe2dFile, bling_k_Fe_diaz2dFile,
132 & bling_gamma_POM2dFile, bling_wsink0_2dFile,
133 & bling_phi_sm2dFile,bling_phi_lg2dFile
134 #ifdef USE_EXFCO2
135 & , apco2file, apco2startdate1, apco2startdate2,
136 & apco2RepCycle, apco2period, apco2StartTime,
137 & exf_inscal_apco2, exf_outscal_apco2, apco2const,
138 & apco2_exfremo_intercept, apco2_exfremo_slope
139 #ifdef USE_EXF_INTERPOLATION
140 & , apco2_lon0, apco2_lon_inc, apco2_lat0, apco2_lat_inc,
141 & apco2_nlon, apco2_nlat, apco2_interpMethod
142 #endif /* USE_EXF_INTERPOLATION */
143 #endif
144
145 C ==========================================================
146 C secperday :: seconds in a day = 24*60*60
147 C permil :: set carbon mol/m3 <---> mol/kg conversion factor
148 C default permil = 1024.5 kg/m3
149 C Pa2Atm :: Conversion factor for atmospheric pressure pLoad
150 C (when coupled to atmospheric model) into Atm.
151 C Default assumes pLoad in Pascal
152 C 1 Atm = 1.01325e5 Pa = 1013.25 mb
153 C pivotal :: Pivotal phytoplankton biomass
154 C Pc_0 :: Maximum phytoplankton carbon-specific growth rate at 0C
155 C Pc_0_diaz :: Maximum diazotroph carbon-specific growth rate at 0C
156 C lambda_0 :: Carbon-specific phytoplankton mortality rate
157 C chl_min :: minimum chlorophyll concentration [ug kg-1]
158 C CtoN :: Carbon to nitrogen ratio in organic matter
159 C NO3toN ::
160 C HtoC ::
161 C O2toN :: Oxygen to nitrogen for biological activity
162 C CatoN :: Calcium to nitrogen uptake by small phyto
163 C masstoN ::
164 C alpha_photo :: [g C g Chl-1 m2 W-1 s-1]
165 C theta_Fe_max_hi :: Maximum Chl:c ratio, abundant iron
166 C theta_Fe_max_lo :: Maximum Chl:c ratio, extreme iron limitation
167 C gamma_irr_mem :: Photoadaptation time scale
168 C gamma_DON :: Decay timescale of DON
169 C gamma_DOP :: Decay timescale of DOP
170 C gamma_POM ::
171 C k_Fe :: Dissolved Fe uptake half-saturation constant
172 C k_Fe_diaz :: Dissolved Fe uptake half-saturation constant for diazotrophs
173 C k_O2 :: Half-saturation constant for aerobic respiration
174 C k_NO3 :: Nitrate uptake half-saturation constant
175 C k_PO4 :: Phosphate uptake half-saturation constant
176 C k_PtoN :: Half-saturation cellular P:N
177 C k_FetoN :: Half-saturation cellular Fe:N
178 C kFe_eq_lig_max :: Maximum Fe-ligand stability constant
179 C kFe_eq_lig_min :: Minimum Fe-ligand stability constant
180 C kFe_eq_lig_Femin :: Constant having to do with photodissociation
181 C kFe_eq_lig_irr :: Iron ligand stability constant
182 C kFe_org :: Organic-matter dependent scavenging rate
183 C kFe_inorg :: Inorganic scavenging rate
184 C PtoN_min :: Minimum P:N uptake ratio
185 C PtoN_max :: Maximum P:N uptake ratio
186 C FetoN_min :: Minimum Fe:N uptake ratio
187 C FetoN_max :: Maximum Fe:N uptake ratio
188 C FetoC_sed :: Fe:P in sediments
189 C remin_min :: Minimum anaerobic respiration rate
190 C oxic_min :: Minimum O2 concentration for aerobic respiration
191 C ligand :: Ligand concentration
192 C kappa_eppley :: Temperature dependence of growth
193 C kappa_eppley_diaz:: Temperature dependence of growth for diazotrophs
194 C kappa_remin :: Temperature dependence of remineralization
195 C ca_remin_depth :: CaCO3 remineralization lengthscale
196 C phi_DOM :: Fraction of non-sinking production to DOM
197 C phi_sm :: Fraction of small phytoplankton biomass converted to detritus
198 C phi_lg :: Fraction of large phytoplankton biomass converted to detritus
199 C phi_dvm ::
200 C sigma_dvm ::
201 C wsink0z :: Depth at which sinking rate starts increasing
202 C wsink0 :: Initial sinking rate
203 C wsinkacc :: Acceleration rate of sinking with depth
204 C parfrac :: fraction of Qsw avail for photosynthesis
205 C alpfe :: solubility of aeolian iron
206 C k0 :: Light attentuation coefficient
207 C epsln :: a very small number
208
209 _RL secperday
210 integer k
211 #ifdef USE_EXF_INTERPOLATION
212 INTEGER gridNx, gridNy
213 INTEGER j
214 _RL inp_lon0, inp_lat0, inp_dLon, inp_dLat
215 #endif
216
217 _BEGIN_MASTER(myThid)
218 errCount = 0
219
220 C ==========================================================
221 C Default values
222
223 secperday = 86400. _d 0
224 permil = 1. _d 0 / 1024.5 _d 0
225 Pa2Atm = 1.01325 _d 5
226 CtoN = 6.75 _d 0
227 HtoC = 48. _d 0 / 106. _d 0
228 O2toN = CtoN * (1. _d 0 + 0.25 _d 0 * HtoC)
229 & + 2. _d 0
230 NO3toN = CtoN * (1. _d 0 + 0.25 _d 0 * HtoC)
231 & * 0.8 _d 0 + 0.6 _d 0
232 CatoN = CtoN * 0.015 _d 0
233 masstoN = CtoN * 12.001 _d 0
234 pivotal = 1.9 _d -3 / 1028. _d 0 / CtoN / permil
235 Pc_0 = 1.7 _d -5
236 Pc_0_diaz = 0.01 _d -5
237 lambda_0 = 0.19 _d 0 / secperday
238 chl_min = 1. _d -5
239 alpha_photo = 0.7 _d -5 * 2.77 _d 18 / 6.022 _d 17
240 theta_Fe_max_hi = 0.04 _d 0
241 theta_Fe_max_lo = 0.01 _d 0
242 gamma_irr_mem = 1. _d 0 / secperday
243 gamma_DON = 0.25 _d 0 / (365.25 _d 0 * secperday)
244 gamma_DOP = 0.5 _d 0 / (365.25 _d 0 * secperday)
245 gamma_POM = 0.12 _d 0 / secperday
246 k_Fe = 1.6 _d -10 / permil
247 k_Fe_diaz = 7. _d -10 / permil
248 k_O2 = 20. _d -6 / permil
249 k_NO3 = 2. _d -6 / permil
250 k_PO4 = 1. _d -8 / permil
251 k_PtoN = 1.5 _d -6 / permil
252 k_FetoN = 8. _d -10 / permil
253 PtoN_min = 1. / 28.
254 PtoN_max = 1. / 9.
255 FetoN_min = 2. _d -6 * 6.75
256 FetoN_max = 25. _d -6 * 6.75
257 FetoC_sed = 1. _d -4
258 kFe_eq_lig_max = 8.0 _d 10 * permil
259 kFe_eq_lig_min = 8.0 _d 9 * permil
260 kFe_eq_lig_Femin = 0.05 _d -9 / permil
261 kFe_eq_lig_irr = 0.1 _d 0
262 kFe_org = 0.5 _d 0 / secperday * permil**(0.58)
263 kFe_inorg = 1. _d 3 / secperday * permil**(0.5)
264 remin_min = 0.15 _d 0
265 oxic_min = 1. _d -6 / permil
266 Ligand = 1. _d -9 / permil
267 kappa_eppley = 0.063 _d 0
268 kappa_eppley_diaz = 0.18 _d 0
269 kappa_remin = -0.032 _d 0
270 ca_remin_depth = 1343. _d 0
271 phi_DOM = 0.1 _d 0
272 phi_sm = 0.18 _d 0
273 phi_lg = 1. _d 0
274 phi_dvm = 0.2 _d 0
275 sigma_dvm = 40.0 _d 0
276 wsink0z = 80. _d 0
277 wsink0 = 16. _d 0 / secperday
278 wsinkacc = 0.05 _d 0 / secperday
279 parfrac = 0.4 _d 0
280 alpfe = 0.01 _d 0
281 k0 = 0.04 _d 0
282 epsln = 1. _d -30
283
284 bling_windFile = ' '
285 bling_atmospFile= ' '
286 bling_iceFile = ' '
287 bling_ironFile = ' '
288 bling_silicaFile= ' '
289 bling_psmFile = ' '
290 bling_plgFile = ' '
291 bling_pdiazFile = ' '
292 bling_pCO2 = 278. _d -6
293 DO k=1,8
294 river_conc_trac(k) = 0. _d 0
295 ENDDO
296 bling_Pc_2dFile = ' '
297 bling_Pc_2d_diazFile = ' '
298 bling_alpha_photo2dFile= ' '
299 bling_k_Fe2dFile = ' '
300 bling_k_Fe_diaz2dFile = ' '
301 bling_gamma_POM2dFile = ' '
302 bling_wsink0_2dFile = ' '
303 bling_phi_DOM2dFile = ' '
304 bling_phi_sm2dFile = ' '
305 bling_phi_lg2dFile = ' '
306
307 #ifdef USE_EXFCO2
308 apco2startdate1 = 0
309 apco2startdate2 = 0
310 apco2StartTime = UNSET_RL
311 apco2period = 0.0 _d 0
312 apco2RepCycle = repeatPeriod
313 apco2const = 0.0 _d 0
314 apco2_exfremo_intercept = 0.0 _d 0
315 apco2_exfremo_slope = 0.0 _d 0
316 apco2file = ' '
317 exf_inscal_apco2 = 1. _d 0
318 exf_outscal_apco2 = 1. _d 0
319 #ifdef USE_EXF_INTERPOLATION
320 C-- set default input location to match (in case of simple Lat-Long grid)
321 C model grid cell-center position (leading to trivial interpolation)
322 inp_lon0 = xgOrigin + delX(1)*exf_half
323 inp_lat0 = ygOrigin + delY(1)*exf_half
324 inp_dLon = delX(1)
325 inp_dLat = delY(1)
326 apco2_lon0 = inp_lon0
327 apco2_lat0 = inp_lat0
328 apco2_nlon = gridNx
329 apco2_nlat = gridNy
330 apco2_lon_inc = inp_dLon
331 DO j=1,MAX_LAT_INC
332 IF (j.LT.gridNy) THEN
333 inp_dLat = (delY(j) + delY(j+1))*exf_half
334 ELSE
335 inp_dLat = 0.
336 ENDIF
337 apco2_lat_inc(j) = inp_dLat
338 ENDDO
339 #endif /* USE_EXF_INTERPOLATION */
340 #endif
341
342 C default periodic forcing to same as for physics
343 bling_forcingPeriod = externForcingPeriod
344 bling_forcingCycle = externForcingCycle
345
346 WRITE(msgBuf,'(A)') ' BLING_READPARMS: opening data.bling'
347 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
348 I SQUEEZE_RIGHT, myThid )
349
350 CALL OPEN_COPY_DATA_FILE( 'data.bling', 'BLING_READPARMS',
351 O iUnit, myThid )
352
353 C-- Read parameters from open data file:
354
355 C- Abiotic parameters
356 READ(UNIT=iUnit,NML=ABIOTIC_PARMS)
357
358 C- BLING parameters
359 READ(UNIT=iUnit,NML=BIOTIC_PARMS)
360
361 C- forcing filenames and parameters
362 READ(UNIT=iUnit,NML=BLING_FORCING)
363
364 WRITE(msgBuf,'(A)')
365 & ' BLING_READPARMS: finished reading data.BLING'
366 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
367 I SQUEEZE_RIGHT, myThid )
368
369 C-- Close the open data file
370 #ifdef SINGLE_DISK_IO
371 CLOSE(iUnit)
372 #else
373 CLOSE(iUnit,STATUS='DELETE')
374 #endif /* SINGLE_DISK_IO */
375
376 C- derive other parameters:
377
378 QSW_underice = .FALSE.
379 #ifdef USE_QSW_UNDERICE
380 QSW_underice = .TRUE.
381 #elif (defined (USE_QSW))
382 C if using Qsw and seaice, then ice fraction is already
383 C taken into account
384 IF ( useSEAICE ) QSW_underice = .TRUE.
385 IF ( useThSIce ) QSW_underice = .TRUE.
386 #endif
387
388 IF ( errCount.GE.1 ) THEN
389 WRITE(msgBuf,'(A,I3,A)')
390 & 'BLING_READPARMS: detected', errCount,' fatal error(s)'
391 CALL PRINT_ERROR( msgBuf, myThid )
392 CALL ALL_PROC_DIE( 0 )
393 STOP 'ABNORMAL END: S/R BLING_READPARMS'
394 ENDIF
395
396 _END_MASTER(myThid)
397
398 C-- Everyone else must wait for the parameters to be loaded
399 _BARRIER
400
401 #endif /* ALLOW_BLING */
402
403 RETURN
404 END

  ViewVC Help
Powered by ViewVC 1.1.22