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 2457 for branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zflx.F90 – NEMO

Ignore:
Timestamp:
2010-12-07T10:51:47+01:00 (13 years ago)
Author:
cetlod
Message:

Improve TOP & OFF components in v3.3beta, see ticket #774

File:
1 edited

Legend:

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

    r2287 r2457  
    2828#endif 
    2929   USE lib_mpp 
     30   USE lib_fortran 
    3031 
    3132   IMPLICIT NONE 
     
    3536   PUBLIC   p4z_flx_init   
    3637 
    37    REAL(wp) :: &  ! pre-industrial atmospheric [co2] (ppm)   
    38       atcox  = 0.20946 ,    &  !: 
    39       atcco2 = 278.            !: 
    40  
    41    REAL(wp) :: & 
    42       xconv  = 0.01/3600      !: coefficients for conversion  
    43  
    44    INTEGER  ::  nspyr         !: number of timestep per year 
    45  
    46 #if defined key_cpl_carbon_cycle 
    47    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  & 
    48       oce_co2            !: ocean carbon flux 
    49    REAL(wp) :: & 
    50       t_atm_co2_flx,  &  !: Total atmospheric carbon flux per year 
    51       t_oce_co2_flx      !: Total ocean carbon flux per year 
    52 #endif 
     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  
    5346 
    5447   !!* Substitution 
     
    7770      REAL(wp), DIMENSION(jpi,jpj) ::   zkgco2, zkgo2, zh2co3 
    7871#if defined key_diatrc && defined key_iomput 
    79       REAL(wp), DIMENSION(jpi,jpj) ::  zcflx, zoflx, zkg, zdpco2, zdpo2 
     72      REAL(wp), DIMENSION(jpi,jpj) ::  zoflx, zkg, zdpco2, zdpo2 
    8073#endif 
    8174      CHARACTER (len=25) :: charout 
     
    8679      !     SURFACE LAYER); THE RESULT OF THIS CALCULATION 
    8780      !     IS USED TO COMPUTE AIR-SEA FLUX OF CO2 
     81 
     82#if defined key_cpl_carbon_cycle 
     83      satmco2(:,:) = atm_co2(:,:) 
     84#endif 
    8885 
    8986      DO jrorr = 1, 10 
     
    150147         DO ji = 1, jpi 
    151148            ! Compute CO2 flux for the sea and air 
    152 #if ! defined key_cpl_carbon_cycle 
    153             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) 
    154150            zflu = zh2co3(ji,jj) * tmask(ji,jj,1) * zkgco2(ji,jj) 
    155 #else 
    156             zfld = atm_co2(ji,jj) * tmask(ji,jj,1) * chemc(ji,jj,1) * zkgco2(ji,jj) 
    157             zflu = zh2co3(ji,jj) * tmask(ji,jj,1) * zkgco2(ji,jj) 
    158             ! compute flux of carbon 
    159151            oce_co2(ji,jj) = ( zfld - zflu ) * rfact & 
    160152               &             * e1t(ji,jj) * e2t(ji,jj) * tmask(ji,jj,1) * 1000. 
    161 #endif 
     153            ! compute the trend 
    162154            tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) / fse3t(ji,jj,1) 
    163155 
     
    170162            ! Save diagnostics 
    171163#  if ! defined key_iomput 
    172             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 
    173166            trc2d(ji,jj,jp_pcs0_2d + 1) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1) 
    174167            trc2d(ji,jj,jp_pcs0_2d + 2) = zkgco2(ji,jj) * tmask(ji,jj,1) 
    175             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 ) ) & 
    176169               &                            * tmask(ji,jj,1) 
    177170#  else 
    178             zcflx(ji,jj) = ( zfld - zflu ) * 1000.  * tmask(ji,jj,1) 
    179171            zoflx(ji,jj) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1) 
    180172            zkg  (ji,jj) = zkgco2(ji,jj) * tmask(ji,jj,1) 
    181             zdpco2(ji,jj) = ( atcco2 - zh2co3(ji,jj)      / ( chemc(ji,jj,1) + rtrn ) ) & 
    182               &             * tmask(ji,jj,1) 
    183             zdpo2 (ji,jj) = ( atcox  - trn(ji,jj,1,jpoxy) / ( chemc(ji,jj,2) + rtrn ) ) & 
    184               &             * 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) 
    185175#  endif 
    186176#endif 
     
    188178      END DO 
    189179 
    190 #if defined key_cpl_carbon_cycle 
    191       ! Total Flux of Carbon 
    192       DO jj = 1, jpj  
    193         DO ji = 1, jpi 
    194            t_atm_co2_flx = t_atm_co2_flx + atm_co2(ji,jj) * tmask_i(ji,jj) 
    195            t_oce_co2_flx = t_oce_co2_flx + oce_co2(ji,jj) * tmask_i(ji,jj) 
    196         END DO 
    197       END DO 
    198  
    199       IF( MOD( kt, nspyr ) == 0 ) THEN 
    200         IF( lk_mpp ) THEN 
    201           CALL mpp_sum( t_atm_co2_flx )   ! sum over the global domain 
    202           CALL mpp_sum( t_oce_co2_flx )   ! sum over the global domain 
    203         ENDIF 
    204         ! Conversion in GtC/yr ; negative for outgoing from ocean 
    205         t_oce_co2_flx = (-1.) * t_oce_co2_flx  * 12. / 1.e15 
    206         ! 
    207         WRITE(numout,*) ' Atmospheric pCO2    :' 
    208         WRITE(numout,*) '-------------------- : ',kt,'  ',t_atm_co2_flx 
    209         WRITE(numout,*) '(ppm)' 
    210         WRITE(numout,*) 'Total Flux of Carbon out of the ocean :' 
    211         WRITE(numout,*) '-------------------- : ',t_oce_co2_flx 
    212         WRITE(numout,*) '(GtC/yr)' 
    213         t_atm_co2_flx = 0. 
    214         t_oce_co2_flx = 0. 
    215 # if defined key_iomput 
    216         CALL iom_put( "tatpco2" , t_atm_co2_flx  ) 
    217         CALL iom_put( "tco2flx" , t_oce_co2_flx  ) 
    218 #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         ! 
    219196      ENDIF 
    220 #endif 
    221197 
    222198      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     
    227203 
    228204# if defined key_diatrc && defined key_iomput 
    229       CALL iom_put( "Cflx" , zcflx  ) 
     205      CALL iom_put( "Cflx" , oce_co2(:,:) / ( e1t(:,:) * e2t(:,:) ) / rfact  ) 
    230206      CALL iom_put( "Oflx" , zoflx  ) 
    231207      CALL iom_put( "Kg"   , zkg    ) 
     
    261237      ENDIF 
    262238 
    263       ! number of time step per year   
    264       nspyr = INT( nyear_len(1) * rday / rdt ) 
    265  
    266 #if defined key_cpl_carbon_cycle 
     239      ! interior global domain surface 
     240      area = glob_sum( e1t(:,:) * e2t(:,:) )   
     241 
    267242      ! Initialization of Flux of Carbon 
    268       oce_co2(:,:) = 0. 
    269       t_atm_co2_flx = 0. 
    270       t_oce_co2_flx = 0. 
    271 #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 
    272248 
    273249   END SUBROUTINE p4z_flx_init 
Note: See TracChangeset for help on using the changeset viewer.