MOM6
mom_ocmip2_co2calc_mod Module Reference

Data Types

type  co2_dope_vector
 

Functions/Subroutines

subroutine, public mom_ocmip2_co2calc (dope_vec, mask, t_in, s_in, dic_in, pt_in, sit_in, ta_in, htotallo, htotalhi, htotal, co2star, alpha, pCO2surf, co3_ion)
 
real function drtsafe (k0, k1, k2, kb, k1p, k2p, k3p, ksi, kw, ks, kf, bt, dic, ft, pt, sit, st, ta, x1, x2, xacc)
 
subroutine ta_iter_1 (k0, k1, k2, kb, k1p, k2p, k3p, ksi, kw, ks, kf, bt, dic, ft, pt, sit, st, ta, x, fn, df)
 

Variables

character(len= *), parameter version = 'unknown'
 

Function/Subroutine Documentation

◆ drtsafe()

real function mom_ocmip2_co2calc_mod::drtsafe ( real  k0,
real  k1,
real  k2,
real  kb,
real  k1p,
real  k2p,
real  k3p,
real  ksi,
real  kw,
real  ks,
real  kf,
real  bt,
real  dic,
real  ft,
real  pt,
real  sit,
real  st,
real  ta,
real  x1,
real  x2,
real  xacc 
)
private

Definition at line 410 of file MOM_OCMIP2_CO2calc.F90.

References ta_iter_1().

Referenced by mom_ocmip2_co2calc().

410 
411 real :: k0, k1, k2, kb, k1p, k2p, k3p, ksi, kw, ks, kf
412 real :: bt, dic, ft, pt, sit, st, ta
413 real :: drtsafe
414 real :: x1, x2, xacc
415 
416 !
417 ! local parameters
418 !
419 
420 integer, parameter :: maxit = 100
421 
422 !
423 ! local variables
424 !
425 
426 integer :: j
427 real :: fl, df, fh, swap, xl, xh, dxold, dx, f, temp
428 
429 call ta_iter_1(k0, k1, k2, kb, k1p, k2p, k3p, ksi, kw, ks, kf, &
430  bt, dic, ft, pt, sit, st, ta, x1, fl, df)
431 call ta_iter_1(k0, k1, k2, kb, k1p, k2p, k3p, ksi, kw, ks, kf, &
432  bt, dic, ft, pt, sit, st, ta, x2, fh, df)
433 if(fl .lt. 0.0) then
434  xl=x1
435  xh=x2
436 else
437  xh=x1
438  xl=x2
439  swap=fl
440  fl=fh
441  fh=swap
442 end if
443 drtsafe=0.5*(x1+x2)
444 dxold=abs(x2-x1)
445 dx=dxold
446 call ta_iter_1(k0, k1, k2, kb, k1p, k2p, k3p, ksi, kw, ks, kf, &
447  bt, dic, ft, pt, sit, st, ta, drtsafe, f, df)
448 do j=1,maxit !{
449  if (((drtsafe-xh)*df-f)*((drtsafe-xl)*df-f) .ge. 0.0 .or. &
450  abs(2.0*f) .gt. abs(dxold*df)) then
451  dxold=dx
452  dx=0.5*(xh-xl)
453  drtsafe=xl+dx
454  if (xl .eq. drtsafe) then
455 ! write (6,*) 'Exiting drtsafe at A on iteration ', j, ', ph = ', -log10(drtsafe)
456  return
457  endif
458  else
459  dxold=dx
460  dx=f/df
461  temp=drtsafe
462  drtsafe=drtsafe-dx
463  if (temp .eq. drtsafe) then
464 ! write (6,*) 'Exiting drtsafe at B on iteration ', j, ', ph = ', -log10(drtsafe)
465  return
466  endif
467  end if
468  if (abs(dx) .lt. xacc) then
469 ! write (6,*) 'Exiting drtsafe at C on iteration ', j, ', ph = ', -log10(drtsafe)
470  return
471  endif
472  call ta_iter_1(k0, k1, k2, kb, k1p, k2p, k3p, ksi, kw, ks, kf, &
473  bt, dic, ft, pt, sit, st, ta, drtsafe, f, df)
474  if(f .lt. 0.0) then
475  xl=drtsafe
476  fl=f
477  else
478  xh=drtsafe
479  fh=f
480  end if
481 enddo !} j
482 
483 return
484 
485 end function drtsafe !}
486 ! </FUNCTION> NAME="drtsafe"
487 
488 
489 !#######################################################################
490 ! <SUBROUTINE NAME="ta_iter_1">
Here is the call graph for this function:
Here is the caller graph for this function:

