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 2104 for branches/DEV_r2006_merge_TRA_TRC/NEMO/TOP_SRC/PISCES/p4zrem.F90 – NEMO

Ignore:
Timestamp:
2010-09-17T14:35:46+02:00 (14 years ago)
Author:
cetlod
Message:

update DEV_r2006_merge_TRA_TRC according to review

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/TOP_SRC/PISCES/p4zrem.F90

    r2082 r2104  
    2727   PRIVATE 
    2828 
    29    PUBLIC   p4z_rem    ! called in p4zbio.F90 
     29   PUBLIC   p4z_rem         ! called in p4zbio.F90 
     30   PUBLIC   p4z_rem_init    ! called in trcsms_pisces.F90 
    3031 
    3132   !! * Shared module variables 
     
    4142     &                   denitr                     !: denitrification array 
    4243 
    43    REAL(wp) ::   & 
    44      xstep            !: Time step duration for biology 
    4544 
    4645   !!* Substitution 
     
    5453CONTAINS 
    5554 
    56    SUBROUTINE p4z_rem(kt, jnt) 
     55   SUBROUTINE p4z_rem( kt ) 
    5756      !!--------------------------------------------------------------------- 
    5857      !!                     ***  ROUTINE p4z_rem  *** 
     
    6261      !! ** Method  : - ??? 
    6362      !!--------------------------------------------------------------------- 
    64       INTEGER, INTENT(in) ::   kt, jnt ! ocean time step 
     63      INTEGER, INTENT(in) ::   kt ! ocean time step 
    6564      INTEGER  ::   ji, jj, jk 
    6665      REAL(wp) ::   zremip, zremik , zlam1b 
    6766      REAL(wp) ::   zkeq  , zfeequi, zsiremin 
    68       REAL(wp) ::   zsatur, zsatur2, znusil 
     67      REAL(wp) ::   zsatur, zsatur1, zsatur2, zsatur22, znusil 
     68      REAL(wp) ::   ztem1, ztem2 
    6969      REAL(wp) ::   zbactfer, zorem, zorem2, zofer 
    7070      REAL(wp) ::   zosil, zdenom1, zscave, zaggdfe 
     
    7272      REAL(wp) ::   zofer2, zdenom, zdenom2 
    7373#endif 
    74       REAL(wp) ::   zlamfac, zonitr 
     74      REAL(wp) ::   zlamfac, zonitr, zstep 
    7575      REAL(wp), DIMENSION(jpi,jpj)     ::   ztempbac 
    7676      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zdepbac, zfesatur, zolimi 
     
    7878 
    7979      !!--------------------------------------------------------------------- 
    80  
    81  
    82       IF( ( kt * jnt ) == nittrc000  )  THEN 
    83          CALL p4z_rem_init                ! Initialization (first time-step only) 
    84          xstep = rfact2 / rday            ! Time step duration for the biology 
    85          nitrfac(:,:,:) = 0.0 
    86          denitr (:,:,:) = 0.0   
    87       ENDIF 
    8880 
    8981 
     
    9486       ztempbac(:,:)   = 0.0 
    9587 
    96 !      Computation of the mean phytoplankton concentration as 
    97 !      a crude estimate of the bacterial biomass 
    98 !      -------------------------------------------------- 
     88      !  Computation of the mean phytoplankton concentration as 
     89      !  a crude estimate of the bacterial biomass 
     90      !   -------------------------------------------------- 
    9991 
    10092      DO jk = 1, jpkm1 
     
    114106         DO jj = 1, jpj 
    115107            DO ji = 1, jpi 
    116  
    117 !    DENITRIFICATION FACTOR COMPUTED FROM O2 LEVELS 
    118 !    ---------------------------------------------- 
    119  
     108               ! denitrification factor computed from O2 levels 
    120109               nitrfac(ji,jj,jk) = MAX(  0.e0, 0.4 * ( 6.e-6  - trn(ji,jj,jk,jpoxy) )    & 
    121110                  &                                / ( oxymin + trn(ji,jj,jk,jpoxy) )  ) 
    122             END DO 
    123          END DO 
    124       END DO 
    125  
    126       nitrfac(:,:,:) = MIN( 1., nitrfac(:,:,:) ) 
    127  
    128  
    129       DO jk = 1, jpkm1 
    130          DO jj = 1, jpj 
    131             DO ji = 1, jpi 
    132  
    133 !     DOC ammonification. Depends on depth, phytoplankton biomass 
    134 !     and a limitation term which is supposed to be a parameterization 
    135 !     of the bacterial activity.  
    136 !     ---------------------------------------------------------------- 
    137                zremik = xremik * xstep / 1.e-6 * xlimbac(ji,jj,jk)         & 
     111               nitrfac(ji,jj,jk) = MIN( 1., nitrfac(ji,jj,jk) ) 
     112            END DO 
     113         END DO 
     114      END DO 
     115 
     116      DO jk = 1, jpkm1 
     117         DO jj = 1, jpj 
     118            DO ji = 1, jpi 
    138119# if defined key_degrad 
    139                   &            * facvol(ji,jj,jk)              & 
     120               zstep = xstep * facvol(ji,jj,jk) 
     121# else 
     122               zstep = xstep 
    140123# endif 
    141                   &            * zdepbac(ji,jj,jk) 
     124               ! DOC ammonification. Depends on depth, phytoplankton biomass 
     125               !     and a limitation term which is supposed to be a parameterization 
     126               !     of the bacterial activity.  
     127               zremik = xremik * zstep / 1.e-6 * xlimbac(ji,jj,jk) * zdepbac(ji,jj,jk)  
    142128               zremik = MAX( zremik, 5.5e-4 * xstep ) 
    143129 
    144 !     Ammonification in oxic waters with oxygen consumption 
    145 !     ----------------------------------------------------- 
     130               !     Ammonification in oxic waters with oxygen consumption 
     131               !     ----------------------------------------------------- 
    146132               zolimi(ji,jj,jk) = MIN(  ( trn(ji,jj,jk,jpoxy) - rtrn ) / o2ut,  & 
    147133                  &                    zremik * ( 1.- nitrfac(ji,jj,jk) ) * trn(ji,jj,jk,jpdoc)  )  
    148134 
    149 !     Ammonification in suboxic waters with denitrification 
    150 !     ------------------------------------------------------- 
     135               !     Ammonification in suboxic waters with denitrification 
     136               !     ------------------------------------------------------- 
    151137               denitr(ji,jj,jk) = MIN(  ( trn(ji,jj,jk,jpno3) - rtrn ) / rdenit,   & 
    152138                  &                     zremik * nitrfac(ji,jj,jk) * trn(ji,jj,jk,jpdoc)  ) 
     
    167153         DO jj = 1, jpj 
    168154            DO ji = 1, jpi 
    169  
    170 !    NH4 nitrification to NO3. Ceased for oxygen concentrations 
    171 !    below 2 umol/L. Inhibited at strong light  
    172 !    ---------------------------------------------------------- 
    173                zonitr  = nitrif * xstep * trn(ji,jj,jk,jpnh4) / ( 1.+ emoy(ji,jj,jk) )     & 
    174155# if defined key_degrad 
    175                   &      * facvol(ji,jj,jk)              & 
     156               zstep = xstep * facvol(ji,jj,jk) 
     157# else 
     158               zstep = xstep 
    176159# endif 
    177                   &      * ( 1.- nitrfac(ji,jj,jk) ) 
    178  
    179 ! 
    180 !   Update of the tracers trends 
    181 !   ---------------------------- 
    182  
    183               tra(ji,jj,jk,jpnh4) = tra(ji,jj,jk,jpnh4) - zonitr 
    184               tra(ji,jj,jk,jpno3) = tra(ji,jj,jk,jpno3) + zonitr 
    185               tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) - o2nit * zonitr 
    186               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) - rno3  * zonitr 
     160               !    NH4 nitrification to NO3. Ceased for oxygen concentrations 
     161               !    below 2 umol/L. Inhibited at strong light  
     162               !    ---------------------------------------------------------- 
     163               zonitr  = nitrif * zstep * trn(ji,jj,jk,jpnh4) / ( 1.+ emoy(ji,jj,jk) ) * ( 1.- nitrfac(ji,jj,jk) )  
     164 
     165               !   Update of the tracers trends 
     166               !   ---------------------------- 
     167 
     168               tra(ji,jj,jk,jpnh4) = tra(ji,jj,jk,jpnh4) - zonitr 
     169               tra(ji,jj,jk,jpno3) = tra(ji,jj,jk,jpno3) + zonitr 
     170               tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) - o2nit * zonitr 
     171               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) - rno3  * zonitr 
    187172 
    188173            END DO 
     
    200185            DO ji = 1, jpi 
    201186 
    202 !    Bacterial uptake of iron. No iron is available in DOC. So 
    203 !    Bacteries are obliged to take up iron from the water. Some 
    204 !    studies (especially at Papa) have shown this uptake to be 
    205 !    significant 
    206 !    ---------------------------------------------------------- 
     187               !    Bacterial uptake of iron. No iron is available in DOC. So 
     188               !    Bacteries are obliged to take up iron from the water. Some 
     189               !    studies (especially at Papa) have shown this uptake to be significant 
     190               !    ---------------------------------------------------------- 
    207191               zbactfer = 15.e-6 * rfact2 * 4.* 0.4 * prmax(ji,jj,jk)           & 
    208                   &               * ( xlimphy(ji,jj,jk) * zdepbac(ji,jj,jk))**2           & 
     192                  &               * ( xlimphy(ji,jj,jk) * zdepbac(ji,jj,jk))           & 
     193                  &               * ( xlimphy(ji,jj,jk) * zdepbac(ji,jj,jk))           & 
    209194                  &                  / ( xkgraz2 + zdepbac(ji,jj,jk) )                    & 
    210195                  &                  * ( 0.5 + SIGN( 0.5, trn(ji,jj,jk,jpfer) -2.e-11 )  ) 
     
    216201               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zbactfer 
    217202#endif 
    218  
    219203            END DO 
    220204         END DO 
     
    230214         DO jj = 1, jpj 
    231215            DO ji = 1, jpi 
    232  
    233 !    POC disaggregation by turbulence and bacterial activity.  
    234 !    ------------------------------------------------------------- 
    235                zremip = xremip * xstep * tgfunc(ji,jj,jk)   & 
    236216# if defined key_degrad 
    237                   &            * facvol(ji,jj,jk)              & 
     217               zstep = xstep * facvol(ji,jj,jk) 
     218# else 
     219               zstep = xstep 
    238220# endif 
    239                   &            * ( 1.- 0.5 * nitrfac(ji,jj,jk) ) 
    240  
    241 !    POC disaggregation rate is reduced in anoxic zone as shown by 
    242 !    sediment traps data. In oxic area, the exponent of the martin s 
    243 !    law is around -0.87. In anoxic zone, it is around -0.35. This 
    244 !    means a disaggregation constant about 0.5 the value in oxic zones 
    245 !    ----------------------------------------------------------------- 
     221               !    POC disaggregation by turbulence and bacterial activity.  
     222               !    ------------------------------------------------------------- 
     223               zremip = xremip * zstep * tgfunc(ji,jj,jk) * ( 1.- 0.5 * nitrfac(ji,jj,jk) )  
     224 
     225               !    POC disaggregation rate is reduced in anoxic zone as shown by 
     226               !    sediment traps data. In oxic area, the exponent of the martin s 
     227               !    law is around -0.87. In anoxic zone, it is around -0.35. This 
     228               !    means a disaggregation constant about 0.5 the value in oxic zones 
     229               !    ----------------------------------------------------------------- 
    246230               zorem  = zremip * trn(ji,jj,jk,jppoc) 
    247231               zofer  = zremip * trn(ji,jj,jk,jpsfe) 
     
    253237#endif 
    254238 
    255 !  Update the appropriate tracers trends 
    256 !  ------------------------------------- 
     239               !  Update the appropriate tracers trends 
     240               !  ------------------------------------- 
    257241 
    258242               tra(ji,jj,jk,jpdoc) = tra(ji,jj,jk,jpdoc) + zorem 
     
    282266         DO jj = 1, jpj 
    283267            DO ji = 1, jpi 
    284  
    285 !     Remineralization rate of BSi depedant on T and saturation 
    286 !     --------------------------------------------------------- 
    287                zsatur  = ( sio3eq(ji,jj,jk) - trn(ji,jj,jk,jpsil) ) / ( sio3eq(ji,jj,jk) + rtrn ) 
    288                zsatur  = MAX( rtrn, zsatur ) 
    289                zsatur2 = zsatur * ( 1. + tsn(ji,jj,jk,jp_tem) / 400.)**4 
    290                znusil  = 0.225  * ( 1. + tsn(ji,jj,jk,jp_tem) / 15.) * zsatur + 0.775 * zsatur2**9 
    291 #    if defined key_degrad 
    292                zsiremin = xsirem * xstep * znusil * facvol(ji,jj,jk) 
     268# if defined key_degrad 
     269               zstep = xstep * facvol(ji,jj,jk) 
    293270# else 
    294                zsiremin = xsirem * xstep * znusil 
    295 #    endif 
    296                zosil = zsiremin * trn(ji,jj,jk,jpdsi) 
     271               zstep = xstep 
     272# endif 
     273               !     Remineralization rate of BSi depedant on T and saturation 
     274               !     --------------------------------------------------------- 
     275               zsatur   = ( sio3eq(ji,jj,jk) - trn(ji,jj,jk,jpsil) ) / ( sio3eq(ji,jj,jk) + rtrn ) 
     276               zsatur   = MAX( rtrn, zsatur ) 
     277               ztem1    = ( 1. + tsn(ji,jj,jk,jp_tem) / 15.) 
     278               ztem2    = ( 1. + tsn(ji,jj,jk,jp_tem) / 400.) 
     279               zsatur1  = zsatur * ztem1 
     280               zsatur2  = zsatur * ztem2 * ztem2 * ztem2 * ztem2 
     281               zsatur22 = zsatur2 * zsatur2 
     282               znusil   = 0.225  * zsatur1 + 0.775 * zsatur22 * zsatur22 * zsatur22 * zsatur22 * zsatur2 
     283               zsiremin = xsirem * zstep * znusil 
     284               zosil    = zsiremin * trn(ji,jj,jk,jpdsi) 
    297285 
    298286               tra(ji,jj,jk,jpdsi) = tra(ji,jj,jk,jpdsi) - zosil 
    299287               tra(ji,jj,jk,jpsil) = tra(ji,jj,jk,jpsil) + zosil 
    300  
    301288               ! 
    302289            END DO 
     
    317304!CDIR NOVERRCHK 
    318305            DO ji = 1, jpi 
    319 ! 
    320 !      Compute de different ratios for scavenging of iron 
    321 !      -------------------------------------------------- 
     306# if defined key_degrad 
     307               zstep = xstep * facvol(ji,jj,jk) 
     308# else 
     309               zstep = xstep 
     310# endif 
     311               !  Compute de different ratios for scavenging of iron 
     312               !  -------------------------------------------------- 
    322313 
    323314#if  defined key_kriest 
    324                 zdenom1 = trn(ji,jj,jk,jppoc) / & 
     315               zdenom1 = trn(ji,jj,jk,jppoc) / & 
    325316           &           ( trn(ji,jj,jk,jppoc) + trn(ji,jj,jk,jpdsi) + trn(ji,jj,jk,jpcal) + rtrn ) 
    326317#else 
    327                 zdenom = 1. / ( trn(ji,jj,jk,jppoc) + trn(ji,jj,jk,jpgoc)  & 
     318               zdenom = 1. / ( trn(ji,jj,jk,jppoc) + trn(ji,jj,jk,jpgoc)  & 
    328319           &            + trn(ji,jj,jk,jpdsi) + trn(ji,jj,jk,jpcal) + rtrn ) 
    329320 
    330                 zdenom1 = trn(ji,jj,jk,jppoc) * zdenom 
    331                 zdenom2 = trn(ji,jj,jk,jpgoc) * zdenom 
    332 #endif 
    333  
    334  
    335 !     scavenging rate of iron. this scavenging rate depends on the 
    336 !     load in particles on which they are adsorbed. The 
    337 !     parameterization has been taken from studies on Th 
    338 !     ------------------------------------------------------------ 
     321               zdenom1 = trn(ji,jj,jk,jppoc) * zdenom 
     322               zdenom2 = trn(ji,jj,jk,jpgoc) * zdenom 
     323#endif 
     324               !  scavenging rate of iron. this scavenging rate depends on the load in particles 
     325               !  on which they are adsorbed. The  parameterization has been taken from studies on Th 
     326               !     ------------------------------------------------------------ 
    339327               zkeq = fekeq(ji,jj,jk) 
    340328               zfeequi = ( -( 1. + zfesatur(ji,jj,jk) * zkeq - zkeq * trn(ji,jj,jk,jpfer) )               & 
     
    349337                  &                      + trn(ji,jj,jk,jpcal) + trn(ji,jj,jk,jpdsi)  ) * 1.e6 
    350338#endif 
    351  
    352 # if defined key_degrad 
    353                zscave = zfeequi * zlam1b * xstep  * facvol(ji,jj,jk) 
    354 # else 
    355                zscave = zfeequi * zlam1b * xstep 
    356 # endif 
    357  
    358 !  Increased scavenging for very high iron concentrations 
    359 !  found near the coasts due to increased lithogenic particles 
    360 !  and let s say it unknown processes (precipitation, ...) 
    361 !  ----------------------------------------------------------- 
     339               zscave = zfeequi * zlam1b * zstep 
     340 
     341               !  Increased scavenging for very high iron concentrations 
     342               !  found near the coasts due to increased lithogenic particles 
     343               !  and let s say it unknown processes (precipitation, ...) 
     344               !  ----------------------------------------------------------- 
    362345               zlamfac = MAX( 0.e0, ( gphit(ji,jj) + 55.) / 30. ) 
    363346               zlamfac = MIN( 1.  , zlamfac ) 
     
    374357#endif 
    375358 
    376 # if defined key_degrad 
    377                zaggdfe = zlam1b * xstep * 0.5 * ( trn(ji,jj,jk,jpfer) - zfeequi ) * facvol(ji,jj,jk) 
    378 # else 
    379                zaggdfe = zlam1b * xstep * 0.5 * ( trn(ji,jj,jk,jpfer) - zfeequi ) 
    380 # endif 
     359               zaggdfe = zlam1b * zstep * 0.5 * ( trn(ji,jj,jk,jpfer) - zfeequi ) 
    381360 
    382361               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) - zscave - zaggdfe 
     
    400379       ENDIF 
    401380 
    402 !     Update the arrays TRA which contain the biological sources and sinks 
    403 !     -------------------------------------------------------------------- 
     381       !     Update the arrays TRA which contain the biological sources and sinks 
     382       !     -------------------------------------------------------------------- 
    404383 
    405384      DO jk = 1, jpkm1 
     
    452431      ENDIF 
    453432 
     433      nitrfac(:,:,:) = 0.0 
     434      denitr (:,:,:) = 0.0   
     435 
    454436   END SUBROUTINE p4z_rem_init 
    455  
    456  
    457  
    458  
    459437 
    460438#else 
Note: See TracChangeset for help on using the changeset viewer.