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.
Changeset 5841 for branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcdms_medusa.F90 – NEMO

Ignore:
Timestamp:
2015-10-30T12:48:06+01:00 (8 years ago)
Author:
jpalmier
Message:

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcdms_medusa.F90

    r5726 r5841  
    3939! 
    4040   SUBROUTINE trc_dms_medusa( chn, chd, mld, xqsr, xdin,   &  !! inputs 
    41      &  dms_surf, dms_andr, dms_simo, dms_aran, dms_hall )    !! outputs 
     41     &  dms_andr, dms_simo, dms_aran, dms_hall )              !! outputs 
    4242!       
    4343!======================================================================= 
     
    7070      !!                    published (and different from the above) 
    7171      !! 
     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      !! 
    7277!======================================================================= 
    7378 
     
    7984      REAL(wp), INTENT( in )    :: xqsr                 !! surface irradiance        (W/m2) 
    8085      REAL(wp), INTENT( in )    :: xdin                 !! surface DIN               (mmol N/m3) 
    81       REAL(wp), INTENT( inout ) :: dms_surf             !! DMS surface concentration (mol/m3)  
    8286      REAL(wp), INTENT( inout ) :: dms_andr             !! DMS surface concentration (mol/m3)  
    8387      REAL(wp), INTENT( inout ) :: dms_simo             !! DMS surface concentration (mol/m3)  
     
    8993      !! temporary variables 
    9094      REAL(wp) ::    fq1,fq2,fq3 
    91 ! 
    92 !! IJT (30/03/13): DMS calc needs this 
    93 !! Julien : in Simo & Dachs, GBC, 2002, DMS is derived from  
    94 !!          CHL/MLD ratio in mg/m4 (i.e. CHL is in mg/m3 
    95 !!          MLD in m). 
    96 !!          In MEDUSA, we already have CHL in mg/m3 for both 
    97 !!          Diatoms and non-diatoms (zchn,zchd); and mld from 
    98 !!          NEMO (hmld) in m. 
    99       CHL = 0.0 
    100 !! 
    101 !!            CHL = mask * TT(I,J,1,PHYTO_TRACER) & 
    102 !!     &       * c2n_p * mw_carbon / CCHL_P(I,J,1,1) 
    103       CHL = chn+chd                                 !! mg/m3  
    104 !! 
    105 !! ------------------------------------------------ 
    106 !!  Calculate the DMS concentration in nM (nanomol/litre) 
    107 !!   from Simo & Dachs, GBC, 2002, modified to be positive-definite 
    108 !!   for MLD>182.536m, using DMS=90./MLD (Aranami & Tsunogai, JGR, 2004) 
    109 !!   Multiply by 1.0E-6 to convert nM to (mol/m3) 
    110 !!       cmr = fm(i,1)*chl/mld(i) 
    111 !!       IF (cmr .lt. 0.02) THEN 
    112 !!         IF (mld(i) .le. 182.536) THEN 
    113 !!           csurf(i,astf_dms) = 1.0e-6*fm(i,1)*(-LOG(mld(i)) + 5.7) 
    114 !!         ELSE 
    115 !!           csurf(i,astf_dms) = 1.0e-6*fm(i,1)*(90./mld(i)) 
    116 !!         ENDIF 
    117 !!       ELSE 
    118 !!         csurf(i,astf_dms) = 1.0e-6*fm(i,1)*(55.8*cmr + 0.6) 
    119 !!       ENDIF 
    120 !! 
    121         cmr      = CHL / mld 
    122 !       sw_dms   = 0.5 + SIGN( 0.5, cmr - 0.02 ) 
    123 !! Jpalm (11-08-2014) 
    124 !! Explanation about the SIGN function : 
    125 !! not easy to read, but maybe "more elegant and efficient") 
    126 !! here for example:  
    127 !! sw_dms = 1 if cmr is greater than 0.02, 
    128 !!          0 if cmr lower than 0.02 
    129 !! then  
    130 !! if cmr < 0.02 
    131 !!  dms_surf =  1.0e-6 * 90.0 / mld  
    132 !!       or  =  1.0e-6 * 5.7 - LOG(mld) 
    133 !! and if cmr > 0.02 
    134 !!  dms_surf = 1.0e-6 * ( 55.8 * cmr + 0.6 ) 
    135 !! what is equivalent to the IF loops formulations. 
    136 !! difference is on the stresholds between mld = 182.536m 
    137 !! (strange value...) 
    138 !! and the Max function... that stay uncertain. 
    139 !! 
    140 !        dms_surf = 1.0e-6 * ( sw_dms *             & 
    141 !     &  ( 55.8 * cmr + 0.6 ) + ( 1.0 - sw_dms ) *  & 
    142 !     &  ( MAX( 90.0 / mld, 5.7 - LOG(mld) ) ) ) 
    143 ! 
    144 ! AXY (12/01/15): the DMS equation donated by the UKMO does not match 
    145 !                 that reported in Halloran et al. (2010); amend the 
    146 !                 equations appropriately 
    147 ! 
    148         if (cmr .lt. 0.02) then 
    149            dms_surf = (-1.0 * log(mld)) + 5.7 
    150         else 
    151            dms_surf = (55.8 * cmr) + 0.6 
    152         endif 
    153 !     
    154         if (mld > 182.5) then 
    155            dms_surf = (90.0 / mld) 
    156         endif 
    157 !      
    158         dms_surf = 1.0e-6 * dms_surf 
    159  
    16095!  
    16196!======================================================================= 
     
    16398! AXY (13/03/15): per remarks above, the following calculations estimate 
    16499!                 DMS using all of the schemes examined for UKESM1 
     100! 
     101      CHL = 0.0 
     102      CHL = chn+chd                                 !! mg/m3  
     103      cmr = CHL / mld 
    165104! 
    166105! AXY (13/03/15): Anderson et al. (2001) 
     
    180119! 
    181120! AXY (13/03/15): Simo & Dachs (2002) 
    182         cmr = CHL / mld 
    183121        fq1 = (-1 * log(mld)) + 5.7 
    184122        fq2 = (55.8 * cmr) + 0.6 
     
    191129!            
    192130! AXY (13/03/15): Aranami & Tsunogai (2004) 
    193         cmr = CHL / mld 
    194131        fq1 = 60.0 / mld 
    195132        fq2 = (55.8 * cmr) + 0.6 
     
    202139!         
    203140! AXY (13/03/15): Halloran et al. (2010) 
    204         cmr = CHL / mld 
    205141        fq1 = (-1 * log(mld)) + 5.7 
    206142        fq2 = (55.8 * cmr) + 0.6 
Note: See TracChangeset for help on using the changeset viewer.