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

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

update of the PISCES comments

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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 
Note: See TracChangeset for help on using the changeset viewer.