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 12276 for NEMO/trunk/src/TOP/PISCES/P4Z/p4zflx.F90 – NEMO

Ignore:
Timestamp:
2019-12-20T12:14:26+01:00 (4 years ago)
Author:
cetlod
Message:

trunk : merge in some cmip6 diagnostics into the trunk before copying it to release-4.0.2(-head). SETTE tests are OK and the is no difference with the revision 12248

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/TOP/PISCES/P4Z/p4zflx.F90

    r11993 r12276  
    8080      CHARACTER (len=25) ::   charout 
    8181      REAL(wp), DIMENSION(jpi,jpj) ::   zkgco2, zkgo2, zh2co3, zoflx,  zpco2atm   
    82       REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zw2d 
    8382      !!--------------------------------------------------------------------- 
    8483      ! 
     
    160159            zfld = zfco2 * chemc(ji,jj,1) * zkgco2(ji,jj)  ! (mol/L) * (m/s) 
    161160            zflu = zh2co3(ji,jj) * zkgco2(ji,jj)                                   ! (mol/L) (m/s) ? 
    162             oce_co2(ji,jj) = ( zfld - zflu ) * rfact2 * e1e2t(ji,jj) * tmask(ji,jj,1) * 1000. 
     161            oce_co2(ji,jj) = ( zfld - zflu ) * tmask(ji,jj,1)  
    163162            ! compute the trend 
    164             tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) * rfact2 / e3t_n(ji,jj,1) * tmask(ji,jj,1) 
     163            tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + oce_co2(ji,jj) * rfact2 / e3t_n(ji,jj,1) 
    165164 
    166165            ! Compute O2 flux  
     
    174173      IF( iom_use("tcflx") .OR. iom_use("tcflxcum") .OR. kt == nitrst   & 
    175174         &                 .OR. (ln_check_mass .AND. kt == nitend) )    & 
    176          t_oce_co2_flx  = glob_sum( 'p4zflx', oce_co2(:,:) )                    !  Total Flux of Carbon 
     175         t_oce_co2_flx  = glob_sum( 'p4zflx', oce_co2(:,:) * e1e2t(:,:) * 1000. )                    !  Total Flux of Carbon 
    177176      t_oce_co2_flx_cum = t_oce_co2_flx_cum + t_oce_co2_flx       !  Cumulative Total Flux of Carbon 
    178177!      t_atm_co2_flx     = glob_sum( 'p4zflx', satmco2(:,:) * e1e2t(:,:) )       ! Total atmospheric pCO2 
     
    186185 
    187186      IF( lk_iomput .AND. knt == nrdttrc ) THEN 
    188          ALLOCATE( zw2d(jpi,jpj) )   
    189          IF( iom_use( "Cflx"  ) )  THEN 
    190             zw2d(:,:) = oce_co2(:,:) / e1e2t(:,:) * rfact2r 
    191             CALL iom_put( "Cflx"     , zw2d )  
    192          ENDIF 
    193          IF( iom_use( "Oflx"  ) )  THEN 
    194             zw2d(:,:) =  zoflx(:,:) * 1000 * tmask(:,:,1) 
    195             CALL iom_put( "Oflx" , zw2d ) 
    196          ENDIF 
    197          IF( iom_use( "Kg"    ) )  THEN 
    198             zw2d(:,:) =  zkgco2(:,:) * tmask(:,:,1) 
    199             CALL iom_put( "Kg"   , zw2d ) 
    200          ENDIF 
    201          IF( iom_use( "Dpco2" ) ) THEN 
    202            zw2d(:,:) = ( zpco2atm(:,:) - zh2co3(:,:) / ( chemc(:,:,1) + rtrn ) ) * tmask(:,:,1) 
    203            CALL iom_put( "Dpco2" ,  zw2d ) 
    204          ENDIF 
    205          IF( iom_use( "Dpo2" ) )  THEN 
    206            zw2d(:,:) = ( atcox * patm(:,:) - atcox * trb(:,:,1,jpoxy) / ( chemo2(:,:,1) + rtrn ) ) * tmask(:,:,1) 
    207            CALL iom_put( "Dpo2"  , zw2d ) 
    208          ENDIF 
    209          CALL iom_put( "tcflx"    , t_oce_co2_flx * rfact2r )   ! molC/s 
    210          CALL iom_put( "tcflxcum" , t_oce_co2_flx_cum       )   ! molC 
    211          ! 
    212          DEALLOCATE( zw2d ) 
     187         CALL iom_put( "AtmCo2"  , satmco2(:,:) * tmask(:,:,1) )   ! Atmospheric CO2 concentration 
     188         CALL iom_put( "Cflx"    , oce_co2(:,:) * 1000. )  
     189         CALL iom_put( "Oflx"    , zoflx(:,:) * 1000.  ) 
     190         CALL iom_put( "Kg"      , zkgco2(:,:) * tmask(:,:,1)  ) 
     191         CALL iom_put( "Dpco2"   , ( zpco2atm(:,:) - zh2co3(:,:) / ( chemc(:,:,1) + rtrn ) ) * tmask(:,:,1) ) 
     192         CALL iom_put( "pCO2sea" , ( zh2co3(:,:) / ( chemc(:,:,1) + rtrn ) ) * tmask(:,:,1) ) 
     193         CALL iom_put( "Dpo2"    , ( atcox * patm(:,:) - atcox * trb(:,:,1,jpoxy) / ( chemo2(:,:,1) + rtrn ) ) * tmask(:,:,1) ) 
     194         CALL iom_put( "tcflx"   , t_oce_co2_flx     )   ! molC/s 
     195         CALL iom_put( "tcflxcum", t_oce_co2_flx_cum )   ! molC 
    213196      ENDIF 
    214197      ! 
     
    239222      ENDIF 
    240223      ! 
    241       REWIND( numnatp_ref )              ! Namelist nampisext in reference namelist : Pisces atm. conditions 
     224      REWIND( numnatp_ref ) 
    242225      READ  ( numnatp_ref, nampisext, IOSTAT = ios, ERR = 901) 
    243226901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisext in reference namelist' ) 
    244       REWIND( numnatp_cfg )              ! Namelist nampisext in configuration namelist : Pisces atm. conditions 
     227 
     228      REWIND( numnatp_cfg ) 
    245229      READ  ( numnatp_cfg, nampisext, IOSTAT = ios, ERR = 902 ) 
    246230902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisext in configuration namelist' ) 
     
    320304         ENDIF 
    321305         ! 
    322          REWIND( numnatp_ref )              ! Namelist nampisatm in reference namelist : Pisces atm. sea level pressure file 
    323306         READ  ( numnatp_ref, nampisatm, IOSTAT = ios, ERR = 901) 
    324307901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisatm in reference namelist' ) 
    325          REWIND( numnatp_cfg )              ! Namelist nampisatm in configuration namelist : Pisces atm. sea level pressure file  
    326308         READ  ( numnatp_cfg, nampisatm, IOSTAT = ios, ERR = 902 ) 
    327309902      IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisatm in configuration namelist' ) 
Note: See TracChangeset for help on using the changeset viewer.