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 – NEMO

Changeset 3496


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

Location:
branches/2012/dev_r3438_LOCEAN15_PISLOB/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z
Files:
3 edited

Legend:

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

    r3475 r3496  
    318318          zrfact2 = 1.e3 * rfact2r 
    319319          CALL iom_put( "REMIN" , zolimi(:,:,:) * tmask(:,:,:) * zrfact2 )  ! Remineralisation rate 
    320           CALL iom_put( "DENIT" , denitr(:,:,:) * tmask(:,:,:) * zrfact2  )  ! Denitrification 
     320          CALL iom_put( "DENIT" , denitr(:,:,:) * rdenit * rno3 * tmask(:,:,:) * zrfact2  )  ! Denitrification 
    321321      ENDIF 
    322322 
  • 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 
  • branches/2012/dev_r3438_LOCEAN15_PISLOB/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsms.F90

    r3481 r3496  
    3737 
    3838   LOGICAL ::  ln_check_mass = .false.       !: Flag to check mass conservation  
    39  
    40    INTEGER ::  numno3  !: logical unit for NO3 budget 
    41    INTEGER ::  numalk  !: logical unit for talk budget 
    42    INTEGER ::  numsil  !: logical unit for Si budget 
    43    INTEGER ::  numfer  !: logical unit for Fer budget 
    44    INTEGER ::  numco2  !: logical unit for co2 budget 
     39   REAL(wp) :: alkbudget, no3budget, silbudget, ferbudget 
     40   INTEGER ::  numco2, numnut  !: logical unit for co2 budget 
    4541 
    4642   !!---------------------------------------------------------------------- 
     
    8480      IF( ln_rsttr  .AND. ln_pisclo )                              CALL p4z_clo            ! damping on closed seas 
    8581      IF( ln_pisdmp .AND. MOD( kt - nn_dttrc, nn_pisdmp ) == 0 )   CALL p4z_dmp( kt )      ! Relaxation of some tracers 
    86                                                                    CALL p4z_chk_mass( kt ) ! Mass conservation checking 
     82      ! 
    8783      IF( ndayflxtr /= nday_year ) THEN      ! New days 
    8884         ! 
     
    148144      END IF 
    149145      ! 
    150        ! 
    151        IF( kt == nitend ) THEN 
    152          ! 
    153          t_atm_co2_flx  = t_atm_co2_flx / glob_sum( e1e2t(:,:) ) 
    154          t_oce_co2_flx  = t_oce_co2_flx         * 12. / 1.e15 * (-1 ) 
    155          tpp            = tpp           * 1000. * 12. / 1.E15 
    156          t_oce_co2_exp  = t_oce_co2_exp * 1000. * 12. / 1.E15 
    157          ! 
    158          IF(lwp) WRITE(numco2,9000) ndastp, t_atm_co2_flx, t_oce_co2_flx, tpp, t_oce_co2_exp 
    159          ! 
    160       ENDIF 
     146      CALL p4z_chk_mass( kt ) ! Mass conservation checking 
    161147 
    162148      IF( nn_timing == 1 )  CALL timing_stop('p4z_sms') 
    163149      ! 
    164  9000  FORMAT(i8,f10.5,e18.10,f10.5,f10.5) 
    165150      ! 
    166151   END SUBROUTINE p4z_sms 
     
    362347      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index       
    363348      !! 
    364       REAL(wp) :: zalkbudget, zno3budget, zsilbudget, zferbudget 
    365       ! 
    366349      NAMELIST/nampismass/ ln_check_mass 
    367350      !!--------------------------------------------------------------------- 
     
    378361 
    379362         IF( ln_check_mass .AND. lwp) THEN      !   Open budget file of NO3, ALK, Si, Fer 
    380             CALL ctl_opn( numno3, 'no3.budget' , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
    381             CALL ctl_opn( numsil, 'sil.budget' , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
    382             CALL ctl_opn( numalk, 'talk.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
    383             CALL ctl_opn( numfer, 'iron.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
     363            CALL ctl_opn( numco2, 'carbon.budget'  , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
     364            CALL ctl_opn( numnut, 'nutrient.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
    384365         ENDIF 
    385          IF(lwp) CALL ctl_opn( numco2, 'carbon.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
    386       ENDIF 
    387  
    388       IF( ln_check_mass ) THEN      !   Compute the budget of NO3, ALK, Si, Fer 
    389          zno3budget = glob_sum( (   trn(:,:,:,jpno3) + trn(:,:,:,jpnh4)  & 
     366      ENDIF 
     367 
     368      IF( ln_check_mass .AND. kt == nitend ) THEN      !   Compute the budget of NO3, ALK, Si, Fer 
     369         no3budget = glob_sum( (   trn(:,:,:,jpno3) + trn(:,:,:,jpnh4)  & 
    390370            &                     + trn(:,:,:,jpphy) + trn(:,:,:,jpdia)  & 
    391371            &                     + trn(:,:,:,jpzoo) + trn(:,:,:,jpmes)  & 
     
    397377            &                     + trn(:,:,:,jpdoc)                     ) * cvol(:,:,:)  )  
    398378         !  
    399          zsilbudget = glob_sum( (   trn(:,:,:,jpsil) + trn(:,:,:,jpgsi)  & 
     379         silbudget = glob_sum( (   trn(:,:,:,jpsil) + trn(:,:,:,jpgsi)  & 
    400380            &                     + trn(:,:,:,jpdsi)                     ) * cvol(:,:,:)  ) 
    401381         !  
    402          zalkbudget = glob_sum( (   trn(:,:,:,jpno3) * rno3              & 
     382         alkbudget = glob_sum( (   trn(:,:,:,jpno3) * rno3              & 
    403383            &                     + trn(:,:,:,jptal)                     & 
    404384            &                     + trn(:,:,:,jpcal) * 2.                ) * cvol(:,:,:)  ) 
    405385         !  
    406          zferbudget = glob_sum( (   trn(:,:,:,jpfer) + trn(:,:,:,jpnfe)  & 
     386         ferbudget = glob_sum( (   trn(:,:,:,jpfer) + trn(:,:,:,jpnfe)  & 
    407387            &                     + trn(:,:,:,jpdfe) + trn(:,:,:,jpbfe)  & 
    408388            &                     + trn(:,:,:,jpsfe) +                   & 
     
    410390            &                     + trn(:,:,:,jpmes) * ferat3            ) * cvol(:,:,:)  ) 
    411391 
    412          IF( lwp ) THEN 
    413             WRITE(numno3,9500) kt,  zno3budget / areatot 
    414             WRITE(numsil,9500) kt,  zsilbudget / areatot 
    415             WRITE(numalk,9500) kt,  zalkbudget / areatot 
    416             WRITE(numfer,9500) kt,  zferbudget / areatot 
     392         ! 
     393         t_atm_co2_flx  = t_atm_co2_flx / glob_sum( e1e2t(:,:) ) 
     394         t_oce_co2_flx  = t_oce_co2_flx         * 12. / 1.e15 * (-1 ) 
     395         tpp            = tpp           * 1000. * 12. / 1.E15 
     396         t_oce_co2_exp  = t_oce_co2_exp * 1000. * 12. / 1.E15 
     397         ! 
     398         no3budget = no3budget / areatot 
     399         silbudget = silbudget / areatot 
     400         alkbudget = alkbudget / areatot 
     401         ferbudget = ferbudget / areatot 
     402         ! 
     403         IF(lwp) THEN 
     404            WRITE(numco2,9000) ndastp, t_atm_co2_flx, t_oce_co2_flx, tpp, t_oce_co2_exp 
     405            WRITE(numnut,9500) ndastp, alkbudget, no3budget, silbudget, ferbudget 
    417406         ENDIF 
    418        ENDIF 
     407         ! 
     408      ENDIF 
    419409       ! 
    420  9500  FORMAT(i10,e18.10)      
     410 9000  FORMAT(i8,f10.5,e18.10,f10.5,f10.5) 
     411 9500  FORMAT(i8,4e18.10)      
    421412       ! 
    422413   END SUBROUTINE p4z_chk_mass 
Note: See TracChangeset for help on using the changeset viewer.