MODULE trcdms_medusa !!====================================================================== !! *** MODULE trcdms_medusa *** !! TOP : MEDUSA !!====================================================================== !! History : !! - ! 2014-08 (J. PalmiƩri - A. Yool) added for UKESM1 project !!---------------------------------------------------------------------- #if defined key_medusa && defined key_roam !!---------------------------------------------------------------------- !! MEDUSA DMS surface concentration !!---------------------------------------------------------------------- !! trc_dms_medusa : !!---------------------------------------------------------------------- USE oce_trc USE trc USE sms_medusa USE lbclnk USE prtctl_trc ! Print control for debugging USE in_out_manager ! I/O manager IMPLICIT NONE PRIVATE PUBLIC trc_dms_medusa ! called in trc_bio_medusa !!* Substitution # include "domzgr_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007) !! $Id$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS !======================================================================= ! SUBROUTINE trc_dms_medusa( chn, chd, mld, xqsr, xdin, & !! inputs & dms_surf, dms_andr, dms_simo, dms_aran, dms_hall ) !! outputs ! !======================================================================= !! !! Title : Calculates DMS ocean surface concentration !! Author : Julien PalmiƩri and Andrew Yool !! Date : 08/08/14 !! !! DMS module is called in trc_bio's huge jk,jj,ji loop !! --> DMS concentration is calculated in a specific cell !! (no need of ji,jj,jk) !! !! AXY (13/03/15): amend to include all four schemes tested !! during winter/spring 2015; these are: !! !! 1. Anderson et al. (2001); this uses fields !! of surface chl, irradiance and nutrients !! to empirically estimate DMS via a broken !! stick approach !! !! 2. Simo & Dachs (2002); this uses fields of !! surface chl and mixed layer depth !! !! 3. Aranami & Tsunogai (2004); this is an !! embellishment of Simo & Dachs !! !! 4. Halloran et al. (2010); this is an !! alternative embellishment of Sim & Dachs !! and is included because it is formally !! published (and different from the above) !! !======================================================================= IMPLICIT NONE ! REAL(wp), INTENT( in ) :: chn !! non-diatom chlorophyll (mg/m3) REAL(wp), INTENT( in ) :: chd !! diatom chlorophyll (mg/m3) REAL(wp), INTENT( in ) :: mld !! mix layer depth (m) REAL(wp), INTENT( in ) :: xqsr !! surface irradiance (W/m2) REAL(wp), INTENT( in ) :: xdin !! surface DIN (mmol N/m3) REAL(wp), INTENT( inout ) :: dms_surf !! DMS surface concentration (mol/m3) REAL(wp), INTENT( inout ) :: dms_andr !! DMS surface concentration (mol/m3) REAL(wp), INTENT( inout ) :: dms_simo !! DMS surface concentration (mol/m3) REAL(wp), INTENT( inout ) :: dms_aran !! DMS surface concentration (mol/m3) REAL(wp), INTENT( inout ) :: dms_hall !! DMS surface concentration (mol/m3) ! REAL(wp) :: CHL, cmr, sw_dms REAL(wp) :: Jterm, Qterm !! temporary variables REAL(wp) :: fq1,fq2,fq3 ! !! IJT (30/03/13): DMS calc needs this !! Julien : in Simo & Dachs, GBC, 2002, DMS is derived from !! CHL/MLD ratio in mg/m4 (i.e. CHL is in mg/m3 !! MLD in m). !! In MEDUSA, we already have CHL in mg/m3 for both !! Diatoms and non-diatoms (zchn,zchd); and mld from !! NEMO (hmld) in m. CHL = 0.0 !! !! CHL = mask * TT(I,J,1,PHYTO_TRACER) & !! & * c2n_p * mw_carbon / CCHL_P(I,J,1,1) CHL = chn+chd !! mg/m3 !! !! ------------------------------------------------ !! Calculate the DMS concentration in nM (nanomol/litre) !! from Simo & Dachs, GBC, 2002, modified to be positive-definite !! for MLD>182.536m, using DMS=90./MLD (Aranami & Tsunogai, JGR, 2004) !! Multiply by 1.0E-6 to convert nM to (mol/m3) !! cmr = fm(i,1)*chl/mld(i) !! IF (cmr .lt. 0.02) THEN !! IF (mld(i) .le. 182.536) THEN !! csurf(i,astf_dms) = 1.0e-6*fm(i,1)*(-LOG(mld(i)) + 5.7) !! ELSE !! csurf(i,astf_dms) = 1.0e-6*fm(i,1)*(90./mld(i)) !! ENDIF !! ELSE !! csurf(i,astf_dms) = 1.0e-6*fm(i,1)*(55.8*cmr + 0.6) !! ENDIF !! cmr = CHL / mld ! sw_dms = 0.5 + SIGN( 0.5, cmr - 0.02 ) !! Jpalm (11-08-2014) !! Explanation about the SIGN function : !! not easy to read, but maybe "more elegant and efficient") !! here for example: !! sw_dms = 1 if cmr is greater than 0.02, !! 0 if cmr lower than 0.02 !! then !! if cmr < 0.02 !! dms_surf = 1.0e-6 * 90.0 / mld !! or = 1.0e-6 * 5.7 - LOG(mld) !! and if cmr > 0.02 !! dms_surf = 1.0e-6 * ( 55.8 * cmr + 0.6 ) !! what is equivalent to the IF loops formulations. !! difference is on the stresholds between mld = 182.536m !! (strange value...) !! and the Max function... that stay uncertain. !! ! dms_surf = 1.0e-6 * ( sw_dms * & ! & ( 55.8 * cmr + 0.6 ) + ( 1.0 - sw_dms ) * & ! & ( MAX( 90.0 / mld, 5.7 - LOG(mld) ) ) ) ! ! AXY (12/01/15): the DMS equation donated by the UKMO does not match ! that reported in Halloran et al. (2010); amend the ! equations appropriately ! if (cmr .lt. 0.02) then dms_surf = (-1.0 * log(mld)) + 5.7 else dms_surf = (55.8 * cmr) + 0.6 endif ! if (mld > 182.5) then dms_surf = (90.0 / mld) endif ! dms_surf = 1.0e-6 * dms_surf ! !======================================================================= ! ! AXY (13/03/15): per remarks above, the following calculations estimate ! DMS using all of the schemes examined for UKESM1 ! ! AXY (13/03/15): Anderson et al. (2001) Jterm = xqsr + 1.0e-6 !! this next line makes a hard-coded assumption about the !! half-saturation constant of MEDUSA (which should be !! done properly; perhaps even scaled with the proportion !! of diatoms and non-diatoms) Qterm = xdin / (xdin + 0.5) fq1 = log10(CHL * Jterm * Qterm) if (fq1 > 1.72) then dms_andr = (8.24 * (fq1 - 1.72)) + 2.29 else dms_andr = 2.29 endif dms_andr = 1.0e-6 * dms_andr ! ! AXY (13/03/15): Simo & Dachs (2002) cmr = CHL / mld fq1 = (-1 * log(mld)) + 5.7 fq2 = (55.8 * cmr) + 0.6 if (cmr < 0.02) then dms_simo = fq1 else dms_simo = fq2 endif dms_simo = 1.0e-6 * dms_simo ! ! AXY (13/03/15): Aranami & Tsunogai (2004) cmr = CHL / mld fq1 = 60.0 / mld fq2 = (55.8 * cmr) + 0.6 if (cmr < 0.02) then dms_aran = fq1 else dms_aran = fq2 endif dms_aran = 1.0e-6 * dms_aran ! ! AXY (13/03/15): Halloran et al. (2010) cmr = CHL / mld fq1 = (-1 * log(mld)) + 5.7 fq2 = (55.8 * cmr) + 0.6 fq3 = (90.0 / mld) if (cmr < 0.02) then dms_hall = fq1 else dms_hall = fq2 endif if (mld > 182.5) then dms_hall = fq3 endif dms_hall = 1.0e-6 * dms_hall END SUBROUTINE trc_dms_medusa !======================================================================= !======================================================================= !======================================================================= #else !!====================================================================== !! Dummy module : No MEDUSA bio-model !!====================================================================== CONTAINS !======================================================================= ! SUBROUTINE trc_dms_medusa( kt ) !! EMPTY Routine ! ! INTEGER, INTENT( in ) :: kt ! WRITE(*,*) 'trc_dms_medusa: You should not have seen this print! error?' END SUBROUTINE trc_dms_medusa #endif !!====================================================================== END MODULE trcdms_medusa