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 3496 for branches/2012/dev_r3438_LOCEAN15_PISLOB/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsed.F90 – NEMO

Ignore:
Timestamp:
2012-10-11T10:39:32+02:00 (12 years ago)
Author:
cetlod
Message:

branch:2012/dev_r3438_LOCEAN15_PISLOB: minor changes in PISCES log files, see ticket #972

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_r3438_LOCEAN15_PISLOB/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsed.F90

    r3495 r3496  
    3838   REAL(wp) :: r1_rday                  !: inverse of rday 
    3939 
     40   INTEGER ::  numnit   
     41 
    4042 
    4143   !!* Substitution 
     
    7072      REAL(wp) ::  zsiloss, zcaloss, zwsbio3, zwsbio4, zwscal, zdep, zwstpoc 
    7173      REAL(wp) ::  ztrfer, ztrpo4, zwdust 
     74!!Ch   
     75      REAL(wp) ::  zrdenittot, zsdenittot, znitrpottot, znitrfix 
     76!!Ch   
    7277      CHARACTER (len=25) :: charout 
    7378      REAL(wp), POINTER, DIMENSION(:,:  ) :: zpdep, zsidep, zwork1, zwork2, zwork3, zwork4 
     
    8388         r1_rday  = 1. / rday 
    8489         r1_ryyss = 1. / ryyss 
     90         IF(lwp) CALL ctl_opn( numnit, 'nitrogen.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
    8591      ENDIF 
    8692      ! 
     
    127133            zirondep(:,:,1) = dustsolub  * dust(:,:) * rfact2 / fse3t(:,:,1) / ( 55.85 * rmtss ) + 3.e-10 * r1_ryyss  
    128134         ENDIF 
    129          zsidep(:,:) = 8.8 * 0.075 * dust(:,:)        * rfact2 / fse3t(:,:,1) / ( 28.1  * rmtss ) 
    130          zpdep (:,:) = 0.1 * 0.021 * dust(:,:) / po4r * rfact2 / fse3t(:,:,1) / ( 31.   * rmtss ) 
     135         zsidep(:,:) = 8.8 * 0.075 * dust(:,:) * rfact2 / fse3t(:,:,1) / ( 28.1  * rmtss ) 
     136         zpdep (:,:) = 0.1 * 0.021 * dust(:,:) * rfact2 / fse3t(:,:,1) / ( 31.   * rmtss ) 
    131137         !                                              ! Iron solubilization of particles in the water column 
    132138         zwdust = 0.005 / ( wdust * 55.85 * 30.42 ) / ( 45. * rday )  
     
    327333      END DO 
    328334  
     335      ! The total gain from nitrogen fixation is scaled to balance the loss by denitrification 
     336      ! ------------------------------------------------------------- 
     337      zrdenittot   = glob_sum ( denitr(:,:,:) * rdenit * xnegtr(:,:,:) * cvol(:,:,:) ) 
     338      zsdenittot   = glob_sum ( zwork4(:,:)   * e1e2t(:,:) ) 
     339      znitrpottot  = glob_sum ( znitrpot(:,:,:)                        * cvol(:,:,:) ) 
     340      IF( kt == nitend .AND. jnt == nrdttrc ) THEN 
     341         zfact = 1.e+3 * rfact2r * rno3 * 365. * 86400. * 14. / 1e12 
     342         IF(lwp) WRITE(numnit,9100) ndastp, znitrpottot * nitrfix * zfact, zrdenittot * zfact , zsdenittot * zfact 
     343      ENDIF 
     344 
    329345      ! Nitrogen change due to nitrogen fixation 
    330346      ! ---------------------------------------- 
     
    362378      IF( nn_timing == 1 )  CALL timing_stop('p4z_sed') 
    363379      ! 
     380 9100  FORMAT(i8,3f10.5) 
     381      ! 
    364382   END SUBROUTINE p4z_sed 
    365383 
Note: See TracChangeset for help on using the changeset viewer.