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 @ 6022

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

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

File size: 6.9 KB
Line 
1MODULE trcdms_medusa
2   !!======================================================================
3   !!                         ***  MODULE trcdms_medusa  ***
4   !! TOP :   MEDUSA
5   !!======================================================================
6   !! History :
7   !!  -   !  2014-08  (J. Palmiéri - 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, xdin,   &  !! inputs
41     &  dms_andr, dms_simo, dms_aran, dms_hall )              !! outputs
42!     
43!=======================================================================
44      !!
45      !! Title  : Calculates DMS ocean surface concentration
46      !! Author : Julien Palmiéri 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!=======================================================================
78
79      IMPLICIT NONE
80!
81      REAL(wp), INTENT( in )    :: chn                  !! non-diatom chlorophyll    (mg/m3)
82      REAL(wp), INTENT( in )    :: chd                  !! diatom chlorophyll        (mg/m3)
83      REAL(wp), INTENT( in )    :: mld                  !! mix layer depth           (m)
84      REAL(wp), INTENT( in )    :: xqsr                 !! surface irradiance        (W/m2)
85      REAL(wp), INTENT( in )    :: xdin                 !! surface DIN               (mmol N/m3)
86      REAL(wp), INTENT( inout ) :: dms_andr             !! DMS surface concentration (mol/m3)
87      REAL(wp), INTENT( inout ) :: dms_simo             !! DMS surface concentration (mol/m3)
88      REAL(wp), INTENT( inout ) :: dms_aran             !! DMS surface concentration (mol/m3)
89      REAL(wp), INTENT( inout ) :: dms_hall             !! DMS surface concentration (mol/m3)
90!
91      REAL(wp) :: CHL, cmr, sw_dms
92      REAL(wp) :: Jterm, Qterm
93      !! temporary variables
94      REAL(wp) ::    fq1,fq2,fq3
95!
96!=======================================================================
97!
98! AXY (13/03/15): per remarks above, the following calculations estimate
99!                 DMS using all of the schemes examined for UKESM1
100!
101      CHL = 0.0
102      CHL = chn+chd                                 !! mg/m3
103      cmr = CHL / mld
104!
105! AXY (13/03/15): Anderson et al. (2001)
106        Jterm = xqsr + 1.0e-6
107        !! this next line makes a hard-coded assumption about the
108        !! half-saturation constant of MEDUSA (which should be
109        !! done properly; perhaps even scaled with the proportion
110        !! of diatoms and non-diatoms)
111        Qterm = xdin / (xdin + 0.5)
112        fq1 = log10(CHL * Jterm * Qterm)
113        if (fq1 > 1.72) then
114           dms_andr = (8.24 * (fq1 - 1.72)) + 2.29
115        else
116           dms_andr = 2.29
117        endif
118        dms_andr = 1.0e-6 * dms_andr
119!
120! AXY (13/03/15): Simo & Dachs (2002)
121        fq1 = (-1 * log(mld)) + 5.7
122        fq2 = (55.8 * cmr) + 0.6
123        if (cmr < 0.02) then
124           dms_simo = fq1
125        else
126           dms_simo = fq2
127        endif
128        dms_simo = 1.0e-6 * dms_simo
129!           
130! AXY (13/03/15): Aranami & Tsunogai (2004)
131        fq1 = 60.0 / mld
132        fq2 = (55.8 * cmr) + 0.6
133        if (cmr < 0.02) then
134           dms_aran = fq1
135        else
136           dms_aran = fq2
137        endif
138        dms_aran = 1.0e-6 * dms_aran
139!       
140! AXY (13/03/15): Halloran et al. (2010)
141        fq1 = (-1 * log(mld)) + 5.7
142        fq2 = (55.8 * cmr) + 0.6
143        fq3 = (90.0 / mld)
144        if (cmr < 0.02) then
145           dms_hall = fq1
146        else
147           dms_hall = fq2
148        endif
149        if (mld > 182.5) then
150           dms_hall = fq3
151        endif
152        dms_hall = 1.0e-6 * dms_hall
153
154  END SUBROUTINE trc_dms_medusa
155
156
157!=======================================================================
158!=======================================================================
159!=======================================================================
160
161#else
162   !!======================================================================
163   !!  Dummy module :                                   No MEDUSA bio-model
164   !!======================================================================
165
166CONTAINS
167
168!=======================================================================
169!
170   SUBROUTINE trc_dms_medusa( kt )                                        !! EMPTY Routine
171!     
172!
173      INTEGER, INTENT( in ) ::   kt
174!
175
176      WRITE(*,*) 'trc_dms_medusa: You should not have seen this print! error?'
177
178   END SUBROUTINE trc_dms_medusa
179#endif
180
181   !!======================================================================
182END MODULE  trcdms_medusa
183
184
Note: See TracBrowser for help on using the repository browser.