/[MITgcm]/MITgcm/pkg/dic/dic_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/dic/dic_readparms.F

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


Revision 1.15 - (show annotations) (download)
Fri Nov 4 20:23:29 2016 UTC (7 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66i, checkpoint66h
Changes since 1.14: +1 -1 lines
revert last changes regarding default value of "fesedflux_pcm"

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_readparms.F,v 1.13 2014/12/05 01:44:32 jmc Exp $
2 C $Name: $
3
4 #include "DIC_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: DIC_READPARMS
8 C !INTERFACE: ==========================================================
9 SUBROUTINE DIC_READPARMS( myThid )
10
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | S/R DIC_READPARMS
14 C | o Initialise and read dic package parameters
15 C *==========================================================*
16 C \ev
17
18 C !USES:
19 IMPLICIT NONE
20
21 C === Global variables ===
22 #include "SIZE.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "DIC_VARS.h"
26 #include "PTRACERS_SIZE.h"
27 #include "PTRACERS_PARAMS.h"
28
29 C !INPUT/OUTPUT PARAMETERS:
30 C === Routine arguments ===
31 C myThid :: My Thread Id. number
32 INTEGER myThid
33 CEOP
34
35 #ifdef ALLOW_DIC
36
37 C === Local variables ===
38 C msgBuf :: Informational/error message buffer
39 C iUnit :: Work variable for IO unit number
40 CHARACTER*(MAX_LEN_MBUF) msgBuf
41 INTEGER iUnit
42
43 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
44
45 C-- Abiotic dic parameters:
46 C permil :: set carbon mol/m3 <---> mol/kg conversion factor
47 C default permil = 1024.5 kg/m3
48 C Pa2Atm :: Conversion factor for atmospheric pressure pLoad (when coupled
49 C to atmospheric model) into Atm. Default assumes pLoad in Pascal
50 C 1 Atm = 1.01325e5 Pa = 1013.25 mb
51
52 NAMELIST /ABIOTIC_PARMS/ permil, Pa2Atm
53
54 #ifdef DIC_BIOTIC
55
56 C-- Biotic dic parameters:
57 C DOPfraction :: fraction of new production going to DOP
58 C KDOPRemin :: DOP remineralization rate (1/s) = 1/(6 month)
59 C KRemin :: remin power law coeff
60 C zcrit :: Minimum Depth (m) over which biological activity
61 C is computed --> determines nlev as the indice of the
62 C first layer deeper than -zcrit
63 C O2crit :: critical oxygen level (mol/m3)
64 C R_OP, R_CP :: stochiometric ratios
65 C R_NP, R_FeP
66 C zca :: scale depth for CaCO3 remineralization (m)
67 CC Parameters for light/nutrient limited bioac
68 C parfrac :: fraction of Qsw that is PAR
69 C k0 :: light attentuation coefficient (1/m)
70 C lit0 :: half saturation light constant (W/m2)
71 C KPO4 :: half saturation phosphate constant (mol/m3)
72 C KFE :: half saturation fe constant (mol/m3)
73 CC Iron chemisty values
74 C alpfe :: solubility of aeolian fe
75 C fesedflux_pcm :: ratio of sediment iron to sinking organic matter
76 C FeIntSec :: y-axis crossing for Fe_flux = fesedflux_pcm*pflux + FeIntSec
77 C freefemax :: max solubility of free iron (mol/m3)
78 CC Control variables
79 C KScav :: iron scavenging rate QQ
80 C ligand_stab :: ligand-free iron stability constant (m3/mol)
81 C ligand_tot :: total free ligand (mol/m3)
82 C alpha :: timescale for biological activity
83 C read in alphaUniform and filled in 2d array alpha
84 C rain_ratio :: inorganic/organic carbon rain ratio
85 C read in rainRatioUniform and filled in 2d array rain_ratio
86
87 NAMELIST /BIOTIC_PARMS/
88 & DOPfraction, KDOPRemin, KRemin, zcrit,
89 & O2crit, R_OP, R_CP, R_NP, R_FeP, zca,
90 & parfrac, k0, lit0, KPO4, KFE, kchl,
91 & alpfe, fesedflux_pcm, FeIntSec, freefemax,
92 & KScav, ligand_stab, ligand_tot,
93 & alphaUniform, rainRatioUniform
94 #endif
95
96 NAMELIST /DIC_FORCING/
97 & DIC_windFile, DIC_atmospFile, DIC_iceFile,
98 & DIC_ironFile, DIC_silicaFile, DIC_parFile,
99 & DIC_chlaFile,
100 & DIC_forcingPeriod, DIC_forcingCycle,
101 & dic_int1, dic_int2, dic_int3, dic_int4, dic_pCO2
102
103 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
104
105 _BEGIN_MASTER(myThid)
106
107 permil = 1. _d 0 / 1024.5 _d 0
108 Pa2Atm = 1.01325 _d 5
109 #ifdef DIC_BIOTIC
110 DOPfraction = 0.67 _d 0
111 KDOPRemin = 1. _d 0/(6. _d 0*30. _d 0*86400. _d 0)
112 KRemin = 0.9 _d 0
113 zcrit = 500. _d 0
114 O2crit = 4. _d -3
115 R_OP =-170. _d 0
116 R_CP = 117. _d 0
117 R_NP = 16. _d 0
118 R_FeP = 0.000468 _d 0
119 zca = 3500. _d 0
120 parfrac = 0.4 _d 0
121 k0 = 0.02 _d 0
122 kchl = 0.02 _d 0
123 lit0 = 30. _d 0
124 KPO4 = 5. _d -4
125 KFE = 1.2 _d -7
126 alpfe = 0.01 _d 0
127 fesedflux_pcm = 6.8 _d -4 * 106. _d 0
128 FeIntSec = 0.5 _d -6 / 86400. _d 0
129 freefemax = 3. _d -7
130 KScav = 0.19 _d 0/(360. _d 0*86400. _d 0)
131 ligand_stab = 1. _d 8
132 ligand_tot = 1. _d -6
133 alphaUniform = 2. _d -3/(360. _d 0 * 86400. _d 0)
134 rainRatioUniform = 7. _d -2
135 #endif
136 DIC_windFile = ' '
137 DIC_atmospFile= ' '
138 DIC_iceFile = ' '
139 DIC_ironFile = ' '
140 DIC_silicaFile= ' '
141 DIC_parFile = ' '
142 DIC_chlaFile = ' '
143 dic_int1 = 0
144 dic_int2 = 0
145 dic_int3 = 0
146 dic_int4 = 0
147 dic_pCO2 = 278. _d -6
148 c default periodic forcing to same as for physics
149 DIC_forcingPeriod = externForcingPeriod
150 DIC_forcingCycle = externForcingCycle
151
152 WRITE(msgBuf,'(A)') ' DIC_READPARMS: opening data.dic'
153 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
154 I SQUEEZE_RIGHT, myThid )
155
156 CALL OPEN_COPY_DATA_FILE( 'data.dic', 'DIC_READPARMS',
157 O iUnit, myThid )
158
159 C-- Read parameters from open data file:
160
161 C- Abiotic parameters
162 READ(UNIT=iUnit,NML=ABIOTIC_PARMS)
163
164 #ifdef DIC_BIOTIC
165 C- Biotic parameters
166 READ(UNIT=iUnit,NML=BIOTIC_PARMS)
167 #endif
168
169 C- forcing filenames and parameters
170 READ(UNIT=iUnit,NML=DIC_FORCING)
171
172 WRITE(msgBuf,'(A)')
173 & ' DIC_READPARMS: finished reading data.dic'
174 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
175 I SQUEEZE_RIGHT, myThid )
176
177 C-- Close the open data file
178 CLOSE(iUnit)
179
180 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
181 C- derive other parameters:
182
183 #ifdef DIC_BIOTIC
184 QSW_underice = .FALSE.
185 #ifdef USE_QSW_UNDERICE
186 QSW_underice = .TRUE.
187 #elif (defined (USE_QSW))
188 C if using Qsw and seaice, then ice fraction is already
189 C taken into account
190 IF ( useSEAICE ) QSW_underice = .TRUE.
191 IF ( useThSIce ) QSW_underice = .TRUE.
192 #endif
193 #endif /* DIC_BIOTIC */
194
195 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
196 C-- Print out parameter values :
197
198 iUnit = standardMessageUnit
199 WRITE(msgBuf,'(A)') ' '
200 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
201 WRITE(msgBuf,'(A)') '// ==================================='
202 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
203 WRITE(msgBuf,'(A)') '// DIC package parameters :'
204 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
205 WRITE(msgBuf,'(A)') '// ==================================='
206 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
207
208 C- namelist ABIOTIC_PARMS
209 CALL WRITE_0D_RL( permil, INDEX_NONE,'permil =',
210 & ' /* Ref. density to convert mol/m3 to mol/kg */')
211 CALL WRITE_0D_RL( Pa2Atm, INDEX_NONE,'Pa2Atm =',
212 & ' /* Atmosph. pressure conversion coeff (to Atm) */')
213
214 #ifdef DIC_BIOTIC
215 C- namelist BIOTIC_PARMS
216 CALL WRITE_0D_RL( DOPfraction, INDEX_NONE,'DOPfraction =',
217 & ' /* Fraction of new production going to DOP */')
218 CALL WRITE_0D_RL( KDOPRemin, INDEX_NONE,'KDOPRemin =',
219 & ' /* DOP remineralization rate (1/s) */')
220 CALL WRITE_0D_RL( KRemin, INDEX_NONE,'KRemin =',
221 & ' /* Remin power law coeff. */')
222 CALL WRITE_0D_RL( zcrit, INDEX_NONE,'zcrit =',
223 & ' /* Minimum depth for biological activity (m) */')
224 CALL WRITE_0D_RL( O2crit, INDEX_NONE,'O2crit =',
225 & ' /* Critical oxygen level (mol/m3) */')
226 CALL WRITE_0D_RL( R_OP, INDEX_NONE,'R_OP =',
227 & ' /* Stochiometric ratio R_OP */')
228 CALL WRITE_0D_RL( R_CP, INDEX_NONE,'R_CP =',
229 & ' /* Stochiometric ratio R_CP */')
230 CALL WRITE_0D_RL( R_NP, INDEX_NONE,'R_NP =',
231 & ' /* Stochiometric ratio R_NP */')
232 CALL WRITE_0D_RL( R_FeP, INDEX_NONE,'R_FeP =',
233 & ' /* Stochiometric ratio R_FeP */')
234 CALL WRITE_0D_RL( zca, INDEX_NONE,'zca =',
235 & ' /* Scale depth for CaCO3 remineralization (m) */')
236 CALL WRITE_0D_RL( parfrac, INDEX_NONE,'parfrac =',
237 & ' /* Fraction of Qsw that is PAR */')
238 CALL WRITE_0D_RL( k0, INDEX_NONE,'k0 =',
239 & ' /* Light attentuation coefficient, water (1/m) */')
240 CALL WRITE_0D_RL( kchl, INDEX_NONE,'kchl =',
241 & ' /* Light attentuation coefficient, chlorophyll (m2/mg) */')
242 CALL WRITE_0D_RL( lit0, INDEX_NONE,'lit0 =',
243 & ' /* Half saturation light constant (W/m2) */')
244 CALL WRITE_0D_RL( KPO4, INDEX_NONE,'KPO4 =',
245 & ' /* Half saturation phosphate constant (mol/m3) */')
246 CALL WRITE_0D_RL( KFE, INDEX_NONE,'KFE =',
247 & ' /* Half saturation fe constant (mol/m3) */')
248 CALL WRITE_0D_RL( alpfe, INDEX_NONE,'alpfe =',
249 & ' /* Solubility of aeolian fe */')
250 CALL WRITE_0D_RL( fesedflux_pcm, INDEX_NONE,'fesedflux_pcm =',
251 & ' /* Sediment Fe flux = fesedflux_pcm*pflux+FeIntSec */')
252 CALL WRITE_0D_RL( FeIntSec, INDEX_NONE,'FeIntSec =',
253 & ' /* Sediment Fe flux = fesedflux_pcm * pflux + FeIntSec */')
254 CALL WRITE_0D_RL( freefemax, INDEX_NONE,'freefemax =',
255 & ' /* Max solubility of free iron (mol/m3) */')
256 CALL WRITE_0D_RL( KScav, INDEX_NONE,'KScav =',
257 & ' /* Iron scavenging rate */')
258 CALL WRITE_0D_RL( ligand_stab, INDEX_NONE,'ligand_stab =',
259 & ' /* Ligand-free iron stability constant (m3/mol) */')
260 CALL WRITE_0D_RL( ligand_tot, INDEX_NONE,'ligand_tot =',
261 & ' /* Total free ligand (mol/m3) */')
262 CALL WRITE_0D_RL( alphaUniform, INDEX_NONE,'alphaUniform =',
263 & ' /* Timescale for biological activity */')
264 CALL WRITE_0D_RL(rainRatioUniform,INDEX_NONE,'rainRatioUniform=',
265 & ' /* Inorganic/organic carbon rain ratio */')
266
267 CALL WRITE_0D_L( QSW_underice, INDEX_NONE, 'QSW_underice =',
268 & ' /* Flag for Qsw under Sea-Ice (i.e. SI fract included) */')
269 #endif
270
271 C- namelist DIC_FORCING
272 CALL WRITE_0D_C( DIC_windFile, -1, INDEX_NONE, 'DIC_windFile =',
273 & ' /* File name of wind speeds */')
274 CALL WRITE_0D_C( DIC_atmospFile, -1,INDEX_NONE,'DIC_atmospFile=',
275 & ' /* File name of atmospheric pressure*/')
276 CALL WRITE_0D_C( DIC_iceFile, -1, INDEX_NONE, 'DIC_iceFile =',
277 & ' /* File name of seaice fraction */')
278 CALL WRITE_0D_C( DIC_ironFile, -1, INDEX_NONE, 'DIC_ironFile =',
279 & ' /* File name of aeolian iron flux */')
280 CALL WRITE_0D_C( DIC_silicaFile, -1,INDEX_NONE,'DIC_silicaFile=',
281 & ' /* File name of surface silica */')
282 CALL WRITE_0D_C( DIC_parFile, -1,INDEX_NONE,'DIC_parFile=',
283 & ' /* File name of photosynthetically available radiation */')
284 CALL WRITE_0D_C( DIC_chlaFile, -1,INDEX_NONE,'DIC_chlaFile=',
285 & ' /* File name of chlorophyll climatology */')
286 CALL WRITE_0D_RL( DIC_forcingPeriod,
287 & INDEX_NONE,'DIC_forcingPeriod =',
288 & ' /* Periodic forcing parameter specific for DIC (s) */')
289 CALL WRITE_0D_RL( DIC_forcingCycle,
290 & INDEX_NONE,'DIC_forcingCycle =',
291 & ' /* Periodic forcing parameter specific for DIC (s) */')
292 CALL WRITE_0D_I( dic_int1, INDEX_NONE, 'dic_int1 =',
293 & ' /* */')
294 CALL WRITE_0D_I( dic_int2, INDEX_NONE, 'dic_int2 =',
295 & ' /* */')
296 CALL WRITE_0D_I( dic_int3, INDEX_NONE, 'dic_int3 =',
297 & ' /* */')
298 CALL WRITE_0D_I( dic_int4, INDEX_NONE, 'dic_int4 =',
299 & ' /* */')
300 CALL WRITE_0D_RL( dic_pCO2, INDEX_NONE,'dic_pCO2 =',
301 & ' /* Atmospheric pCO2 to be read in data.dic */')
302
303 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
304
305 IF ( dic_int1.EQ.0 .AND. dic_pCO2.NE.278. _d -6 ) THEN
306 WRITE(msgBuf,'(A)')
307 & 'DIC_READPARMS: cannot change default dic_pCO2 if dic_int1=0'
308 CALL PRINT_ERROR( msgBuf, myThid )
309 STOP 'ABNORMAL END: S/R DIC_READPARMS: dic_pCO2 error'
310 ENDIF
311 #ifdef ALLOW_OLD_VIRTUALFLUX
312 IF ( PTRACERS_EvPrRn(1).NE.UNSET_RL .OR.
313 & PTRACERS_EvPrRn(2).NE.UNSET_RL ) THEN
314 WRITE(msgBuf,'(2A)') 'DIC_READPARMS: ',
315 & 'when ALLOW_OLD_VIRTUALFLUX is defined (in DIC_OPTIONS.h)'
316 CALL PRINT_ERROR( msgBuf, myThid )
317 IF ( PTRACERS_EvPrRn(1).NE.UNSET_RL ) THEN
318 WRITE(msgBuf,'(2A)') 'DIC_READPARMS: ',
319 & ' cannot set PTRACERS_EvPrRn(1) (in data.ptracers)'
320 CALL PRINT_ERROR( msgBuf, myThid )
321 ENDIF
322 IF ( PTRACERS_EvPrRn(2).NE.UNSET_RL ) THEN
323 WRITE(msgBuf,'(2A)') 'DIC_READPARMS: ',
324 & ' cannot set PTRACERS_EvPrRn(2) (in data.ptracers)'
325 CALL PRINT_ERROR( msgBuf, myThid )
326 ENDIF
327 STOP 'ABNORMAL END: S/R DIC_READPARMS'
328 ENDIF
329 #endif /* ALLOW_OLD_VIRTUALFLUX */
330
331 _END_MASTER(myThid)
332
333 C-- Everyone else must wait for the parameters to be loaded
334 _BARRIER
335
336 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
337
338 #endif /* ALLOW_DIC */
339
340 RETURN
341 END

  ViewVC Help
Powered by ViewVC 1.1.22