◆ mom_ocmip2_co2calc()

subroutine, public mom_ocmip2_co2calc_mod::mom_ocmip2_co2calc ( type(co2_dope_vector), intent(in)  dope_vec,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(in)  mask,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(in)  t_in,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(in)  s_in,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(in)  dic_in,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(in)  pt_in,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(in)  sit_in,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(in)  ta_in,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(in)  htotallo,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(in)  htotalhi,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(inout)  htotal,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(out), optional  co2star,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(out), optional  alpha,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(out), optional  pCO2surf,
real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), intent(out), optional  co3_ion 
)

Definition at line 127 of file MOM_OCMIP2_CO2calc.F90.

References drtsafe().

127 
128 real, parameter :: permeg = 1.e-6
129 real, parameter :: xacc = 1.0e-10
130 
131 !
132 ! arguments
133 !
134 type(co2_dope_vector), intent(in) :: dope_vec
135 real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), &
136  intent(in):: mask, &
137  t_in, &
138  s_in, &
139  dic_in, &
140  pt_in, &
141  sit_in, &
142  ta_in, &
143  htotallo, &
144  htotalhi
145 real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), &
146  intent(inout) :: htotal
147 real, dimension(dope_vec%isd:dope_vec%ied,dope_vec%jsd:dope_vec%jed), &
148  intent(out), optional :: alpha, &
149  pco2surf, &
150  co2star, &
151  co3_ion
152 !
153 ! local variables
154 !
155 integer :: isc, iec, jsc, jec
156 integer :: i,j
157 real :: alpha_internal
158 real :: bt
159 real :: co2star_internal
160 real :: dlogtk
161 real :: ft
162 real :: htotal2
163 real :: invtk
164 real :: is
165 real :: is2
166 real :: k0
167 real :: k1
168 real :: k2
169 real :: k1p
170 real :: k2p
171 real :: k3p
172 real :: kb
173 real :: kf
174 real :: ks
175 real :: ksi
176 real :: kw
177 real :: log100
178 real :: s2
179 real :: scl
180 real :: sqrtis
181 real :: sqrts
182 real :: st
183 real :: tk
184 real :: tk100
185 real :: tk1002
186 real :: logf_of_s
187 
188 ! Set the loop indices.
189  isc = dope_vec%isc ; iec = dope_vec%iec
190  jsc = dope_vec%jsc ; jec = dope_vec%jec
191 
192 !
193 ! Initialize the module
194 !
195  log100 = log(100.0)
196 
197  do j = jsc, jec !{
198  do i = isc, iec !{
199 !
200 !---------------------------------------------------------------------
201 !
202 !***********************************************************************
203 ! Calculate all constants needed to convert between various measured
204 ! carbon species. References for each equation are noted in the code.
205 ! Once calculated, the constants are stored and passed in the common
206 ! block "const". The original version of this code was based on
207 ! the code by Dickson in Version 2 of "Handbook of Methods for the
208 ! Analysis of the Various Parameters of the Carbon Dioxide System
209 ! in Seawater", DOE, 1994 (SOP No. 3, p25-26).
210  tk = 273.15 + t_in(i,j)
211  tk100 = tk / 100.0
212  tk1002 = tk100**2
213  invtk = 1.0 / tk
214  dlogtk = log(tk)
215  is = 19.924 * s_in(i,j) /(1000.0 -1.005 * s_in(i,j))
216  is2 = is * is
217  sqrtis = sqrt(is)
218  s2 = s_in(i,j) * s_in(i,j)
219  sqrts = sqrt(s_in(i,j))
220  scl = s_in(i,j) / 1.80655
221  logf_of_s = log(1.0 - 0.001005 * s_in(i,j))
222 !
223 ! k0 from Weiss 1974
224 !
225 
226  k0 = exp(93.4517/tk100 - 60.2409 + 23.3585 * log(tk100) + &
227  s_in(i,j) * (0.023517 - 0.023656 * tk100 + &
228  0.0047036 * tk1002))
229 !
230 ! k1 = [H][HCO3]/[H2CO3]
231 ! k2 = [H][CO3]/[HCO3]
232 !
233 ! Millero p.664 (1995) using Mehrbach et al. data on seawater scale
234 !
235 
236  k1 = 10.0**(-(3670.7 * invtk - 62.008 + 9.7944 * dlogtk - &
237  0.0118 * s_in(i,j) + 0.000116 * s2))
238  k2 = 10.0**(-(1394.7 * invtk + 4.777 - &
239  0.0184 * s_in(i,j) + 0.000118 * s2))
240 !
241 ! kb = [H][BO2]/[HBO2]
242 !
243 ! Millero p.669 (1995) using data from Dickson (1990)
244 !
245 
246  kb = exp((-8966.90 - 2890.53 * sqrts - 77.942 * s_in(i,j) + &
247  1.728 * sqrts**3 - 0.0996 * s2) * invtk + (148.0248 + &
248  137.1942 * sqrts + 1.62142 * s_in(i,j)) + (-24.4344 - &
249  25.085 * sqrts - 0.2474 * s_in(i,j)) * dlogtk + &
250  0.053105 * sqrts * tk)
251 !
252 ! k1p = [H][H2PO4]/[H3PO4]
253 !
254 ! DOE(1994) eq 7.2.20 with footnote using data from Millero (1974)
255 !
256 
257  k1p = exp(-4576.752 * invtk + 115.525 - 18.453 * dlogtk + &
258  (-106.736 * invtk + 0.69171) * sqrts + (-0.65643 * &
259  invtk - 0.01844) * s_in(i,j))
260 !
261 ! k2p = [H][HPO4]/[H2PO4]
262 !
263 ! DOE(1994) eq 7.2.23 with footnote using data from Millero (1974))
264 !
265 
266  k2p = exp(-8814.715 * invtk + 172.0883 - 27.927 * (-160.340 * &
267  invtk + 1.3566) * sqrts + (0.37335 * invtk - &
268  0.05778) * s_in(i,j))
269 !
270 !-----------------------------------------------------------------------
271 ! k3p = [H][PO4]/[HPO4]
272 !
273 ! DOE(1994) eq 7.2.26 with footnote using data from Millero (1974)
274 !
275 
276  k3p = exp(-3070.75 * invtk - 18.141 +(17.27039 * invtk + &
277  2.81197) * sqrts + (-44.99486 * invtk - 0.09984) * &
278  s_in(i,j))
279 !
280 !-----------------------------------------------------------------------
281 ! ksi = [H][SiO(OH)3]/[Si(OH)4]
282 !
283 ! Millero p.671 (1995) using data from Yao and Millero (1995)
284 !
285  ksi = exp(-8904.2 * invtk + 117.385 - 19.334 * dlogtk + &
286  (-458.79 * invtk + 3.5913) * sqrtis + (188.74 * &
287  invtk - 1.5998) * is + (-12.1652 * invtk + 0.07871) * &
288  is2 + logf_of_s)
289 !
290 !-----------------------------------------------------------------------
291 ! kw = [H][OH]
292 !
293 ! Millero p.670 (1995) using composite data
294 !
295 
296  kw = exp(-13847.26 * invtk + 148.9652 - 23.6521 * dlogtk + &
297  (118.67 * invtk - 5.977 + 1.0495 * dlogtk) * sqrts - &
298  0.01615 * s_in(i,j))
299 !
300 !-----------------------------------------------------------------------
301 ! ks = [H][SO4]/[HSO4]
302 !
303 ! Dickson (1990, J. chem. Thermodynamics 22, 113)
304 !
305  ks = exp(-4276.1 * invtk + 141.328 - 23.093 * dlogtk + &
306  (-13856.0 * invtk + 324.57 - 47.986 * dlogtk) * &
307  sqrtis + (35474.0 * invtk - 771.54 + 114.723 * &
308  dlogtk) * is - 2698.0 * invtk * sqrtis**3 + &
309  1776.0 * invtk * is2 + logf_of_s)
310 !
311 !-----------------------------------------------------------------------
312 ! kf = [H][F]/[HF]
313 !
314 ! Dickson and Riley (1979) -- change pH scale to total
315 !
316  kf = exp(1590.2 * invtk - 12.641 + 1.525 * sqrtis + logf_of_s + &
317  log(1.0 + (0.1400 / 96.062) * scl / ks))
318 !
319 !-----------------------------------------------------------------------
320 ! Calculate concentrations for borate, sulfate, and fluoride
321 !
322 ! Uppstrom (1974)
323 !
324  bt = 0.000232 / 10.811 * scl
325 !
326 ! Morris & Riley (1966)
327 !
328  st = 0.14 / 96.062 * scl
329 !
330 ! Riley (1965)
331 !
332  ft = 0.000067 / 18.9984 * scl
333 !
334 !***********************************************************************
335 !
336 ! Calculate [H+] total when DIC and TA are known at T, S and 1 atm.
337 ! The solution converges to err of xacc. The solution must be within
338 ! the range x1 to x2.
339 !
340 ! If DIC and TA are known then either a root finding or iterative method
341 ! must be used to calculate htotal. In this case we use the
342 ! Newton-Raphson "safe" method taken from "Numerical Recipes"
343 ! (function "rtsafe.f" with error trapping removed).
344 !
345 ! As currently set, this procedure iterates about 12 times. The x1
346 ! and x2 values set below will accomodate ANY oceanographic values.
347 ! If an initial guess of the pH is known, then the number of
348 ! iterations can be reduced to about 5 by narrowing the gap between
349 ! x1 and x2. It is recommended that the first few time steps be run
350 ! with x1 and x2 set as below. After that, set x1 and x2 to the
351 ! previous value of the pH +/- ~0.5. The current setting of xacc will
352 ! result in co2star accurate to 3 significant figures (xx.y). Making
353 ! xacc bigger will result in faster convergence also, but this is not
354 ! recommended (xacc of 10**-9 drops precision to 2 significant
355 ! figures).
356 !
357  if (mask(i,j) .ne. 0.0) then !{
358  htotal(i,j) = drtsafe(k0, k1, k2, kb, k1p, k2p, k3p, ksi, kw, &
359  ks, kf, bt, dic_in(i,j), ft, pt_in(i,j),&
360  sit_in(i,j), st, ta_in(i,j), &
361  htotalhi(i,j), htotallo(i,j), xacc)
362  endif
363 !
364 ! Calculate [CO2*] as defined in DOE Methods Handbook 1994 Ver.2,
365 ! ORNL/CDIAC-74, Dickson and Goyet, eds. (Ch 2 p 10, Eq A.49)
366 !
367  htotal2 = htotal(i,j) * htotal(i,j)
368  co2star_internal = dic_in(i,j) * htotal2 / (htotal2 + &
369  k1 * htotal(i,j) + k1 * k2)
370  if (present(co2star)) co2star(i,j) = co2star_internal
371  if (present(co3_ion)) co3_ion(i,j) = co2star_internal * k1 * k2 / htotal2
372 !
373 ! Weiss & Price (1980, Mar. Chem., 8, 347-359; Eq 13 with table 6
374 ! values)
375 !
376  if (present(alpha) .or. present(pco2surf)) then
377  alpha_internal = exp(-162.8301 + 218.2968 / tk100 + 90.9241 * &
378  (dlogtk -log100) - 1.47696 * tk1002 + &
379  s_in(i,j) * (0.025695 - 0.025225 * tk100 + &
380  0.0049867 * tk1002))
381  endif
382  if (present(alpha)) alpha(i,j) = alpha_internal
383  if (present(pco2surf)) then
384  pco2surf(i,j) = co2star_internal / (alpha_internal * permeg)
385  endif
386  enddo !} i
387  enddo !} j
388 
389 return
390 
391 end subroutine mom_ocmip2_co2calc !}
392 ! </SUBROUTINE> NAME="MOM_ocmip2_co2calc"
393 
394 
395 !#######################################################################
396 ! <FUNCTION NAME="drtsafe">
Here is the call graph for this function:

