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/p4zsed.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/p4zsed.F90

    r10788 r12537  
    22   !!====================================================================== 
    33   !!                         ***  MODULE p4sed  *** 
    4    !! TOP :   PISCES Compute loss of organic matter in the sediments 
     4   !! TOP :   PISCES Compute loss of biogenic matter in the sediments 
     5   !!                Compute gain/loss of tracers from dust, rivers and  
     6   !!                sediments  
     7   !!                This module is used both by PISCES and PISCES-QUOTA 
    58   !!====================================================================== 
    69   !! History :   1.0  !  2004-03 (O. Aumont) Original code 
     
    811   !!             3.4  !  2011-06 (C. Ethe) USE of fldread 
    912   !!             3.5  !  2012-07 (O. Aumont) improvment of river input of nutrients  
    10    !!---------------------------------------------------------------------- 
     13   !!----------------------------------------------------------------------- 
    1114   !!   p4z_sed        :  Compute loss of organic matter in the sediments 
    12    !!---------------------------------------------------------------------- 
     15   !!                  :  Compute gain/loss of tracers from dust, rivers and  
     16   !!                     sediments  
     17   !!----------------------------------------------------------------------- 
    1318   USE oce_trc         !  shared variables between ocean and passive tracers 
    1419   USE trc             !  passive tracers common variables  
     
    4348      !!                     ***  ROUTINE p4z_sed  *** 
    4449      !! 
    45       !! ** Purpose :   Compute loss of organic matter in the sediments. This 
    46       !!              is by no way a sediment model. The loss is simply  
    47       !!              computed to balance the inout from rivers and dust 
     50      !! ** Purpose :   Compute loss of biogenic matter in the sediments. This 
     51      !!              is by no way a real sediment model. The loss is simply  
     52      !!              computed from metamodels. 
     53      !!              Loss/gain of tracers are also computed here for  
     54      !!              dust, rivers, sediments and hydrothermal vents (Fe)  
     55      !!              N2 fixation is modeled using an implicit approach 
    4856      !! 
    4957      !! ** Method  : - ??? 
     
    93101      zsedc   (:,:) = 0.e0 
    94102 
    95       ! Iron input/uptake due to sea ice : Crude parameterization based on Lancelot et al. 
     103      ! Iron input/uptake due to sea ice : Crude parameterization based on  
     104      ! Lancelot et al. Iron concentration in sea-ice is constant and set  
     105      ! in the namelist_pisces (icefeinput). ln_ironice is forced to false 
     106      ! when nn_ice_tr = 1 
    96107      ! ---------------------------------------------------- 
    97108      IF( ln_ironice ) THEN   
     
    99110         ALLOCATE( zironice(jpi,jpj) ) 
    100111         !                                               
     112         ! Compute the iron flux between sea ice and sea water 
    101113         DO jj = 1, jpj 
    102114            DO ji = 1, jpi 
     
    106118            END DO 
    107119         END DO 
    108          ! 
     120         ! Update of the TRA array 
    109121         tra(:,:,1,jpfer) = tra(:,:,1,jpfer) + zironice(:,:)  
    110122         !  
     
    121133         !                                               
    122134         ALLOCATE( zsidep(jpi,jpj), zpdep(jpi,jpj,jpk), zirondep(jpi,jpj,jpk) ) 
    123          !                                              ! Iron and Si deposition at the surface 
     135         ! Iron, P and Si deposition at the surface 
     136         ! Iron flux at the surface due to dust deposition. Solubility can be  
     137         ! be variable if ln_solub is set to true. In that case, solubility  
     138         ! has to be provided in the specific input file (read in p4zsbc) 
     139         ! ------------------------------------------------------------------ 
    124140         IF( ln_solub ) THEN 
    125141            zirondep(:,:,1) = solub(:,:) * dust(:,:) * mfrac * rfact2 / e3t_n(:,:,1) / 55.85 + 3.e-10 * r1_ryyss  
     
    127143            zirondep(:,:,1) = dustsolub  * dust(:,:) * mfrac * rfact2 / e3t_n(:,:,1) / 55.85 + 3.e-10 * r1_ryyss  
    128144         ENDIF 
     145         ! Si and P flux at the surface due to dust deposition. The content  
     146         ! and the solubility are hard coded 
     147         ! ---------------------------------------------------------------- 
    129148         zsidep(:,:)   = 8.8 * 0.075 * dust(:,:) * mfrac * rfact2 / e3t_n(:,:,1) / 28.1  
    130149         zpdep (:,:,1) = 0.1 * 0.021 * dust(:,:) * mfrac * rfact2 / e3t_n(:,:,1) / 31. / po4r  
    131          !                                              ! Iron solubilization of particles in the water column 
    132          !                                              ! dust in kg/m2/s ---> 1/55.85 to put in mol/Fe ;  wdust in m/j 
    133          zwdust = 0.03 * rday / ( wdust * 55.85 ) / ( 270. * rday ) 
     150         ! Iron solubilization of particles in the water column 
     151         ! dust in kg/m2/s ---> 1/55.85 to put in mol/Fe ;  wdust in m/d 
     152         ! Dust are supposed to sink at wdust sinking speed. 3% of the iron  
     153         ! in dust is hypothesized to be soluble at a dissolution rate set to  
     154         ! 1/(250 days). The vertical distribution of iron in dust is computed  
     155         ! from a steady state assumption. Parameters are very uncertain and  
     156         ! are estimated from the literature quoted in Raiswell et al. (2011)  
     157         ! -------------------------------------------------------------------  
     158         zwdust = 0.03 * rday / ( wdust * 55.85 ) / ( 250. * rday ) 
    134159         DO jk = 2, jpkm1 
    135             zirondep(:,:,jk) = dust(:,:) * mfrac * zwdust * rfact2 * EXP( -gdept_n(:,:,jk) / 540. ) 
     160            zirondep(:,:,jk) = dust(:,:) * mfrac * zwdust * rfact2 * EXP( -gdept_n(:,:,jk) / (250. * wdust) ) 
    136161            zpdep   (:,:,jk) = zirondep(:,:,jk) * 0.023 
    137162         END DO 
    138          !                                              ! Iron solubilization of particles in the water column 
     163         ! Solubilization of particles in the water column (Si, P, Fe) 
    139164         tra(:,:,1,jpsil) = tra(:,:,1,jpsil) + zsidep  (:,:) 
    140165         DO jk = 1, jpkm1 
     
    156181      
    157182      ! Add the external input of nutrients from river 
    158       ! ---------------------------------------------------------- 
     183      ! ---------------------------------------------- 
    159184      IF( ln_river ) THEN 
    160185         DO jj = 1, jpj 
     
    171196            ENDDO 
    172197         ENDDO 
     198         ! When prognostic ligands are activated, ligands are supplied  
     199         ! to the ocean by rivers. We assume that the amount of ligands 
     200         ! is equal to that of iron (iron is completely complexed) 
     201         ! ------------------------------------------------------------ 
    173202         IF (ln_ligand) THEN 
    174203            DO jj = 1, jpj 
     
    180209            ENDDO 
    181210         ENDIF 
     211         ! PISCES-QUOTA part 
    182212         IF( ln_p5z ) THEN 
    183213            DO jj = 1, jpj 
     
    200230 
    201231      ! Add the external input of iron from hydrothermal vents 
    202       ! ------------------------------------------------------ 
     232      ! Please refer to Tagliabue et al. (2010) for more information 
     233      ! ------------------------------------------------------------ 
    203234      IF( ln_hydrofe ) THEN 
    204235            tra(:,:,:,jpfer) = tra(:,:,:,jpfer) + hydrofe(:,:,:) * rfact2 
     
    211242      ENDIF 
    212243 
    213       ! OA: Warning, the following part is necessary to avoid CFL problems above the sediments 
     244      ! OA: Warning, the following part is necessary to avoid CFL problems  
     245      ! above the sediments. Vertical sinking speed is limited using the  
     246      ! typical CFL criterion 
    214247      ! -------------------------------------------------------------------- 
    215248      DO jj = 1, jpj 
     
    222255      END DO 
    223256      ! 
     257      ! No sediment module activated 
    224258      IF( .NOT.lk_sed ) THEN 
    225259! 
     
    233267         ENDIF 
    234268 
    235          ! Computation of the sediment denitrification proportion: The metamodel from midlleburg (2006) is being used 
    236          ! Computation of the fraction of organic matter that is permanently buried from Dunne's model 
     269         ! Computation of the sediment denitrification proportion: The metamodel  
     270         ! from Middleburg (2006) is used 
     271         ! Computation of the fraction of organic matter that is permanently  
     272         ! buried from Dunne's model (2007) 
    237273         ! ------------------------------------------------------- 
    238274         DO jj = 1, jpj 
     
    259295      ENDIF 
    260296 
    261       ! This loss is scaled at each bottom grid cell for equilibrating the total budget of silica in the ocean. 
    262       ! Thus, the amount of silica lost in the sediments equal the supply at the surface (dust+rivers) 
    263       ! ------------------------------------------------------ 
     297      ! Fraction of dSi that is remineralized in the sediments. This is  
     298      ! set so that the burial in sediments equals the total input of Si 
     299      ! by rivers and dust (sedsilfrac) 
     300      ! ---------------------------------------------------------------- 
    264301      IF( .NOT.lk_sed )  zrivsil = 1._wp - sedsilfrac 
    265302 
     303      ! Loss of bSi and CaCO3 to the sediments 
    266304      DO jj = 1, jpj 
    267305         DO ji = 1, jpi 
     
    278316      ! 
    279317      IF( .NOT.lk_sed ) THEN 
     318         ! Dissolution of CaCO3 and bSi in the sediments. This is  
     319         ! instantaneous since here sediments are not explicitly  
     320         ! modeled. The amount of CaCO3 that dissolves in the sediments 
     321         ! is computed using a metamodel constructed from Archer (1996) 
     322         ! ------------------------------------------------------------ 
    280323         DO jj = 1, jpj 
    281324            DO ji = 1, jpi 
     
    298341      ENDIF 
    299342      ! 
     343      ! Loss of particulate organic carbon and Fe to the sediments 
    300344      DO jj = 1, jpj 
    301345         DO ji = 1, jpi 
     
    311355      END DO 
    312356      ! 
     357      ! Loss of particulate organic N and P to the sediments (p5z) 
    313358      IF( ln_p5z ) THEN 
    314359         DO jj = 1, jpj 
     
    327372 
    328373      IF( .NOT.lk_sed ) THEN 
     374         ! Degradation of organic matter in the sediments. The metamodel of  
     375         ! Middleburg (2006) is used here to mimic the diagenetic reactions.  
    329376         ! The 0.5 factor in zpdenit is to avoid negative NO3 concentration after 
    330377         ! denitrification in the sediments. Not very clever, but simpliest option. 
     378         ! ------------------------------------------------------------------------ 
    331379         DO jj = 1, jpj 
    332380            DO ji = 1, jpi 
     
    360408 
    361409 
    362       ! Nitrogen fixation process 
    363       ! Small source iron from particulate inorganic iron 
    364       !----------------------------------- 
     410      ! Nitrogen fixation process : light limitation of diazotrophy 
     411      ! Small source of iron from particulate inorganic iron (photochemistry) 
     412      !---------------------------------------------------------------------- 
    365413      DO jk = 1, jpkm1 
    366414         zlight (:,:,jk) =  ( 1.- EXP( -etot_ndcy(:,:,jk) / diazolight ) ) * ( 1. - fr_i(:,:) )  
    367415         zsoufer(:,:,jk) = zlight(:,:,jk) * 2E-11 / ( 2E-11 + biron(:,:,jk) ) 
    368416      ENDDO 
     417 
     418      ! Diazotrophy (nitrogen fixation) is modeled according to an empirical 
     419      ! formulation. This is described in Aumont et al. (2015). Limitation  
     420      ! by P and Fe is computed. Inhibition by high N concentrations is imposed. 
     421      ! Diazotrophy sensitivity to temperature is parameterized as in  
     422      ! Ye et al. (2012)   
     423      ! ------------------------------------------------------------------------ 
    369424      IF( ln_p4z ) THEN 
     425         ! PISCES part 
    370426         DO jk = 1, jpkm1 
    371427            DO jj = 1, jpj 
    372428               DO ji = 1, jpi 
    373                   !                      ! Potential nitrogen fixation dependant on temperature and iron 
     429                  ! Potential nitrogen fixation dependant on temperature and iron 
    374430                  ztemp = tsn(ji,jj,jk,jp_tem) 
    375431                  zmudia = MAX( 0.,-0.001096*ztemp**2 + 0.057*ztemp -0.637 ) * 7.625 
    376                   !       Potential nitrogen fixation dependant on temperature and iron 
    377432                  xdianh4 = trb(ji,jj,jk,jpnh4) / ( concnnh4 + trb(ji,jj,jk,jpnh4) ) 
    378433                  xdiano3 = trb(ji,jj,jk,jpno3) / ( concnno3 + trb(ji,jj,jk,jpno3) ) * (1. - xdianh4) 
     
    388443         END DO 
    389444      ELSE       ! p5z 
     445         ! PISCES-QUOTA part 
    390446         DO jk = 1, jpkm1 
    391447            DO jj = 1, jpj 
    392448               DO ji = 1, jpi 
    393                   !                      ! Potential nitrogen fixation dependant on temperature and iron 
     449                  ! Potential nitrogen fixation dependant on temperature and iron 
    394450                  ztemp = tsn(ji,jj,jk,jp_tem) 
    395451                  zmudia = MAX( 0.,-0.001096*ztemp**2 + 0.057*ztemp -0.637 ) * 7.625 
    396                   !       Potential nitrogen fixation dependant on temperature and iron 
    397452                  xdianh4 = trb(ji,jj,jk,jpnh4) / ( concnnh4 + trb(ji,jj,jk,jpnh4) ) 
    398453                  xdiano3 = trb(ji,jj,jk,jpno3) / ( concnno3 + trb(ji,jj,jk,jpno3) ) * (1. - xdianh4) 
     
    410465      ENDIF 
    411466 
    412       ! Nitrogen change due to nitrogen fixation 
    413       ! ---------------------------------------- 
     467      ! Update of the TRA arrays due to nitrogen fixation 
     468      ! ------------------------------------------------- 
    414469      IF( ln_p4z ) THEN 
     470         ! PISCES part 
    415471         DO jk = 1, jpkm1 
    416472            DO jj = 1, jpj 
     
    428484                  tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + 30E-6 * zfact * 1.0 / 3.0 * 1.0 / 3.0 
    429485                  tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + 0.002 * 4E-10 * zsoufer(ji,jj,jk) * rfact2 / rday 
    430                   tra(ji,jj,jk,jppo4) = tra(ji,jj,jk,jppo4) + concdnh4 / ( concdnh4 + trb(ji,jj,jk,jppo4) ) & 
    431                   &                     * 0.001 * trb(ji,jj,jk,jpdoc) * xstep 
    432486              END DO 
    433487            END DO  
    434488         END DO 
    435489      ELSE    ! p5z 
     490         ! PISCES-QUOTA part 
    436491         DO jk = 1, jpkm1 
    437492            DO jj = 1, jpj 
     
    475530               CALL iom_put( "INTNFIX" , zwork )  
    476531            ENDIF 
    477             IF( iom_use("SedCal" ) ) CALL iom_put( "SedCal", zsedcal(:,:) * zfact ) 
    478             IF( iom_use("SedSi" ) )  CALL iom_put( "SedSi",  zsedsi (:,:) * zfact ) 
    479             IF( iom_use("SedC" ) )   CALL iom_put( "SedC",   zsedc  (:,:) * zfact ) 
    480             IF( iom_use("Sdenit" ) ) CALL iom_put( "Sdenit", sdenit (:,:) * zfact * rno3 ) 
     532            IF( iom_use("SedCal" ) ) CALL iom_put( "SedCal", zsedcal(:,:) * zfact ) ! Permanent burial of CaCO3 in sediments 
     533            IF( iom_use("SedSi" ) )  CALL iom_put( "SedSi",  zsedsi (:,:) * zfact ) ! Permanent burial of bSi in sediments 
     534            IF( iom_use("SedC" ) )   CALL iom_put( "SedC",   zsedc  (:,:) * zfact ) ! Permanent burial of OC in sediments 
     535            IF( iom_use("Sdenit" ) ) CALL iom_put( "Sdenit", sdenit (:,:) * zfact * rno3 ) ! Denitrification in the sediments 
    481536         ENDIF 
    482537      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.