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

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

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


Revision 1.16 - (hide annotations) (download)
Wed Aug 9 15:23:38 2017 UTC (6 years, 10 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, HEAD
Changes since 1.15: +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 mlosch 1.16 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_readparms.F,v 1.15 2016/11/04 20:23:29 jmc Exp $
2     C $Name: BASE $
3 dfer 1.1
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 jmc 1.13 #include "PTRACERS_SIZE.h"
27     #include "PTRACERS_PARAMS.h"
28 dfer 1.1
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 jmc 1.7
43 dfer 1.1 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 jmc 1.3 C default permil = 1024.5 kg/m3
48 dfer 1.1 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 dfer 1.4 C KDOPRemin :: DOP remineralization rate (1/s) = 1/(6 month)
59 dfer 1.1 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 jmc 1.12 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 dfer 1.1 C freefemax :: max solubility of free iron (mol/m3)
78     CC Control variables
79 jmc 1.3 C KScav :: iron scavenging rate QQ
80 dfer 1.1 C ligand_stab :: ligand-free iron stability constant (m3/mol)
81     C ligand_tot :: total free ligand (mol/m3)
82 jmc 1.7 C alpha :: timescale for biological activity
83 jmc 1.8 C read in alphaUniform and filled in 2d array alpha
84 dfer 1.1 C rain_ratio :: inorganic/organic carbon rain ratio
85 jmc 1.8 C read in rainRatioUniform and filled in 2d array rain_ratio
86 dfer 1.1
87     NAMELIST /BIOTIC_PARMS/
88     & DOPfraction, KDOPRemin, KRemin, zcrit,
89     & O2crit, R_OP, R_CP, R_NP, R_FeP, zca,
90 jmc 1.12 & parfrac, k0, lit0, KPO4, KFE, kchl,
91     & alpfe, fesedflux_pcm, FeIntSec, freefemax,
92 dfer 1.1 & KScav, ligand_stab, ligand_tot,
93 jmc 1.8 & alphaUniform, rainRatioUniform
94 dfer 1.1 #endif
95    
96 dfer 1.2 NAMELIST /DIC_FORCING/
97 jmc 1.5 & DIC_windFile, DIC_atmospFile, DIC_iceFile,
98 stephd 1.11 & DIC_ironFile, DIC_silicaFile, DIC_parFile,
99 jmc 1.12 & DIC_chlaFile,
100 jmc 1.5 & DIC_forcingPeriod, DIC_forcingCycle,
101 dfer 1.2 & dic_int1, dic_int2, dic_int3, dic_int4, dic_pCO2
102    
103 dfer 1.1 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 jmc 1.12 kchl = 0.02 _d 0
123 dfer 1.1 lit0 = 30. _d 0
124     KPO4 = 5. _d -4
125     KFE = 1.2 _d -7
126     alpfe = 0.01 _d 0
127 jmc 1.15 fesedflux_pcm = 6.8 _d -4 * 106. _d 0
128 jmc 1.12 FeIntSec = 0.5 _d -6 / 86400. _d 0
129 dfer 1.1 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 jmc 1.8 alphaUniform = 2. _d -3/(360. _d 0 * 86400. _d 0)
134     rainRatioUniform = 7. _d -2
135 dfer 1.1 #endif
136 jmc 1.5 DIC_windFile = ' '
137     DIC_atmospFile= ' '
138     DIC_iceFile = ' '
139     DIC_ironFile = ' '
140     DIC_silicaFile= ' '
141 stephd 1.11 DIC_parFile = ' '
142 jmc 1.12 DIC_chlaFile = ' '
143 dfer 1.2 dic_int1 = 0
144     dic_int2 = 0
145     dic_int3 = 0
146     dic_int4 = 0
147 jmc 1.10 dic_pCO2 = 278. _d -6
148 dfer 1.2 c default periodic forcing to same as for physics
149 jmc 1.5 DIC_forcingPeriod = externForcingPeriod
150     DIC_forcingCycle = externForcingCycle
151 dfer 1.1
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 dfer 1.2 C- forcing filenames and parameters
170     READ(UNIT=iUnit,NML=DIC_FORCING)
171    
172 dfer 1.1 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 mlosch 1.16 #ifdef SINGLE_DISK_IO
179 dfer 1.1 CLOSE(iUnit)
180 mlosch 1.16 #else
181     CLOSE(iUnit,STATUS='DELETE')
182     #endif /* SINGLE_DISK_IO */
183 dfer 1.1
184     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
185     C- derive other parameters:
186    
187     #ifdef DIC_BIOTIC
188 jmc 1.3 QSW_underice = .FALSE.
189     #ifdef USE_QSW_UNDERICE
190     QSW_underice = .TRUE.
191     #elif (defined (USE_QSW))
192     C if using Qsw and seaice, then ice fraction is already
193     C taken into account
194     IF ( useSEAICE ) QSW_underice = .TRUE.
195     IF ( useThSIce ) QSW_underice = .TRUE.
196 dfer 1.1 #endif
197     #endif /* DIC_BIOTIC */
198    
199 dfer 1.4 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
200     C-- Print out parameter values :
201    
202     iUnit = standardMessageUnit
203     WRITE(msgBuf,'(A)') ' '
204     CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
205     WRITE(msgBuf,'(A)') '// ==================================='
206     CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
207 jmc 1.5 WRITE(msgBuf,'(A)') '// DIC package parameters :'
208 dfer 1.4 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
209     WRITE(msgBuf,'(A)') '// ==================================='
210     CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
211    
212     C- namelist ABIOTIC_PARMS
213 jmc 1.9 CALL WRITE_0D_RL( permil, INDEX_NONE,'permil =',
214 dfer 1.4 & ' /* Ref. density to convert mol/m3 to mol/kg */')
215 jmc 1.9 CALL WRITE_0D_RL( Pa2Atm, INDEX_NONE,'Pa2Atm =',
216 dfer 1.4 & ' /* Atmosph. pressure conversion coeff (to Atm) */')
217    
218 dfer 1.6 #ifdef DIC_BIOTIC
219 dfer 1.4 C- namelist BIOTIC_PARMS
220 jmc 1.9 CALL WRITE_0D_RL( DOPfraction, INDEX_NONE,'DOPfraction =',
221 dfer 1.4 & ' /* Fraction of new production going to DOP */')
222 jmc 1.9 CALL WRITE_0D_RL( KDOPRemin, INDEX_NONE,'KDOPRemin =',
223 dfer 1.4 & ' /* DOP remineralization rate (1/s) */')
224 jmc 1.9 CALL WRITE_0D_RL( KRemin, INDEX_NONE,'KRemin =',
225 dfer 1.4 & ' /* Remin power law coeff. */')
226 jmc 1.9 CALL WRITE_0D_RL( zcrit, INDEX_NONE,'zcrit =',
227 dfer 1.4 & ' /* Minimum depth for biological activity (m) */')
228 jmc 1.9 CALL WRITE_0D_RL( O2crit, INDEX_NONE,'O2crit =',
229 dfer 1.4 & ' /* Critical oxygen level (mol/m3) */')
230 jmc 1.9 CALL WRITE_0D_RL( R_OP, INDEX_NONE,'R_OP =',
231 dfer 1.4 & ' /* Stochiometric ratio R_OP */')
232 jmc 1.9 CALL WRITE_0D_RL( R_CP, INDEX_NONE,'R_CP =',
233 dfer 1.4 & ' /* Stochiometric ratio R_CP */')
234 jmc 1.9 CALL WRITE_0D_RL( R_NP, INDEX_NONE,'R_NP =',
235 dfer 1.4 & ' /* Stochiometric ratio R_NP */')
236 jmc 1.9 CALL WRITE_0D_RL( R_FeP, INDEX_NONE,'R_FeP =',
237 dfer 1.4 & ' /* Stochiometric ratio R_FeP */')
238 jmc 1.9 CALL WRITE_0D_RL( zca, INDEX_NONE,'zca =',
239 dfer 1.4 & ' /* Scale depth for CaCO3 remineralization (m) */')
240 jmc 1.9 CALL WRITE_0D_RL( parfrac, INDEX_NONE,'parfrac =',
241 dfer 1.4 & ' /* Fraction of Qsw that is PAR */')
242 jmc 1.9 CALL WRITE_0D_RL( k0, INDEX_NONE,'k0 =',
243 jmc 1.12 & ' /* Light attentuation coefficient, water (1/m) */')
244     CALL WRITE_0D_RL( kchl, INDEX_NONE,'kchl =',
245     & ' /* Light attentuation coefficient, chlorophyll (m2/mg) */')
246 jmc 1.9 CALL WRITE_0D_RL( lit0, INDEX_NONE,'lit0 =',
247 dfer 1.4 & ' /* Half saturation light constant (W/m2) */')
248 jmc 1.9 CALL WRITE_0D_RL( KPO4, INDEX_NONE,'KPO4 =',
249 dfer 1.4 & ' /* Half saturation phosphate constant (mol/m3) */')
250 jmc 1.9 CALL WRITE_0D_RL( KFE, INDEX_NONE,'KFE =',
251 dfer 1.4 & ' /* Half saturation fe constant (mol/m3) */')
252 jmc 1.9 CALL WRITE_0D_RL( alpfe, INDEX_NONE,'alpfe =',
253 dfer 1.4 & ' /* Solubility of aeolian fe */')
254 jmc 1.12 CALL WRITE_0D_RL( fesedflux_pcm, INDEX_NONE,'fesedflux_pcm =',
255     & ' /* Sediment Fe flux = fesedflux_pcm*pflux+FeIntSec */')
256     CALL WRITE_0D_RL( FeIntSec, INDEX_NONE,'FeIntSec =',
257     & ' /* Sediment Fe flux = fesedflux_pcm * pflux + FeIntSec */')
258 jmc 1.9 CALL WRITE_0D_RL( freefemax, INDEX_NONE,'freefemax =',
259 dfer 1.4 & ' /* Max solubility of free iron (mol/m3) */')
260 jmc 1.9 CALL WRITE_0D_RL( KScav, INDEX_NONE,'KScav =',
261 dfer 1.4 & ' /* Iron scavenging rate */')
262 jmc 1.9 CALL WRITE_0D_RL( ligand_stab, INDEX_NONE,'ligand_stab =',
263 dfer 1.4 & ' /* Ligand-free iron stability constant (m3/mol) */')
264 jmc 1.9 CALL WRITE_0D_RL( ligand_tot, INDEX_NONE,'ligand_tot =',
265 dfer 1.4 & ' /* Total free ligand (mol/m3) */')
266 jmc 1.9 CALL WRITE_0D_RL( alphaUniform, INDEX_NONE,'alphaUniform =',
267 jmc 1.7 & ' /* Timescale for biological activity */')
268 jmc 1.9 CALL WRITE_0D_RL(rainRatioUniform,INDEX_NONE,'rainRatioUniform=',
269 dfer 1.4 & ' /* Inorganic/organic carbon rain ratio */')
270 dfer 1.6
271     CALL WRITE_0D_L( QSW_underice, INDEX_NONE, 'QSW_underice =',
272     & ' /* Flag for Qsw under Sea-Ice (i.e. SI fract included) */')
273     #endif
274    
275     C- namelist DIC_FORCING
276 jmc 1.5 CALL WRITE_0D_C( DIC_windFile, -1, INDEX_NONE, 'DIC_windFile =',
277 dfer 1.4 & ' /* File name of wind speeds */')
278 jmc 1.5 CALL WRITE_0D_C( DIC_atmospFile, -1,INDEX_NONE,'DIC_atmospFile=',
279 dfer 1.4 & ' /* File name of atmospheric pressure*/')
280 jmc 1.5 CALL WRITE_0D_C( DIC_iceFile, -1, INDEX_NONE, 'DIC_iceFile =',
281 dfer 1.4 & ' /* File name of seaice fraction */')
282 jmc 1.5 CALL WRITE_0D_C( DIC_ironFile, -1, INDEX_NONE, 'DIC_ironFile =',
283 dfer 1.4 & ' /* File name of aeolian iron flux */')
284 jmc 1.5 CALL WRITE_0D_C( DIC_silicaFile, -1,INDEX_NONE,'DIC_silicaFile=',
285 dfer 1.4 & ' /* File name of surface silica */')
286 stephd 1.11 CALL WRITE_0D_C( DIC_parFile, -1,INDEX_NONE,'DIC_parFile=',
287     & ' /* File name of photosynthetically available radiation */')
288 jmc 1.12 CALL WRITE_0D_C( DIC_chlaFile, -1,INDEX_NONE,'DIC_chlaFile=',
289     & ' /* File name of chlorophyll climatology */')
290 jmc 1.9 CALL WRITE_0D_RL( DIC_forcingPeriod,
291 jmc 1.5 & INDEX_NONE,'DIC_forcingPeriod =',
292     & ' /* Periodic forcing parameter specific for DIC (s) */')
293 jmc 1.9 CALL WRITE_0D_RL( DIC_forcingCycle,
294 jmc 1.5 & INDEX_NONE,'DIC_forcingCycle =',
295     & ' /* Periodic forcing parameter specific for DIC (s) */')
296 dfer 1.4 CALL WRITE_0D_I( dic_int1, INDEX_NONE, 'dic_int1 =',
297     & ' /* */')
298     CALL WRITE_0D_I( dic_int2, INDEX_NONE, 'dic_int2 =',
299     & ' /* */')
300     CALL WRITE_0D_I( dic_int3, INDEX_NONE, 'dic_int3 =',
301     & ' /* */')
302     CALL WRITE_0D_I( dic_int4, INDEX_NONE, 'dic_int4 =',
303     & ' /* */')
304 jmc 1.9 CALL WRITE_0D_RL( dic_pCO2, INDEX_NONE,'dic_pCO2 =',
305 dfer 1.4 & ' /* Atmospheric pCO2 to be read in data.dic */')
306    
307     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
308    
309 jmc 1.10 IF ( dic_int1.EQ.0 .AND. dic_pCO2.NE.278. _d -6 ) THEN
310     WRITE(msgBuf,'(A)')
311     & 'DIC_READPARMS: cannot change default dic_pCO2 if dic_int1=0'
312     CALL PRINT_ERROR( msgBuf, myThid )
313     STOP 'ABNORMAL END: S/R DIC_READPARMS: dic_pCO2 error'
314     ENDIF
315 jmc 1.13 #ifdef ALLOW_OLD_VIRTUALFLUX
316     IF ( PTRACERS_EvPrRn(1).NE.UNSET_RL .OR.
317     & PTRACERS_EvPrRn(2).NE.UNSET_RL ) THEN
318     WRITE(msgBuf,'(2A)') 'DIC_READPARMS: ',
319     & 'when ALLOW_OLD_VIRTUALFLUX is defined (in DIC_OPTIONS.h)'
320     CALL PRINT_ERROR( msgBuf, myThid )
321     IF ( PTRACERS_EvPrRn(1).NE.UNSET_RL ) THEN
322     WRITE(msgBuf,'(2A)') 'DIC_READPARMS: ',
323     & ' cannot set PTRACERS_EvPrRn(1) (in data.ptracers)'
324     CALL PRINT_ERROR( msgBuf, myThid )
325     ENDIF
326     IF ( PTRACERS_EvPrRn(2).NE.UNSET_RL ) THEN
327     WRITE(msgBuf,'(2A)') 'DIC_READPARMS: ',
328     & ' cannot set PTRACERS_EvPrRn(2) (in data.ptracers)'
329     CALL PRINT_ERROR( msgBuf, myThid )
330     ENDIF
331     STOP 'ABNORMAL END: S/R DIC_READPARMS'
332     ENDIF
333     #endif /* ALLOW_OLD_VIRTUALFLUX */
334 jmc 1.10
335 dfer 1.1 _END_MASTER(myThid)
336    
337     C-- Everyone else must wait for the parameters to be loaded
338     _BARRIER
339    
340     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
341    
342     #endif /* ALLOW_DIC */
343    
344     RETURN
345     END

  ViewVC Help
Powered by ViewVC 1.1.22