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 14385 for NEMO/branches/2021/dev_r14383_PISCES_NEWDEV_PISCO/src/TOP/PISCES/P4Z/p5zmicro.F90 – NEMO

Ignore:
Timestamp:
2021-02-03T16:03:34+01:00 (3 years ago)
Author:
cetlod
Message:

dev_r11708_aumont_PISCES_QUOTA : merge with the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14383_PISCES_NEWDEV_PISCO/src/TOP/PISCES/P4Z/p5zmicro.F90

    r13295 r14385  
    1515   USE trc             !  passive tracers common variables  
    1616   USE sms_pisces      !  PISCES Source Minus Sink variables 
    17    USE p4zlim 
     17   USE p4zlim          !  PISCES nutrient limitation term of PISCES std 
    1818   USE p5zlim          !  Phytoplankton limitation terms 
    1919   USE iom             !  I/O manager 
     
    5050   REAL(wp), PUBLIC ::  srespir     !: half sturation constant for grazing 1  
    5151   REAL(wp), PUBLIC ::  ssigma      !: Fraction excreted as semi-labile DOM 
     52   REAL(wp), PUBLIC ::  xsigma      !: Width of the grazing window 
     53   REAL(wp), PUBLIC ::  xsigmadel   !: Maximum additional width of the grazing window at low food density 
    5254   LOGICAL,  PUBLIC ::  bmetexc     !: Use of excess carbon for respiration 
    5355 
     
    7880      REAL(wp) :: zcompapi, zgraze  , zdenom, zfact, zfood, zfoodlim 
    7981      REAL(wp) :: ztmp1, ztmp2, ztmp3, ztmp4, ztmp5, ztmptot 
    80       REAL(wp) :: zepsherf, zepshert, zepsherv, zrespirc, zrespirn, zrespirp, zbasresb, zbasresi 
     82      REAL(wp) :: zepsherf, zepshert, zepsherq, zepsherv, zrespirc, zrespirn, zrespirp, zbasresb, zbasresi 
    8183      REAL(wp) :: zgraztotc, zgraztotn, zgraztotp, zgraztotf, zbasresn, zbasresp, zbasresf 
    8284      REAL(wp) :: zgradoc, zgradon, zgradop, zgraref, zgradoct, zgradont, zgradopt, zgrareft 
     
    8890      REAL(wp) :: zgrazpc, zgrazpn, zgrazpp, zgrazpf, zbeta, zrfact2, zmetexcess 
    8991      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing, zfezoo, zzligprod 
     92      REAL(wp) :: zsigma, zdiffdn, zdiffpn, zdiffdp, zproport, zproport2 
    9093      CHARACTER (len=25) :: charout 
    9194      !!--------------------------------------------------------------------- 
     
    9396      IF( ln_timing )   CALL timing_start('p5z_micro') 
    9497      ! 
     98      ! Use of excess carbon for metabolism 
    9599      zmetexcess = 0.0 
    96100      IF ( bmetexc ) zmetexcess = 1.0 
     
    99103         zcompaz = MAX( ( tr(ji,jj,jk,jpzoo,Kbb) - 1.e-9 ), 0.e0 ) 
    100104         zfact   = xstep * tgfunc2(ji,jj,jk) * zcompaz 
     105         ! Proportion of nano and diatoms that are within the size range 
     106         ! accessible to microzooplankton.  
     107         zproport  = min(sized(ji,jj,jk),1.8)**(-0.48)*min(1.0, exp(-1.1 * MAX(0., ( sized(ji,jj,jk) - 1.8 ))**0.8 )) 
     108         zproport2 = sizen(ji,jj,jk)**(-0.48) 
     109         zproport2 = 1.0 
     110         !  linear mortality of mesozooplankton 
     111         !  A michaelis menten modulation term is used to avoid extinction of  
     112         !  microzooplankton at very low food concentrations. Mortality is  
     113         !  enhanced in low O2 waters 
     114         !  ----------------------------------------------------------------- 
    101115 
    102116         !   Michaelis-Menten mortality rates of microzooplankton 
     
    105119         &        + 3. * nitrfac(ji,jj,jk) ) 
    106120 
    107          !   Zooplankton mortality. A square function has been selected with 
    108          !   no real reason except that it seems to be more stable and may mimic predation. 
    109          !   ------------------------------------------------------------------------------ 
     121         !  Zooplankton quadratic mortality. A square function has been selected with 
     122         !  to mimic predation and disease (density dependent mortality). It also tends 
     123         !  to stabilise the model 
     124         !  ------------------------------------------------------------------------- 
    110125         ztortz = mzrat * 1.e6 * zfact * tr(ji,jj,jk,jpzoo,Kbb) * (1. - nitrfac(ji,jj,jk)) 
    111126 
    112127         !   Computation of the abundance of the preys 
    113128         !   A threshold can be specified in the namelist 
    114          !   -------------------------------------------- 
    115          zcompadi  = MIN( MAX( ( tr(ji,jj,jk,jpdia,Kbb) - xthreshdia ), 0.e0 ), xsizedia ) 
    116          zcompaph  = MAX( ( tr(ji,jj,jk,jpphy,Kbb) - xthreshphy ), 0.e0 ) 
     129         !   Nanophyto and diatoms have a specific treatment with  
     130         !   teir preference decreasing with size. 
     131         !   -------------------------------------------------------- 
     132         zcompadi  = zproport  * MAX( ( tr(ji,jj,jk,jpdia,Kbb) - xthreshdia ), 0.e0 ) 
     133         zcompaph  = zproport2 * MAX( ( tr(ji,jj,jk,jpphy,Kbb) - xthreshphy ), 0.e0 ) 
    117134         zcompaz   = MAX( ( tr(ji,jj,jk,jpzoo,Kbb) - xthreshzoo ), 0.e0 ) 
    118135         zcompapi  = MAX( ( tr(ji,jj,jk,jppic,Kbb) - xthreshpic ), 0.e0 ) 
    119136         zcompapoc = MAX( ( tr(ji,jj,jk,jppoc,Kbb) - xthreshpoc ), 0.e0 ) 
    120           
    121          !   Microzooplankton grazing 
    122          !   ------------------------ 
     137                
     138         ! Microzooplankton grazing 
     139         ! The total amount of food is the sum of all preys accessible to mesozooplankton  
     140         ! multiplied by their food preference 
     141         ! A threshold can be specified in the namelist (xthresh). However, when food  
     142         ! concentration is close to this threshold, it is decreased to avoid the  
     143         ! accumulation of food in the mesozoopelagic domain 
     144         ! ------------------------------------------------------------------------------- 
    123145         zfood     = xprefn * zcompaph + xprefc * zcompapoc + xprefd * zcompadi   & 
    124146         &           + xprefz * zcompaz + xprefp * zcompapi 
     
    127149         zgraze    = grazrat * xstep * tgfunc2(ji,jj,jk) * tr(ji,jj,jk,jpzoo,Kbb) * (1. - nitrfac(ji,jj,jk))  
    128150 
    129          !   An active switching parameterization is used here. 
    130          !   We don't use the KTW parameterization proposed by  
    131          !   Vallina et al. because it tends to produce to steady biomass 
    132          !   composition and the variance of Chl is too low as it grazes 
    133          !   too strongly on winning organisms. Thus, instead of a square 
    134          !   a 1.5 power value is used which decreases the pressure on the 
    135          !   most abundant species 
    136          !   ------------------------------------------------------------   
    137          ztmp1 = xprefn * zcompaph**1.5 
    138          ztmp2 = xprefp * zcompapi**1.5 
    139          ztmp3 = xprefc * zcompapoc**1.5 
    140          ztmp4 = xprefd * zcompadi**1.5 
    141          ztmp5 = xprefz * zcompaz**1.5 
     151         ! An active switching parameterization is used here. 
     152         ! We don't use the KTW parameterization proposed by  
     153         ! Vallina et al. because it tends to produce too steady biomass 
     154         ! composition and the variance of Chl is too low as it grazes 
     155         ! too strongly on winning organisms. We use a generalized 
     156         ! switching parameterization proposed by Morozov and  
     157         ! Petrovskii (2013) 
     158         ! ------------------------------------------------------------   
     159         ! The width of the selection window is increased when preys 
     160         ! have low abundance, .i.e. zooplankton become less specific  
     161         ! to avoid starvation. 
     162         ! ---------------------------------------------------------- 
     163         zsigma = 1.0 - zdenom**3/(0.1**3+zdenom**3) 
     164         zsigma = xsigma + xsigmadel * zsigma 
     165         zdiffpn = exp( -ABS(log(0.7 * sizep(ji,jj,jk) / (3.0 * sizen(ji,jj,jk) + rtrn )) )**2 / zsigma**2 ) 
     166         zdiffdn = exp( -ABS(log(3.0 * sizen(ji,jj,jk) / (5.0 * sized(ji,jj,jk) + rtrn )) )**2 / zsigma**2) 
     167         zdiffdp = exp( -ABS(log(0.7 * sizep(ji,jj,jk) / (5.0 * sized(ji,jj,jk) + rtrn )) )**2 / zsigma**2) 
     168         ztmp1 = xprefn * zcompaph * ( zcompaph + zdiffdn * zcompadi + zdiffpn * zcompapi ) / ( 1.0 + zdiffdn + zdiffpn ) 
     169         ztmp2 = xprefp * zcompapi * ( zcompapi + zdiffpn * zcompaph + zdiffdp * zcompadi ) / ( 1.0 + zdiffpn + zdiffdp ) 
     170         ztmp3 = xprefc * zcompapoc**2 
     171         ztmp4 = xprefd * zcompadi * ( zdiffdp * zcompapi + zdiffdn * zcompaph + zcompadi ) / ( 1.0 + zdiffdn + zdiffdp ) 
     172         ztmp5 = xprefz * zcompaz**2 
    142173         ztmptot = ztmp1 + ztmp2 + ztmp3 + ztmp4 + ztmp5 + rtrn 
    143174         ztmp1 = ztmp1 / ztmptot 
     
    149180         !   Microzooplankton regular grazing on the different preys 
    150181         !   ------------------------------------------------------- 
     182               !   Nanophytoplankton 
    151183         zgraznc   = zgraze  * ztmp1  * zdenom 
    152184         zgraznn   = zgraznc * tr(ji,jj,jk,jpnph,Kbb) / (tr(ji,jj,jk,jpphy,Kbb) + rtrn) 
    153185         zgraznp   = zgraznc * tr(ji,jj,jk,jppph,Kbb) / (tr(ji,jj,jk,jpphy,Kbb) + rtrn) 
    154186         zgraznf   = zgraznc * tr(ji,jj,jk,jpnfe,Kbb) / (tr(ji,jj,jk,jpphy,Kbb) + rtrn) 
     187 
     188               ! Picophytoplankton 
    155189         zgrazpc   = zgraze  * ztmp2  * zdenom 
    156190         zgrazpn   = zgrazpc * tr(ji,jj,jk,jpnpi,Kbb) / (tr(ji,jj,jk,jppic,Kbb) + rtrn) 
    157191         zgrazpp   = zgrazpc * tr(ji,jj,jk,jpppi,Kbb) / (tr(ji,jj,jk,jppic,Kbb) + rtrn) 
    158192         zgrazpf   = zgrazpc * tr(ji,jj,jk,jppfe,Kbb) / (tr(ji,jj,jk,jppic,Kbb) + rtrn) 
     193 
     194               ! Microzooplankton 
    159195         zgrazz    = zgraze  * ztmp5   * zdenom 
     196 
     197               ! small POC 
    160198         zgrazpoc  = zgraze  * ztmp3   * zdenom 
    161199         zgrazpon  = zgrazpoc * tr(ji,jj,jk,jppon,Kbb) / ( tr(ji,jj,jk,jppoc,Kbb) + rtrn ) 
    162200         zgrazpop  = zgrazpoc * tr(ji,jj,jk,jppop,Kbb) / ( tr(ji,jj,jk,jppoc,Kbb) + rtrn ) 
    163201         zgrazpof  = zgrazpoc* tr(ji,jj,jk,jpsfe,Kbb) / (tr(ji,jj,jk,jppoc,Kbb) + rtrn) 
     202 
     203               ! Diatoms 
    164204         zgrazdc   = zgraze  * ztmp4  * zdenom 
    165205         zgrazdn   = zgrazdc * tr(ji,jj,jk,jpndi,Kbb) / (tr(ji,jj,jk,jpdia,Kbb) + rtrn) 
     
    167207         zgrazdf   = zgrazdc * tr(ji,jj,jk,jpdfe,Kbb) / (tr(ji,jj,jk,jpdia,Kbb) + rtrn) 
    168208         ! 
     209               ! Total ingestion rates in C, P, Fe, N 
    169210         zgraztotc = zgraznc + zgrazpoc + zgrazdc + zgrazz + zgrazpc 
    170211         zgraztotn = zgraznn + zgrazpn + zgrazpon + zgrazdn + zgrazz * no3rat3 
    171212         zgraztotp = zgraznp + zgrazpp + zgrazpop + zgrazdp + zgrazz * po4rat3 
    172          zgraztotf = zgraznf + zgrazpf + zgrazpof + zgrazdf + zgrazz * ferat3 
     213         zgraztotf = zgraznf + zgrazpf + zgrazpof + zgrazdf + zgrazz * feratz 
    173214         ! 
    174215         ! Grazing by microzooplankton 
     
    181222         zgrasratp =  (zgraztotp + rtrn) / ( zgraztotc + rtrn ) 
    182223 
    183          !   Growth efficiency is made a function of the quality  
    184          !   and the quantity of the preys 
    185          !   --------------------------------------------------- 
    186          zepshert  = MIN( 1., zgrasratn/ no3rat3, zgrasratp/ po4rat3, zgrasratf / ferat3) 
     224         ! Mesozooplankton efficiency.  
     225         ! We adopt a formulation proposed by Mitra et al. (2007) 
     226         ! The gross growth efficiency is controled by the most limiting nutrient. 
     227         ! Growth is also further decreased when the food quality is poor. This is currently 
     228         ! hard coded : it can be decreased by up to 50% (zepsherq) 
     229         ! GGE can also be decreased when food quantity is high, zepsherf (Montagnes and  
     230         ! Fulton, 2012) 
     231         ! ----------------------------------------------------------------------------------- 
     232         zepshert  = MIN( 1., zgrasratn/ no3rat3, zgrasratp/ po4rat3, zgrasratf / feratz) 
    187233         zbeta     = MAX( 0., (epsher - epshermin) ) 
     234         ! Food density deprivation of GGE 
    188235         zepsherf  = epshermin + zbeta / ( 1.0 + 0.04E6 * 12. * zfood * zbeta ) 
    189          zepsherv  = zepsherf * zepshert 
    190  
    191          !   Respiration of microzooplankton 
    192          !   Excess carbon in the food is used preferentially 
    193          !   ------------------------------------------------ 
     236         ! Food quality deprivation of GGE 
     237         zepsherq  = 0.5 + (1.0 - 0.5) * zepshert * ( 1.0 + 1.0 ) / ( zepshert + 1.0 ) 
     238         ! Actual GGE 
     239         zepsherv  = zepsherf * zepshert * zepsherq 
     240 
     241         ! Respiration of microzooplankton 
     242         ! Excess carbon in the food is used preferentially 
     243         ! when activated by zmetexcess 
     244         ! ------------------------------------------------ 
    194245         zexcess  = zgraztotc * zepsherf * (1.0 - zepshert) * zmetexcess 
    195246         zbasresb = MAX(0., zrespz - zexcess) 
     
    197248         zrespirc = srespir * zepsherv * zgraztotc + zbasresb 
    198249          
    199          !   When excess carbon is used, the other elements in excess 
    200          !   are also used proportionally to their abundance 
    201          !   -------------------------------------------------------- 
     250         ! When excess carbon is used, the other elements in excess 
     251         ! are also used proportionally to their abundance 
     252         ! -------------------------------------------------------- 
    202253         zexcess  = ( zgrasratn/ no3rat3 - zepshert ) / ( 1.0 - zepshert + rtrn) 
    203254         zbasresn = zbasresi * zexcess * zgrasratn  
    204255         zexcess  = ( zgrasratp/ po4rat3 - zepshert ) / ( 1.0 - zepshert + rtrn) 
    205256         zbasresp = zbasresi * zexcess * zgrasratp 
    206          zexcess  = ( zgrasratf/ ferat3 - zepshert ) / ( 1.0 - zepshert + rtrn) 
     257         zexcess  = ( zgrasratf/ feratz - zepshert ) / ( 1.0 - zepshert + rtrn) 
    207258         zbasresf = zbasresi * zexcess * zgrasratf 
    208259 
    209          !   Voiding of the excessive elements as DOM 
    210          !   ---------------------------------------- 
     260         ! Voiding of the excessive elements as DOM 
     261         ! ---------------------------------------- 
    211262         zgradoct   = (1. - unassc - zepsherv) * zgraztotc - zbasresi   
    212263         zgradont   = (1. - unassn) * zgraztotn - zepsherv * no3rat3 * zgraztotc - zbasresn 
    213264         zgradopt   = (1. - unassp) * zgraztotp - zepsherv * po4rat3 * zgraztotc - zbasresp 
    214          zgrareft   = (1. - unassc) * zgraztotf - zepsherv * ferat3 * zgraztotc - zbasresf 
    215  
    216          !  Since only semilabile DOM is represented in PISCES 
    217          !  part of DOM is in fact labile and is then released 
    218          !  as dissolved inorganic compounds (ssigma) 
    219          !  -------------------------------------------------- 
     265         zgrareft   = (1. - unassc) * zgraztotf - zepsherv * feratz * zgraztotc - zbasresf 
     266 
     267         ! Since only semilabile DOM is represented in PISCES 
     268         ! part of DOM is in fact labile and is then released 
     269         ! as dissolved inorganic compounds (ssigma) 
     270         ! -------------------------------------------------- 
    220271         zgradoc =  zgradoct * ssigma 
    221272         zgradon =  zgradont * ssigma 
     
    226277         zgraref = zgrareft 
    227278 
    228          !   Defecation as a result of non assimilated products 
    229          !   -------------------------------------------------- 
     279         ! Defecation as a result of non assimilated products 
     280         ! -------------------------------------------------- 
    230281         zgrapoc   = zgraztotc * unassc 
    231282         zgrapon   = zgraztotn * unassn 
     
    233284         zgrapof   = zgraztotf * unassc 
    234285 
    235          !  Addition of respiration to the release of inorganic nutrients 
    236          !  ------------------------------------------------------------- 
     286         ! Addition of respiration to the release of inorganic nutrients 
     287         ! ------------------------------------------------------------- 
    237288         zgrarem = zgrarem + zbasresi + zrespirc 
    238289         zgraren = zgraren + zbasresn + zrespirc * no3rat3 
    239290         zgrarep = zgrarep + zbasresp + zrespirc * po4rat3 
    240          zgraref = zgraref + zbasresf + zrespirc * ferat3 
     291         zgraref = zgraref + zbasresf + zrespirc * feratz 
    241292 
    242293         !   Update of the TRA arrays 
     
    279330         tr(ji,jj,jk,jppon,Krhs) = tr(ji,jj,jk,jppon,Krhs) + no3rat3 * ztortz + zgrapon - zgrazpon 
    280331         tr(ji,jj,jk,jppop,Krhs) = tr(ji,jj,jk,jppop,Krhs) + po4rat3 * ztortz + zgrapop - zgrazpop 
    281          tr(ji,jj,jk,jpsfe,Krhs) = tr(ji,jj,jk,jpsfe,Krhs) + ferat3 * ztortz  + zgrapof - zgrazpof 
     332         tr(ji,jj,jk,jpsfe,Krhs) = tr(ji,jj,jk,jpsfe,Krhs) + feratz * ztortz  + zgrapof - zgrazpof 
    282333         ! 
    283334         ! calcite production 
     
    287338         zprcaca = part * zprcaca 
    288339         tr(ji,jj,jk,jpdic,Krhs) = tr(ji,jj,jk,jpdic,Krhs) + zgrarem - zprcaca 
    289          tr(ji,jj,jk,jptal,Krhs) = tr(ji,jj,jk,jptal,Krhs) - 2. * zprcaca     & 
    290          &                     + rno3 * zgraren 
     340         tr(ji,jj,jk,jptal,Krhs) = tr(ji,jj,jk,jptal,Krhs) - 2. * zprcaca + rno3 * zgraren 
    291341         tr(ji,jj,jk,jpcal,Krhs) = tr(ji,jj,jk,jpcal,Krhs) + zprcaca 
    292342      END_3D 
     
    321371      !! ** Purpose :   Initialization of microzooplankton parameters 
    322372      !! 
    323       !! ** Method  :   Read the nampiszoo namelist and check the parameters 
     373      !! ** Method  :   Read the namp5zzoo namelist and check the parameters 
    324374      !!                called at the first timestep (nittrc000) 
    325375      !! 
    326       !! ** input   :   Namelist nampiszoo 
     376      !! ** input   :   Namelist namp5zzoo 
    327377      !! 
    328378      !!---------------------------------------------------------------------- 
     
    332382         &                xprefp, xprefd, xprefz, xthreshdia, xthreshphy, & 
    333383         &                xthreshpic, xthreshpoc, xthreshzoo, xthresh, xkgraz, & 
    334          &                epsher, epshermin, ssigma, srespir, unassc, unassn, unassp 
     384         &                epsher, epshermin, ssigma, srespir, unassc, unassn, unassp,   & 
     385         &                xsigma, xsigmadel    
    335386      !!---------------------------------------------------------------------- 
    336387      ! 
     
    370421         WRITE(numout,*) '    half sturation constant for grazing 1           xkgraz      =', xkgraz 
    371422         WRITE(numout,*) '    Use of excess carbon for respiration            bmetexc     =', bmetexc 
     423         WRITE(numout,*) '      Width of the grazing window                     xsigma      =', xsigma 
     424         WRITE(numout,*) '      Maximum additional width of the grazing window  xsigmadel   =', xsigmadel 
    372425      ENDIF 
    373426      ! 
Note: See TracChangeset for help on using the changeset viewer.