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_CO2_cmip/NEMOGCM/NEMO/TOP_SRC/MEDUSA – NEMO

source: branches/NERC/dev_r5518_GO6_CO2_cmip/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcdms_medusa.F90 @ 9285

Last change on this file since 9285 was 9258, checked in by marc, 6 years ago

Adding Julien's GMED ticket 365 for DMS constants for Anderson scheme (incl fixes to a couple of other tickets)

File size: 7.7 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   !!----------------------------------------------------------------------
10#if defined key_medusa && defined key_roam
11   !!----------------------------------------------------------------------
12   !!                                        MEDUSA DMS surface concentration
13   !!----------------------------------------------------------------------
14   !!   trc_dms_medusa        : 
15   !!----------------------------------------------------------------------
16      USE oce_trc
17      USE trc
18      USE sms_medusa
19      USE lbclnk
20      USE prtctl_trc      ! Print control for debugging
21      USE in_out_manager  ! I/O manager
22
23      IMPLICIT NONE
24      PRIVATE
25
26      PUBLIC   trc_dms_medusa    ! called in trc_bio_medusa
27
28   !!* Substitution
29#  include "domzgr_substitute.h90"
30   !!----------------------------------------------------------------------
31   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
32   !! $Id$
33   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
34   !!----------------------------------------------------------------------
35
36
37CONTAINS
38
39!=======================================================================
40!
41   SUBROUTINE trc_dms_medusa( chn, chd, mld, xqsr, xdin, xlim,  &  !! inputs
42     &  dms_andr, dms_simo, dms_aran, dms_hall, dms_andm)           !! outputs
43!     
44!=======================================================================
45      !!
46      !! Title  : Calculates DMS ocean surface concentration
47      !! Author : Julien Palmieri and Andrew Yool
48      !! Date   : 08/08/14
49      !!
50      !! DMS module is called in trc_bio's huge jk,jj,ji loop
51      !! --> DMS concentration is calculated in a specific cell
52      !! (no need of ji,jj,jk)
53      !!
54      !! AXY (13/03/15): amend to include all four schemes tested
55      !!                 during winter/spring 2015; these are:
56      !!
57      !!                 1. Anderson et al. (2001); this uses fields
58      !!                    of surface chl, irradiance and nutrients
59      !!                    to empirically estimate DMS via a broken
60      !!                    stick approach
61      !!
62      !!                 2. Simo & Dachs (2002); this uses fields of
63      !!                    surface chl and mixed layer depth
64      !!
65      !!                 3. Aranami & Tsunogai (2004); this is an
66      !!                    embellishment of Simo & Dachs
67      !!
68      !!                 4. Halloran et al. (2010); this is an
69      !!                    alternative embellishment of Sim & Dachs
70      !!                    and is included because it is formally
71      !!                    published (and different from the above)
72      !!
73      !! AXY (25/05/17): add extra "corrected" Anderson scheme
74      !!
75      !!                 5. As Anderson et al. (2001) but modified to
76      !!                    more accurately reflect nutrient limitation
77      !!                    status of phytoplankton community
78      !!
79      !! AXY (08/07/15): amend to remove Julien's original calculation
80      !!                 as this is now superfluous; the four schemes
81      !!                 are calculated and one is chosen to be passed
82      !!                 to the atmosphere in trc_bio_medusa
83      !!
84!=======================================================================
85
86      IMPLICIT NONE
87!
88      REAL(wp), INTENT( in )    :: chn                  !! non-diatom chlorophyll    (mg/m3)
89      REAL(wp), INTENT( in )    :: chd                  !! diatom chlorophyll        (mg/m3)
90      REAL(wp), INTENT( in )    :: mld                  !! mix layer depth           (m)
91      REAL(wp), INTENT( in )    :: xqsr                 !! surface irradiance        (W/m2)
92      REAL(wp), INTENT( in )    :: xdin                 !! surface DIN               (mmol N/m3)
93      REAL(wp), INTENT( in )    :: xlim                 !! surface DIN limitation    (mmol N/m3)
94      REAL(wp), INTENT( inout ) :: dms_andr             !! DMS surface concentration (nmol/L)
95      REAL(wp), INTENT( inout ) :: dms_simo             !! DMS surface concentration (nmol/L)
96      REAL(wp), INTENT( inout ) :: dms_aran             !! DMS surface concentration (nmol/L)
97      REAL(wp), INTENT( inout ) :: dms_hall             !! DMS surface concentration (nmol/L)
98      REAL(wp), INTENT( inout ) :: dms_andm             !! DMS surface concentration (nmol/L)
99!
100      REAL(wp) :: CHL, cmr, sw_dms
101      REAL(wp) :: Jterm, Qterm
102      !! temporary variables
103      REAL(wp) ::    fq1,fq2,fq3
104!
105!=======================================================================
106!
107! AXY (13/03/15): per remarks above, the following calculations estimate
108!                 DMS using all of the schemes examined for UKESM1
109!
110      CHL = 0.0
111      CHL = chn+chd                                 !! mg/m3
112      cmr = CHL / mld
113!
114! AXY (13/03/15): Anderson et al. (2001)
115!! JPALM --19-12-2017-- Tunable through the namelist
116!!                      within dmsmin - dmscut - dmsslp
117        Jterm = xqsr + 1.0e-6
118        !! this next line makes a hard-coded assumption about the
119        !! half-saturation constant of MEDUSA (which should be
120        !! done properly; perhaps even scaled with the proportion
121        !! of diatoms and non-diatoms)
122        Qterm = xdin / (xdin + 0.5)
123        fq1 = log10(CHL * Jterm * Qterm)
124        if (fq1 > dmscut) then
125           dms_andr = (dmsslp * (fq1 - dmscut)) + dmsmin
126        else
127           dms_andr = dmsmin
128        endif
129!
130! AXY (13/03/15): Simo & Dachs (2002)
131        fq1 = (-1.0 * log(mld)) + 5.7
132        fq2 = (55.8 * cmr) + 0.6
133        if (cmr < 0.02) then
134           dms_simo = fq1
135        else
136           dms_simo = fq2
137        endif
138!           
139! AXY (13/03/15): Aranami & Tsunogai (2004)
140        fq1 = 60.0 / mld
141        fq2 = (55.8 * cmr) + 0.6
142        if (cmr < 0.02) then
143           dms_aran = fq1
144        else
145           dms_aran = fq2
146        endif
147!       
148! AXY (13/03/15): Halloran et al. (2010)
149        fq1 = (-1.0 * log(mld)) + 5.7
150        fq2 = (55.8 * cmr) + 0.6
151        fq3 = (90.0 / mld)
152        if (cmr < 0.02) then
153           dms_hall = fq1
154        else
155           dms_hall = fq2
156        endif
157        if (mld > 182.5) then
158           dms_hall = fq3
159        endif
160!
161! AXY (25/05/17): modified Anderson et al. (2001)
162        Jterm = xqsr + 1.0e-6
163        !! this version fixes the hard-coded assumption above
164        Qterm = xlim
165        fq1 = log10(CHL * Jterm * Qterm)
166        if (fq1 > 1.72) then
167           dms_andm = (8.24 * (fq1 - 1.72)) + 2.29
168        else
169           dms_andm = 2.29
170        endif
171
172  END SUBROUTINE trc_dms_medusa
173
174
175!=======================================================================
176!=======================================================================
177!=======================================================================
178
179#else
180   !!======================================================================
181   !!  Dummy module :                                   No MEDUSA bio-model
182   !!======================================================================
183
184CONTAINS
185
186!=======================================================================
187!
188   SUBROUTINE trc_dms_medusa( kt )                                        !! EMPTY Routine
189!     
190!
191      INTEGER, INTENT( in ) ::   kt
192!
193
194      WRITE(*,*) 'trc_dms_medusa: You should not have seen this print! error?'
195
196   END SUBROUTINE trc_dms_medusa
197#endif
198
199   !!======================================================================
200END MODULE  trcdms_medusa
201
202
203
Note: See TracBrowser for help on using the repository browser.