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

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

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

JPALM -- 11-04-2017 -- MEDUSA spring tidy-up refreshning session

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