◆ ta_iter_1()

subroutine mom_ocmip2_co2calc_mod::ta_iter_1 ( real  k0,
real  k1,
real  k2,
real  kb,
real  k1p,
real  k2p,
real  k3p,
real  ksi,
real  kw,
real  ks,
real  kf,
real  bt,
real  dic,
real  ft,
real  pt,
real  sit,
real  st,
real  ta,
real  x,
real  fn,
real  df 
)
private

Definition at line 508 of file MOM_OCMIP2_CO2calc.F90.

Referenced by drtsafe().

508 
509 real :: k0, k1, k2, kb, k1p, k2p, k3p, ksi, kw, ks, kf
510 real :: bt, dic, ft, pt, sit, st, ta, x, fn, df
511 
512 !
513 ! local variables
514 !
515 
516 real :: x2, x3, k12, k12p, k123p, c, a, a2, da, b, b2, db
517 
518 x2 = x*x
519 x3 = x2*x
520 k12 = k1*k2
521 k12p = k1p*k2p
522 k123p = k12p*k3p
523 c = 1.0 + st/ks
524 a = x3 + k1p*x2 + k12p*x + k123p
525 a2 = a*a
526 da = 3.0*x2 + 2.0*k1p*x + k12p
527 b = x2 + k1*x + k12
528 b2 = b*b
529 db = 2.0*x + k1
530 !
531 ! fn = hco3+co3+borate+oh+hpo4+2*po4+silicate+hfree+hso4+hf+h3po4-ta
532 !
533 fn = k1*x*dic/b + 2.0*dic*k12/b + bt/ (1.0 + x/kb) + kw/x + &
534  pt*k12p*x/a + 2.0*pt*k123p/a + sit/(1.0 + x/ksi) - &
535  x/c - st/(1.0 + ks/x/c) - ft/(1.0 + kf/x) - pt*x3/a - ta
536 !
537 ! df = dfn/dx
538 !
539 df = ((k1*dic*b) - k1*x*dic*db)/b2 - 2.0*dic*k12*db/b2 - &
540  bt/kb/(1.0+x/kb)**2 - kw/x2 + (pt*k12p*(a - x*da))/a2 - &
541  2.0*pt*k123p*da/a2 - sit/ksi/ (1.0+x/ksi)**2 - 1.0/c + &
542  st*(1.0 + ks/x/c)**(-2)*(ks/c/x2) + &
543  ft*(1.0 + kf/x)**(-2)*kf/x2 - pt*x2*(3.0*a-x*da)/a2
544 
545 return
546 
547 end subroutine ta_iter_1 !}
548 ! </SUBROUTINE> NAME="ta_iter_1"
549 
550 end module mom_ocmip2_co2calc_mod !}
Here is the caller graph for this function:

Variable Documentation

◆ version

character(len=*), parameter mom_ocmip2_co2calc_mod::version = 'unknown'
private

Definition at line 61 of file MOM_OCMIP2_CO2calc.F90.

61  integer :: isd, ied, jsd, jed