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.
gas_transfer.F90 in branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/TOP_SRC/MEDUSA – NEMO

source: branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/TOP_SRC/MEDUSA/gas_transfer.F90 @ 10196

Last change on this file since 10196 was 10196, checked in by jpalmier, 6 years ago

add DMS flux --

File size: 5.4 KB
Line 
1MODULE gastransfer
2   !!======================================================================
3   !!                         ***  MODULE gas_transfer  ***
4   !! TOP :   MEDUSA
5   !!======================================================================
6   !! History :
7   !!   -   ! 2015-06 (A. Yool)            added for UKESM1 project
8   !!   -   ! 2018-10 (A. Yool)            comment fixing
9   !!----------------------------------------------------------------------
10#if defined key_medusa && defined key_roam
11      USE oce_trc
12      USE trc
13      USE sms_medusa
14      USE lbclnk
15      USE prtctl_trc      ! Print control for debugging
16      USE in_out_manager  ! I/O manager
17
18      IMPLICIT NONE
19      PRIVATE
20
21      PUBLIC   gas_transfer  ! called by trcbio_medusa.F90 module
22
23   !!* Substitution
24#  include "domzgr_substitute.h90"
25   !!----------------------------------------------------------------------
26   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
27   !! $Id$
28   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
29   !!----------------------------------------------------------------------
30
31CONTAINS
32
33      subroutine gas_transfer(wind, N, eqn, kw660)
34! --------------------------------------------------------------------
35!  Gas transfer velocity
36! --------------------------------------------------------------------
37!
38! Title  : Calculates gas transfer velocity
39! Author : Andrew Yool
40! Date   : 15/10/04
41!
42! This subroutine uses near-surface wind speed to calculate gas
43! transfer velocity for use in CO2 and O2 exchange calculations.
44!
45! Note that the parameterisation of Wanninkhof quoted here is a
46! truncation of the original equation.  It excludes a chemical
47! enhancement function (based on temperature), although such
48! temperature dependence is reported negligible by Etcheto &
49! Merlivat (1988).
50!
51! Note also that in calculating scalar wind, the variance of the
52! wind over the period of a timestep is ignored.  Some authors,
53! for instance OCMIP-2, favour including some reference to the
54! variability of wind.  However, their wind fields are averaged
55! over relatively long time periods, and so this issue may be
56! safely (!) ignored here.
57!
58! AXY (12/06/2015)
59! UPDATED: revised formulation from Wanninkhof (2014) update to
60! original 1992 paper. Full reference is:
61!
62! Wanninkhof, R. (2014). Relationship between wind speed and gas
63! exchange over the ocean revisited. LIMNOLOGY AND OCEANOGRAPHY-METHODS
64! 12, 351-362, doi:10.4319/lom.2014.12.351
65!
66! Subroutine inputs are (in order) :
67!     wind      wind velocity at 10 m (m/s)
68!     N         size of input array (value 1 at this time)
69!     eqn       choice of parameterisation:
70!               1 = Liss & Merlivat (1986)    [approximated]
71!               2 = Wanninkhof (1992)         [sans enhancement]
72!               3 = Nightingale et al. (2000) [good]
73!               4 = Nightingale et al. (2000) [better]
74!               5 = Nightingale et al. (2000) [best]
75!               6 = OCMIP-2                   [sans variability]
76!               7 = Wanninkhof (2014)         [assumes 6h avg winds]
77! (*) k         gas transfer velocity (m/s)
78!
79! Where (*) is the function output and (+) is a diagnostic output.
80!
81      implicit none
82
83      INTEGER, INTENT(in) :: N, eqn
84! Input variables
85!     real(kind=wp), INTENT(in),  DIMENSION(N) :: wind
86      real(wp), INTENT(in)  :: wind
87!
88! Output variables
89!     real(kind=wp), INTENT(out), DIMENSION(N) :: kw660
90      real(wp), INTENT(out) :: kw660
91!
92!     INTEGER :: eqn
93!
94! Coefficients for various parameterisations
95      real(wp) :: a(7)
96      real(wp) :: b(7)
97!
98!     real(wp), DIMENSION(N) :: tmp_k
99      real(wp) :: tmp_k
100!
101! Values of coefficients
102      data a(1) / 0.166 /  ! Liss & Merlivat (1986)    [approximated]
103      data a(2) / 0.3   /  ! Wanninkhof (1992)         [sans enhancement]
104      data a(3) / 0.23  /  ! Nightingale et al. (2000) [good]
105      data a(4) / 0.23  /  ! Nightingale et al. (2000) [better]
106      data a(5) / 0.222 /  ! Nightingale et al. (2000) [best]
107      data a(6) / 0.337 /  ! OCMIP-2                   [sans variability]
108      data a(7) / 0.251 /  ! Wanninkhof (2014)         [assumes 6h avg winds]
109!
110      data b(1) / 0.133 /
111      data b(2) / 0.0   /
112      data b(3) / 0.0   /
113      data b(4) / 0.1   /
114      data b(5) / 0.333 /
115      data b(6) / 0.0   /
116      data b(7) / 0.0   /
117!
118! Which parameterisation is to be used?
119!     eqn = 7
120!
121! Calculate gas transfer velocity (cm/h)
122      tmp_k = (a(eqn) * wind**2) + (b(eqn) * wind)
123!
124! Convert tmp_k from cm/h to m/s
125      kw660 = tmp_k / (100. * 3600.)
126!
127      return
128
129    end subroutine gas_transfer
130
131!=======================================================================
132!=======================================================================
133!=======================================================================
134
135#else
136   !!======================================================================
137   !!  Dummy module :                                   No MEDUSA bio-model
138   !!======================================================================
139
140CONTAINS
141
142   SUBROUTINE gas_transfer(wind, N, eqn, kw660)
143      USE par_kind
144
145      REAL(wp), INTENT( in )    :: wind
146      REAL(wp), INTENT( in )    :: kw660
147      INTEGER, INTENT(in) :: N, eqn
148
149      WRITE(*,*) 'gas_transfer: You should not have seen this print! error?', kt
150
151   END SUBROUTINE gas_transfer
152#endif
153
154   !!======================================================================
155END MODULE gastransfer
Note: See TracBrowser for help on using the repository browser.