/[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.10 - (show annotations) (download)
Sun Apr 11 20:54:49 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.9: +9 -2 lines
store default Atm.pCO2 in parameter "dic_pCO2"

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

  ViewVC Help
Powered by ViewVC 1.1.22