1 | MODULE p4zche |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE p4zche *** |
---|
4 | !! TOP : PISCES Sea water chemistry computed following OCMIP protocol |
---|
5 | !!====================================================================== |
---|
6 | !! History : OPA ! 1988 (E. Maier-Reimer) Original code |
---|
7 | !! - ! 1998 (O. Aumont) addition |
---|
8 | !! - ! 1999 (C. Le Quere) modification |
---|
9 | !! NEMO 1.0 ! 2004 (O. Aumont) modification |
---|
10 | !! - ! 2006 (R. Gangsto) modification |
---|
11 | !! 2.0 ! 2007-12 (C. Ethe, G. Madec) F90 |
---|
12 | !! ! 2011-02 (J. Simeon, J.Orr ) update O2 solubility constants |
---|
13 | !!---------------------------------------------------------------------- |
---|
14 | #if defined key_pisces |
---|
15 | !!---------------------------------------------------------------------- |
---|
16 | !! 'key_pisces' PISCES bio-model |
---|
17 | !!---------------------------------------------------------------------- |
---|
18 | !! p4z_che : Sea water chemistry computed following OCMIP protocol |
---|
19 | !!---------------------------------------------------------------------- |
---|
20 | USE oce_trc ! shared variables between ocean and passive tracers |
---|
21 | USE trc ! passive tracers common variables |
---|
22 | USE sms_pisces ! PISCES Source Minus Sink variables |
---|
23 | USE lib_mpp ! MPP library |
---|
24 | |
---|
25 | IMPLICIT NONE |
---|
26 | PRIVATE |
---|
27 | |
---|
28 | PUBLIC p4z_che ! |
---|
29 | PUBLIC p4z_che_alloc ! |
---|
30 | |
---|
31 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: sio3eq ! chemistry of Si |
---|
32 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: fekeq ! chemistry of Fe |
---|
33 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: chemc ! Solubilities of O2 and CO2 |
---|
34 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: chemo2 ! Solubilities of O2 and CO2 |
---|
35 | |
---|
36 | REAL(wp), PUBLIC :: atcox = 0.20946 ! units atm |
---|
37 | |
---|
38 | REAL(wp) :: salchl = 1. / 1.80655 ! conversion factor for salinity --> chlorinity (Wooster et al. 1969) |
---|
39 | REAL(wp) :: o2atm = 1. / ( 1000. * 0.20946 ) |
---|
40 | |
---|
41 | REAL(wp) :: akcc1 = -171.9065 ! coeff. for apparent solubility equilibrium |
---|
42 | REAL(wp) :: akcc2 = -0.077993 ! Millero et al. 1995 from Mucci 1983 |
---|
43 | REAL(wp) :: akcc3 = 2839.319 |
---|
44 | REAL(wp) :: akcc4 = 71.595 |
---|
45 | REAL(wp) :: akcc5 = -0.77712 |
---|
46 | REAL(wp) :: akcc6 = 0.00284263 |
---|
47 | REAL(wp) :: akcc7 = 178.34 |
---|
48 | REAL(wp) :: akcc8 = -0.07711 |
---|
49 | REAL(wp) :: akcc9 = 0.0041249 |
---|
50 | |
---|
51 | REAL(wp) :: rgas = 83.143 ! universal gas constants |
---|
52 | REAL(wp) :: oxyco = 1. / 22.4144 ! converts from liters of an ideal gas to moles |
---|
53 | |
---|
54 | REAL(wp) :: bor1 = 0.00023 ! borat constants |
---|
55 | REAL(wp) :: bor2 = 1. / 10.82 |
---|
56 | |
---|
57 | REAL(wp) :: ca0 = -162.8301 ! WEISS & PRICE 1980, units mol/(kg atm) |
---|
58 | REAL(wp) :: ca1 = 218.2968 |
---|
59 | REAL(wp) :: ca2 = 90.9241 |
---|
60 | REAL(wp) :: ca3 = -1.47696 |
---|
61 | REAL(wp) :: ca4 = 0.025695 |
---|
62 | REAL(wp) :: ca5 = -0.025225 |
---|
63 | REAL(wp) :: ca6 = 0.0049867 |
---|
64 | |
---|
65 | REAL(wp) :: c10 = -3670.7 ! Coeff. for 1. dissoc. of carbonic acid (Edmond and Gieskes, 1970) |
---|
66 | REAL(wp) :: c11 = 62.008 |
---|
67 | REAL(wp) :: c12 = -9.7944 |
---|
68 | REAL(wp) :: c13 = 0.0118 |
---|
69 | REAL(wp) :: c14 = -0.000116 |
---|
70 | |
---|
71 | REAL(wp) :: c20 = -1394.7 ! coeff. for 2. dissoc. of carbonic acid (Millero, 1995) |
---|
72 | REAL(wp) :: c21 = -4.777 |
---|
73 | REAL(wp) :: c22 = 0.0184 |
---|
74 | REAL(wp) :: c23 = -0.000118 |
---|
75 | |
---|
76 | REAL(wp) :: st1 = 0.14 ! constants for calculate concentrations for sulfate |
---|
77 | REAL(wp) :: st2 = 1./96.062 ! (Morris & Riley 1966) |
---|
78 | REAL(wp) :: ks0 = 141.328 |
---|
79 | REAL(wp) :: ks1 = -4276.1 |
---|
80 | REAL(wp) :: ks2 = -23.093 |
---|
81 | REAL(wp) :: ks3 = -13856. |
---|
82 | REAL(wp) :: ks4 = 324.57 |
---|
83 | REAL(wp) :: ks5 = -47.986 |
---|
84 | REAL(wp) :: ks6 = 35474. |
---|
85 | REAL(wp) :: ks7 = -771.54 |
---|
86 | REAL(wp) :: ks8 = 114.723 |
---|
87 | REAL(wp) :: ks9 = -2698. |
---|
88 | REAL(wp) :: ks10 = 1776. |
---|
89 | REAL(wp) :: ks11 = 1. |
---|
90 | REAL(wp) :: ks12 = -0.001005 |
---|
91 | |
---|
92 | REAL(wp) :: ft1 = 0.000067 ! constants for calculate concentrations for fluorides |
---|
93 | REAL(wp) :: ft2 = 1./18.9984 ! (Dickson & Riley 1979 ) |
---|
94 | REAL(wp) :: kf0 = -12.641 |
---|
95 | REAL(wp) :: kf1 = 1590.2 |
---|
96 | REAL(wp) :: kf2 = 1.525 |
---|
97 | REAL(wp) :: kf3 = 1.0 |
---|
98 | REAL(wp) :: kf4 = -0.001005 |
---|
99 | |
---|
100 | REAL(wp) :: cb0 = -8966.90 ! Coeff. for 1. dissoc. of boric acid |
---|
101 | REAL(wp) :: cb1 = -2890.53 ! (Dickson and Goyet, 1994) |
---|
102 | REAL(wp) :: cb2 = -77.942 |
---|
103 | REAL(wp) :: cb3 = 1.728 |
---|
104 | REAL(wp) :: cb4 = -0.0996 |
---|
105 | REAL(wp) :: cb5 = 148.0248 |
---|
106 | REAL(wp) :: cb6 = 137.1942 |
---|
107 | REAL(wp) :: cb7 = 1.62142 |
---|
108 | REAL(wp) :: cb8 = -24.4344 |
---|
109 | REAL(wp) :: cb9 = -25.085 |
---|
110 | REAL(wp) :: cb10 = -0.2474 |
---|
111 | REAL(wp) :: cb11 = 0.053105 |
---|
112 | |
---|
113 | REAL(wp) :: cw0 = -13847.26 ! Coeff. for dissoc. of water (Dickson and Riley, 1979 ) |
---|
114 | REAL(wp) :: cw1 = 148.9652 |
---|
115 | REAL(wp) :: cw2 = -23.6521 |
---|
116 | REAL(wp) :: cw3 = 118.67 |
---|
117 | REAL(wp) :: cw4 = -5.977 |
---|
118 | REAL(wp) :: cw5 = 1.0495 |
---|
119 | REAL(wp) :: cw6 = -0.01615 |
---|
120 | |
---|
121 | ! ! volumetric solubility constants for o2 in ml/L |
---|
122 | REAL(wp) :: ox0 = 2.00856 ! from Table 1 for Eq 8 of Garcia and Gordon, 1992. |
---|
123 | REAL(wp) :: ox1 = 3.22400 ! corrects for moisture and fugacity, but not total atmospheric pressure |
---|
124 | REAL(wp) :: ox2 = 3.99063 ! Original PISCES code noted this was a solubility, but |
---|
125 | REAL(wp) :: ox3 = 4.80299 ! was in fact a bunsen coefficient with units L-O2/(Lsw atm-O2) |
---|
126 | REAL(wp) :: ox4 = 9.78188e-1 ! Hence, need to divide EXP( zoxy ) by 1000, ml-O2 => L-O2 |
---|
127 | REAL(wp) :: ox5 = 1.71069 ! and atcox = 0.20946 to add the 1/atm dimension. |
---|
128 | REAL(wp) :: ox6 = -6.24097e-3 |
---|
129 | REAL(wp) :: ox7 = -6.93498e-3 |
---|
130 | REAL(wp) :: ox8 = -6.90358e-3 |
---|
131 | REAL(wp) :: ox9 = -4.29155e-3 |
---|
132 | REAL(wp) :: ox10 = -3.11680e-7 |
---|
133 | |
---|
134 | ! ! coeff. for seawater pressure correction : millero 95 |
---|
135 | ! ! AGRIF doesn't like the DATA instruction |
---|
136 | REAL(wp) :: devk11 = -25.5 |
---|
137 | REAL(wp) :: devk12 = -15.82 |
---|
138 | REAL(wp) :: devk13 = -29.48 |
---|
139 | REAL(wp) :: devk14 = -25.60 |
---|
140 | REAL(wp) :: devk15 = -48.76 |
---|
141 | ! |
---|
142 | REAL(wp) :: devk21 = 0.1271 |
---|
143 | REAL(wp) :: devk22 = -0.0219 |
---|
144 | REAL(wp) :: devk23 = 0.1622 |
---|
145 | REAL(wp) :: devk24 = 0.2324 |
---|
146 | REAL(wp) :: devk25 = 0.5304 |
---|
147 | ! |
---|
148 | REAL(wp) :: devk31 = 0. |
---|
149 | REAL(wp) :: devk32 = 0. |
---|
150 | REAL(wp) :: devk33 = 2.608E-3 |
---|
151 | REAL(wp) :: devk34 = -3.6246E-3 |
---|
152 | REAL(wp) :: devk35 = 0. |
---|
153 | ! |
---|
154 | REAL(wp) :: devk41 = -3.08E-3 |
---|
155 | REAL(wp) :: devk42 = 1.13E-3 |
---|
156 | REAL(wp) :: devk43 = -2.84E-3 |
---|
157 | REAL(wp) :: devk44 = -5.13E-3 |
---|
158 | REAL(wp) :: devk45 = -11.76E-3 |
---|
159 | ! |
---|
160 | REAL(wp) :: devk51 = 0.0877E-3 |
---|
161 | REAL(wp) :: devk52 = -0.1475E-3 |
---|
162 | REAL(wp) :: devk53 = 0. |
---|
163 | REAL(wp) :: devk54 = 0.0794E-3 |
---|
164 | REAL(wp) :: devk55 = 0.3692E-3 |
---|
165 | |
---|
166 | !!* Substitution |
---|
167 | #include "top_substitute.h90" |
---|
168 | !!---------------------------------------------------------------------- |
---|
169 | !! NEMO/TOP 3.3 , NEMO Consortium (2010) |
---|
170 | !! $Id: p4zche.F90 3294 2012-01-28 16:44:18Z rblod $ |
---|
171 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
172 | !!---------------------------------------------------------------------- |
---|
173 | CONTAINS |
---|
174 | |
---|
175 | SUBROUTINE p4z_che |
---|
176 | !!--------------------------------------------------------------------- |
---|
177 | !! *** ROUTINE p4z_che *** |
---|
178 | !! |
---|
179 | !! ** Purpose : Sea water chemistry computed following OCMIP protocol |
---|
180 | !! |
---|
181 | !! ** Method : - ... |
---|
182 | !!--------------------------------------------------------------------- |
---|
183 | INTEGER :: ji, jj, jk |
---|
184 | REAL(wp) :: ztkel, zt , zt2 , zsal , zsal2 , zbuf1 , zbuf2 |
---|
185 | REAL(wp) :: ztgg , ztgg2, ztgg3 , ztgg4 , ztgg5 |
---|
186 | REAL(wp) :: zpres, ztc , zcl , zcpexp, zoxy , zcpexp2 |
---|
187 | REAL(wp) :: zsqrt, ztr , zlogt , zcek1 |
---|
188 | REAL(wp) :: zis , zis2 , zsal15, zisqrt |
---|
189 | REAL(wp) :: zckb , zck1 , zck2 , zckw , zak1 , zak2 , zakb , zaksp0, zakw |
---|
190 | REAL(wp) :: zst , zft , zcks , zckf , zaksp1 |
---|
191 | !!--------------------------------------------------------------------- |
---|
192 | ! |
---|
193 | IF( nn_timing == 1 ) CALL timing_start('p4z_che') |
---|
194 | ! |
---|
195 | ! CHEMICAL CONSTANTS - SURFACE LAYER |
---|
196 | ! ---------------------------------- |
---|
197 | !CDIR NOVERRCHK |
---|
198 | DO jj = 1, jpj |
---|
199 | !CDIR NOVERRCHK |
---|
200 | DO ji = 1, jpi |
---|
201 | ! ! SET ABSOLUTE TEMPERATURE |
---|
202 | ztkel = tsn(ji,jj,1,jp_tem) + 273.16 |
---|
203 | zt = ztkel * 0.01 |
---|
204 | zt2 = zt * zt |
---|
205 | zsal = tsn(ji,jj,1,jp_sal) + ( 1.- tmask(ji,jj,1) ) * 35. |
---|
206 | zsal2 = zsal * zsal |
---|
207 | zlogt = LOG( zt ) |
---|
208 | ! ! LN(K0) OF SOLUBILITY OF CO2 (EQ. 12, WEISS, 1980) |
---|
209 | ! ! AND FOR THE ATMOSPHERE FOR NON IDEAL GAS |
---|
210 | zcek1 = ca0 + ca1 / zt + ca2 * zlogt + ca3 * zt2 + zsal * ( ca4 + ca5 * zt + ca6 * zt2 ) |
---|
211 | ! ! LN(K0) OF SOLUBILITY OF O2 and N2 in ml/L (EQ. 8, GARCIA AND GORDON, 1992) |
---|
212 | ztgg = LOG( ( 298.15 - tsn(ji,jj,1,jp_tem) ) / ztkel ) ! Set the GORDON & GARCIA scaled temperature |
---|
213 | ztgg2 = ztgg * ztgg |
---|
214 | ztgg3 = ztgg2 * ztgg |
---|
215 | ztgg4 = ztgg3 * ztgg |
---|
216 | ztgg5 = ztgg4 * ztgg |
---|
217 | zoxy = ox0 + ox1 * ztgg + ox2 * ztgg2 + ox3 * ztgg3 + ox4 * ztgg4 + ox5 * ztgg5 & |
---|
218 | + zsal * ( ox6 + ox7 * ztgg + ox8 * ztgg2 + ox9 * ztgg3 ) + ox10 * zsal2 |
---|
219 | |
---|
220 | ! ! SET SOLUBILITIES OF O2 AND CO2 |
---|
221 | chemc(ji,jj,1) = EXP( zcek1 ) * 1.e-6 * rhop(ji,jj,1) / 1000. ! mol/(L uatm) |
---|
222 | chemc(ji,jj,2) = ( EXP( zoxy ) * o2atm ) * oxyco ! mol/(L atm) |
---|
223 | ! |
---|
224 | END DO |
---|
225 | END DO |
---|
226 | |
---|
227 | ! OXYGEN SOLUBILITY - DEEP OCEAN |
---|
228 | ! ------------------------------- |
---|
229 | !CDIR NOVERRCHK |
---|
230 | DO jk = 1, jpk |
---|
231 | !CDIR NOVERRCHK |
---|
232 | DO jj = 1, jpj |
---|
233 | !CDIR NOVERRCHK |
---|
234 | DO ji = 1, jpi |
---|
235 | ztkel = tsn(ji,jj,jk,jp_tem) + 273.16 |
---|
236 | zsal = tsn(ji,jj,jk,jp_sal) + ( 1.- tmask(ji,jj,jk) ) * 35. |
---|
237 | zsal2 = zsal * zsal |
---|
238 | ztgg = LOG( ( 298.15 - tsn(ji,jj,jk,jp_tem) ) / ztkel ) ! Set the GORDON & GARCIA scaled temperature |
---|
239 | ztgg2 = ztgg * ztgg |
---|
240 | ztgg3 = ztgg2 * ztgg |
---|
241 | ztgg4 = ztgg3 * ztgg |
---|
242 | ztgg5 = ztgg4 * ztgg |
---|
243 | zoxy = ox0 + ox1 * ztgg + ox2 * ztgg2 + ox3 * ztgg3 + ox4 * ztgg4 + ox5 * ztgg5 & |
---|
244 | + zsal * ( ox6 + ox7 * ztgg + ox8 * ztgg2 + ox9 * ztgg3 ) + ox10 * zsal2 |
---|
245 | chemo2(ji,jj,jk) = ( EXP( zoxy ) * o2atm ) * oxyco * atcox ! mol/(L atm) |
---|
246 | END DO |
---|
247 | END DO |
---|
248 | END DO |
---|
249 | |
---|
250 | |
---|
251 | |
---|
252 | ! CHEMICAL CONSTANTS - DEEP OCEAN |
---|
253 | ! ------------------------------- |
---|
254 | !CDIR NOVERRCHK |
---|
255 | DO jk = 1, jpk |
---|
256 | !CDIR NOVERRCHK |
---|
257 | DO jj = 1, jpj |
---|
258 | !CDIR NOVERRCHK |
---|
259 | DO ji = 1, jpi |
---|
260 | |
---|
261 | ! SET PRESSION |
---|
262 | zpres = 1.025e-1 * fsdept(ji,jj,jk) |
---|
263 | |
---|
264 | ! SET ABSOLUTE TEMPERATURE |
---|
265 | ztkel = tsn(ji,jj,jk,jp_tem) + 273.16 |
---|
266 | zsal = tsn(ji,jj,jk,jp_sal) + ( 1.-tmask(ji,jj,jk) ) * 35. |
---|
267 | zsqrt = SQRT( zsal ) |
---|
268 | zsal15 = zsqrt * zsal |
---|
269 | zlogt = LOG( ztkel ) |
---|
270 | ztr = 1. / ztkel |
---|
271 | zis = 19.924 * zsal / ( 1000.- 1.005 * zsal ) |
---|
272 | zis2 = zis * zis |
---|
273 | zisqrt = SQRT( zis ) |
---|
274 | ztc = tsn(ji,jj,jk,jp_tem) + ( 1.- tmask(ji,jj,jk) ) * 20. |
---|
275 | |
---|
276 | ! CHLORINITY (WOOSTER ET AL., 1969) |
---|
277 | zcl = zsal * salchl |
---|
278 | |
---|
279 | ! TOTAL SULFATE CONCENTR. [MOLES/kg soln] |
---|
280 | zst = st1 * zcl * st2 |
---|
281 | |
---|
282 | ! TOTAL FLUORIDE CONCENTR. [MOLES/kg soln] |
---|
283 | zft = ft1 * zcl * ft2 |
---|
284 | |
---|
285 | ! DISSOCIATION CONSTANT FOR SULFATES on free H scale (Dickson 1990) |
---|
286 | zcks = EXP( ks1 * ztr + ks0 + ks2 * zlogt & |
---|
287 | & + ( ks3 * ztr + ks4 + ks5 * zlogt ) * zisqrt & |
---|
288 | & + ( ks6 * ztr + ks7 + ks8 * zlogt ) * zis & |
---|
289 | & + ks9 * ztr * zis * zisqrt + ks10 * ztr *zis2 + LOG( ks11 + ks12 *zsal ) ) |
---|
290 | |
---|
291 | ! DISSOCIATION CONSTANT FOR FLUORIDES on free H scale (Dickson and Riley 79) |
---|
292 | zckf = EXP( kf1 * ztr + kf0 + kf2 * zisqrt + LOG( kf3 + kf4 * zsal ) ) |
---|
293 | |
---|
294 | ! DISSOCIATION CONSTANT FOR CARBONATE AND BORATE |
---|
295 | zckb = ( cb0 + cb1 * zsqrt + cb2 * zsal + cb3 * zsal15 + cb4 * zsal * zsal ) * ztr & |
---|
296 | & + ( cb5 + cb6 * zsqrt + cb7 * zsal ) & |
---|
297 | & + ( cb8 + cb9 * zsqrt + cb10 * zsal ) * zlogt + cb11 * zsqrt * ztkel & |
---|
298 | & + LOG( ( 1.+ zst / zcks + zft / zckf ) / ( 1.+ zst / zcks ) ) |
---|
299 | |
---|
300 | zck1 = c10 * ztr + c11 + c12 * zlogt + c13 * zsal + c14 * zsal * zsal |
---|
301 | zck2 = c20 * ztr + c21 + c22 * zsal + c23 * zsal**2 |
---|
302 | |
---|
303 | ! PKW (H2O) (DICKSON AND RILEY, 1979) |
---|
304 | zckw = cw0 * ztr + cw1 + cw2 * zlogt + ( cw3 * ztr + cw4 + cw5 * zlogt ) * zsqrt + cw6 * zsal |
---|
305 | |
---|
306 | |
---|
307 | ! APPARENT SOLUBILITY PRODUCT K'SP OF CALCITE IN SEAWATER |
---|
308 | ! (S=27-43, T=2-25 DEG C) at pres =0 (atmos. pressure) (MUCCI 1983) |
---|
309 | zaksp0 = akcc1 + akcc2 * ztkel + akcc3 * ztr + akcc4 * LOG10( ztkel ) & |
---|
310 | & + ( akcc5 + akcc6 * ztkel + akcc7 * ztr ) * zsqrt + akcc8 * zsal + akcc9 * zsal15 |
---|
311 | |
---|
312 | ! K1, K2 OF CARBONIC ACID, KB OF BORIC ACID, KW (H2O) (LIT.?) |
---|
313 | zak1 = 10**(zck1) |
---|
314 | zak2 = 10**(zck2) |
---|
315 | zakb = EXP( zckb ) |
---|
316 | zakw = EXP( zckw ) |
---|
317 | zaksp1 = 10**(zaksp0) |
---|
318 | |
---|
319 | ! FORMULA FOR CPEXP AFTER EDMOND & GIESKES (1970) |
---|
320 | ! (REFERENCE TO CULBERSON & PYTKOQICZ (1968) AS MADE |
---|
321 | ! IN BROECKER ET AL. (1982) IS INCORRECT; HERE RGAS IS |
---|
322 | ! TAKEN TENFOLD TO CORRECT FOR THE NOTATION OF pres IN |
---|
323 | ! DBAR INSTEAD OF BAR AND THE EXPRESSION FOR CPEXP IS |
---|
324 | ! MULTIPLIED BY LN(10.) TO ALLOW USE OF EXP-FUNCTION |
---|
325 | ! WITH BASIS E IN THE FORMULA FOR AKSPP (CF. EDMOND |
---|
326 | ! & GIESKES (1970), P. 1285-1286 (THE SMALL |
---|
327 | ! FORMULA ON P. 1286 IS RIGHT AND CONSISTENT WITH THE |
---|
328 | ! SIGN IN PARTIAL MOLAR VOLUME CHANGE AS SHOWN ON P. 1285)) |
---|
329 | zcpexp = zpres /(rgas*ztkel) |
---|
330 | zcpexp2 = zpres * zpres/(rgas*ztkel) |
---|
331 | |
---|
332 | ! KB OF BORIC ACID, K1,K2 OF CARBONIC ACID PRESSURE |
---|
333 | ! CORRECTION AFTER CULBERSON AND PYTKOWICZ (1968) |
---|
334 | ! (CF. BROECKER ET AL., 1982) |
---|
335 | |
---|
336 | zbuf1 = - ( devk11 + devk21 * ztc + devk31 * ztc * ztc ) |
---|
337 | zbuf2 = 0.5 * ( devk41 + devk51 * ztc ) |
---|
338 | ak13(ji,jj,jk) = zak1 * EXP( zbuf1 * zcpexp + zbuf2 * zcpexp2 ) |
---|
339 | |
---|
340 | zbuf1 = - ( devk12 + devk22 * ztc + devk32 * ztc * ztc ) |
---|
341 | zbuf2 = 0.5 * ( devk42 + devk52 * ztc ) |
---|
342 | ak23(ji,jj,jk) = zak2 * EXP( zbuf1 * zcpexp + zbuf2 * zcpexp2 ) |
---|
343 | |
---|
344 | zbuf1 = - ( devk13 + devk23 * ztc + devk33 * ztc * ztc ) |
---|
345 | zbuf2 = 0.5 * ( devk43 + devk53 * ztc ) |
---|
346 | akb3(ji,jj,jk) = zakb * EXP( zbuf1 * zcpexp + zbuf2 * zcpexp2 ) |
---|
347 | |
---|
348 | zbuf1 = - ( devk14 + devk24 * ztc + devk34 * ztc * ztc ) |
---|
349 | zbuf2 = 0.5 * ( devk44 + devk54 * ztc ) |
---|
350 | akw3(ji,jj,jk) = zakw * EXP( zbuf1 * zcpexp + zbuf2 * zcpexp2 ) |
---|
351 | |
---|
352 | |
---|
353 | ! APPARENT SOLUBILITY PRODUCT K'SP OF CALCITE |
---|
354 | ! AS FUNCTION OF PRESSURE FOLLOWING MILLERO |
---|
355 | ! (P. 1285) AND BERNER (1976) |
---|
356 | zbuf1 = - ( devk15 + devk25 * ztc + devk35 * ztc * ztc ) |
---|
357 | zbuf2 = 0.5 * ( devk45 + devk55 * ztc ) |
---|
358 | aksp(ji,jj,jk) = zaksp1 * EXP( zbuf1 * zcpexp + zbuf2 * zcpexp2 ) |
---|
359 | |
---|
360 | ! TOTAL BORATE CONCENTR. [MOLES/L] |
---|
361 | borat(ji,jj,jk) = bor1 * zcl * bor2 |
---|
362 | |
---|
363 | ! Iron and SIO3 saturation concentration from ... |
---|
364 | sio3eq(ji,jj,jk) = EXP( LOG( 10.) * ( 6.44 - 968. / ztkel ) ) * 1.e-6 |
---|
365 | fekeq (ji,jj,jk) = 10**( 17.27 - 1565.7 / ( 273.15 + ztc ) ) |
---|
366 | |
---|
367 | END DO |
---|
368 | END DO |
---|
369 | END DO |
---|
370 | ! |
---|
371 | IF( nn_timing == 1 ) CALL timing_stop('p4z_che') |
---|
372 | ! |
---|
373 | END SUBROUTINE p4z_che |
---|
374 | |
---|
375 | |
---|
376 | INTEGER FUNCTION p4z_che_alloc() |
---|
377 | !!---------------------------------------------------------------------- |
---|
378 | !! *** ROUTINE p4z_che_alloc *** |
---|
379 | !!---------------------------------------------------------------------- |
---|
380 | ALLOCATE( sio3eq(jpi,jpj,jpk), fekeq(jpi,jpj,jpk), chemc(jpi,jpj,2), chemo2(jpi,jpj,jpk), STAT=p4z_che_alloc ) |
---|
381 | ! |
---|
382 | IF( p4z_che_alloc /= 0 ) CALL ctl_warn('p4z_che_alloc : failed to allocate arrays.') |
---|
383 | ! |
---|
384 | END FUNCTION p4z_che_alloc |
---|
385 | |
---|
386 | #else |
---|
387 | !!====================================================================== |
---|
388 | !! Dummy module : No PISCES bio-model |
---|
389 | !!====================================================================== |
---|
390 | CONTAINS |
---|
391 | SUBROUTINE p4z_che( kt ) ! Empty routine |
---|
392 | INTEGER, INTENT(in) :: kt |
---|
393 | WRITE(*,*) 'p4z_che: You should not have seen this print! error?', kt |
---|
394 | END SUBROUTINE p4z_che |
---|
395 | #endif |
---|
396 | |
---|
397 | !!====================================================================== |
---|
398 | END MODULE p4zche |
---|