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.
trcdms_medusa.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/trcdms_medusa.F90 @ 10196

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

add DMS flux --

File size: 13.3 KB
Line 
1MODULE trcdms_medusa
2   !!======================================================================
3   !!                         ***  MODULE trcdms_medusa  ***
4   !! TOP :   MEDUSA
5   !!======================================================================
6   !! History :
7   !!  -   !  2014-08  (J. Palmieri - A. Yool)    added for UKESM1 project
8   !!  -   !  2017-05  (A. Yool)                  add extra Anderson scheme
9   !!  -   !  2018-10 (A. Yool)                   Add air-sea DMS flux
10   !!----------------------------------------------------------------------
11#if defined key_medusa && defined key_roam
12   !!----------------------------------------------------------------------
13   !!                                        MEDUSA DMS surface concentration
14   !!----------------------------------------------------------------------
15   !!   trc_dms_medusa        : 
16   !!----------------------------------------------------------------------
17      USE oce_trc
18      USE trc
19      USE sms_medusa
20      USE lbclnk
21      USE prtctl_trc      ! Print control for debugging
22      USE in_out_manager  ! I/O manager
23
24      IMPLICIT NONE
25      PRIVATE
26
27      PUBLIC   trc_dms_medusa    ! called in trc_bio_medusa
28      PUBLIC   dms_flux_ocn      ! called in air_sea
29
30   !!* Substitution
31#  include "domzgr_substitute.h90"
32   !!----------------------------------------------------------------------
33   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
34   !! $Id$
35   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
36   !!----------------------------------------------------------------------
37
38
39CONTAINS
40
41!=======================================================================
42!
43   SUBROUTINE trc_dms_medusa( chn, chd, mld, xqsr, xdin, xlim,  &  !! inputs
44     &  dms_andr, dms_simo, dms_aran, dms_hall, dms_andm)           !! outputs
45!     
46!=======================================================================
47      !!
48      !! Title  : Calculates DMS ocean surface concentration
49      !! Author : Julien Palmieri and Andrew Yool
50      !! Date   : 08/08/14
51      !!
52      !! DMS module is called in trc_bio's huge jk,jj,ji loop
53      !! --> DMS concentration is calculated in a specific cell
54      !! (no need of ji,jj,jk)
55      !!
56      !! AXY (13/03/15): amend to include all four schemes tested
57      !!                 during winter/spring 2015; these are:
58      !!
59      !!                 1. Anderson et al. (2001); this uses fields
60      !!                    of surface chl, irradiance and nutrients
61      !!                    to empirically estimate DMS via a broken
62      !!                    stick approach
63      !!
64      !!                 2. Simo & Dachs (2002); this uses fields of
65      !!                    surface chl and mixed layer depth
66      !!
67      !!                 3. Aranami & Tsunogai (2004); this is an
68      !!                    embellishment of Simo & Dachs
69      !!
70      !!                 4. Halloran et al. (2010); this is an
71      !!                    alternative embellishment of Sim & Dachs
72      !!                    and is included because it is formally
73      !!                    published (and different from the above)
74      !!
75      !! AXY (25/05/17): add extra "corrected" Anderson scheme
76      !!
77      !!                 5. As Anderson et al. (2001) but modified to
78      !!                    more accurately reflect nutrient limitation
79      !!                    status of phytoplankton community
80      !!
81      !! AXY (08/07/15): amend to remove Julien's original calculation
82      !!                 as this is now superfluous; the four schemes
83      !!                 are calculated and one is chosen to be passed
84      !!                 to the atmosphere in trc_bio_medusa
85      !!
86!=======================================================================
87
88      IMPLICIT NONE
89!
90      REAL(wp), INTENT( in )    :: chn                  !! non-diatom chlorophyll    (mg/m3)
91      REAL(wp), INTENT( in )    :: chd                  !! diatom chlorophyll        (mg/m3)
92      REAL(wp), INTENT( in )    :: mld                  !! mix layer depth           (m)
93      REAL(wp), INTENT( in )    :: xqsr                 !! surface irradiance        (W/m2)
94      REAL(wp), INTENT( in )    :: xdin                 !! surface DIN               (mmol N/m3)
95      REAL(wp), INTENT( in )    :: xlim                 !! surface DIN limitation    (mmol N/m3)
96      REAL(wp), INTENT( inout ) :: dms_andr             !! DMS surface concentration (nmol/L)
97      REAL(wp), INTENT( inout ) :: dms_simo             !! DMS surface concentration (nmol/L)
98      REAL(wp), INTENT( inout ) :: dms_aran             !! DMS surface concentration (nmol/L)
99      REAL(wp), INTENT( inout ) :: dms_hall             !! DMS surface concentration (nmol/L)
100      REAL(wp), INTENT( inout ) :: dms_andm             !! DMS surface concentration (nmol/L)
101!
102      REAL(wp) :: CHL, cmr, sw_dms
103      REAL(wp) :: Jterm, Qterm
104      !! temporary variables
105      REAL(wp) ::    fq1,fq2,fq3
106!
107!=======================================================================
108!
109! AXY (13/03/15): per remarks above, the following calculations estimate
110!                 DMS using all of the schemes examined for UKESM1
111!
112      CHL = 0.0
113      CHL = chn+chd                                 !! mg/m3
114      cmr = CHL / mld
115!
116! AXY (13/03/15): Anderson et al. (2001)
117!! JPALM --19-12-2017-- Tunable through the namelist
118!!                      within dmsmin - dmscut - dmsslp
119        Jterm = xqsr + 1.0e-6
120        !! this next line makes a hard-coded assumption about the
121        !! half-saturation constant of MEDUSA (which should be
122        !! done properly; perhaps even scaled with the proportion
123        !! of diatoms and non-diatoms)
124        Qterm = xdin / (xdin + 0.5)
125        fq1 = log10(CHL * Jterm * Qterm)
126        if (fq1 > dmscut) then
127           dms_andr = (dmsslp * (fq1 - dmscut)) + dmsmin
128        else
129           dms_andr = dmsmin
130        endif
131!
132! AXY (13/03/15): Simo & Dachs (2002)
133        fq1 = (-1.0 * log(mld)) + 5.7
134        fq2 = (55.8 * cmr) + 0.6
135        if (cmr < 0.02) then
136           dms_simo = fq1
137        else
138           dms_simo = fq2
139        endif
140!           
141! AXY (13/03/15): Aranami & Tsunogai (2004)
142        fq1 = 60.0 / mld
143        fq2 = (55.8 * cmr) + 0.6
144        if (cmr < 0.02) then
145           dms_aran = fq1
146        else
147           dms_aran = fq2
148        endif
149!       
150! AXY (13/03/15): Halloran et al. (2010)
151        fq1 = (-1.0 * log(mld)) + 5.7
152        fq2 = (55.8 * cmr) + 0.6
153        fq3 = (90.0 / mld)
154        if (cmr < 0.02) then
155           dms_hall = fq1
156        else
157           dms_hall = fq2
158        endif
159        if (mld > 182.5) then
160           dms_hall = fq3
161        endif
162!
163! AXY (25/05/17): modified Anderson et al. (2001)
164        Jterm = xqsr + 1.0e-6
165        !! this version fixes the hard-coded assumption above
166        Qterm = xlim
167        fq1 = log10(CHL * Jterm * Qterm)
168        if (fq1 > 1.72) then
169           dms_andm = (8.24 * (fq1 - 1.72)) + 2.29
170        else
171           dms_andm = 2.29
172        endif
173
174   END SUBROUTINE trc_dms_medusa
175
176
177!=======================================================================
178!=======================================================================
179!=======================================================================
180
181
182!=======================================================================
183!
184   SUBROUTINE dms_flux_ocn( wind_10m, tstar, dms_conc, i_dms_flux,  &  !! inputs
185     &                      f_dms )                                    !! outputs
186!     
187!=======================================================================
188      !!
189      !! Title  : Calculates DMS air-sea exchange
190      !! Author : Andrew Yool, based on UKMO original code
191      !! Date   : 11/10/18
192      !!
193      !! Air-sea DMS flux is normally calculated by the UM atmosphere,
194      !! as part of its aerosols; however, the OMIP simulation for CMIP6
195      !! is ocean-only and does not include the UM; consequently, this
196      !! code has been added to permit ocean-only UKESM1 to produce an
197      !! air-sea DMS flux in addition to surface DMS which, hitherto,
198      !! was all it would produce; code is largely copy-pasted from the
199      !! UKMO original (UM code block is dms_flux_4A.F90); the code
200      !! here is hard-wired to use single input values (i.e. not a 2D
201      !! area) and make use of the Liss & Merlivat (1986) function
202      !!
203      !! This DMS function is called from air_sea.F90
204
205!---------------------------------------------------------------------
206! Purpose: To calculate the flux of DMS (as kg m-2 s-1 of sulphur)
207!          from the ocean surface as a function of its concentration
208!          in seawater and of windspeed. The sea-air exchange can
209!          be determined according to one of three commonly-used
210!          parametrization schemes, those of Liss & Merlivat (1986),
211!          Wanninkhof (1992) or Nightingale et al. (2000). The routine
212!          is called by Aero_Ctl.
213!
214! Method:  The Schmidt number
215!          for DMS is calculated as in Saltzman et al. (1993), and
216!          used with the windspeed to determine the mass transfer (or
217!          "piston") velocity according to the desired parametrization.
218!          This is then used to determine the sea-air mass flux of DMS
219!          as a function of sea-water DMS concentration. High surface
220!          temperatures (caused by the land portion of a gridbox when
221!          coastal tiling is not active) cause negative Sc values which
222!          would give a floating-point error in the k_DMS calculation,
223!          so the Tstar values are capped. This shouldn't be a problem
224!          when coastal tiling is on as then the Tstar values passed in
225!          are those for sea only.
226!
227! Code Owner: Please refer to the UM file CodeOwners.txt
228! This file belongs in section: Aerosols
229!
230! Code Description:
231!  Language: Fortran 90
232!  This code is written to UMDP3 v8 programming standards
233!
234!---------------------------------------------------------------------
235
236      IMPLICIT NONE
237!
238      REAL(wp), INTENT( in )    :: wind_10m      !! 10m wind (m/s)
239      REAL(wp), INTENT( in )    :: tstar         !! SST (degrees C)
240      REAL(wp), INTENT( in )    :: dms_conc      !! surface DMS (nmol / l)
241      INTEGER,  INTENT(in)      :: i_dms_flux    !! gas transfer choice
242!
243      REAL(wp), INTENT( inout ) :: f_dms         !! DMS flux (kg S m-2 s-1)
244
245! Local variables:
246      REAL     :: sc     ! Schmidt number
247      REAL     :: k_dms  ! Piston velocity of DMS (cm h-1)
248      REAL     :: t_c    ! Surface temperature in degrees Celsius
249! Piston velocities for gases with Schmidt numbers of 600 & 660 resp. (cm h-1)
250      REAL     :: k_600
251      REAL     :: k_660
252      REAL     :: n      ! Schmidt number exponent
253      REAL, PARAMETER :: t_max = 47.0  !! Max T to avoid breaking the Sc fit (C)
254
255! Calculate the Schmidt number (Sc):
256      t_c = MIN(tstar, t_max)
257      sc  = 2674.0 - (147.12*t_c) + (3.726*t_c**2)  &
258            - (0.038*t_c**3)
259
260! Determine the mass transfer (or "piston") velocity (k_DMS) over sea
261! according to the specified parametrization scheme:
262
263      if (i_dms_flux .eq. 1) then
264! ----------------------------------------------------------------------
265!        Liss & Merlivat (1986)
266         IF (wind_10m .le. 3.6) THEN
267            k_600 = 0.17 * wind_10m
268            n = -2.0/3.0
269         ELSEIF ( wind_10m .gt. 3.6 .AND. wind_10m .le. 13.0 ) THEN
270            k_600 = (2.85 * wind_10m) - 9.65
271            n = -0.5
272         ELSE
273            k_600 = (5.90 * wind_10m) - 49.3
274            n = -0.5
275         END IF
276         k_dms = k_600 * (sc / 600.0)**n
277      elseif (i_dms_flux .eq. 2) then
278! ----------------------------------------------------------------------
279!        Wanninkhof (1992)
280         k_660 = 0.31 * wind_10m**2
281         n = -0.5
282         k_dms = k_660 * (sc / 660.0)**n
283      elseif (i_dms_flux .eq. 3) then
284! ----------------------------------------------------------------------
285!        Nightingale et al. (2000)
286         k_600 = (0.222 * wind_10m**2) + (0.333 * wind_10m)
287         n = -0.5
288         k_dms = k_600 * (sc / 600.0)**n
289      else
290! ----------------------------------------------------------------------
291!        You shouldn't be here
292         k_dms = 0.0
293      endif
294
295! Finally, calculate the sea-air flux of DMS as a function of k_DMS
296! and dissolved DMS concentration. The former requires a conversion
297! from cm hour-1 to ms-1, and the latter from nanomoles per litre to
298! kg[S] m-3, to return the flux in kg[S] m-2 sec-1.
299
300      f_dms = (k_dms / 3.6e5) * (dms_conc * 32.0e-9)
301
302   END SUBROUTINE dms_flux_ocn
303
304
305!=======================================================================
306!=======================================================================
307!=======================================================================
308
309#else
310   !!======================================================================
311   !!  Dummy module :                                   No MEDUSA bio-model
312   !!======================================================================
313
314CONTAINS
315
316!=======================================================================
317!
318   SUBROUTINE trc_dms_medusa( kt )                                        !! EMPTY Routine
319!     
320!
321      INTEGER, INTENT( in ) ::   kt
322!
323
324      WRITE(*,*) 'trc_dms_medusa: You should not have seen this print! error?'
325
326   END SUBROUTINE trc_dms_medusa
327#endif
328
329   !!======================================================================
330END MODULE  trcdms_medusa
331
332
333
Note: See TracBrowser for help on using the repository browser.