/[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.1 - (show annotations) (download)
Tue Apr 8 16:18:43 2008 UTC (16 years, 2 months ago) by dfer
Branch: MAIN
Removing dic_abiotic_param.F and dic_biotic_param.F to create
dic_readparms.F and get a data.dic

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_biotic_param.F,v 1.11 2008/04/07 20:31:16 dfer 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 "GRID.h"
26 #include "DYNVARS.h"
27 #include "DIC_VARS.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 INTEGER i,j,k,bi,bj
43 _RL alphaloc, rain_ratioloc
44
45 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
46
47 C-- Abiotic dic parameters:
48 C permil :: set carbon mol/m3 <---> mol/kg conversion factor
49 C default permil = 1024.5 kg/m3
50 C Pa2Atm :: Conversion factor for atmospheric pressure pLoad (when coupled
51 C to atmospheric model) into Atm. Default assumes pLoad in Pascal
52 C 1 Atm = 1.01325e5 Pa = 1013.25 mb
53
54 NAMELIST /ABIOTIC_PARMS/ permil, Pa2Atm
55
56 #ifdef DIC_BIOTIC
57
58 C-- Biotic dic parameters:
59 C DOPfraction :: fraction of new production going to DOP
60 C KDOPRemin :: DOP remineralization rate (s) = 1/(6 month)
61 C KRemin :: remin power law coeff
62 C zcrit :: Minimum Depth (m) over which biological activity
63 C is computed --> determines nlev as the indice of the
64 C first layer deeper than -zcrit
65 C O2crit :: critical oxygen level (mol/m3)
66 C R_OP, R_CP :: stochiometric ratios
67 C R_NP, R_FeP
68 C zca :: scale depth for CaCO3 remineralization (m)
69 CC Parameters for light/nutrient limited bioac
70 C parfrac :: fraction of Qsw that is PAR
71 C k0 :: light attentuation coefficient (1/m)
72 C lit0 :: half saturation light constant (W/m2)
73 C KPO4 :: half saturation phosphate constant (mol/m3)
74 C KFE :: half saturation fe constant (mol/m3)
75 CC Iron chemisty values
76 C alpfe :: solubility of aeolian fe
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 :: timescape for biological activity
83 C read in alphaloc and filled in 2d array alpha
84 C rain_ratio :: inorganic/organic carbon rain ratio
85 C read in rain_ratioloc 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,
91 & alpfe, freefemax,
92 & KScav, ligand_stab, ligand_tot,
93 & alphaloc, rain_ratioloc
94 #endif
95
96 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
97
98 _BEGIN_MASTER(myThid)
99
100 permil = 1. _d 0 / 1024.5 _d 0
101 Pa2Atm = 1.01325 _d 5
102 #ifdef DIC_BIOTIC
103 DOPfraction = 0.67 _d 0
104 KDOPRemin = 1. _d 0/(6. _d 0*30. _d 0*86400. _d 0)
105 KRemin = 0.9 _d 0
106 zcrit = 500. _d 0
107 O2crit = 4. _d -3
108 R_OP =-170. _d 0
109 R_CP = 117. _d 0
110 R_NP = 16. _d 0
111 R_FeP = 0.000468 _d 0
112 zca = 3500. _d 0
113 parfrac = 0.4 _d 0
114 k0 = 0.02 _d 0
115 lit0 = 30. _d 0
116 KPO4 = 5. _d -4
117 KFE = 1.2 _d -7
118 alpfe = 0.01 _d 0
119 freefemax = 3. _d -7
120 KScav = 0.19 _d 0/(360. _d 0*86400. _d 0)
121 ligand_stab = 1. _d 8
122 ligand_tot = 1. _d -6
123 alphaloc = 2. _d -3/(360. _d 0 * 86400. _d 0)
124 rain_ratioloc = 7. _d -2
125 #endif
126
127
128 WRITE(msgBuf,'(A)') ' DIC_READPARMS: opening data.dic'
129 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
130 I SQUEEZE_RIGHT, myThid )
131
132 CALL OPEN_COPY_DATA_FILE( 'data.dic', 'DIC_READPARMS',
133 O iUnit, myThid )
134
135 C-- Read parameters from open data file:
136
137 C- Abiotic parameters
138 READ(UNIT=iUnit,NML=ABIOTIC_PARMS)
139
140 #ifdef DIC_BIOTIC
141 C- Biotic parameters
142 READ(UNIT=iUnit,NML=BIOTIC_PARMS)
143 #endif
144
145 WRITE(msgBuf,'(A)')
146 & ' DIC_READPARMS: finished reading data.dic'
147 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
148 I SQUEEZE_RIGHT, myThid )
149
150 C-- Close the open data file
151 CLOSE(iUnit)
152
153 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
154 C- derive other parameters:
155
156 #ifdef DIC_BIOTIC
157
158 #ifndef AD_SAFE
159 k = 1
160 DO WHILE ( k .LT. Nr .AND. rC(k) .GE. -zcrit )
161 k = k+1
162 ENDDO
163 nlev = k
164 #else
165 nlev=Nr
166 #endif
167
168 #endif /* DIC_BIOTIC */
169
170 _END_MASTER(myThid)
171
172 C-- Everyone else must wait for the parameters to be loaded
173 _BARRIER
174
175 #ifdef DIC_BIOTIC
176 DO bj = myByLo(myThid), myByHi(myThid)
177 DO bi = myBxLo(myThid), myBxHi(myThid)
178 DO j=1-Oly,sNy+Oly
179 DO i=1-Olx,sNx+Olx
180 alpha(i,j,bi,bj) = alphaloc
181 rain_ratio(i,j,bi,bj)= rain_ratioloc
182 ENDDO
183 ENDDO
184 ENDDO
185 ENDDO
186 #endif /* DIC_BIOTIC */
187
188 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
189
190 #endif /* ALLOW_DIC */
191
192 RETURN
193 END

  ViewVC Help
Powered by ViewVC 1.1.22