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 12537 for NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zprod.F90 – NEMO

Ignore:
Timestamp:
2020-03-11T16:02:54+01:00 (4 years ago)
Author:
aumont
Message:

Comments in routines have been revised and significantly augmented

File:
1 edited

Legend:

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

    r12496 r12537  
    22   !!====================================================================== 
    33   !!                         ***  MODULE p4zprod  *** 
    4    !! TOP :  Growth Rate of the two phytoplanktons groups  
     4   !! TOP :  Growth Rate of the two phytoplankton groups of PISCES  
    55   !!====================================================================== 
    66   !! History :   1.0  !  2004     (O. Aumont) Original code 
     
    2424   PUBLIC   p4z_prod         ! called in p4zbio.F90 
    2525   PUBLIC   p4z_prod_init    ! called in trcsms_pisces.F90 
    26    PUBLIC   p4z_prod_alloc 
     26   PUBLIC   p4z_prod_alloc   ! called in trcini_pisces.F90 
    2727 
    2828   REAL(wp), PUBLIC ::   pislopen     !: 
     
    4040 
    4141   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   quotan   !: proxy of N quota in Nanophyto 
    42    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   quotad   !: proxy of N quota in diatomee 
     42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   quotad   !: proxy of N quota in diatoms 
    4343    
    4444   REAL(wp) ::   r1_rday    ! 1 / rday 
     
    5757      !!                     ***  ROUTINE p4z_prod  *** 
    5858      !! 
    59       !! ** Purpose :   Compute the phytoplankton production depending on 
    60       !!              light, temperature and nutrient availability 
    61       !! 
    62       !! ** Method  : - ??? 
     59      !! ** Purpose :   Computes phytoplankton production depending on 
     60      !!                light, temperature and nutrient availability 
     61      !!                Computes also the uptake of Iron and Si as well  
     62      !!                as the chlorophyll content of the cells 
    6363      !!--------------------------------------------------------------------- 
    6464      INTEGER, INTENT(in) ::   kt, knt   ! 
     
    9595      zmxl_fac(:,:,:) = 0._wp ; zmxl_chl(:,:,:) = 0._wp  
    9696 
    97       ! Computation of the optimal production 
     97      ! Computation of the maximimum production 
     98      ! Parameters are taken from Bissinger et al. (2008) 
    9899      zprmaxn(:,:,:) = 0.8_wp * r1_rday * tgfunc(:,:,:) 
    99100      zprmaxd(:,:,:) = zprmaxn(:,:,:) 
     
    114115 
    115116      ! Impact of the day duration and light intermittency on phytoplankton growth 
     117      ! Intermittency is supposed to have a similar effect on production as  
     118      ! day length. The correcting factor is zmxl_fac. zmxl_chl is the fractional 
     119      ! day length and is used to compute the mean PAR during daytime. 
     120      ! Formulation for the impact of day length on PP is from Thompson (1999) 
     121      ! -------------------------------------------------------------------------  
    116122      DO jk = 1, jpkm1 
    117123         DO jj = 1 ,jpj 
     
    132138      zprdia(:,:,:) = zprmaxd(:,:,:) * zmxl_fac(:,:,:) 
    133139 
    134       ! Maximum light intensity 
    135140      WHERE( zstrn(:,:) < 1.e0 ) zstrn(:,:) = 24. 
    136141 
    137142      ! Computation of the P-I slope for nanos and diatoms 
     143      ! The formulation proposed by Geider et al. (1997) has been modified  
     144      ! to exclude the effect of nutrient limitation and temperature in the PI 
     145      ! curve following Vichi et al. (2007) 
     146      ! ----------------------------------------------------------------------- 
    138147      DO jk = 1, jpkm1 
    139148         DO jj = 1, jpj 
     
    145154                  zconctemp2  = trb(ji,jj,jk,jpdia) - zconctemp 
    146155                  ! 
     156                  ! The initial slope of the PI curve can be increased for nano 
     157                  ! to account for photadaptation, for instance in the DCM 
    147158                  zpislopeadn(ji,jj,jk) = pislopen * ( 1.+ zadap  * EXP( -0.25 * enano(ji,jj,jk) ) )  & 
    148159                  &                   * trb(ji,jj,jk,jpnch) /( trb(ji,jj,jk,jpphy) * 12. + rtrn) 
     
    179190 
    180191      !  Computation of a proxy of the N/C ratio 
     192      !  Steady state is assumed 
    181193      !  --------------------------------------- 
    182194      DO jk = 1, jpkm1 
     
    199211 
    200212                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) 
     213                   ! Si/C of diatoms 
     214                   ! ------------------------ 
     215                   ! Si/C increases with iron stress and silicate availability (zsilfac) 
     216                   ! Si/C is arbitrariliy increased for very high Si concentrations 
     217                   ! to mimic the very high ratios observed in the Southern Ocean (zsilfac2) 
     218                   ! ----------------------------------------------------------------------- 
    206219                  zlim  = trb(ji,jj,jk,jpsil) / ( trb(ji,jj,jk,jpsil) + xksi1 ) 
    207220                  zsilim = MIN( zprdia(ji,jj,jk) / ( zprmaxd(ji,jj,jk) + rtrn ), xlimsi(ji,jj,jk) ) 
     
    219232      END DO 
    220233 
    221       !  Mixed-layer effect on production  
    222       !  Sea-ice effect on production 
    223  
     234      ! Sea-ice effect on production 
     235      ! No production is assumed below sea ice 
     236      ! --------------------------------------  
    224237      DO jk = 1, jpkm1 
    225238         DO jj = 1, jpj 
     
    231244      END DO 
    232245 
    233       ! Computation of the various production terms  
     246      ! Computation of the various production  and nutrient uptake terms 
     247      ! --------------------------------------------------------------- 
    234248      DO jk = 1, jpkm1 
    235249         DO jj = 1, jpj 
    236250            DO ji = 1, jpi 
    237251               IF( etot_ndcy(ji,jj,jk) > 1.E-3 ) THEN 
    238                   !  production terms for nanophyto. (C) 
     252                  !  production term of nanophyto. (C) 
    239253                  zprorcan(ji,jj,jk) = zprbio(ji,jj,jk)  * xlimphy(ji,jj,jk) * trb(ji,jj,jk,jpphy) * rfact2 
     254 
     255                  !  New production (uptake of NO3) 
    240256                  zpronewn(ji,jj,jk)  = zprorcan(ji,jj,jk)* xnanono3(ji,jj,jk) / ( xnanono3(ji,jj,jk) + xnanonh4(ji,jj,jk) + rtrn ) 
    241257                  ! 
    242258                  zratio = trb(ji,jj,jk,jpnfe) / ( trb(ji,jj,jk,jpphy) * fecnm + rtrn ) 
     259 
     260                  !  Iron uptake rates of nanophytoplankton. Upregulation   
     261                  !  is parameterized at low iron concentrations. Typical  
     262                  !  formulation used in quota formulations. Uptake is downregulated 
     263                  !  when the quota is close to the maximum quota  
    243264                  zmax   = MAX( 0., ( 1. - zratio ) / ABS( 1.05 - zratio ) )  
    244265                  zprofen(ji,jj,jk) = fecnm * zprmaxn(ji,jj,jk) * ( 1.0 - fr_i(ji,jj) )  & 
     
    246267                  &             * biron(ji,jj,jk) / ( biron(ji,jj,jk) + concnfe(ji,jj,jk) )  & 
    247268                  &             * zmax * trb(ji,jj,jk,jpphy) * rfact2 
    248                   !  production terms for diatoms (C) 
     269                  !  production terms of diatoms (C) 
    249270                  zprorcad(ji,jj,jk) = zprdia(ji,jj,jk) * xlimdia(ji,jj,jk) * trb(ji,jj,jk,jpdia) * rfact2 
     271 
     272                  ! New production (uptake of NO3) 
    250273                  zpronewd(ji,jj,jk) = zprorcad(ji,jj,jk) * xdiatno3(ji,jj,jk) / ( xdiatno3(ji,jj,jk) + xdiatnh4(ji,jj,jk) + rtrn ) 
    251                   ! 
     274 
     275                  !  Iron uptake rates of nanophytoplankton. Upregulation   
     276                  !  is parameterized at low iron concentrations. Typical  
     277                  !  formulation used in quota formulations. Uptake is downregulated 
     278                  !  when the quota is close to the maximum quota  
    252279                  zratio = trb(ji,jj,jk,jpdfe) / ( trb(ji,jj,jk,jpdia) * fecdm + rtrn ) 
    253280                  zmax   = MAX( 0., ( 1. - zratio ) / ABS( 1.05 - zratio ) )  
     
    262289 
    263290      ! Computation of the chlorophyll production terms 
     291      ! The parameterization is taken from Geider et al. (1997) 
     292      ! ------------------------------------------------------- 
    264293      DO jk = 1, jpkm1 
    265294         DO jj = 1, jpj 
    266295            DO ji = 1, jpi 
    267296               IF( etot_ndcy(ji,jj,jk) > 1.E-3 ) THEN 
    268                   !  production terms for nanophyto. ( chlorophyll ) 
     297                  !  production term for nanophyto. ( chlorophyll ) 
    269298                  znanotot = enanom(ji,jj,jk) / ( zmxl_chl(ji,jj,jk) + rtrn ) 
    270299                  zprod    = rday * zprorcan(ji,jj,jk) * zprchln(ji,jj,jk) * xlimphy(ji,jj,jk) 
    271300                  zprochln = chlcmin * 12. * zprorcan (ji,jj,jk) 
     301                  ! The maximum reachable Chl quota is modulated by temperature 
     302                  ! following Geider (1987) 
    272303                  chlcnm_n   = MIN ( chlcnm, ( chlcnm / (1. - 1.14 / 43.4 *tsn(ji,jj,jk,jp_tem))) * (1. - 1.14 / 43.4 * 20.)) 
    273304                  zprochln = zprochln + (chlcnm_n-chlcmin) * 12. * zprod / & 
    274305                                        & (  zpislopeadn(ji,jj,jk) * znanotot +rtrn) 
    275                   !  production terms for diatoms ( chlorophyll ) 
     306                  !  production terms of diatoms ( chlorophyll ) 
    276307                  zdiattot = ediatm(ji,jj,jk) / ( zmxl_chl(ji,jj,jk) + rtrn ) 
    277308                  zprod    = rday * zprorcad(ji,jj,jk) * zprchld(ji,jj,jk) * xlimdia(ji,jj,jk) 
    278309                  zprochld = chlcmin * 12. * zprorcad(ji,jj,jk) 
     310                  ! The maximum reachable Chl quota is modulated by temperature 
     311                  ! following Geider (1987) 
    279312                  chlcdm_n   = MIN ( chlcdm, ( chlcdm / (1. - 1.14 / 43.4 * tsn(ji,jj,jk,jp_tem))) * (1. - 1.14 / 43.4 * 20.)) 
    280313                  zprochld = zprochld + (chlcdm_n-chlcmin) * 12. * zprod / & 
     
    319352     END DO 
    320353     ! 
     354     ! Production and uptake of ligands by phytoplankton. This part is activated  
     355     ! when ln_ligand is set to .true. in the namelist. Ligand uptake is small  
     356     ! and based on the FeL model by Morel et al. (2008) and on the study of 
     357     ! Shaked and Lis (2012) 
     358     ! ------------------------------------------------------------------------- 
    321359     IF( ln_ligand ) THEN 
    322360         zpligprod1(:,:,:) = 0._wp    ;    zpligprod2(:,:,:) = 0._wp 
     
    328366                    zfeup    = texcretn * zprofen(ji,jj,jk) + texcretd * zprofed(ji,jj,jk) 
    329367                    tra(ji,jj,jk,jplgw) = tra(ji,jj,jk,jplgw) + zdocprod * ldocp    & 
    330                     &       - zfeup * plig(ji,jj,jk) / ( rtrn + plig(ji,jj,jk) + 2.E3 * (1.0 - plig(ji,jj,jk) ) ) 
     368                    &       - zfeup * plig(ji,jj,jk) / ( rtrn + plig(ji,jj,jk) + 2.E3 * (1.0 - plig(ji,jj,jk) ) ) * lthet 
    331369                    zpligprod1(ji,jj,jk) = zdocprod * ldocp 
    332                     zpligprod2(ji,jj,jk) = zfeup * plig(ji,jj,jk) * lthet 
     370                    zpligprod2(ji,jj,jk) = zfeup * plig(ji,jj,jk) / ( rtrn + plig(ji,jj,jk) & 
     371                    &                      + 2.E3 * (1.0 - plig(ji,jj,jk) ) ) * lthet 
    333372                 ENDIF 
    334373              END DO 
     
    373412          ENDIF 
    374413          IF( iom_use( "LPRODP" ) )  THEN 
    375               zw3d(:,:,:) = zpligprod1(:,:,:) * 1e9 * zfact * tmask(:,:,:) 
     414              zw3d(:,:,:) = zpligprod1(:,:,:) * 1e9 * zfact * tmask(:,:,:)  ! Ligand production by phytoplankton 
    376415              CALL iom_put( "LPRODP"  , zw3d ) 
    377416          ENDIF 
    378417          IF( iom_use( "LDETP" ) )  THEN 
    379               zw3d(:,:,:) = zpligprod2(:,:,:) * 1e9 * zfact * tmask(:,:,:) 
     418              zw3d(:,:,:) = zpligprod2(:,:,:) * 1e9 * zfact * tmask(:,:,:)  ! Uptake of ligands by phytoplankton 
    380419              CALL iom_put( "LDETP"  , zw3d ) 
    381420          ENDIF 
     
    392431          ENDIF 
    393432          IF( iom_use( "LNlight" ) .OR. iom_use( "LDlight" ) )  THEN 
    394               zw3d(:,:,:) = zprbio (:,:,:) / (zprmaxn(:,:,:) + rtrn) * tmask(:,:,:) ! light limitation term 
     433              zw3d(:,:,:) = zprbio (:,:,:) / (zprmaxn(:,:,:) + rtrn) * tmask(:,:,:) ! light limitation term of nanophytoplankton 
    395434              CALL iom_put( "LNlight"  , zw3d ) 
    396435              ! 
    397               zw3d(:,:,:) = zprdia (:,:,:) / (zprmaxd(:,:,:) + rtrn) * tmask(:,:,:)  ! light limitation term 
     436              zw3d(:,:,:) = zprdia (:,:,:) / (zprmaxd(:,:,:) + rtrn) * tmask(:,:,:)  ! light limitation term of diatoms 
    398437              CALL iom_put( "LDlight"  , zw3d ) 
    399438          ENDIF 
     
    474513      !! ** Purpose :   Initialization of phytoplankton production parameters 
    475514      !! 
    476       !! ** Method  :   Read the nampisprod namelist and check the parameters 
     515      !! ** Method  :   Read the namp4zprod namelist and check the parameters 
    477516      !!      called at the first timestep (nittrc000) 
    478517      !! 
    479       !! ** input   :   Namelist nampisprod 
     518      !! ** input   :   Namelist namp4zprod 
    480519      !!---------------------------------------------------------------------- 
    481520      INTEGER ::   ios   ! Local integer 
     
    491530      ENDIF 
    492531      ! 
    493       REWIND( numnatp_ref )              ! Namelist nampisprod in reference namelist : Pisces phytoplankton production 
     532      REWIND( numnatp_ref )              ! Namelist namp4zprod in reference namelist : Pisces phytoplankton production 
    494533      READ  ( numnatp_ref, namp4zprod, IOSTAT = ios, ERR = 901) 
    495534901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zprod in reference namelist' ) 
    496       REWIND( numnatp_cfg )              ! Namelist nampisprod in configuration namelist : Pisces phytoplankton production 
     535      REWIND( numnatp_cfg )              ! Namelist namp4zprod in configuration namelist : Pisces phytoplankton production 
    497536      READ  ( numnatp_cfg, namp4zprod, IOSTAT = ios, ERR = 902 ) 
    498537902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zprod in configuration namelist' ) 
Note: See TracChangeset for help on using the changeset viewer.