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 2528 for trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zflx.F90 – NEMO

Ignore:
Timestamp:
2010-12-27T18:33:53+01:00 (13 years ago)
Author:
rblod
Message:

Update NEMOGCM from branch nemo_v3_3_beta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zflx.F90

    • Property svn:executable deleted
    r1836 r2528  
    2828#endif 
    2929   USE lib_mpp 
     30   USE lib_fortran 
    3031 
    3132   IMPLICIT NONE 
     
    3334 
    3435   PUBLIC   p4z_flx   
    35  
    36    REAL(wp) :: &  ! pre-industrial atmospheric [co2] (ppm)   
    37       atcox  = 0.20946 ,    &  !: 
    38       atcco2 = 278.            !: 
    39  
    40    REAL(wp) :: & 
    41       xconv  = 0.01/3600      !: coefficients for conversion  
    42  
    43    INTEGER  ::  nspyr         !: number of timestep per year 
    44  
    45 #if defined key_cpl_carbon_cycle 
    46    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  & 
    47       oce_co2            !: ocean carbon flux 
    48    REAL(wp) :: & 
    49       t_atm_co2_flx,  &  !: Total atmospheric carbon flux per year 
    50       t_oce_co2_flx      !: Total ocean carbon flux per year 
    51 #endif 
     36   PUBLIC   p4z_flx_init   
     37 
     38   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  oce_co2            !: ocean carbon flux  
     39   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  satmco2            !: atmospheric pco2 
     40   REAL(wp)                             ::  t_oce_co2_flx      !: Total ocean carbon flux  
     41   REAL(wp)                             ::  t_atm_co2_flx      !: global mean of atmospheric pco2 
     42   REAL(wp)                             ::  area               !: ocean surface 
     43   REAL(wp)                             ::  atcco2 = 278.      !: pre-industrial atmospheric [co2] (ppm)     
     44   REAL(wp)                             ::  atcox  = 0.20946   !: 
     45   REAL(wp)                             ::  xconv  = 0.01/3600 !: coefficients for conversion  
    5246 
    5347   !!* Substitution 
    5448#  include "top_substitute.h90" 
    5549   !!---------------------------------------------------------------------- 
    56    !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)  
     50   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    5751   !! $Id$  
    58    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     52   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    5953   !!---------------------------------------------------------------------- 
    6054 
     
    7569      REAL(wp) ::   zph, zah2, zbot, zdic, zalk, zsch_o2, zalka, zsch_co2 
    7670      REAL(wp), DIMENSION(jpi,jpj) ::   zkgco2, zkgo2, zh2co3 
    77 #if defined key_trc_diaadd && defined key_iomput 
    78       REAL(wp), DIMENSION(jpi,jpj) ::  zcflx, zoflx, zkg, zdpco2, zdpo2 
     71#if defined key_diatrc && defined key_iomput 
     72      REAL(wp), DIMENSION(jpi,jpj) ::  zoflx, zkg, zdpco2, zdpo2 
    7973#endif 
    8074      CHARACTER (len=25) :: charout 
    8175 
    8276      !!--------------------------------------------------------------------- 
    83  
    84  
    85       IF( kt == nittrc000  )   CALL p4z_flx_init      ! Initialization (first time-step only) 
    8677 
    8778      ! SURFACE CHEMISTRY (PCO2 AND [H+] IN 
    8879      !     SURFACE LAYER); THE RESULT OF THIS CALCULATION 
    8980      !     IS USED TO COMPUTE AIR-SEA FLUX OF CO2 
     81 
     82#if defined key_cpl_carbon_cycle 
     83      satmco2(:,:) = atm_co2(:,:) 
     84#endif 
    9085 
    9186      DO jrorr = 1, 10 
     
    128123!CDIR NOVERRCHK 
    129124         DO ji = 1, jpi 
    130             ztc  = MIN( 35., tn(ji,jj,1) ) 
     125            ztc  = MIN( 35., tsn(ji,jj,1,jp_tem) ) 
    131126            ztc2 = ztc * ztc 
    132127            ztc3 = ztc * ztc2  
     
    138133            ! Compute the piston velocity for O2 and CO2 
    139134            zkgwan = 0.3 * zws  + 2.5 * ( 0.5246 + 0.016256 * ztc + 0.00049946  * ztc2 ) 
    140 # if defined key_off_degrad 
     135# if defined key_degrad 
    141136            zkgwan = zkgwan * xconv * ( 1.- fr_i(ji,jj) ) * tmask(ji,jj,1) * facvol(ji,jj,1) 
    142137#else 
     
    152147         DO ji = 1, jpi 
    153148            ! Compute CO2 flux for the sea and air 
    154 #if ! defined key_cpl_carbon_cycle 
    155             zfld = atcco2 * tmask(ji,jj,1) * chemc(ji,jj,1) * zkgco2(ji,jj) 
     149            zfld = satmco2(ji,jj) * tmask(ji,jj,1) * chemc(ji,jj,1) * zkgco2(ji,jj) 
    156150            zflu = zh2co3(ji,jj) * tmask(ji,jj,1) * zkgco2(ji,jj) 
    157 #else 
    158             zfld = atm_co2(ji,jj) * tmask(ji,jj,1) * chemc(ji,jj,1) * zkgco2(ji,jj) 
    159             zflu = zh2co3(ji,jj) * tmask(ji,jj,1) * zkgco2(ji,jj) 
    160             ! compute flux of carbon 
    161151            oce_co2(ji,jj) = ( zfld - zflu ) * rfact & 
    162152               &             * e1t(ji,jj) * e2t(ji,jj) * tmask(ji,jj,1) * 1000. 
    163 #endif 
     153            ! compute the trend 
    164154            tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) / fse3t(ji,jj,1) 
    165155 
     
    169159            tra(ji,jj,1,jpoxy) = tra(ji,jj,1,jpoxy) + ( zfld16 - zflu16 ) / fse3t(ji,jj,1) 
    170160 
    171 #if defined key_trc_diaadd  
     161#if defined key_diatrc  
    172162            ! Save diagnostics 
    173163#  if ! defined key_iomput 
    174             trc2d(ji,jj,jp_pcs0_2d    ) = ( zfld - zflu )     * 1000. * tmask(ji,jj,1) 
     164            zfact = 1. / ( e1t(ji,jj) * e2t(ji,jj) ) / rfact 
     165            trc2d(ji,jj,jp_pcs0_2d    ) = oce_co2(ji,jj) * zfact 
    175166            trc2d(ji,jj,jp_pcs0_2d + 1) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1) 
    176167            trc2d(ji,jj,jp_pcs0_2d + 2) = zkgco2(ji,jj) * tmask(ji,jj,1) 
    177             trc2d(ji,jj,jp_pcs0_2d + 3) = ( atcco2 - zh2co3(ji,jj) / ( chemc(ji,jj,1) + rtrn ) ) & 
     168            trc2d(ji,jj,jp_pcs0_2d + 3) = ( satmco2(ji,jj) - zh2co3(ji,jj) / ( chemc(ji,jj,1) + rtrn ) ) & 
    178169               &                            * tmask(ji,jj,1) 
    179170#  else 
    180             zcflx(ji,jj) = ( zfld - zflu ) * 1000.  * tmask(ji,jj,1) 
    181171            zoflx(ji,jj) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1) 
    182172            zkg  (ji,jj) = zkgco2(ji,jj) * tmask(ji,jj,1) 
    183             zdpco2(ji,jj) = ( atcco2 - zh2co3(ji,jj)      / ( chemc(ji,jj,1) + rtrn ) ) & 
    184               &             * tmask(ji,jj,1) 
    185             zdpo2 (ji,jj) = ( atcox  - trn(ji,jj,1,jpoxy) / ( chemc(ji,jj,2) + rtrn ) ) & 
    186               &             * tmask(ji,jj,1) 
     173            zdpco2(ji,jj) = ( satmco2(ji,jj) - zh2co3(ji,jj) / ( chemc(ji,jj,1) + rtrn ) ) * tmask(ji,jj,1) 
     174            zdpo2 (ji,jj) = ( atcox  - trn(ji,jj,1,jpoxy) / ( chemc(ji,jj,2) + rtrn ) ) * tmask(ji,jj,1) 
    187175#  endif 
    188176#endif 
     
    190178      END DO 
    191179 
    192 #if defined key_cpl_carbon_cycle 
    193       ! Total Flux of Carbon 
    194       DO jj = 1, jpj  
    195         DO ji = 1, jpi 
    196            t_atm_co2_flx = t_atm_co2_flx + atm_co2(ji,jj) * tmask_i(ji,jj) 
    197            t_oce_co2_flx = t_oce_co2_flx + oce_co2(ji,jj) * tmask_i(ji,jj) 
    198         END DO 
    199       END DO 
    200  
    201       IF( MOD( kt, nspyr ) == 0 ) THEN 
    202         IF( lk_mpp ) THEN 
    203           CALL mpp_sum( t_atm_co2_flx )   ! sum over the global domain 
    204           CALL mpp_sum( t_oce_co2_flx )   ! sum over the global domain 
    205         ENDIF 
    206         ! Conversion in GtC/yr ; negative for outgoing from ocean 
    207         t_oce_co2_flx = (-1.) * t_oce_co2_flx  * 12. / 1.e15 
    208         ! 
    209         WRITE(numout,*) ' Atmospheric pCO2    :' 
    210         WRITE(numout,*) '-------------------- : ',kt,'  ',t_atm_co2_flx 
    211         WRITE(numout,*) '(ppm)' 
    212         WRITE(numout,*) 'Total Flux of Carbon out of the ocean :' 
    213         WRITE(numout,*) '-------------------- : ',t_oce_co2_flx 
    214         WRITE(numout,*) '(GtC/yr)' 
    215         t_atm_co2_flx = 0. 
    216         t_oce_co2_flx = 0. 
    217 # if defined key_iomput 
    218         CALL iom_put( "tatpco2" , t_atm_co2_flx  ) 
    219         CALL iom_put( "tco2flx" , t_oce_co2_flx  ) 
    220 #endif 
     180      t_oce_co2_flx = t_oce_co2_flx + glob_sum( oce_co2(:,:) )                     ! Cumulative Total Flux of Carbon 
     181      IF( kt == nitend ) THEN 
     182         t_atm_co2_flx = glob_sum( satmco2(:,:) * e1t(:,:) * e2t(:,:) )            ! Total atmospheric pCO2 
     183         ! 
     184         t_oce_co2_flx = (-1.) * t_oce_co2_flx  * 12. / 1.e15                      ! Conversion in PgC ; negative for out of the ocean 
     185         t_atm_co2_flx = t_atm_co2_flx  / area                                     ! global mean of atmospheric pCO2 
     186         ! 
     187         IF( lwp) THEN 
     188            WRITE(numout,*) 
     189            WRITE(numout,*) ' Global mean of atmospheric pCO2 (ppm) at it= ', kt, ' date= ', ndastp 
     190            WRITE(numout,*) '------------------------------------------------------- :  ',t_atm_co2_flx 
     191            WRITE(numout,*) 
     192            WRITE(numout,*) ' Cumulative total Flux of Carbon out of the ocean (PgC) :' 
     193            WRITE(numout,*) '-------------------------------------------------------  ',t_oce_co2_flx 
     194         ENDIF 
     195         ! 
    221196      ENDIF 
    222 #endif 
    223197 
    224198      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     
    228202      ENDIF 
    229203 
    230 # if defined key_trc_diaadd && defined key_iomput 
    231       CALL iom_put( "Cflx" , zcflx  ) 
     204# if defined key_diatrc && defined key_iomput 
     205      CALL iom_put( "Cflx" , oce_co2(:,:) / ( e1t(:,:) * e2t(:,:) ) / rfact  ) 
    232206      CALL iom_put( "Oflx" , zoflx  ) 
    233207      CALL iom_put( "Kg"   , zkg    ) 
     
    246220      !! 
    247221      !! ** Method  :   Read the nampisext namelist and check the parameters 
    248       !!      called at the first timestep (nittrc000) 
     222      !!      called at the first timestep (nit000) 
    249223      !! ** input   :   Namelist nampisext 
    250224      !! 
     
    263237      ENDIF 
    264238 
    265       ! number of time step per year   
    266       nspyr = INT( nyear_len(1) * rday / rdt ) 
    267  
    268 #if defined key_cpl_carbon_cycle 
     239      ! interior global domain surface 
     240      area = glob_sum( e1t(:,:) * e2t(:,:) )   
     241 
    269242      ! Initialization of Flux of Carbon 
    270       oce_co2(:,:) = 0. 
    271       t_atm_co2_flx = 0. 
    272       t_oce_co2_flx = 0. 
    273 #endif 
     243      oce_co2(:,:)  = 0._wp 
     244      t_atm_co2_flx = 0._wp 
     245      ! Initialisation of atmospheric pco2 
     246      satmco2(:,:)  = atcco2 
     247      t_oce_co2_flx = 0._wp 
    274248 
    275249   END SUBROUTINE p4z_flx_init 
Note: See TracChangeset for help on using the changeset viewer.