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 2504 for branches/CMIP5_IPSL/NEMO – NEMO

Ignore:
Timestamp:
2010-12-23T09:18:45+01:00 (13 years ago)
Author:
cetlod
Message:

Computation of monthly mean ocean carbon flux in PISCES

Location:
branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES
Files:
2 edited

Legend:

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

    r1830 r2504  
    4141      xconv  = 0.01/3600      !: coefficients for conversion  
    4242 
    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 
     43   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  oce_co2            !: ocean carbon flux  
     44   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  satmco2            !: atmospheric pco2 
     45   REAL(wp)                             ::  t_oce_co2_flx      !: Total ocean carbon flux  
     46   REAL(wp)                             ::  t_atm_co2_flx      !: global mean of atmospheric pco2 
     47   REAL(wp)                             ::  area               !: ocean surface 
    5248 
    5349   !!* Substitution 
     
    8884      !     SURFACE LAYER); THE RESULT OF THIS CALCULATION 
    8985      !     IS USED TO COMPUTE AIR-SEA FLUX OF CO2 
     86 
     87#if defined key_cpl_carbon_cycle 
     88      satmco2(:,:) = atm_co2(:,:) 
     89#endif 
    9090 
    9191      DO jrorr = 1, 10 
     
    152152         DO ji = 1, jpi 
    153153            ! 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) 
     154            zfld = satmco2(ji,jj) * tmask(ji,jj,1) * chemc(ji,jj,1) * zkgco2(ji,jj) 
    156155            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 
    161156            oce_co2(ji,jj) = ( zfld - zflu ) * rfact & 
    162157               &             * e1t(ji,jj) * e2t(ji,jj) * tmask(ji,jj,1) * 1000. 
    163 #endif 
     158            ! compute the trend 
    164159            tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) / fse3t(ji,jj,1) 
    165160 
     
    175170            trc2d(ji,jj,jp_pcs0_2d + 1) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1) 
    176171            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 ) ) & 
     172            trc2d(ji,jj,jp_pcs0_2d + 3) = ( satmco2(ji,jj) - zh2co3(ji,jj) / ( chemc(ji,jj,1) + rtrn ) ) & 
    178173               &                            * tmask(ji,jj,1) 
    179174#  else 
     
    181176            zoflx(ji,jj) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1) 
    182177            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) 
     178            zdpco2(ji,jj) = ( satmco2(ji,jj) - zh2co3(ji,jj) / ( chemc(ji,jj,1) + rtrn ) ) * tmask(ji,jj,1) 
     179            zdpo2 (ji,jj) = ( atcox  - trn(ji,jj,1,jpoxy) / ( chemc(ji,jj,2) + rtrn ) ) * tmask(ji,jj,1) 
    187180#  endif 
    188181#endif 
     
    190183      END DO 
    191184 
    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 
     185      t_oce_co2_flx = t_oce_co2_flx + SUM( oce_co2(:,:) * tmask_i(:,:) )           ! Cumulative Total Flux of Carbon 
     186      IF( kt == nitend ) THEN 
     187         t_atm_co2_flx = SUM( satmco2(:,:) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) )  ! Total atmospheric pCO2 
     188         ! 
     189         IF( lk_mpp ) THEN                                                         ! sum over the global domain 
     190           CALL mpp_sum( t_atm_co2_flx )    
     191           CALL mpp_sum( t_oce_co2_flx )    
     192         ENDIF 
     193         t_oce_co2_flx = (-1.) * t_oce_co2_flx  * 12. / 1.e15                      ! Conversion in PgC ; negative for out of the ocean 
     194         t_atm_co2_flx = t_atm_co2_flx  / area                                     ! global mean of atmospheric pCO2 
     195         ! 
     196         IF( lwp) THEN 
     197            WRITE(numout,*) 
     198            WRITE(numout,*) ' Global mean of atmospheric pCO2 (ppm) at it= ', kt, ' date= ', ndastp, ' : ',t_atm_co2_flx 
     199            WRITE(numout,*)  
     200            WRITE(numout,*) ' Cumulative total Flux of Carbon out of the ocean (PgC) :' , t_oce_co2_flx 
     201            WRITE(numout,*)  
     202         ENDIF 
     203         ! 
    221204      ENDIF 
    222 #endif 
    223205 
    224206      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     
    263245      ENDIF 
    264246 
    265       ! number of time step per year   
    266       nspyr = INT( nyear_len(1) * rday / rdt ) 
    267  
    268 #if defined key_cpl_carbon_cycle 
     247      ! interior global domain surface 
     248      area = SUM( e1t(:,:) * e2t(:,:) * tmask_i(:,:) ) 
     249      IF( lk_mpp ) CALL mpp_sum( area ) 
     250 
    269251      ! Initialization of Flux of Carbon 
    270252      oce_co2(:,:) = 0. 
    271253      t_atm_co2_flx = 0. 
     254      ! Initialisation of atmospheric pco2 
     255      satmco2(:,:) = atcco2 
    272256      t_oce_co2_flx = 0. 
    273 #endif 
    274257 
    275258   END SUBROUTINE p4z_flx_init 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES/p4zprod.F90

    r1830 r2504  
    4949      rpis180                    ,  &  !: rpi / 180 
    5050      tpp                              !: Total primary production 
    51  
    52    INTEGER  ::  nspyr                  !: number of timesteps per year 
    5351 
    5452   !!* Substitution 
     
    347345      END DO 
    348346 
    349  
    350       IF( MOD( kt, nspyr ) == 0 .AND. jnt == nrdttrc ) THEN 
     347     IF( kt == nitend .AND. jnt == nrdttrc ) THEN 
    351348        IF( lk_mpp ) CALL mpp_sum( tpp ) 
    352         WRITE(numout,*) 'Total PP :' 
     349        WRITE(numout,*) 'Total PP (Gtc) :' 
    353350        WRITE(numout,*) '-------------------- : ',tpp * 12. / 1.E12 
    354         WRITE(numout,*) '(GtC/yr)' 
    355         tpp = 0. 
     351        WRITE(numout,*) 
    356352      ENDIF 
    357353 
     
    469465      ENDIF 
    470466 
    471       ! number of timesteps per year 
    472       nspyr  = INT( nyear_len(1) * rday / rdt ) 
    473  
    474467      rpis180   = rpi / 180. 
    475468      texcret   = 1.0 - excret 
Note: See TracChangeset for help on using the changeset viewer.