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.
trcoxy_medusa.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/trcoxy_medusa.F90 @ 5841

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

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

File size: 9.6 KB
Line 
1MODULE trcoxy_medusa
2   !!======================================================================
3   !!                         ***  MODULE trcoxy_medusa  ***
4   !! TOP :   MEDUSA
5   !!======================================================================
6   !! History :
7   !!  -   !  2011-07  (A. Yool)             added for ROAM project
8   !!----------------------------------------------------------------------
9#if defined key_medusa && defined key_roam
10   !!----------------------------------------------------------------------
11   !!                                        MEDUSA oxygen cycle
12   !!----------------------------------------------------------------------
13   !!   trc_oxy_medusa        : 
14   !!----------------------------------------------------------------------
15      USE oce_trc
16      USE trc
17      USE sms_medusa
18      USE lbclnk
19      USE prtctl_trc      ! Print control for debugging
20
21      IMPLICIT NONE
22      PRIVATE
23     
24      PUBLIC   trc_oxy_medusa    ! called in trc_bio_medusa
25
26   !!* Substitution
27#  include "domzgr_substitute.h90"
28   !!----------------------------------------------------------------------
29   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
30   !! $Id$
31   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33
34! The following is a map of the subroutines contained within this module
35! - trc_oxy_medusa
36!      - CALLS oxy_schmidt
37!      - CALLS oxy_sato
38
39CONTAINS
40
41!=======================================================================
42!
43   SUBROUTINE trc_oxy_medusa( pt, ps, kw660, pp0, o2,  &  !! inputs
44      kwo2, o2flux, o2sat )                               !! outputs
45!     
46!=======================================================================
47      !!
48      !! Title  : Calculates O2 change due to air-sea gas exchange
49      !! Author : Andrew Yool
50      !! Date   : 15/10/04 (revised 08/07/11)
51      !!
52      !! This subroutine calculates oxygen air-sea gas exchange in the
53      !! surface layer of the ocean.  The formulation is taken from one
54      !! written by Ray Najjar for the OCMIP-2 project.  The routine
55      !! calls two other subroutines, oxy_schmidt.f (calculates Schmidt
56      !! number of oxygen) and oxy_sato.f (calculates oxygen saturation
57      !! concentration at 1 atm).
58      !!
59      !! AXY (23/06/15): revised to allow common gas transfer velocity
60      !!                 to be used for CO2 and O2; outputs of this
61      !!                 routine amended to mmol/m3 from mol/m3
62      !!
63      !! Function inputs are (in order) :
64      !!     pt      temperature                     (degrees C)
65      !!     ps      salinity                        (PSU)
66      !!     kw660   gas transfer velocity           (m/s)
67      !!     pp0     surface pressure                (divided by 1 atm)
68      !!     o2      surface O2 concentration        (mmol/m3)
69      !! (+) kwo2    gas transfer velocity for O2    (m/s)
70      !! (*) o2flux  exchange rate of oxygen         (mmol/m2/s)
71      !! (+) o2sat   oxygen saturation concentration (mmol/m3)
72      !!
73      !! Where (*) is the function output (note its units). 
74      !!
75!=======================================================================
76
77      implicit none
78!
79      REAL(wp), INTENT( in )    :: pt
80      REAL(wp), INTENT( in )    :: ps
81      REAL(wp), INTENT( in )    :: kw660
82      REAL(wp), INTENT( in )    :: pp0
83      REAL(wp), INTENT( in )    :: o2
84      REAL(wp), INTENT( out )   :: kwo2, o2flux, o2sat
85!
86      REAL(wp) :: o2schmidt, o2sato, mol_o2
87!
88! Oxygen to mol / m3
89!
90      mol_o2 = o2 / 1000.
91!
92! Calculate oxygen Schmidt number
93!
94      call oxy_schmidt(pt, o2schmidt)
95!
96! Calculate the transfer velocity for O2 (m/s)
97!
98      kwo2 = kw660 * (660 / o2schmidt)**0.5
99!
100! Calculate the saturation concentration for oxygen (mol/m3)
101!
102      call oxy_sato(pt, ps, o2sato)
103      o2sat = o2sato * pp0
104!
105! Calculate time rate of change of O2 due to gas exchange (mol/m3/s)
106!
107      o2flux = kwo2 * (o2sat - mol_o2)
108!
109! Oxygen flux and saturation to mmol / m3
110!
111      o2sat  =  o2sat * 1000.
112      o2flux = o2flux * 1000.
113!
114      END SUBROUTINE trc_oxy_medusa
115
116!=======================================================================
117!=======================================================================
118!=======================================================================
119
120!=======================================================================
121!
122   SUBROUTINE oxy_schmidt( pt, &  !! input
123      o2_schmidt )                !! output
124!     
125!=======================================================================
126      !!
127      !! Title  : Calculates Schmidt number for ocean uptake of O2
128      !! Author : Andrew Yool
129      !! Date   : 14/10/04 (revised 08/07/11)
130      !!
131      !! This subroutine calculates the Schmidt number for O2 using sea
132      !! surface temperature.  The code is based upon that developed as
133      !! part of the OCMIP-2 project (1998-2000).  The coefficients used
134      !! are taken from Keeling et al. (1998, GBC, 12, 141-163).
135      !!
136      !! AXY (23/06/2015)
137      !! UPDATED: revised formulation from Wanninkhof (2014) for
138      !! consistency with MOCSY
139      !!
140      !! Winninkhof, R. (2014). Relationship between wind speed and gas
141      !! exchange over the ocean revisited. LIMNOLOGY AND OCEANOGRAPHY-METHODS
142      !! 12, 351-362, doi:10.4319/lom.2014.12.351
143      !!
144      !! Function inputs are (in order) :
145      !!     t           temperature (degrees C)
146      !! (*) o2_schmidt  oxygen Schmidt number
147      !!
148      !! Where (*) is the function output.
149      !!
150!=======================================================================
151
152      implicit none
153!
154      REAL(wp) :: pt, o2_schmidt
155      REAL(wp) :: a0, a1, a2, a3, a4
156!
157! AXY (23/06/15): OCMIP-2 coefficients
158!     data a0 /    1638.0 /
159!     data a1 /    -81.83 /
160!     data a2 /     1.483 /
161!     data a3 / -0.008004 /
162!
163! AXY (23/06/15): Wanninkhof (2014) coefficients
164      data a0 /     1920.4 /
165      data a1 /     -135.6 /
166      data a2 /     5.2121 /
167      data a3 /   -0.10939 /
168      data a4 / 0.00093777 /
169!
170!     o2_schmidt = a0 + pt*(a1 + pt*(a2 + pt*a3))
171      o2_schmidt = a0 + pt*(a1 + pt*(a2 + pt*(a3 + pt*a4)))
172!
173      END SUBROUTINE oxy_schmidt
174
175!=======================================================================
176!=======================================================================
177!=======================================================================
178
179!=======================================================================
180!
181   SUBROUTINE oxy_sato( pt, ps, &  !! inputs
182      o2_sato )                    !! output
183!     
184!=======================================================================
185      !!
186      !! Title  : Calculates O2 saturation at 1 atm pressure
187      !! Author : Andrew Yool
188      !! Date   : 14/10/04 (revised 08/07/11)
189      !!
190      !! This subroutine calculates the oxygen saturation concentration
191      !! at 1 atmosphere pressure in mol/m3 given ambient temperature
192      !! and salinity.  This formulation is (ostensibly) taken from
193      !! Garcia & Gordon (1992, L&O, 1307-1312).  The function works
194      !! in the range -1.9 <= T <= 40, 0 <= S <= 42.
195      !!
196      !! Function inputs are (in order) :
197      !!     pt       temperature (degrees C)
198      !!     ps       salinity (PSU)
199      !! (*) o2_sato  oxygen saturation (mol/m3)
200      !!
201      !! Where (*) is the function output (note its units). 
202      !!
203      !! Check value : T = 10, S = 35, oxy_sato = 0.282015 mol/m3
204      !!
205!=======================================================================
206
207      implicit none
208!
209      REAL(wp) :: pt, ps, o2_sato
210!
211      REAL(wp) :: a0, a1, a2, a3, a4, a5
212      REAL(wp) :: b0, b1, b2, b3
213      REAL(wp) :: c0
214!
215      REAL(wp) :: tt, tk, ts, ts2, ts3, ts4, ts5
216      REAL(wp) :: ans1, ans2
217!
218      data a0 /  2.00907    /
219      data a1 /  3.22014    /
220      data a2 /  4.05010    /
221      data a3 /  4.94457    /
222      data a4 / -2.56847E-1 /
223      data a5 /  3.88767    /
224!
225      data b0 / -6.24523E-3 /
226      data b1 / -7.37614E-3 /
227      data b2 / -1.03410E-2 /
228      data b3 / -8.17083E-3 /
229!
230      data c0 / -4.88682E-7 /
231!     
232      tt   = 298.15 - pt
233      tk   = 273.15 + pt
234      ts   = log(tt / tk)
235      ts2  = ts**2
236      ts3  = ts**3
237      ts4  = ts**4
238      ts5  = ts**5
239      ans1 = a0 + a1*ts + a2*ts2 + a3*ts3 + a4*ts4 + a5*ts5  &
240           + ps*(b0 + b1*ts + b2*ts2 + b3*ts3)               &
241           + c0*(ps*ps)
242      ans2 = exp(ans1)
243!
244!  Convert from ml/l to mol/m3
245!
246      o2_sato = (ans2 / 22391.6) * 1000.0
247!
248      END SUBROUTINE oxy_sato
249
250!=======================================================================
251!=======================================================================
252!=======================================================================
253
254#else
255   !!======================================================================
256   !!  Dummy module :                                   No MEDUSA bio-model
257   !!======================================================================
258
259CONTAINS
260
261   SUBROUTINE trc_oxy_medusa( pt, ps, kw660, pp0, o2,  &  !! inputs
262      o2flux, o2sat )                                     !! outputs
263      USE par_kind
264
265      REAL(wp), INTENT( in )    :: pt
266      REAL(wp), INTENT( in )    :: ps
267      REAL(wp), INTENT( in )    :: kw660
268      REAL(wp), INTENT( in )    :: pp0
269      REAL(wp), INTENT( in )    :: o2
270      REAL(wp), INTENT( inout ) :: o2flux, o2sat
271
272      WRITE(*,*) 'trc_oxy_medusa: You should not have seen this print! error?', kt
273
274   END SUBROUTINE trc_oxy_medusa
275#endif
276
277   !!======================================================================
278END MODULE  trcoxy_medusa
279 
Note: See TracBrowser for help on using the repository browser.