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 13233 for NEMO – NEMO

Changeset 13233 for NEMO


Ignore:
Timestamp:
2020-07-02T20:34:16+02:00 (4 years ago)
Author:
aumont
Message:

update of the PISCES comments

Location:
NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES
Files:
20 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zagg.F90

    r12537 r13233  
    100100                  zaggdoc2 = ( 3.53E3 * zfact + 0.1 * xstep ) * trb(ji,jj,jk,jpgoc) * 0.3 * trb(ji,jj,jk,jpdoc) 
    101101                  ! tranfer of DOC to POC due to brownian motion 
     102                  ! The temperature dependency has been omitted. 
    102103                  zaggdoc3 =  114. * 0.3 * trb(ji,jj,jk,jpdoc) *xstep * 0.3 * trb(ji,jj,jk,jpdoc) 
    103104 
     
    123124                  ! 
    124125                  zfact = xstep * xdiss(ji,jj,jk) 
    125                   !  Part I : Coagulation dependent on turbulence 
     126                  ! Part I : Coagulation dependent on turbulence 
    126127                  ! The stickiness has been assumed to be 0.1 
    127128                  zaggtmp = 25.9  * zfact * trb(ji,jj,jk,jppoc) 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zbio.F90

    r12759 r13233  
    6666 
    6767      ! ASSIGN THE SHEAR RATE THAT IS USED FOR AGGREGATION 
    68       ! OF PHYTOPLANKTON AND DETRITUS 
     68      ! OF PHYTOPLANKTON AND DETRITUS. Shear rate is supposed to equal 1 
     69      ! in the mixed layer and 0.1 below the mixed layer. 
    6970      xdiss(:,:,:) = 1. 
    7071      DO jk = 2, jpkm1 
     
    8081      CALL p4z_fechem  ( kt, knt )     ! Iron chemistry/scavenging 
    8182      ! 
    82       IF( ln_p4z ) THEN 
     83      IF( ln_p4z ) THEN  ! PISCES standard 
     84         ! Phytoplankton only sources/sinks terms 
    8385         CALL p4z_lim  ( kt, knt )     ! co-limitations by the various nutrients 
    8486         CALL p4z_prod ( kt, knt )     ! phytoplankton growth rate over the global ocean.  
    8587         !                             ! (for each element : C, Si, Fe, Chl ) 
    8688         CALL p4z_mort ( kt      )     ! phytoplankton mortality 
    87          !                             ! zooplankton sources/sinks routines  
     89         ! zooplankton sources/sinks routines  
    8890         CALL p4z_micro( kt, knt )     ! microzooplankton 
    8991         CALL p4z_meso ( kt, knt )     ! mesozooplankton 
    90       ELSE 
     92      ELSE  ! PISCES-QUOTA 
     93         ! Phytoplankton only sources/sinks terms 
    9194         CALL p5z_lim  ( kt, knt )     ! co-limitations by the various nutrients 
    9295         CALL p5z_prod ( kt, knt )     ! phytoplankton growth rate over the global ocean.  
    9396         !                             ! (for each element : C, N, P, Si, Fe, Chl ) 
    9497         CALL p5z_mort ( kt      )     ! phytoplankton mortality 
    95          !                             ! zooplankton sources/sinks routines  
     98         ! zooplankton sources/sinks routines  
    9699         CALL p5z_micro( kt, knt )     ! microzooplankton 
    97100         CALL p5z_meso ( kt, knt )     ! mesozooplankton 
     
    99102      ! 
    100103      CALL p4z_agg     ( kt, knt )     ! Aggregation of particles 
    101       CALL p4z_rem     ( kt, knt )     ! remineralization terms of organic matter+scavenging of Fe 
     104      CALL p4z_rem     ( kt, knt )     ! remineralization terms of organic matter 
    102105      CALL p4z_poc     ( kt, knt )     ! Remineralization of organic particles 
    103106      ! 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zlim.F90

    r12759 r13233  
    8484      !! 
    8585      !! ** Method  : - Limitation follows the Liebieg law of the minimum 
     86      !!              - Monod approach for N, P and Si. Quota approach  
     87      !!                for Iron 
    8688      !!--------------------------------------------------------------------- 
    8789      INTEGER, INTENT(in)  :: kt, knt 
     
    113115               ! Computation of a variable Ks of diatoms taking into account 
    114116               ! that increasing biomass is made of generally bigger cells 
     117               ! The allometric relationship is classical. 
    115118               !------------------------------------------------------------ 
    116119               z1_trbphy   = 1. / ( trb(ji,jj,jk,jpphy) + rtrn ) 
     
    156159 
    157160               ! Michaelis-Menten Limitation term by nutrients: Nanophyto 
     161               ! Optimal parameterization by Smith and Pahlow series of  
     162               ! papers is used. Optimal allocation is supposed independant 
     163               ! for all nutrients.  
    158164               ! -------------------------------------------------------- 
    159                ! Limitation of Fe uptake 
     165 
     166               ! Limitation of Fe uptake (Quota formalism) 
    160167               zfalim = (1.-fananof) / fananof 
    161168               xnanofer(ji,jj,jk) = (1. - fananof) * biron(ji,jj,jk) / ( biron(ji,jj,jk) + zfalim * concnfe(ji,jj,jk) ) 
     
    181188               !   Michaelis-Menten Limitation term by nutrients : Diatoms 
    182189               !   ------------------------------------------------------- 
    183                ! Limitation of Fe uptake 
     190               ! Limitation of Fe uptake (Quota formalism) 
    184191               zfalim = (1.-fadiatf) / fadiatf 
    185192               xdiatfer(ji,jj,jk) = (1. - fadiatf) * biron(ji,jj,jk) / ( biron(ji,jj,jk) + zfalim * concdfe(ji,jj,jk) ) 
     
    256263            DO ji = 1, jpi 
    257264               ! denitrification factor computed from O2 levels 
     265               ! This factor diagnoses below which level of O2 denitrification 
     266               ! is active 
    258267               nitrfac(ji,jj,jk) = MAX(  0.e0, 0.4 * ( 6.e-6  - trb(ji,jj,jk,jpoxy) )    & 
    259268                  &                                / ( oxymin + trb(ji,jj,jk,jpoxy) )  ) 
     
    261270               ! 
    262271               ! redox factor computed from NO3 levels 
     272               ! This factor diagnoses below which level of NO3 additional redox 
     273               ! reactions are taking place. 
    263274               nitrfac2(ji,jj,jk) = MAX( 0.e0,       ( 1.E-6 - trb(ji,jj,jk,jpno3) )  & 
    264275                  &                                / ( 1.E-6 + trb(ji,jj,jk,jpno3) ) ) 
     
    296307      !!---------------------------------------------------------------------- 
    297308      INTEGER ::   ios   ! Local integer 
    298       ! 
     309 
     310      ! Namelist block 
    299311      NAMELIST/namp4zlim/ concnno3, concdno3, concnnh4, concdnh4, concnfer, concdfer, concbfe,   & 
    300312         &                concbno3, concbnh4, xsizedia, xsizephy, xsizern, xsizerd,          &  
     
    348360      !!---------------------------------------------------------------------- 
    349361      !!                     ***  ROUTINE p5z_lim_alloc  *** 
     362      !!  
     363      !            Allocation of the arrays used in this module 
    350364      !!---------------------------------------------------------------------- 
    351365      USE lib_mpp , ONLY: ctl_stop 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zlys.F90

    r11536 r13233  
    5151      !!                OF CACO3 TO THE CACO3 SEDIMENT POOL. 
    5252      !! 
    53       !! ** Method  : - ??? 
     53      !! ** Method  : - pH is computed using the MOCSY module and dissolution 
     54      !!                is a function of the saturation state of CO3 
    5455      !!--------------------------------------------------------------------- 
    5556      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step and ??? 
     
    7172      !     COMPUTE [CO3--] and [H+] CONCENTRATIONS 
    7273      !     ------------------------------------------- 
    73  
     74      !     Call the carbonate chemistry subroutine to compute pH 
     75      !     This subroutine is in the p4zche module 
    7476      CALL solve_at_general( zhinit, zhi ) 
    7577 
     
    8587 
    8688      !     --------------------------------------------------------- 
    87       !        CALCULATE DEGREE OF CACO3 SATURATION AND CORRESPONDING 
    88       !        DISSOLOUTION AND PRECIPITATION OF CACO3 (BE AWARE OF 
    89       !        MGCO3) 
     89      !     CALCULATE DEGREE OF CACO3 SATURATION AND CORRESPONDING 
     90      !     DISSOLOUTION AND PRECIPITATION OF CACO3 (BE AWARE OF 
     91      !     MGCO3) 
    9092      !     --------------------------------------------------------- 
    9193 
     
    106108               zexcess  = zexcess0**nca 
    107109 
    108                ! AMOUNT CACO3 (12C) THAT RE-ENTERS SOLUTION 
    109                !       (ACCORDING TO THIS FORMULATION ALSO SOME PARTICULATE 
    110                !       CACO3 GETS DISSOLVED EVEN IN THE CASE OF OVERSATURATION) 
     110               ! AMOUNT CACO3 THAT RE-ENTERS SOLUTION 
    111111               zdispot = kdca * zexcess * trb(ji,jj,jk,jpcal) 
    112               ! CHANGE OF [CO3--] , [ALK], PARTICULATE [CACO3], 
    113               !      AND [SUM(CO2)] DUE TO CACO3 DISSOLUTION/PRECIPITATION 
    114               zcaldiss(ji,jj,jk)  = zdispot * rfact2 / rmtss ! calcite dissolution 
    115               ! 
    116               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) + 2. * zcaldiss(ji,jj,jk) 
    117               tra(ji,jj,jk,jpcal) = tra(ji,jj,jk,jpcal) -      zcaldiss(ji,jj,jk) 
    118               tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) +      zcaldiss(ji,jj,jk) 
     112               ! CHANGE OF [CO3--] , [ALK], PARTICULATE [CACO3], 
     113               ! AND [SUM(CO2)] DUE TO CACO3 DISSOLUTION/PRECIPITATION 
     114               zcaldiss(ji,jj,jk)  = zdispot * rfact2 / rmtss ! calcite dissolution 
     115               ! 
     116               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) + 2. * zcaldiss(ji,jj,jk) 
     117               tra(ji,jj,jk,jpcal) = tra(ji,jj,jk,jpcal) -      zcaldiss(ji,jj,jk) 
     118               tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) +      zcaldiss(ji,jj,jk) 
    119119            END DO 
    120120         END DO 
    121121      END DO 
    122       ! 
    123122 
     123      ! output of diagnostics 
    124124      IF( lk_iomput .AND. knt == nrdttrc ) THEN 
    125125         IF( iom_use( "PH"     ) ) CALL iom_put( "PH"    , -1. * LOG10( MAX( hi(:,:,:), rtrn ) ) * tmask(:,:,:) ) 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zmeso.F90

    r13200 r13233  
    4545   REAL(wp), PUBLIC ::  epsher2      !: growth efficiency 
    4646   REAL(wp), PUBLIC ::  epsher2min   !: minimum growth efficiency at high food for grazing 2 
     47   REAL(wp), PUBLIC ::  xsigma2      !: Width of the predation window 
     48   REAL(wp), PUBLIC ::  xsigma2del   !: Maximum width of the predation window at low food density 
    4749   REAL(wp), PUBLIC ::  grazflux     !: mesozoo flux feeding rate 
    4850   REAL(wp), PUBLIC ::  xfracmig     !: Fractional biomass of meso that performs DVM 
     
    169171               ! ---------------------------------------------------------- 
    170172               zsigma = 1.0 - zdenom**2/(0.05**2+zdenom**2) 
    171                zsigma = 0.5 + 1.0 * zsigma 
     173               zsigma = xsigma2 + xsigma2del * zsigma 
    172174               ! Nanophytoplankton and diatoms are the only preys considered 
    173175               ! to be close enough to have potential interference 
     
    186188               !   Mesozooplankton regular grazing on the different preys 
    187189               !   ------------------------------------------------------ 
    188                zgrazdc   = zgraze2  * ztmp3 * zdenom 
    189                zgraznc   = zgraze2  * ztmp1 * zdenom 
    190                zgrazpoc  = zgraze2  * ztmp2 * zdenom 
    191                zgrazz    = zgraze2  * ztmp4 * zdenom 
    192  
     190               zgrazdc   = zgraze2  * ztmp3 * zdenom  ! diatoms 
     191               zgraznc   = zgraze2  * ztmp1 * zdenom  ! nanophytoplankton 
     192               zgrazpoc  = zgraze2  * ztmp2 * zdenom  ! small POC 
     193               zgrazz    = zgraze2  * ztmp4 * zdenom  ! microzooplankton 
     194 
     195               ! Ingestion rates of the Fe content of the different preys 
    193196               zgraznf   = zgraznc  * trb(ji,jj,jk,jpnfe) / ( trb(ji,jj,jk,jpphy) + rtrn) 
    194197               zgrazdf   = zgrazdc  * trb(ji,jj,jk,jpdfe) / ( trb(ji,jj,jk,jpdia) + rtrn) 
     
    228231               zgrazfffp = zproport * zgrazfffp 
    229232               zgrazfffg = zproport * zgrazfffg 
     233 
     234               ! Total ingestion rates in C, N, Fe 
    230235               zgraztotc = zgrazdc + zgrazz + zgraznc + zgrazpoc + zgrazffep + zgrazffeg 
    231236               zgraztotn = zgrazdc * quotad(ji,jj,jk) + zgrazz + zgraznc * quotan(ji,jj,jk)   & 
     
    248253               zepshert  = MIN( 1., zgrasratn, zgrasratf / ferat3) 
    249254               zbeta     = MAX(0., (epsher2 - epsher2min) ) 
     255               ! Food quantity deprivation of GGE 
    250256               zepsherf  = epsher2min + zbeta / ( 1.0 + 0.04E6 * 12. * zfood * zbeta )  
     257               ! Food quality deprivation of GGE 
    251258               zepsherq  = 0.5 + (1.0 - 0.5) * zepshert * ( 1.0 + 1.0 ) / ( zepshert + 1.0 ) 
     259               ! Actual GGE 
    252260               zepsherv  = zepsherf * zepshert * zepsherq 
    253261               !  
     
    258266               ! according to a infinite chain of predators (ANderson et al., 2013) 
    259267               zmortzgoc = unass2 / ( 1. - epsher2 ) * ztortz + zrespz 
     268 
     269               ! Update of the trends 
    260270               tra(ji,jj,jk,jpmes) = tra(ji,jj,jk,jpmes) - zmortz + zepsherv * zgraztotc 
    261271               tra(ji,jj,jk,jpdia) = tra(ji,jj,jk,jpdia) - zgrazdc 
     
    502512         WRITE(numout,*) '      Fraction of mesozoo excretion as DOM           sigma2       =', sigma2 
    503513         WRITE(numout,*) '      half sturation constant for grazing 2          xkgraz2      =', xkgraz2 
     514         WRITE(numout,*) '      Width of the grazing window                     xsigma2     =', xsigma2 
     515         WRITE(numout,*) '      Maximum additional width of the grazing window  xsigma2del  =', xsigma2del 
    504516         WRITE(numout,*) '      Diurnal vertical migration of mesozoo.         ln_dvm_meso  =', ln_dvm_meso 
    505517         WRITE(numout,*) '      Fractional biomass of meso  that performs DVM  xfracmig     =', xfracmig 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zmicro.F90

    r13200 r13233  
    4242   REAL(wp), PUBLIC ::   epsher      !: growth efficiency for grazing 1  
    4343   REAL(wp), PUBLIC ::   epshermin   !: minimum growth efficiency for grazing 1 
     44   REAL(wp), PUBLIC ::   xsigma      !: Width of the grazing window 
     45   REAL(wp), PUBLIC ::   xsigmadel   !: Maximum additional width of the grazing window at low food density  
     46 
    4447 
    4548   !!---------------------------------------------------------------------- 
     
    5962      !!                parameterization. 
    6063      !!                All living compartments smaller than microzooplankton 
    61       !!                are potential preys of mesozooplankton 
     64      !!                are potential preys of microzooplankton 
    6265      !! 
    6366      !! ** Method  : - ??? 
     
    146149               ! ---------------------------------------------------------- 
    147150               zsigma = 1.0 - zdenom**2/(0.05**2+zdenom**2) 
    148                zsigma = 0.5 + 1.0*zsigma 
     151               zsigma = xsigma + xsigmadel * zsigma 
    149152               zdiffdn = exp( -ABS(log(1.67 * sizen(ji,jj,jk) / (5.0 * sized(ji,jj,jk) + rtrn )) )**2 / zsigma**2) 
    150153               ztmp1 = xprefn * zcompaph * ( zcompaph + zdiffdn * zcompadi ) / ( 1.0 + zdiffdn ) 
     
    156159               ztmp3 = ztmp3 / ztmptot 
    157160 
    158                zgraznc   = zgraze   * ztmp1 * zdenom 
    159                zgrazdc   = zgraze   * ztmp2 * zdenom 
    160                zgrazpoc  = zgraze   * ztmp3 * zdenom 
    161  
     161               ! Ingestion terms on the different preys of microzooplankton 
     162               zgraznc   = zgraze   * ztmp1 * zdenom  ! Nanophytoplankton 
     163               zgrazdc   = zgraze   * ztmp2 * zdenom  ! Diatoms 
     164               zgrazpoc  = zgraze   * ztmp3 * zdenom  ! POC 
     165 
     166               ! Ingestion terms on the iron content of the different preys 
    162167               zgraznf   = zgraznc  * trb(ji,jj,jk,jpnfe) / (trb(ji,jj,jk,jpphy) + rtrn) 
    163168               zgrazpof  = zgrazpoc * trb(ji,jj,jk,jpsfe) / (trb(ji,jj,jk,jppoc) + rtrn) 
    164169               zgrazdf   = zgrazdc  * trb(ji,jj,jk,jpdfe) / (trb(ji,jj,jk,jpdia) + rtrn) 
    165170               ! 
     171               ! Total ingestion rate in C, Fe, N units 
    166172               zgraztotc = zgraznc + zgrazpoc + zgrazdc 
    167173               zgraztotf = zgraznf + zgrazdf  + zgrazpof  
     
    183189               zepshert  =  MIN( 1., zgrasratn, zgrasratf / ferat3) 
    184190               zbeta     = MAX(0., (epsher - epshermin) ) 
     191               ! Food quantity deprivation of the GGE 
    185192               zepsherf  = epshermin + zbeta / ( 1.0 + 0.04E6 * 12. * zfood * zbeta ) 
     193               ! Food quality deprivation of the GGE 
    186194               zepsherq  = 0.5 + (1.0 - 0.5) * zepshert * ( 1.0 + 1.0 ) / ( zepshert + 1.0 ) 
     195               ! Actual GGE of microzooplankton 
    187196               zepsherv  = zepsherf * zepshert * zepsherq 
     197               ! Excretion of Fe 
    188198               zgrafer   = zgraztotc * MAX( 0. , ( 1. - unass ) * zgrasratf - ferat3 * zepsherv )  
     199               ! Excretion of C, N, P 
    189200               zgrarem   = zgraztotc * ( 1. - zepsherv - unass ) 
     201               ! Egestion of C, N, P 
    190202               zgrapoc   = zgraztotc * unass 
    191203 
    192204               !  Update of the TRA arrays 
    193205               !  ------------------------ 
     206               ! Fraction of excretion as inorganic nutrients and DIC 
    194207               zgrarsig  = zgrarem * sigma1 
    195208               tra(ji,jj,jk,jppo4) = tra(ji,jj,jk,jppo4) + zgrarsig 
     
    287300      NAMELIST/namp4zzoo/ part, grazrat, resrat, mzrat, xprefn, xprefc, & 
    288301         &                xprefd,  xthreshdia,  xthreshphy,  xthreshpoc, & 
    289          &                xthresh, xkgraz, epsher, epshermin, sigma1, unass 
     302         &                xthresh, xkgraz, epsher, epshermin, sigma1, unass  & 
     303         &                xsigma, xsigmadel 
    290304      !!---------------------------------------------------------------------- 
    291305      ! 
     
    321335         WRITE(numout,*) '      Minimum efficicency of microzoo growth          epshermin   =', epshermin 
    322336         WRITE(numout,*) '      Fraction of microzoo excretion as DOM           sigma1      =', sigma1 
    323          WRITE(numout,*) '      half sturation constant for grazing 1           xkgraz      =', xkgraz 
     337         WRITE(numout,*) '      half saturation constant for grazing 1          xkgraz      =', xkgraz 
     338         WRITE(numout,*) '      Width of the grazing window                     xsigma      =', xsigma 
     339         WRITE(numout,*) '      Maximum additional width of the grazing window  xsigmadel   =', xsigmadel 
     340 
    324341      ENDIF 
    325342      ! 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zmort.F90

    r12537 r13233  
    4848      !!--------------------------------------------------------------------- 
    4949      ! 
    50       CALL p4z_nano            ! nanophytoplankton 
    51       CALL p4z_diat            ! diatoms 
     50      CALL p4z_mort_nano            ! nanophytoplankton 
     51      CALL p4z_mort_diat            ! diatoms 
    5252      ! 
    5353   END SUBROUTINE p4z_mort 
    5454 
    5555 
    56    SUBROUTINE p4z_nano 
    57       !!--------------------------------------------------------------------- 
    58       !!                     ***  ROUTINE p4z_nano  *** 
     56   SUBROUTINE p4z_mort_nano 
     57      !!--------------------------------------------------------------------- 
     58      !!                     ***  ROUTINE p4z_mort_nano  *** 
    5959      !! 
    6060      !! ** Purpose :   Compute the mortality terms for nanophytoplankton 
    6161      !! 
    62       !! ** Method  : - ??? 
     62      !! ** Method  :   Both quadratic and simili linear mortality terms 
    6363      !!--------------------------------------------------------------------- 
    6464      INTEGER  ::   ji, jj, jk 
     
    6969      !!--------------------------------------------------------------------- 
    7070      ! 
    71       IF( ln_timing )   CALL timing_start('p4z_nano') 
     71      IF( ln_timing )   CALL timing_start('p4z_mort_nano') 
    7272      ! 
    7373      prodcal(:,:,:) = 0._wp   ! calcite production variable set to zero 
     
    101101               tra(ji,jj,jk,jpnch) = tra(ji,jj,jk,jpnch) - zmortp * zfactch 
    102102               tra(ji,jj,jk,jpnfe) = tra(ji,jj,jk,jpnfe) - zmortp * zfactfe 
     103 
    103104               ! Production PIC particles due to mortality 
    104105               zprcaca = xfracal(ji,jj,jk) * zmortp 
    105106               prodcal(ji,jj,jk) = prodcal(ji,jj,jk) + zprcaca  ! prodcal=prodcal(nanophy)+prodcal(microzoo)+prodcal(mesozoo) 
     107 
     108               ! POC associated with the shell is supposed to be routed to  
     109               ! big particles because of the ballasting effect 
    106110               zfracal = 0.5 * xfracal(ji,jj,jk) 
    107111               tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) - zprcaca 
     
    112116               prodpoc(ji,jj,jk) = prodpoc(ji,jj,jk) + ( 1. - zfracal ) * zmortp 
    113117               prodgoc(ji,jj,jk) = prodgoc(ji,jj,jk) + zfracal * zmortp 
     118 
     119               ! Update the arrays TRA which contains the biological sources and sinks 
    114120               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + ( 1. - zfracal ) * zmortp * zfactfe 
    115121               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zfracal * zmortp * zfactfe 
     
    124130       ENDIF 
    125131      ! 
    126       IF( ln_timing )   CALL timing_stop('p4z_nano') 
    127       ! 
    128    END SUBROUTINE p4z_nano 
    129  
    130  
    131    SUBROUTINE p4z_diat 
    132       !!--------------------------------------------------------------------- 
    133       !!                     ***  ROUTINE p4z_diat  *** 
     132      IF( ln_timing )   CALL timing_stop('p4z_mort_nano') 
     133      ! 
     134   END SUBROUTINE p4z_mort_nano 
     135 
     136 
     137   SUBROUTINE p4z_mort_diat 
     138      !!--------------------------------------------------------------------- 
     139      !!                     ***  ROUTINE p4z_mort_diat  *** 
    134140      !! 
    135141      !! ** Purpose :   Compute the mortality terms for diatoms 
    136142      !! 
    137       !! ** Method  : - ??? 
     143      !! ** Method  : - Both quadratic and simili linear mortality terms 
    138144      !!--------------------------------------------------------------------- 
    139145      INTEGER  ::   ji, jj, jk 
     
    144150      !!--------------------------------------------------------------------- 
    145151      ! 
    146       IF( ln_timing )   CALL timing_start('p4z_diat') 
     152      IF( ln_timing )   CALL timing_start('p4z_mort_diat') 
    147153      ! 
    148154      ! Aggregation term for diatoms is increased in case of nutrient 
    149155      ! stress as observed in reality. The stressed cells become more 
    150156      ! sticky and coagulate to sink quickly out of the euphotic zone 
     157      ! This is due to the production of EPS by stressed cells 
    151158      ! ------------------------------------------------------------- 
    152159 
     
    183190               tra(ji,jj,jk,jpdsi) = tra(ji,jj,jk,jpdsi) - zmortp2 * zfactsi 
    184191               tra(ji,jj,jk,jpgsi) = tra(ji,jj,jk,jpgsi) + zmortp2 * zfactsi 
     192 
     193               ! Half of the linear mortality term is routed to big particles 
     194               ! becaue of the ballasting effect 
    185195               tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) + zrespp2 + 0.5 * ztortp2 
    186196               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + 0.5 * ztortp2 
     
    199209      ENDIF 
    200210      ! 
    201       IF( ln_timing )   CALL timing_stop('p4z_diat') 
    202       ! 
    203    END SUBROUTINE p4z_diat 
     211      IF( ln_timing )   CALL timing_stop('p4z_mort_diat') 
     212      ! 
     213   END SUBROUTINE p4z_mort_diat 
    204214 
    205215 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zopt.F90

    r11536 r13233  
    8080      ze2(:,:,:) = 0._wp 
    8181      ze3(:,:,:) = 0._wp 
    82       ! 
    83       !                                        !* attenuation coef. function of Chlorophyll and wavelength (Red-Green-Blue) 
    84       !                                        !  -------------------------------------------------------- 
     82 
     83      ! Attenuation coef. function of Chlorophyll and wavelength (Red-Green-Blue) 
     84      ! Thus the light penetration scheme is based on a decomposition of PAR 
     85      ! into three wave length domains. This was first officially published 
     86      ! in Lengaigne et al. (2007). 
     87      ! -------------------------------------------------------- 
    8588                     zchl3d(:,:,:) = trb(:,:,:,jpnch) + trb(:,:,:,jpdch) 
    8689      IF( ln_p5z )   zchl3d(:,:,:) = zchl3d(:,:,:)    + trb(:,:,:,jppch) 
    8790      ! 
     91      ! Computation of the light attenuation parameters based on a  
     92      ! look-up table 
    8893      DO jk = 1, jpkm1    
    8994         DO jj = 1, jpj 
     
    99104         END DO 
    100105      END DO 
    101       !                                        !* Photosynthetically Available Radiation (PAR) 
    102       !                                        !  -------------------------------------- 
     106 
     107      ! Photosynthetically Available Radiation (PAR) 
     108      ! Two cases are considered in the following :  
     109      ! (1) An explicit diunal cycle is activated. In that case, mean  
     110      ! QSR is used as PISCES in its current state has not been parameterized 
     111      ! for an explicit diurnal cycle 
     112      ! (2) no diurnal cycle of SW is active and in that case, QSR is used. 
     113      ! -------------------------------------------- 
    103114      IF( l_trcdm2dc ) THEN                     !  diurnal cycle 
    104115         ! 
     116         ! SW over the ice free zone of the grid cell. This assumes that 
     117         ! SW is zero below sea ice which is a very crude assumption that is  
     118         ! not fully correct with LIM3 and SI3 but no information is  
     119         ! currently available to do a better job. SHould be improved in the  
     120         ! (near) future. 
    105121         zqsr_corr(:,:) = qsr_mean(:,:) / ( 1.-fr_i(:,:) + rtrn ) 
    106122         ! 
    107123         CALL p4z_opt_par( kt, zqsr_corr, ze1, ze2, ze3, pqsr100 = zqsr100 )  
    108124         ! 
     125         ! Used PAR is computed for each phytoplankton species 
     126         ! etot_ndcy is PAR at level jk averaged over 24h. 
     127         ! Due to their size, they have different light absorption characteristics 
    109128         DO jk = 1, nksrp       
    110129            etot_ndcy(:,:,jk) =        ze1(:,:,jk) +        ze2(:,:,jk) +       ze3(:,:,jk) 
     
    117136            END DO 
    118137         ENDIF 
    119          ! 
     138 
     139         ! SW over the ice free zone of the grid cell. This assumes that 
     140         ! SW is zero below sea ice which is a very crude assumption that is  
     141         ! not fully correct with LIM3 and SI3 but no information is  
     142         ! currently available to do a better job. SHould be improved in the  
     143         ! (near) future. 
    120144         zqsr_corr(:,:) = qsr(:,:) / ( 1.-fr_i(:,:) + rtrn ) 
    121145         ! 
    122146         CALL p4z_opt_par( kt, zqsr_corr, ze1, ze2, ze3 )  
    123          ! 
     147 
     148         ! Total PAR computation at level jk that includes the diurnal cycle 
    124149         DO jk = 1, nksrp       
    125150            etot(:,:,jk) =  ze1(:,:,jk) + ze2(:,:,jk) + ze3(:,:,jk) 
    126151         END DO 
    127152         ! 
    128       ELSE 
    129          ! 
     153      ELSE ! no diurnal cycle 
     154         ! 
     155         ! SW over the ice free zone of the grid cell. This assumes that 
     156         ! SW is zero below sea ice which is a very crude assumption that is  
     157         ! not fully correct with LIM3 and SI3 but no information is  
     158         ! currently available to do a better job. SHould be improved in the  
     159         ! (near) future. 
    130160         zqsr_corr(:,:) = qsr(:,:) / ( 1.-fr_i(:,:) + rtrn ) 
    131          ! 
     161 
    132162         CALL p4z_opt_par( kt, zqsr_corr, ze1, ze2, ze3, pqsr100 = zqsr100  )  
    133          ! 
     163 
     164         ! Used PAR is computed for each phytoplankton species 
     165         ! Due to their size, they have different light absorption characteristics 
    134166         DO jk = 1, nksrp       
    135             etot (:,:,jk) =        ze1(:,:,jk) +        ze2(:,:,jk) +       ze3(:,:,jk) 
    136             enano(:,:,jk) =  1.85 * ze1(:,:,jk) + 0.69 * ze2(:,:,jk) + 0.46 * ze3(:,:,jk) 
    137             ediat(:,:,jk) =  1.62 * ze1(:,:,jk) + 0.74 * ze2(:,:,jk) + 0.63 * ze3(:,:,jk) 
     167            etot (:,:,jk) =        ze1(:,:,jk) +        ze2(:,:,jk) +       ze3(:,:,jk) ! Total PAR 
     168            enano(:,:,jk) =  1.85 * ze1(:,:,jk) + 0.69 * ze2(:,:,jk) + 0.46 * ze3(:,:,jk) ! Nanophytoplankton 
     169            ediat(:,:,jk) =  1.62 * ze1(:,:,jk) + 0.74 * ze2(:,:,jk) + 0.63 * ze3(:,:,jk) ! Diatoms 
    138170         END DO 
    139171         IF( ln_p5z ) THEN 
    140172            DO jk = 1, nksrp       
    141               epico(:,:,jk) =  1.94 * ze1(:,:,jk) + 0.66 * ze2(:,:,jk) + 0.4 * ze3(:,:,jk) 
     173              epico(:,:,jk) =  1.94 * ze1(:,:,jk) + 0.66 * ze2(:,:,jk) + 0.4 * ze3(:,:,jk) ! Picophytoplankton (PISCES-QUOTA) 
    142174            END DO 
    143175         ENDIF 
     
    146178 
    147179 
     180      ! Biophysical feedback part (computation of vertical penetration of SW) 
    148181      IF( ln_qsr_bio ) THEN                    !* heat flux accros w-level (used in the dynamics) 
    149182         !                                     !  ------------------------ 
     
    154187            etot3(:,:,jk) =  ( ze0(:,:,jk) + ze1(:,:,jk) + ze2(:,:,jk) + ze3(:,:,jk) ) * tmask(:,:,jk) 
    155188         END DO 
    156          !                                     !  ------------------------ 
    157       ENDIF 
    158       !                                        !* Euphotic depth and level 
    159       neln   (:,:) = 1                            !  ------------------------ 
     189 
     190      ENDIF 
     191 
     192      ! Euphotic depth and level 
     193      ! Two definitions of the euphotic zone are used here.  
     194      ! (1) The classical definition based on the relative threshold value 
     195      ! (2) An alternative definition based on a absolute threshold value. 
     196      ! ------------------------------------------------------------------- 
    160197      heup   (:,:) = gdepw_n(:,:,2) 
    161198      heup_01(:,:) = gdepw_n(:,:,2) 
     
    176213      END DO 
    177214      ! 
     215      ! The euphotic depth can not exceed 300 meters. 
    178216      heup   (:,:) = MIN( 300., heup   (:,:) ) 
    179217      heup_01(:,:) = MIN( 300., heup_01(:,:) ) 
    180       !                                        !* mean light over the mixed layer 
    181       zdepmoy(:,:)   = 0.e0                    !  ------------------------------- 
     218 
     219      ! Mean PAR over the mixed layer 
     220      ! ----------------------------- 
     221      zdepmoy(:,:)   = 0.e0 
    182222      zetmp1 (:,:)   = 0.e0 
    183223      zetmp2 (:,:)   = 0.e0 
     
    187227            DO ji = 1, jpi 
    188228               IF( gdepw_n(ji,jj,jk+1) <= hmld(ji,jj) ) THEN 
    189                   zetmp1 (ji,jj) = zetmp1 (ji,jj) + etot     (ji,jj,jk) * e3t_n(ji,jj,jk) ! remineralisation 
    190                   zetmp2 (ji,jj) = zetmp2 (ji,jj) + etot_ndcy(ji,jj,jk) * e3t_n(ji,jj,jk) ! production 
     229                  zetmp1 (ji,jj) = zetmp1 (ji,jj) + etot     (ji,jj,jk) * e3t_n(ji,jj,jk) ! Actual PAR 
     230                  zetmp2 (ji,jj) = zetmp2 (ji,jj) + etot_ndcy(ji,jj,jk) * e3t_n(ji,jj,jk) ! Par averaged over 24h 
    191231                  zdepmoy(ji,jj) = zdepmoy(ji,jj) +                       e3t_n(ji,jj,jk) 
    192232               ENDIF 
     
    195235      END DO 
    196236      ! 
    197       emoy(:,:,:) = etot(:,:,:)       ! remineralisation 
     237      emoy(:,:,:) = etot(:,:,:)       ! PAR 
    198238      zpar(:,:,:) = etot_ndcy(:,:,:)  ! diagnostic : PAR with no diurnal cycle  
    199239      ! 
     
    209249         END DO 
    210250      END DO 
    211       ! 
     251 
     252      ! Computation of the mean usable light for the different phytoplankton 
     253      ! groups based on their absorption characteristics. 
    212254      zdepmoy(:,:)   = 0.e0 
    213255      zetmp3 (:,:)   = 0.e0 
     
    218260            DO ji = 1, jpi 
    219261               IF( gdepw_n(ji,jj,jk+1) <= MIN(hmld(ji,jj), heup_01(ji,jj)) ) THEN 
    220                   zetmp3 (ji,jj) = zetmp3 (ji,jj) + enano    (ji,jj,jk) * e3t_n(ji,jj,jk) ! production 
    221                   zetmp4 (ji,jj) = zetmp4 (ji,jj) + ediat    (ji,jj,jk) * e3t_n(ji,jj,jk) ! production 
     262                  zetmp3 (ji,jj) = zetmp3 (ji,jj) + enano    (ji,jj,jk) * e3t_n(ji,jj,jk) ! Nanophytoplankton 
     263                  zetmp4 (ji,jj) = zetmp4 (ji,jj) + ediat    (ji,jj,jk) * e3t_n(ji,jj,jk) ! Diatoms  
    222264                  zdepmoy(ji,jj) = zdepmoy(ji,jj) +                       e3t_n(ji,jj,jk) 
    223265               ENDIF 
     
    241283      ! 
    242284      IF( ln_p5z ) THEN 
     285         ! Picophytoplankton when using PISCES-QUOTA 
    243286         zetmp5 (:,:) = 0.e0 
    244287         DO jk = 1, nksrp 
     
    246289               DO ji = 1, jpi 
    247290                  IF( gdepw_n(ji,jj,jk+1) <= MIN(hmld(ji,jj), heup_01(ji,jj)) ) THEN 
    248                      zetmp5(ji,jj)  = zetmp5 (ji,jj) + epico(ji,jj,jk) * e3t_n(ji,jj,jk) ! production 
     291                     zetmp5(ji,jj)  = zetmp5 (ji,jj) + epico(ji,jj,jk) * e3t_n(ji,jj,jk) 
    249292                  ENDIF 
    250293               END DO 
     
    265308         END DO 
    266309      ENDIF 
     310 
     311      ! Output of the diagnostics 
    267312      IF( lk_iomput ) THEN 
    268313        IF( knt == nrdttrc ) THEN 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zpoc.F90

    r12537 r13233  
    8989      solgoc = 0.04/ 2.56 * 1./ ( 1.-50**(-0.04) ) 
    9090 
    91       ! Initialisation of temporary arrys 
     91      ! Initialisation of temporary arrays 
    9292      IF( ln_p4z ) THEN 
    9393         zremipoc(:,:,:) = xremip 
     
    419419              DO ji = 1, jpi 
    420420                 IF (tmask(ji,jj,jk) == 1.) THEN 
    421                     ! POC disaggregation by bacterial activity. It is a function 
     421                    ! POC solubilisation by bacterial activity. It is a function 
    422422                    ! of the mean lability and of temperature  
    423423                    ! ---------------------------------------------------------- 
     
    538538      ALLOCATE( alphan(jcpoc) , reminp(jcpoc) , alphap(jpi,jpj,jpk,jcpoc) ) 
    539539      ! 
    540       IF (jcpoc > 1) THEN 
     540      IF (jcpoc > 1) THEN  ! Case when more than one lability class is used 
    541541         ! 
    542542         remindelta = LOG(4. * 1000. ) / REAL(jcpoc-1, wp) 
     
    562562         reminp(jcpoc) = reminp(jcpoc) * xremip / alphan(jcpoc) 
    563563 
    564       ELSE 
     564      ELSE  ! Only one lability class is used 
    565565         alphan(jcpoc) = 1. 
    566566         reminp(jcpoc) = xremip 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zprod.F90

    r13200 r13233  
    2626   PUBLIC   p4z_prod_alloc   ! called in trcini_pisces.F90 
    2727 
    28    REAL(wp), PUBLIC ::   pislopen     !: 
    29    REAL(wp), PUBLIC ::   pisloped     !: 
    30    REAL(wp), PUBLIC ::   xadap        !: 
    31    REAL(wp), PUBLIC ::   excretn      !: 
    32    REAL(wp), PUBLIC ::   excretd      !: 
    33    REAL(wp), PUBLIC ::   bresp        !: 
    34    REAL(wp), PUBLIC ::   chlcnm       !: 
    35    REAL(wp), PUBLIC ::   chlcdm       !: 
    36    REAL(wp), PUBLIC ::   chlcmin      !: 
    37    REAL(wp), PUBLIC ::   fecnm        !: 
    38    REAL(wp), PUBLIC ::   fecdm        !: 
    39    REAL(wp), PUBLIC ::   grosip       !: 
     28   REAL(wp), PUBLIC ::   pislopen     !:  P-I slope of nanophytoplankton 
     29   REAL(wp), PUBLIC ::   pisloped     !:  P-I slope of diatoms 
     30   REAL(wp), PUBLIC ::   xadap        !:  Adaptation factor to low light  
     31   REAL(wp), PUBLIC ::   excretn      !:  Excretion ratio of nanophyto 
     32   REAL(wp), PUBLIC ::   excretd      !:  Excretion ratio of diatoms 
     33   REAL(wp), PUBLIC ::   bresp        !:  Basal respiration rate 
     34   REAL(wp), PUBLIC ::   chlcnm       !:  Maximum Chl/C ratio of nano 
     35   REAL(wp), PUBLIC ::   chlcdm       !:  Maximum Chl/C ratio of diatoms 
     36   REAL(wp), PUBLIC ::   chlcmin      !:  Minimum Chl/C ratio of phytoplankton 
     37   REAL(wp), PUBLIC ::   fecnm        !:  Maximum Fe/C ratio of nano 
     38   REAL(wp), PUBLIC ::   fecdm        !:  Maximum Fe/C ratio of diatoms 
     39   REAL(wp), PUBLIC ::   grosip       !:  Mean Si/C ratio of diatoms 
    4040 
    4141   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   quotan   !: proxy of N quota in Nanophyto 
     
    6161      !!                Computes also the uptake of Iron and Si as well  
    6262      !!                as the chlorophyll content of the cells 
     63      !!                PISCES relies on a mixed Monod-Quota formalism  
    6364      !!--------------------------------------------------------------------- 
    6465      INTEGER, INTENT(in) ::   kt, knt   ! 
     
    9495      zmxl_fac(:,:,:) = 0._wp ; zmxl_chl(:,:,:) = 0._wp  
    9596 
    96       ! Computation of the maximimum production 
     97      ! Computation of the maximimum production. Based on a Q10 description 
     98      ! of the thermal dependency 
    9799      ! Parameters are taken from Bissinger et al. (2008) 
    98100      zprmaxn(:,:,:) = 0.8_wp * r1_rday * tgfunc(:,:,:) 
     
    100102 
    101103      ! compute the day length depending on latitude and the day 
     104      ! Astronomical parameterization taken from HAMOCC3 
    102105      zrum = REAL( nday_year - 80, wp ) / REAL( nyear_len(1), wp ) 
    103106      zcodel = ASIN(  SIN( zrum * rpi * 2._wp ) * SIN( rad * 23.5_wp )  ) 
     
    115118      ! Impact of the day duration and light intermittency on phytoplankton growth 
    116119      ! Intermittency is supposed to have a similar effect on production as  
    117       ! day length. The correcting factor is zmxl_fac. zmxl_chl is the fractional 
    118       ! day length and is used to compute the mean PAR during daytime. 
    119       ! Formulation for the impact of day length on PP is from Thompson (1999) 
     120      ! day length (Shatwell et al., 2012). The correcting factor is zmxl_fac.  
     121      ! zmxl_chl is the fractional day length and is used to compute the mean 
     122      ! PAR during daytime. The effect of mixing is computed using the  
     123      ! absolute light level definition of the euphotic zone 
    120124      ! -------------------------------------------------------------------------  
    121125      DO jk = 1, jpkm1 
     
    137141      zprdia(:,:,:) = zprmaxd(:,:,:) * zmxl_fac(:,:,:) 
    138142 
    139       WHERE( zstrn(:,:) < 1.e0 ) zstrn(:,:) = 24. 
    140  
    141143      ! Computation of the P-I slope for nanos and diatoms 
    142144      ! The formulation proposed by Geider et al. (1997) has been modified  
     
    155157                  ! The initial slope of the PI curve can be increased for nano 
    156158                  ! to account for photadaptation, for instance in the DCM 
     159                  ! This parameterization is adhoc and should be either  
     160                  ! improved or removed in future versions of the model 
     161 
     162                  ! Nanophytoplankton 
    157163                  zpislopeadn(ji,jj,jk) = pislopen * ( 1.+ zadap  * EXP( -0.25 * enano(ji,jj,jk) ) )  & 
    158164                  &                   * trb(ji,jj,jk,jpnch) /( trb(ji,jj,jk,jpphy) * 12. + rtrn) 
    159                   ! 
     165 
     166                  ! Diatoms 
    160167                  zpislopeadd(ji,jj,jk) = (pislopen * zconctemp2 + pisloped * zconctemp) / ( trb(ji,jj,jk,jpdia) + rtrn )   & 
    161168                  &                   * trb(ji,jj,jk,jpdch) /( trb(ji,jj,jk,jpdia) * 12. + rtrn) 
     
    170177               IF( etot_ndcy(ji,jj,jk) > 1.E-3 ) THEN 
    171178                   ! Computation of production function for Carbon 
    172                    !  --------------------------------------------- 
     179                   ! Actual light levels are used here  
     180                   ! ---------------------------------------------- 
    173181                   zpislopen = zpislopeadn(ji,jj,jk) / ( ( r1_rday + bresp * r1_rday ) & 
    174182                   &            * zmxl_fac(ji,jj,jk) * rday + rtrn) 
     
    177185                   zprbio(ji,jj,jk) = zprbio(ji,jj,jk) * ( 1.- EXP( -zpislopen * enano(ji,jj,jk) )  ) 
    178186                   zprdia(ji,jj,jk) = zprdia(ji,jj,jk) * ( 1.- EXP( -zpisloped * ediat(ji,jj,jk) )  ) 
     187 
    179188                   !  Computation of production function for Chlorophyll 
    180                    !-------------------------------------------------- 
     189                   !  Mean light level in the mixed layer (when appropriate) 
     190                   !  is used here (acclimation is in general slower than  
     191                   !  the characteristic time scales of vertical mixing) 
     192                   !  ------------------------------------------------------ 
    181193                   zpislopen = zpislopeadn(ji,jj,jk) / ( zprmaxn(ji,jj,jk) * zmxl_chl(ji,jj,jk) * rday + rtrn ) 
    182194                   zpisloped = zpislopeadd(ji,jj,jk) / ( zprmaxd(ji,jj,jk) * zmxl_chl(ji,jj,jk) * rday + rtrn ) 
     
    188200      END DO 
    189201 
    190       !  Computation of a proxy of the N/C ratio 
    191       !  Steady state is assumed 
    192       !  --------------------------------------- 
     202      !  Computation of a proxy of the N/C quota from nutrient limitation  
     203      !  and light limitation. Steady state is assumed to allow the computation 
     204      !  ---------------------------------------------------------------------- 
    193205      DO jk = 1, jpkm1 
    194206         DO jj = 1, jpj 
     
    210222 
    211223               IF( etot_ndcy(ji,jj,jk) > 1.E-3 ) THEN 
     224 
    212225                   ! Si/C of diatoms 
    213226                   ! ------------------------ 
     
    215228                   ! Si/C is arbitrariliy increased for very high Si concentrations 
    216229                   ! to mimic the very high ratios observed in the Southern Ocean (zsilfac2) 
     230                   ! A parameterization derived from Flynn (2003) is used for the control 
     231                   ! when Si is not limiting which is similar to the parameterisation 
     232                   ! proposed by Gurney and Davidson (1999). 
    217233                   ! ----------------------------------------------------------------------- 
    218234                 zlim  = trb(ji,jj,jk,jpsil) / ( trb(ji,jj,jk,jpsil) + xksi1 ) 
     
    271287                  sizena(ji,jj,jk) = min(xsizern, max( sizena(ji,jj,jk), zsizetmp ) ) 
    272288 
    273                   !  Iron uptake rates of nanophytoplankton. Upregulation   
    274                   !  is parameterized at low iron concentrations. Typical  
    275                   !  formulation used in quota formulations. Uptake is downregulated 
    276                   !  when the quota is close to the maximum quota  
     289                  ! Iron uptake rates of nanophytoplankton. Upregulation is   
     290                  ! not parameterized at low iron concentrations as observations 
     291                  ! do not suggest it for accimated cells. Uptake is 
     292                  ! downregulated when the quota is close to the maximum quota 
    277293                  zratio = 1.0 - MIN(1.0,trb(ji,jj,jk,jpnfe) / ( trb(ji,jj,jk,jpphy) * fecnm + rtrn ) ) 
    278294                  zmax   = MAX( 0., MIN( 1.0, zratio**2/ (0.05**2+zratio**2) ) )  
     
    281297                  &          + xnanonh4(ji,jj,jk) ) * (1. - xnanofer(ji,jj,jk) ) )   & 
    282298                  &          * xnanofer(ji,jj,jk) * zmax * trb(ji,jj,jk,jpphy) * rfact2 
    283                   !  production terms of diatoms (C) 
     299                  ! production terms of diatoms (C) 
    284300                  zprorcad(ji,jj,jk) = zprdia(ji,jj,jk) * xlimdia(ji,jj,jk) * trb(ji,jj,jk,jpdia) * rfact2 
    285301 
     
    297313                  sizeda(ji,jj,jk) = min(xsizerd, max( sizeda(ji,jj,jk), zsizetmp ) ) 
    298314 
    299                   !  Iron uptake rates of nanophytoplankton. Upregulation   
    300                   !  is parameterized at low iron concentrations. Typical  
    301                   !  formulation used in quota formulations. Uptake is downregulated 
    302                   !  when the quota is close to the maximum quota  
     315                  ! Iron uptake rates of diatoms. Upregulation is   
     316                  ! not parameterized at low iron concentrations as observations 
     317                  ! do not suggest it for accimated cells. Uptake is 
     318                  ! downregulated when the quota is close to the maximum quota 
    303319                  zratio = 1.0 - MIN(1.0, trb(ji,jj,jk,jpdfe) / ( trb(ji,jj,jk,jpdia) * fecdm + rtrn ) ) 
    304320                  zmax   = MAX( 0., MIN( 1.0, zratio**2/ (0.05**2+zratio**2) ) )  
     
    323339                  zprod    = rday * zprorcan(ji,jj,jk) * zprchln(ji,jj,jk) * xlimphy(ji,jj,jk) 
    324340                  zprochln = chlcmin * 12. * zprorcan (ji,jj,jk) 
     341 
    325342                  ! The maximum reachable Chl quota is modulated by temperature 
    326343                  ! following Geider (1987) 
     
    328345                  zprochln = zprochln + (chlcnm_n-chlcmin) * 12. * zprod / & 
    329346                                        & (  zpislopeadn(ji,jj,jk) * znanotot +rtrn) 
    330                   !  production terms of diatoms ( chlorophyll ) 
     347 
     348                  ! production terms of diatoms ( chlorophyll ) 
    331349                  zdiattot = ediatm(ji,jj,jk) / ( zmxl_chl(ji,jj,jk) + rtrn ) 
    332350                  zprod    = rday * zprorcad(ji,jj,jk) * zprchld(ji,jj,jk) * xlimdia(ji,jj,jk) 
    333351                  zprochld = chlcmin * 12. * zprorcad(ji,jj,jk) 
     352 
    334353                  ! The maximum reachable Chl quota is modulated by temperature 
    335354                  ! following Geider (1987) 
     
    337356                  zprochld = zprochld + (chlcdm_n-chlcmin) * 12. * zprod / & 
    338357                                        & ( zpislopeadd(ji,jj,jk) * zdiattot +rtrn ) 
    339                   !   Update the arrays TRA which contain the Chla sources and sinks 
     358 
     359                  ! Update the arrays TRA which contain the Chla sources and sinks 
    340360                  tra(ji,jj,jk,jpnch) = tra(ji,jj,jk,jpnch) + zprochln * texcretn 
    341361                  tra(ji,jj,jk,jpdch) = tra(ji,jj,jk,jpdch) + zprochld * texcretd 
     
    377397        END DO 
    378398     END DO 
    379      ! 
     399 
    380400     ! Production and uptake of ligands by phytoplankton. This part is activated  
    381401     ! when ln_ligand is set to .true. in the namelist. Ligand uptake is small  
     
    403423 
    404424 
     425    ! Output of the diagnostics 
    405426    ! Total primary production per year 
    406427    IF( iom_use( "tintpp" ) .OR. ( ln_check_mass .AND. kt == nitend .AND. knt == nrdttrc )  )  & 
     
    423444              CALL iom_put( "PPNEWN"  , zw3d ) 
    424445              ! 
    425               zw3d(:,:,:) = zpronewd(:,:,:) * zfact * tmask(:,:,:)  ! new primary production by diatomes 
     446              zw3d(:,:,:) = zpronewd(:,:,:) * zfact * tmask(:,:,:)  ! new primary production by diatoms 
    426447              CALL iom_put( "PPNEWD"  , zw3d ) 
    427448          ENDIF 
     
    434455              CALL iom_put( "PFeN"  , zw3d ) 
    435456              ! 
    436               zw3d(:,:,:) = zprofed(:,:,:) * zfact * tmask(:,:,:)  ! biogenic iron production by  diatomes 
     457              zw3d(:,:,:) = zprofed(:,:,:) * zfact * tmask(:,:,:)  ! biogenic iron production by  diatoms 
    437458              CALL iom_put( "PFeD"  , zw3d ) 
    438459          ENDIF 
     
    546567      INTEGER ::   ios   ! Local integer 
    547568      ! 
     569      ! Namelist block 
    548570      NAMELIST/namp4zprod/ pislopen, pisloped, xadap, bresp, excretn, excretd,  & 
    549571         &                 chlcnm, chlcdm, chlcmin, fecnm, fecdm, grosip 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zrem.F90

    r12682 r13233  
    9292      ! Computation of the mean bacterial concentration 
    9393      ! this parameterization has been deduced from a model version 
    94       ! that was modeling explicitely bacteria 
    95       ! ------------------------------------------------------- 
     94      ! that was modeling explicitely bacteria. This is a very old param  
     95      ! that will be very soon updated based on results from a much more 
     96      ! recent version of PISCES with bacteria. 
     97      ! ---------------------------------------------------------------- 
    9698      DO jk = 1, jpkm1 
    9799         DO jj = 1, jpj 
     
    111113      END DO 
    112114 
    113       IF( ln_p4z ) THEN 
     115      IF( ln_p4z ) THEN ! Standard PISCES code 
    114116         DO jk = 1, jpkm1 
    115117            DO jj = 1, jpj 
     
    152154            END DO 
    153155         END DO 
    154       ELSE 
     156      ELSE ! PISCES-QUOTA 
    155157         DO jk = 1, jpkm1 
    156158            DO jj = 1, jpj 
     
    231233 
    232234               ! Bacterial uptake of iron. No iron is available in DOC. So 
    233                ! Bacteries are obliged to take up iron from the water. Some 
     235               ! Bacteria are obliged to take up iron from the water. Some 
    234236               ! studies (especially at Papa) have shown this uptake to be significant 
    235237               ! --------------------------------------------------------------------- 
     
    262264         DO jj = 1, jpj 
    263265            DO ji = 1, jpi 
    264                ! Remineralization rate of BSi depedant on T and saturation 
     266 
     267               ! Remineralization rate of BSi dependent on T and saturation 
    265268               ! The parameterization is taken from Ridgwell et al. (2002)  
    266269               ! --------------------------------------------------------- 
     
    269272               zsatur2  = ( 1. + tsn(ji,jj,jk,jp_tem) / 400.)**37 
    270273               znusil   = 0.225  * ( 1. + tsn(ji,jj,jk,jp_tem) / 15.) * zsatur + 0.775 * zsatur2 * zsatur**9.25 
     274 
     275               ! Two fractions of bSi are considered : a labile one and a more 
     276               ! refractory one based on the commonly observed two step  
     277               ! dissolution of bSi (initial rapid dissolution followed by  
     278               ! more slowly dissolution). 
    271279               ! Computation of the vertical evolution of the labile fraction 
    272280               ! of bSi. This is computed assuming steady state. 
     281               ! -------------------------------------------------------------- 
    273282               IF ( gdept_n(ji,jj,jk) > zdep ) THEN 
    274283                  zfacsib(ji,jj,jk) = zfacsib(ji,jj,jk-1) * EXP( -0.5 * ( xsiremlab - xsirem )  & 
     
    280289               zsiremin = ( xsiremlab * zfacsi(ji,jj,jk) + xsirem * ( 1. - zfacsi(ji,jj,jk) ) ) * xstep * znusil 
    281290               zosil    = zsiremin * trb(ji,jj,jk,jpgsi) 
     291 
    282292               ! Update of the TRA arrays 
    283293               tra(ji,jj,jk,jpgsi) = tra(ji,jj,jk,jpgsi) - zosil 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zsed.F90

    r13200 r13233  
    3535   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:  ) :: sdenit     !: Nitrate reduction in the sediments 
    3636   REAL(wp) :: r1_rday                  !: inverse of rday 
    37    LOGICAL, SAVE :: lk_sed 
     37   LOGICAL, SAVE :: lk_sed              !: Explicit sediment module 
    3838 
    3939   !!---------------------------------------------------------------------- 
     
    4848      !!                     ***  ROUTINE p4z_sed  *** 
    4949      !! 
    50       !! ** Purpose :   Compute loss of biogenic matter in the sediments. This 
     50      !! ** Purpose : Compute the loss of biogenic matter in the sediments. This 
    5151      !!              is by no way a real sediment model. The loss is simply  
    5252      !!              computed from metamodels. 
     
    5555      !!              N2 fixation is modeled using an implicit approach 
    5656      !! 
    57       !! ** Method  : - ??? 
     57      !! ** Method  : - Fluxes with the sediments are mainly modeled using 
     58      !!                statiscal metamodels. 
    5859      !!--------------------------------------------------------------------- 
    5960      ! 
     
    8182      IF( kt == nittrc000 .AND. knt == 1 )   THEN 
    8283          r1_rday  = 1. / rday 
     84          ! Configuration with an active two-way sediment module  
    8385          IF (ln_sediment .AND. ln_sed_2way) THEN 
    8486             lk_sed = .TRUE. 
     
    109111         !                                               
    110112         ALLOCATE( zironice(jpi,jpj) ) 
    111          !                                               
     113 
    112114         ! Compute the iron flux between sea ice and sea water 
     115         ! Simple parameterization assuming a fixed constant concentration in 
     116         ! sea-ice (icefeinput) 
     117         ! ------------------------------------------------------------------ 
    113118         DO jj = 1, jpj 
    114119            DO ji = 1, jpi 
     
    133138         !                                               
    134139         ALLOCATE( zsidep(jpi,jpj), zpdep(jpi,jpj,jpk), zirondep(jpi,jpj,jpk) ) 
     140 
    135141         ! Iron, P and Si deposition at the surface 
    136142         ! Iron flux at the surface due to dust deposition. Solubility can be  
    137143         ! be variable if ln_solub is set to true. In that case, solubility  
    138144         ! has to be provided in the specific input file (read in p4zsbc) 
     145         ! mfrac is the mean iron relative weight content of dust 
    139146         ! ------------------------------------------------------------------ 
    140147         IF( ln_solub ) THEN 
     
    143150            zirondep(:,:,1) = dustsolub  * dust(:,:) * mfrac * rfact2 / e3t_n(:,:,1) / 55.85 + 3.e-10 * r1_ryyss  
    144151         ENDIF 
     152 
    145153         ! Si and P flux at the surface due to dust deposition. The content  
    146154         ! and the solubility are hard coded 
     
    148156         zsidep(:,:)   = 8.8 * 0.075 * dust(:,:) * mfrac * rfact2 / e3t_n(:,:,1) / 28.1  
    149157         zpdep (:,:,1) = 0.1 * 0.021 * dust(:,:) * mfrac * rfact2 / e3t_n(:,:,1) / 31. / po4r  
     158 
    150159         ! Iron solubilization of particles in the water column 
    151160         ! dust in kg/m2/s ---> 1/55.85 to put in mol/Fe ;  wdust in m/d 
     
    159168         DO jk = 2, jpkm1 
    160169            zirondep(:,:,jk) = dust(:,:) * mfrac * zwdust * rfact2 * EXP( -gdept_n(:,:,jk) / (250. * wdust) ) 
    161 !            zpdep   (:,:,jk) = zirondep(:,:,jk) * 0.023 
    162170            zpdep   (:,:,jk) = zirondep(:,:,jk) * 0.38 / po4r 
    163171         END DO 
     172 
    164173         ! Solubilization of particles in the water column (Si, P, Fe) 
    165174         tra(:,:,1,jpsil) = tra(:,:,1,jpsil) + zsidep  (:,:) 
     
    197206            ENDDO 
    198207         ENDDO 
     208 
    199209         ! When prognostic ligands are activated, ligands are supplied  
    200210         ! to the ocean by rivers. We assume that the amount of ligands 
     
    262272         ! ------------------------------------------------------ 
    263273         IF( ln_ironsed ) THEN 
    264                             tra(:,:,:,jpfer) = tra(:,:,:,jpfer) + ironsed(:,:,:) * rfact2 
     274            tra(:,:,:,jpfer) = tra(:,:,:,jpfer) + ironsed(:,:,:) * rfact2 
    265275            ! 
    266276            IF( lk_iomput .AND. knt == nrdttrc .AND. iom_use( "Ironsed" ) )   & 
     
    434444                  xdiano3 = trb(ji,jj,jk,jpno3) / ( concnno3 + trb(ji,jj,jk,jpno3) ) * (1. - xdianh4) 
    435445                  zlim = ( 1.- xdiano3 - xdianh4 ) 
     446                  ! Nitrogen fixation is almost fully halted when the N  
     447                  ! limitation term (xdiano3+xdianh4) is > 0.9 
    436448                  IF( zlim <= 0.1 )   zlim = 0.01 
    437449                  zfact = zlim * rfact2 
     
    454466                  xdiano3 = trb(ji,jj,jk,jpno3) / ( concnno3 + trb(ji,jj,jk,jpno3) ) * (1. - xdianh4) 
    455467                  zlim = ( 1.- xdiano3 - xdianh4 ) 
     468 
     469                  ! Nitrogen fixation is almost fully halted when the N  
     470                  ! limitation term (xdiano3+xdianh4) is > 0.9 
    456471                  IF( zlim <= 0.1 )   zlim = 0.01 
    457472                  zfact = zlim * rfact2 
     
    474489               DO ji = 1, jpi 
    475490                  zfact = nitrpot(ji,jj,jk) * nitrfix 
     491                  ! 1/3 of the diazotrophs growth is supposed to be excreted 
     492                  ! as NH4. 1/3 as DOC and the rest is routed POC and GOC as  
     493                  ! a result of mortality by predation. Completely adhoc param  
    476494                  tra(ji,jj,jk,jpnh4) = tra(ji,jj,jk,jpnh4) + zfact / 3.0 
    477495                  tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) + rno3 * zfact / 3.0 
     
    481499                  tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) + zfact * 1.0 / 3.0 * 1.0 / 3.0 
    482500                  tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) + ( o2ut + o2nit ) * zfact * 2.0 / 3.0 + o2nit * zfact / 3.0 
     501                  ! Fe/c of diazotrophs is assumed to be 30umol Fe/mol C 
    483502                  tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) - 30E-6 * zfact * 1.0 / 3.0 
    484503                  tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + 30E-6 * zfact * 1.0 / 3.0 * 2.0 / 3.0 
     
    494513               DO ji = 1, jpi 
    495514                  zfact = nitrpot(ji,jj,jk) * nitrfix 
     515                  ! 1/3 of the diazotrophs growth is supposed to be excreted 
     516                  ! as NH4. 1/3 as DOC and the rest is routed POC and GOC as  
     517                  ! a result of mortality by predation. Completely adhoc param  
    496518                  tra(ji,jj,jk,jpnh4) = tra(ji,jj,jk,jpnh4) + zfact / 3.0 
    497519                  tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) + rno3 * zfact / 3.0 
     520                  ! N/P ratio of diazotrophs is supposed to be 46 
    498521                  tra(ji,jj,jk,jppo4) = tra(ji,jj,jk,jppo4) - 16.0 / 46.0 * zfact * ( 1.0 - 1.0 / 3.0 ) & 
    499522                  &                     * ztrpo4(ji,jj,jk) / (ztrpo4(ji,jj,jk) + ztrdop(ji,jj,jk) + rtrn) 
     
    510533                  tra(ji,jj,jk,jpgop) = tra(ji,jj,jk,jpgop) + 16.0 / 46.0 * zfact * 1.0 / 3.0 * 1.0 /3.0 
    511534                  tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) + ( o2ut + o2nit ) * zfact * 2.0 / 3.0 + o2nit * zfact / 3.0 
     535                  ! Fe/c of diazotrophs is assumed to be 30umol Fe/mol C 
    512536                  tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) - 30E-6 * zfact * 1.0 / 3.0  
    513537                  tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + 30E-6 * zfact * 1.0 / 3.0 * 2.0 / 3.0 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zsink.F90

    r12537 r13233  
    9595      END DO 
    9696 
    97       ! Sinking speed of the small particles is constant 
     97      ! Sinking speed of the small particles is always constant 
    9898      wsbio3(:,:,:) = wsbio 
    9999 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zsms.F90

    r12759 r13233  
    7474        IF( .NOT. ln_rsttr ) THEN 
    7575            CALL p4z_che            ! initialize the chemical constants 
    76             CALL ahini_for_at(hi)   !  set PH at kt=nit000 
     76            CALL ahini_for_at(hi)   ! set PH at kt=nit000 
    7777            t_oce_co2_flx_cum = 0._wp 
    7878        ELSE 
     
    8484      IF( ln_pisdmp .AND. MOD( kt - nn_dttrc, nn_pisdmp ) == 0 )   CALL p4z_dmp( kt )      ! Relaxation of some tracers 
    8585      ! 
    86       rfact = r2dttrc 
     86      rfact = r2dttrc  ! time step of PISCES 
    8787      ! 
    8888      IF( ( ln_top_euler .AND. kt == nittrc000 )  .OR. ( .NOT.ln_top_euler .AND. kt <= nittrc000 + nn_dttrc ) ) THEN 
    89          rfactr  = 1. / rfact 
    90          rfact2  = rfact / REAL( nrdttrc, wp ) 
    91          rfact2r = 1. / rfact2 
    92          xstep = rfact2 / rday         ! Time step duration for biology 
     89         rfactr  = 1. / rfact  ! inverse of the time step 
     90         rfact2  = rfact / REAL( nrdttrc, wp )  ! time step of the biological SMS 
     91         rfact2r = 1. / rfact2  ! Inverse of the biological time step 
     92         xstep = rfact2 / rday         ! Time step duration for biology relative to a day 
    9393         IF(lwp) WRITE(numout,*)  
    9494         IF(lwp) WRITE(numout,*) '    Passive Tracer  time step    rfact  = ', rfact, ' rdt = ', rdt 
     
    147147            tra(:,:,:,jn) = 0._wp 
    148148         END DO 
    149          ! 
     149         ! Euler-forward temporal scheme 
    150150         IF( ln_top_euler ) THEN 
    151151            DO jn = jp_pcs0, jp_pcs1 
     
    167167         ! 
    168168         CALL sed_model( kt )     !  Main program of Sediment model 
    169          ! 
     169         ! Eulor forward temporal scheme 
    170170         IF( ln_top_euler ) THEN 
    171171            DO jn = jp_pcs0, jp_pcs1 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p5zlim.F90

    r12759 r13233  
    5959 
    6060   !!*  Allometric variations of the quotas 
    61    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqnnmin    !: ??? 
    62    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqnnmax    !: ??? 
    63    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqpnmin    !: ??? 
    64    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqpnmax    !: ??? 
    65    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqnpmin    !: ??? 
    66    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqnpmax    !: ??? 
    67    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqppmin    !: ??? 
    68    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqppmax    !: ??? 
    69    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqndmin    !: ??? 
    70    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqndmax    !: ??? 
    71    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqpdmin    !: ??? 
    72    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqpdmax    !: ??? 
     61   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqnnmin    !: Minimum N quota of nanophyto 
     62   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqnnmax    !: Maximum N quota of nanophyto 
     63   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqpnmin    !: Minimum P quota of nanophyto 
     64   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqpnmax    !: Maximum P quota of picophyto 
     65   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqnpmin    !: Minimum N quota of picophyto 
     66   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqnpmax    !: Maximum N quota of picophyto 
     67   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqppmin    !: Minimum P quota of picophyto 
     68   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqppmax    !: Maximum P quota of picophyto 
     69   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqndmin    !: Minimum N quota of diatoms 
     70   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqndmax    !: Maximum N quota of diatoms 
     71   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqpdmin    !: Minimum P quota of diatoms 
     72   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:,:)  ::   xqpdmax    !: Maximum P quota of diatoms 
    7373 
    7474   !!* Phytoplankton nutrient limitation terms 
     
    521521      !! ** Purpose :   Initialization of nutrient limitation parameters 
    522522      !! 
    523       !! ** Method  :   Read the nampislim and nampisquota namelists and check 
     523      !! ** Method  :   Read the namp5zlim and nampisquota namelists and check 
    524524      !!      the parameters called at the first timestep (nittrc000) 
    525525      !! 
    526       !! ** input   :   Namelist nampislim 
     526      !! ** input   :   Namelist namp5zlim 
    527527      !! 
    528528      !!---------------------------------------------------------------------- 
     
    540540      !!---------------------------------------------------------------------- 
    541541      ! 
    542       REWIND( numnatp_ref )              ! Namelist nampislim in reference namelist : Pisces nutrient limitation parameters 
     542      REWIND( numnatp_ref )              ! Namelist namp5zlim in reference namelist : Pisces nutrient limitation parameters 
    543543      READ  ( numnatp_ref, namp5zlim, IOSTAT = ios, ERR = 901) 
    544 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampislim in reference namelist' ) 
    545       ! 
    546       REWIND( numnatp_cfg )              ! Namelist nampislim in configuration namelist : Pisces nutrient limitation parameters  
     544901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namp5zlim in reference namelist' ) 
     545      ! 
     546      REWIND( numnatp_cfg )              ! Namelist namp5zlim in configuration namelist : Pisces nutrient limitation parameters  
    547547      READ  ( numnatp_cfg, namp5zlim, IOSTAT = ios, ERR = 902 ) 
    548 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampislim in configuration namelist' ) 
     548902   IF( ios >  0 ) CALL ctl_nam ( ios , 'namp5zlim in configuration namelist' ) 
    549549      IF(lwm) WRITE ( numonp, namp5zlim ) 
    550550      ! 
     
    614614      ENDIF 
    615615      ! 
     616      ! Metabolic cost of nitrate and ammonium utilisation 
    616617      zpsino3  = 2.3 * rno3 
    617618      zpsinh4  = 1.8 * rno3 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p5zmeso.F90

    r12759 r13233  
    5252   REAL(wp), PUBLIC ::  grazflux     !: mesozoo flux feeding rate 
    5353   REAL(wp), PUBLIC ::  xfracmig     !: Fractional biomass of meso that performs DVM 
     54   REAL(wp), PUBLIC ::  xsigma2      !: Width of the predation window 
     55   REAL(wp), PUBLIC ::  xsigma2del   !: Maximum width of the predation window at low food density 
    5456   LOGICAL,  PUBLIC ::  bmetexc2     !: Use of excess carbon for respiration 
    5557   LOGICAL , PUBLIC ::  ln_dvm_meso  !: Boolean to activate DVM of mesozooplankton 
     
    189191               ! ---------------------------------------------------------- 
    190192               zsigma = 1.0 - zdenom**2/(0.05**2+zdenom**2) 
    191                zsigma = 0.5 + 1.0 * zsigma 
     193               zsigma = xsigma2 + xsigma2del * zsigma 
    192194               ! Nanophytoplankton and diatoms are the only preys considered 
    193195               ! to be close enough to have potential interference 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p5zmicro.F90

    r12537 r13233  
    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 
     
    161163               ! ---------------------------------------------------------- 
    162164               zsigma = 1.0 - zdenom**2/(0.05**2+zdenom**2) 
    163                zsigma = 0.5 + 1.0*zsigma 
     165               zsigma = xsigma + xsigmadel * zsigma 
    164166               zdiffpn = exp( -ABS(log(0.5 * sizep(ji,jj,jk) / (3.0 * sizen(ji,jj,jk) + rtrn )) )**2 / zsigma**2 ) 
    165167               zdiffdn = exp( -ABS(log(3.0 * sizen(ji,jj,jk) / (5.0 * sized(ji,jj,jk) + rtrn )) )**2 / zsigma**2) 
     
    179181               !   Microzooplankton regular grazing on the different preys 
    180182               !   ------------------------------------------------------- 
    181                zgraznc   = zgraze  * ztmp1  * zdenom 
     183               !   Nanophytoplankton 
     184               zgraznc   = zgraze  * ztmp1  * zdenom   
    182185               zgraznn   = zgraznc * trb(ji,jj,jk,jpnph) / (trb(ji,jj,jk,jpphy) + rtrn) 
    183186               zgraznp   = zgraznc * trb(ji,jj,jk,jppph) / (trb(ji,jj,jk,jpphy) + rtrn) 
    184187               zgraznf   = zgraznc * trb(ji,jj,jk,jpnfe) / (trb(ji,jj,jk,jpphy) + rtrn) 
     188 
     189               ! Picophytoplankton 
    185190               zgrazpc   = zgraze  * ztmp2  * zdenom 
    186191               zgrazpn   = zgrazpc * trb(ji,jj,jk,jpnpi) / (trb(ji,jj,jk,jppic) + rtrn) 
    187192               zgrazpp   = zgrazpc * trb(ji,jj,jk,jpppi) / (trb(ji,jj,jk,jppic) + rtrn) 
    188193               zgrazpf   = zgrazpc * trb(ji,jj,jk,jppfe) / (trb(ji,jj,jk,jppic) + rtrn) 
     194               ! Microzooplankton 
    189195               zgrazz    = zgraze  * ztmp5   * zdenom 
     196 
     197               ! small POC 
    190198               zgrazpoc  = zgraze  * ztmp3   * zdenom 
    191199               zgrazpon  = zgrazpoc * trb(ji,jj,jk,jppon) / ( trb(ji,jj,jk,jppoc) + rtrn ) 
    192200               zgrazpop  = zgrazpoc * trb(ji,jj,jk,jppop) / ( trb(ji,jj,jk,jppoc) + rtrn ) 
    193201               zgrazpof  = zgrazpoc* trb(ji,jj,jk,jpsfe) / (trb(ji,jj,jk,jppoc) + rtrn) 
     202 
     203               ! Diatoms 
    194204               zgrazdc   = zgraze  * ztmp4  * zdenom 
    195205               zgrazdn   = zgrazdc * trb(ji,jj,jk,jpndi) / (trb(ji,jj,jk,jpdia) + rtrn) 
     
    197207               zgrazdf   = zgrazdc * trb(ji,jj,jk,jpdfe) / (trb(ji,jj,jk,jpdia) + rtrn) 
    198208               ! 
     209               ! Total ingestion rates in C, P, Fe, N 
    199210               zgraztotc = zgraznc + zgrazpoc + zgrazdc + zgrazz + zgrazpc 
    200211               zgraztotn = zgraznn + zgrazpn + zgrazpon + zgrazdn + zgrazz * no3rat3 
     
    221232               zepshert  = MIN( 1., zgrasratn/ no3rat3, zgrasratp/ po4rat3, zgrasratf / ferat3) 
    222233               zbeta     = MAX( 0., (epsher - epshermin) ) 
     234               ! Food density deprivation of GGE 
    223235               zepsherf  = epshermin + zbeta / ( 1.0 + 0.04E6 * 12. * zfood * zbeta ) 
     236               ! Food quality deprivation of GGE 
    224237               zepsherq  = 0.5 + (1.0 - 0.5) * zepshert * ( 1.0 + 1.0 ) / ( zepshert + 1.0 ) 
     238               ! Actual GGE 
    225239               zepsherv  = zepsherf * zepshert * zepsherq 
    226240 
    227241               ! Respiration of microzooplankton 
    228242               ! Excess carbon in the food is used preferentially 
     243               ! when activated by zmetexcess 
    229244               ! ------------------------------------------------ 
    230245               zexcess  = zgraztotc * zepsherf * (1.0 - zepshert) * zmetexcess 
     
    380395         &                xprefp, xprefd, xprefz, xthreshdia, xthreshphy, & 
    381396         &                xthreshpic, xthreshpoc, xthreshzoo, xthresh, xkgraz, & 
    382          &                epsher, epshermin, ssigma, srespir, unassc, unassn, unassp 
     397         &                epsher, epshermin, ssigma, srespir, unassc, unassn, unassp,   & 
     398         &                xsigma, xsigmadel    
    383399      !!---------------------------------------------------------------------- 
    384400      ! 
     
    420436         WRITE(numout,*) '    half sturation constant for grazing 1           xkgraz      =', xkgraz 
    421437         WRITE(numout,*) '    Use of excess carbon for respiration            bmetexc     =', bmetexc 
     438         WRITE(numout,*) '      Width of the grazing window                     xsigma      =', xsigma 
     439         WRITE(numout,*) '      Maximum additional width of the grazing window  xsigmadel   =', xsigmadel 
    422440      ENDIF 
    423441      ! 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p5zmort.F90

    r12677 r13233  
    5353      !!--------------------------------------------------------------------- 
    5454 
    55       CALL p5z_nano            ! nanophytoplankton 
    56       CALL p5z_pico            ! picophytoplankton 
    57       CALL p5z_diat            ! diatoms 
     55      CALL p5z_mort_nano            ! nanophytoplankton 
     56      CALL p5z_mort_pico            ! picophytoplankton 
     57      CALL p5z_mort_diat            ! diatoms 
    5858 
    5959   END SUBROUTINE p5z_mort 
    6060 
    6161 
    62    SUBROUTINE p5z_nano 
    63       !!--------------------------------------------------------------------- 
    64       !!                     ***  ROUTINE p5z_nano  *** 
     62   SUBROUTINE p5z_mort_nano 
     63      !!--------------------------------------------------------------------- 
     64      !!                     ***  ROUTINE p5z_mort_nano  *** 
    6565      !! 
    6666      !! ** Purpose :   Compute the mortality terms for nanophytoplankton 
    6767      !! 
    68       !! ** Method  : - ??? 
     68      !! ** Method  : - Both quadratic and simili linear mortality terms 
    6969      !!--------------------------------------------------------------------- 
    7070      INTEGER  :: ji, jj, jk 
     
    7575      !!--------------------------------------------------------------------- 
    7676      ! 
    77       IF( ln_timing )   CALL timing_start('p5z_nano') 
     77      IF( ln_timing )   CALL timing_start('p5z_mort_nano') 
    7878      ! 
    7979      prodcal(:,:,:) = 0.  !: calcite production variable set to zero 
     
    8282            DO ji = 1, jpi 
    8383               zcompaph = MAX( ( trb(ji,jj,jk,jpphy) - 1e-9 ), 0.e0 ) 
     84 
    8485               ! Quadratic mortality of nano due to aggregation during 
    8586               ! blooms (Doney et al. 1996) 
     
    127128       ENDIF 
    128129      ! 
    129       IF( ln_timing )   CALL timing_stop('p5z_nano') 
    130       ! 
    131    END SUBROUTINE p5z_nano 
    132  
    133  
    134    SUBROUTINE p5z_pico 
    135       !!--------------------------------------------------------------------- 
    136       !!                     ***  ROUTINE p5z_pico  *** 
     130      IF( ln_timing )   CALL timing_stop('p5z_mort_nano') 
     131      ! 
     132   END SUBROUTINE p5z_mort_nano 
     133 
     134 
     135   SUBROUTINE p5z_mort_pico 
     136      !!--------------------------------------------------------------------- 
     137      !!                     ***  ROUTINE p5z_mort_pico  *** 
    137138      !! 
    138139      !! ** Purpose :   Compute the mortality terms for picophytoplankton 
    139140      !! 
    140       !! ** Method  : - ??? 
     141      !! ** Method  : - Both quadratic and semilininear terms are used 
    141142      !!--------------------------------------------------------------------- 
    142143      INTEGER  :: ji, jj, jk 
     
    147148      !!--------------------------------------------------------------------- 
    148149      ! 
    149       IF( ln_timing )   CALL timing_start('p5z_pico') 
     150      IF( ln_timing )   CALL timing_start('p5z_mort_pico') 
    150151      ! 
    151152      DO jk = 1, jpkm1 
     
    191192       ENDIF 
    192193      ! 
    193       IF( ln_timing )   CALL timing_stop('p5z_pico') 
    194       ! 
    195    END SUBROUTINE p5z_pico 
    196  
    197  
    198    SUBROUTINE p5z_diat 
    199       !!--------------------------------------------------------------------- 
    200       !!                     ***  ROUTINE p5z_diat  *** 
     194      IF( ln_timing )   CALL timing_stop('p5z_mort_pico') 
     195      ! 
     196   END SUBROUTINE p5z_mort_pico 
     197 
     198 
     199   SUBROUTINE p5z_mort_diat 
     200      !!--------------------------------------------------------------------- 
     201      !!                     ***  ROUTINE p5z_mort_diat  *** 
    201202      !! 
    202203      !! ** Purpose :   Compute the mortality terms for diatoms 
     
    211212      !!--------------------------------------------------------------------- 
    212213      ! 
    213       IF( ln_timing )   CALL timing_start('p5z_diat') 
     214      IF( ln_timing )   CALL timing_start('p5z_mort_diat') 
    214215      ! 
    215216 
     
    271272      ENDIF 
    272273      ! 
    273       IF( ln_timing )   CALL timing_stop('p5z_diat') 
    274       ! 
    275    END SUBROUTINE p5z_diat 
     274      IF( ln_timing )   CALL timing_stop('p5z_mort_diat') 
     275      ! 
     276   END SUBROUTINE p5z_mort_diat 
    276277 
    277278 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p5zprod.F90

    r12537 r13233  
    22   !!====================================================================== 
    33   !!                         ***  MODULE p5zprod  *** 
    4    !! TOP :  Growth Rate of the two phytoplanktons groups  
     4   !! TOP :  Growth Rate of the three phytoplanktons groups  
     5   !!        PISCES-QUOTA version of the module 
    56   !!====================================================================== 
    67   !! History :   1.0  !  2004     (O. Aumont) Original code 
     
    2930 
    3031   !! * Shared module variables 
    31    REAL(wp), PUBLIC ::  pislopen        !: 
    32    REAL(wp), PUBLIC ::  pislopep        !: 
    33    REAL(wp), PUBLIC ::  pisloped        !: 
    34    REAL(wp), PUBLIC ::  xadap           !: 
    35    REAL(wp), PUBLIC ::  excretn         !: 
    36    REAL(wp), PUBLIC ::  excretp         !: 
    37    REAL(wp), PUBLIC ::  excretd         !: 
    38    REAL(wp), PUBLIC ::  bresp           !: 
    39    REAL(wp), PUBLIC ::  thetanpm        !: 
    40    REAL(wp), PUBLIC ::  thetannm        !: 
    41    REAL(wp), PUBLIC ::  thetandm        !: 
    42    REAL(wp), PUBLIC ::  chlcmin         !: 
    43    REAL(wp), PUBLIC ::  grosip          !: 
    44  
    45    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   zdaylen 
     32   REAL(wp), PUBLIC ::  pislopen        !: P-I slope of nanophytoplankton 
     33   REAL(wp), PUBLIC ::  pislopep        !: P-I slope of picophytoplankton 
     34   REAL(wp), PUBLIC ::  pisloped        !: P-I slope of diatoms 
     35   REAL(wp), PUBLIC ::  xadap           !: Adaptation factor to low light 
     36   REAL(wp), PUBLIC ::  excretn         !: Excretion ratio of nanophyto 
     37   REAL(wp), PUBLIC ::  excretp         !: Excretion ratio of picophyto 
     38   REAL(wp), PUBLIC ::  excretd         !: Excretion ratio of diatoms 
     39   REAL(wp), PUBLIC ::  bresp           !: Basal respiration rate 
     40   REAL(wp), PUBLIC ::  thetanpm        !: Maximum Chl/N ratio of picophyto 
     41   REAL(wp), PUBLIC ::  thetannm        !: Maximum Chl/N ratio of nanophyto 
     42   REAL(wp), PUBLIC ::  thetandm        !: Maximum Chl/N ratio of diatoms 
     43   REAL(wp), PUBLIC ::  chlcmin         !: Minimum Chl/C ratio of phytoplankton 
     44   REAL(wp), PUBLIC ::  grosip          !: Mean Si/C ratio of diatoms 
     45 
     46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   zdaylen ! day length 
    4647    
    4748   REAL(wp) :: r1_rday                !: 1 / rday 
    48    REAL(wp) :: texcretn               !: 1 - excret  
     49   REAL(wp) :: texcretn               !: 1 - excretn  
    4950   REAL(wp) :: texcretp               !: 1 - excretp  
    50    REAL(wp) :: texcretd               !: 1 - excret2         
     51   REAL(wp) :: texcretd               !: 1 - excretd         
    5152 
    5253   !!---------------------------------------------------------------------- 
     
    6364      !! ** Purpose :   Compute the phytoplankton production depending on 
    6465      !!              light, temperature and nutrient availability 
    65       !! 
    66       !! ** Method  : - ??? 
     66      !!              Computes also the uptake of nutrients. PISCES-quota 
     67      !!              relies on a full quota formalism 
    6768      !!--------------------------------------------------------------------- 
    6869      ! 
     
    99100      ! 
    100101      IF( ln_timing )   CALL timing_start('p5z_prod') 
    101       ! 
     102 
     103      ! Initialize the local arrays 
    102104      zprorcan(:,:,:) = 0._wp ; zprorcap(:,:,:) = 0._wp ; zprorcad(:,:,:) = 0._wp 
    103105      zprofed (:,:,:) = 0._wp ; zprofep (:,:,:) = 0._wp ; zprofen (:,:,:) = 0._wp 
     
    110112      zrespn  (:,:,:) = 0._wp ; zrespp  (:,:,:) = 0._wp ; zrespd  (:,:,:) = 0._wp  
    111113 
    112       ! Computation of the optimal production 
     114      ! Computation of the optimal production rates and nutrient uptake 
     115      ! rates. Based on a Q10 description of the thermal dependency. 
    113116      zprnut (:,:,:) = 0.6_wp * (1.0 + zpsino3 * qnnmax ) * r1_rday * tgfunc(:,:,:) 
    114117      zprnutp(:,:,:) =  0.6_wp * (1. + zpsino3 * qnpmax ) * r1_rday * tgfunc3(:,:,:) 
     
    118121 
    119122      ! compute the day length depending on latitude and the day 
     123      ! Astronomical parameterization taken from HAMOCC3 
    120124      zrum = REAL( nday_year - 80, wp ) / REAL( nyear_len(1), wp ) 
    121125      zcodel = ASIN(  SIN( zrum * rpi * 2._wp ) * SIN( rad * 23.5_wp )  ) 
     
    131135      END DO 
    132136 
    133          ! Impact of the day duration on phytoplankton growth 
     137      ! Impact of the day duration and light intermittency on phytoplankton growth 
     138      ! Intermittency is supposed to have a similar effect on production as  
     139      ! day length (Shatwell et al., 2012). The correcting factor is zmxl_fac.  
     140      ! zmxl_chl is the fractional day length and is used to compute the mean 
     141      ! PAR during daytime. The effect of mixing is computed using the  
     142      ! absolute light level definition of the euphotic zone 
     143      ! -------------------------------------------------------------------------  
    134144      DO jk = 1, jpkm1 
    135145         DO jj = 1 ,jpj 
     
    154164      ! Maximum light intensity 
    155165      zdaylen(:,:) = MAX(1., zstrn(:,:)) / 24. 
    156       WHERE( zstrn(:,:) < 1.e0 ) zstrn(:,:) = 24. 
    157  
     166 
     167      ! Computation of the P-I slope for nanos, picos and diatoms 
     168      ! The formulation proposed by Geider et al. (1997) has been used. 
    158169      DO jk = 1, jpkm1 
    159170         DO jj = 1, jpj 
    160171            DO ji = 1, jpi 
    161172               IF( etot_ndcy(ji,jj,jk) > 1.E-3 ) THEN 
    162                   ! Computation of the P-I slope for nanos and diatoms 
    163173                  ztn         = MAX( 0., tsn(ji,jj,jk,jp_tem) - 15. ) 
    164174                  zadap       = xadap * ztn / ( 2.+ ztn ) 
    165                   ! 
     175                  ! Nanophytoplankton 
    166176                  zpislopeadn(ji,jj,jk) = pislopen * trb(ji,jj,jk,jpnch)    & 
    167177                  &                       /( trb(ji,jj,jk,jpphy) * 12. + rtrn) 
     178 
     179                  ! Picophytoplankton 
    168180                  zpislopeadp(ji,jj,jk) = pislopep * ( 1. + zadap * EXP( -0.25 * epico(ji,jj,jk) ) )   & 
    169181                  &                       * trb(ji,jj,jk,jppch) /( trb(ji,jj,jk,jppic) * 12. + rtrn) 
     182 
     183                  ! Diatoms 
    170184                  zpislopeadd(ji,jj,jk) = pisloped * trb(ji,jj,jk,jpdch)    & 
    171185                     &                    /( trb(ji,jj,jk,jpdia) * 12. + rtrn) 
     
    176190 
    177191                  ! Computation of production function for Carbon 
     192                  ! Actual light levels are used here  
    178193                  !  --------------------------------------------- 
    179194                  zprbio(ji,jj,jk) = zprbio(ji,jj,jk) * ( 1.- EXP( -zpislopen * enano(ji,jj,jk) / zmxl_chl(ji,jj,jk) )  ) 
     
    181196                  zprdia(ji,jj,jk) = zprdia(ji,jj,jk) * ( 1.- EXP( -zpisloped * ediat(ji,jj,jk) / zmxl_chl(ji,jj,jk))  ) 
    182197 
    183                   ! Computation of production function for Chlorophyll 
    184                   !  ------------------------------------------------- 
     198                  !  Computation of production function for Chlorophyll 
     199                  !  Mean light level in the mixed layer (when appropriate) 
     200                  !  is used here (acclimation is in general slower than  
     201                  !  the characteristic time scales of vertical mixing) 
     202                  !  ------------------------------------------------------ 
    185203                  zpislopen = zpislopen * zmxl_fac(ji,jj,jk) / ( zmxl_chl(ji,jj,jk) + rtrn ) 
    186204                  zpisloped = zpisloped * zmxl_fac(ji,jj,jk) / ( zmxl_chl(ji,jj,jk) + rtrn ) 
     
    199217 
    200218               IF( etot_ndcy(ji,jj,jk) > 1.E-3 ) THEN 
    201                   !    Si/C of diatoms 
    202                   !    ------------------------ 
    203                   !    Si/C increases with iron stress and silicate availability 
    204                   !    Si/C is arbitrariliy increased for very high Si concentrations 
    205                   !    to mimic the very high ratios observed in the Southern Ocean (silpot2) 
     219                  ! Si/C of diatoms 
     220                  ! ------------------------ 
     221                  ! Si/C increases with iron stress and silicate availability (zsilfac) 
     222                  ! Si/C is arbitrariliy increased for very high Si concentrations 
     223                  ! to mimic the very high ratios observed in the Southern Ocean (zsilfac2) 
     224                  ! A parameterization derived from Flynn (2003) is used for the control 
     225                  ! when Si is not limiting which is similar to the parameterisation 
     226                  ! proposed by Gurney and Davidson (1999). 
     227                  ! ----------------------------------------------------------------------- 
    206228                  zlim  = trb(ji,jj,jk,jpsil) / ( trb(ji,jj,jk,jpsil) + xksi1 ) 
    207229                  zsilim = MIN( zprdia(ji,jj,jk) / ( zprmaxd(ji,jj,jk) + rtrn ), xlimsi(ji,jj,jk) ) 
     
    225247      END DO 
    226248 
    227       !  Sea-ice effect on production                                                                                
     249      !  Sea-ice effect on production 
     250      ! No production is assumed below sea ice 
     251      ! --------------------------------------  
    228252      DO jk = 1, jpkm1 
    229253         DO jj = 1, jpj 
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/trcini_pisces.F90

    r12537 r13233  
    7474      USE p4zpoc          !  Remineralization of organic particles 
    7575      USE p4zligand       !  Remineralization of organic ligands 
    76       USE p5zlim          !  Co-limitations of differents nutrients 
    77       USE p5zprod         !  Growth rate of the 2 phyto groups 
    78       USE p5zmicro        !  Sources and sinks of microzooplankton 
    79       USE p5zmeso         !  Sources and sinks of mesozooplankton 
    80       USE p5zmort         !  Mortality terms for phytoplankton 
     76      USE p5zlim          !  Co-limitations of differents nutrients (QUOTA) 
     77      USE p5zprod         !  Growth rate of the 3 phyto groups (QUOTA) 
     78      USE p5zmicro        !  Sources and sinks of microzooplankton (QUOTA) 
     79      USE p5zmeso         !  Sources and sinks of mesozooplankton (QUOTA) 
     80      USE p5zmort         !  Mortality terms for phytoplankton (QUOTA) 
    8181      ! 
    8282      REAL(wp), SAVE ::   sco2   =  2.312e-3_wp 
     
    253253 
    254254 
     255      ! Initialization of the different PISCES modules 
     256      ! Mainly corresponds to the namelist use 
     257      ! ---------------------------------------------- 
    255258      CALL p4z_sink_init         !  vertical flux of particulate organic matter 
    256259      CALL p4z_opt_init          !  Optic: PAR in the water column 
     
    271274         & CALL p4z_ligand_init  !  remineralisation of organic ligands 
    272275 
    273       IF( ln_p4z ) THEN 
     276      IF( ln_p4z ) THEN ! PISCES-std 
    274277         CALL p4z_mort_init      !  phytoplankton mortality  
    275278         CALL p4z_micro_init     !  microzooplankton 
    276279         CALL p4z_meso_init      !  mesozooplankton 
    277       ELSE 
     280      ELSE ! PISCES-QUOTA 
    278281         CALL p5z_mort_init      !  phytoplankton mortality  
    279282         CALL p5z_micro_init     !  microzooplankton 
Note: See TracChangeset for help on using the changeset viewer.