New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
mocsy_gasflux.F90 in branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA – NEMO

source: branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA/mocsy_gasflux.F90 @ 7894

Last change on this file since 7894 was 5841, checked in by jpalmier, 8 years ago

JPALM --30-10-2015-- Add MOCSY and DMS to MEDUSA-NEMO3.6

File size: 6.7 KB
Line 
1MODULE mocsy_gasflux
2
3CONTAINS
4
5! --------------------------------------------------------------------
6!  Schmidt CO2 number
7! --------------------------------------------------------------------
8!
9! Title  : Calculates Schmidt number for ocean uptake of CO2
10! Author : Andrew Yool
11! Date   : 14/10/04
12!
13! This function calculates the Schmidt number for CO2 using sea surface
14! temperature.  The code is based upon that developed as part of the
15! OCMIP-2 project (1998-2000).  The coefficients used are taken from
16! Wanninkhof (1992, JGR, 97, 7373-7382).
17!
18! AXY (12/06/2015)
19! UPDATED: coefficients used below are now those from Wanninkhof (2014)
20! update to original 1992 paper. Full reference is:
21!
22! Winninkhof, R. (2014). Relationship between wind speed and gas
23! exchange over the ocean revisited. LIMNOLOGY AND OCEANOGRAPHY-METHODS
24! 12, 351-362, doi:10.4319/lom.2014.12.351
25!
26! Check answer for the function at 20 degrees C is 668.
27!
28! Function inputs are (in order) :
29!     t            temperature (degrees C)
30! (*) co2_schmidt  carbon dioxide Schmidt number
31!
32! Where (*) is the function output.
33!
34      subroutine schmidt_co2(pt, N, co2_schmidt)
35
36      USE mocsy_singledouble
37
38      implicit none
39!
40      INTEGER, INTENT(in) :: N
41      real(kind=wp), INTENT(in),  DIMENSION(N) :: pt
42      real(kind=wp), INTENT(out), DIMENSION(N) :: co2_schmidt
43!
44      real(kind=wp)              :: a0, a1, a2, a3, a4
45!
46!     data a0 /    2073.1 /
47!     data a1 /   -125.62 /
48!     data a2 /    3.6276 /
49!     data a3 / -0.043219 /
50!
51      data a0 /    2116.8 /
52      data a1 /   -136.25 /
53      data a2 /    4.7353 /
54      data a3 / -0.092307 /
55      data a4 / 0.0007555 /
56!
57! Wanninkhof (1992)
58!     co2_schmidt = a0 + pt*(a1 + pt*(a2 + pt*a3))
59!
60! Wanninkhof (2014) adds in an extra term
61      co2_schmidt = a0 + pt*(a1 + pt*(a2 + pt*(a3 + pt*a4)))
62!
63      return
64
65      end subroutine schmidt_co2
66
67! --------------------------------------------------------------------
68!  Surface K0
69! --------------------------------------------------------------------
70!
71! Title  : Calculates surface K0 from surface T & S
72! Author : Andrew Yool
73! Date   : 18/06/15
74!
75! This function is derived from code included in the MOCSY package
76! produced by Jim Orr.
77!
78      subroutine surface_K0(ptmp, saln, N, K0)
79
80      USE mocsy_singledouble
81
82      implicit none
83!
84      INTEGER, INTENT(in) :: N
85      real(kind=wp), INTENT(in),  DIMENSION(N) :: ptmp, saln
86      real(kind=wp), INTENT(out), DIMENSION(N) :: K0
87!
88      real(kind=wp), DIMENSION(N) :: tk, invtk, tmp
89      real(kind=wp)               :: a0, a1, a2, a3, a4
90!
91      tk    = ptmp + 273.15d0
92      invtk = 1.0d0 / tk
93      tmp = (9345.17d0*invtk) - 60.2409d0 + (23.3585d0 * LOG(tk/100.0d0))
94      K0 = EXP( tmp + saln*(0.023517d0 - (0.00023656d0*tk) + (0.0047036e-4_wp*tk*tk)) )
95!
96      return
97
98      end subroutine surface_K0
99
100! --------------------------------------------------------------------
101!  Calculate xCO2
102! --------------------------------------------------------------------
103!
104!>    Compute xCO2 from arrays of pCO2atm, in situ T, S, & atm pressure
105SUBROUTINE pCO2atm2xCO2(pCO2atm, temp, salt, Patm, N, xCO2)
106  !    Purpose:
107  !    Compute xCO2 from arrays of pCO2atm, in situ T, S, & atm pressure
108
109  USE mocsy_singledouble
110
111  IMPLICIT NONE
112
113  !> number of records
114  INTEGER, intent(in) :: N
115
116! INPUT variables
117  !> atmospheric partial pressure of CO2 [uatm]
118  ! AXY (22/06/15): amended this next line to "in" as that's what it should be!
119  REAL(kind=wp), INTENT(in), DIMENSION(N) :: pCO2atm
120  !> in situ temperature [C]
121  REAL(kind=wp), INTENT(in), DIMENSION(N) :: temp
122  !> salinity [psu]
123  REAL(kind=wp), INTENT(in), DIMENSION(N) :: salt
124  !> atmospheric pressure [atm]
125  REAL(kind=wp), INTENT(in), DIMENSION(N) :: Patm
126!f2py optional , depend(temp) :: n=len(temp)
127
128! OUTPUT variables:
129  !> mole fraction of CO2 [ppm]
130  REAL(kind=wp), INTENT(out), DIMENSION(N) :: xCO2
131
132! LOCAL variables:
133  REAL(kind=wp) :: dpCO2atm, dPatm
134  REAL(kind=wp), DIMENSION(N) :: pH20
135  REAL(kind=wp) :: dxCO2
136
137  INTEGER :: i
138
139  call vapress(temp, salt, N, pH20)
140
141  DO i = 1,N
142     dpCO2atm  = DBLE(pCO2atm(i))
143     dPatm     = DBLE(Patm(i))
144     dxCO2     = dpCO2atm / (dPatm - pH20(i))
145     xCO2(i) = REAL(dxCO2)
146  END DO
147
148  RETURN
149END SUBROUTINE pCO2atm2xCO2
150
151! --------------------------------------------------------------------
152!  Calculate pCO2atm
153! --------------------------------------------------------------------
154!
155!>    Compute pCO2atm from arrays of xCO2, in situ T, S, & atm pressure
156SUBROUTINE x2pCO2atm(xCO2, temp, salt, Patm, N, pCO2atm)
157  !    Purpose:
158  !    Compute pCO2atm from arrays of xCO2, in situ T, S, & atm pressure
159
160  USE mocsy_singledouble
161
162  IMPLICIT NONE
163
164  !> number of records
165  INTEGER, intent(in) :: N
166
167! INPUT variables
168  !> mole fraction of CO2 [ppm]
169  REAL(kind=wp), INTENT(in), DIMENSION(N) :: xCO2
170  !> in situ temperature [C]
171  REAL(kind=wp), INTENT(in), DIMENSION(N) :: temp
172  !> salinity [psu]
173  REAL(kind=wp), INTENT(in), DIMENSION(N) :: salt
174  !> atmospheric pressure [atm]
175  REAL(kind=wp), INTENT(in), DIMENSION(N) :: Patm
176!f2py optional , depend(temp) :: n=len(temp)
177
178! OUTPUT variables:
179  !> oceanic partial pressure of CO2 [uatm]
180  REAL(kind=wp), INTENT(out), DIMENSION(N) :: pCO2atm
181
182! LOCAL variables:
183  REAL(kind=wp) :: dxCO2, dPatm
184  REAL(kind=wp), DIMENSION(N) :: pH20
185  REAL(kind=wp) :: dpCO2atm
186
187  INTEGER :: i
188
189! Compute vapor pressure of seawater [in atm]
190  call vapress(temp, salt, N, pH20)
191
192  DO i = 1,N
193     dxCO2     = DBLE(xCO2(i))
194     dPatm     = DBLE(Patm(i))
195     dpCO2atm = (dPatm - pH20(i)) * dxCO2
196     pCO2atm(i) = REAL(dpCO2atm)
197  END DO
198
199  RETURN
200END SUBROUTINE x2pCO2atm
201
202! --------------------------------------------------------------------
203!  Calculate seawater vapor pressure
204! --------------------------------------------------------------------
205!
206!>    Compute vapor pressure of seawater (atm) following preocedure from Weiss & Price (1980)
207SUBROUTINE vapress(temp, salt, N, vpsw)
208  !    Purpose:
209  !    Compute vapor pressure of seawater (atm) following preocedure from Weiss & Price (1980)
210
211  USE mocsy_singledouble
212  IMPLICIT NONE
213
214  !> number of records
215  INTEGER, intent(in) :: N
216
217! INPUT variables
218  !> in situ temperature [C]
219  REAL(kind=wp), INTENT(in), DIMENSION(N) :: temp
220  !> salinity [psu]
221  REAL(kind=wp), INTENT(in), DIMENSION(N) :: salt
222!f2py optional , depend(temp) :: n=len(temp)
223
224! OUTPUT variables:
225  !> vapor pressure of seawater [atm]
226  REAL(kind=wp), INTENT(out), DIMENSION(N) :: vpsw
227
228! LOCAL variables:
229  REAL(kind=wp) :: tk, dsalt
230
231  INTEGER :: i
232
233  DO i = 1,N
234     dsalt = DBLE(salt(i))
235     tk = 273.15d0 + DBLE(temp(i))     !Absolute temperature (Kelvin)
236     vpsw(i) = exp(24.4543d0 - 67.4509d0*(100.0d0/tk) - 4.8489d0*log(tk/100) - 0.000544d0*dsalt)
237  END DO
238
239  RETURN
240END SUBROUTINE vapress
241
242END MODULE mocsy_gasflux
Note: See TracBrowser for help on using the repository browser.