MODULE p4zflx !!====================================================================== !! *** MODULE p4zflx *** !! TOP : PISCES CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE !!====================================================================== !! History : - ! 1988-07 (E. MAIER-REIMER) Original code !! - ! 1998 (O. Aumont) additions !! - ! 1999 (C. Le Quere) modifications !! 1.0 ! 2004 (O. Aumont) modifications !! 2.0 ! 2007-12 (C. Ethe, G. Madec) F90 !!---------------------------------------------------------------------- #if defined key_pisces !!---------------------------------------------------------------------- !! 'key_pisces' PISCES bio-model !!---------------------------------------------------------------------- !! p4z_flx : CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE !! p4z_flx_init : Read the namelist !!---------------------------------------------------------------------- USE trc USE oce_trc ! USE trc USE sms_pisces USE prtctl_trc USE p4zche USE iom #if defined key_cpl_carbon_cycle USE sbc_oce , ONLY : atm_co2 #endif USE lib_mpp IMPLICIT NONE PRIVATE PUBLIC p4z_flx REAL(wp) :: & ! pre-industrial atmospheric [co2] (ppm) atcox = 0.20946 , & !: atcco2 = 278. !: REAL(wp) :: & xconv = 0.01/3600 !: coefficients for conversion INTEGER :: nspyr !: number of timestep per year #if defined key_cpl_carbon_cycle REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: & oce_co2 !: ocean carbon flux REAL(wp) :: & t_atm_co2_flx, & !: Total atmospheric carbon flux per year t_oce_co2_flx !: Total ocean carbon flux per year #endif !!* Substitution # include "top_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007) !! $Id: p4zflx.F90 1830 2010-04-12 13:03:51Z cetlod $ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE p4z_flx ( kt ) !!--------------------------------------------------------------------- !! *** ROUTINE p4z_flx *** !! !! ** Purpose : CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE !! !! ** Method : - ??? !!--------------------------------------------------------------------- INTEGER, INTENT(in) :: kt INTEGER :: ji, jj, jrorr REAL(wp) :: ztc, ztc2, ztc3, zws, zkgwan REAL(wp) :: zfld, zflu, zfld16, zflu16, zfact REAL(wp) :: zph, zah2, zbot, zdic, zalk, zsch_o2, zalka, zsch_co2 REAL(wp), DIMENSION(jpi,jpj) :: zkgco2, zkgo2, zh2co3 #if defined key_trc_diaadd && defined key_iomput REAL(wp), DIMENSION(jpi,jpj) :: zcflx, zoflx, zkg, zdpco2, zdpo2 #endif CHARACTER (len=25) :: charout !!--------------------------------------------------------------------- IF( kt == nittrc000 ) CALL p4z_flx_init ! Initialization (first time-step only) ! SURFACE CHEMISTRY (PCO2 AND [H+] IN ! SURFACE LAYER); THE RESULT OF THIS CALCULATION ! IS USED TO COMPUTE AIR-SEA FLUX OF CO2 DO jrorr = 1, 10 !CDIR NOVERRCHK DO jj = 1, jpj !CDIR NOVERRCHK DO ji = 1, jpi ! DUMMY VARIABLES FOR DIC, H+, AND BORATE zbot = borat(ji,jj,1) zfact = rhop(ji,jj,1) / 1000. + rtrn zdic = trn(ji,jj,1,jpdic) / zfact zph = MAX( hi(ji,jj,1), 1.e-10 ) / zfact zalka = trn(ji,jj,1,jptal) / zfact ! CALCULATE [ALK]([CO3--], [HCO3-]) zalk = zalka - ( akw3(ji,jj,1) / zph - zph + zbot / ( 1.+ zph / akb3(ji,jj,1) ) ) ! CALCULATE [H+] AND [H2CO3] zah2 = SQRT( (zdic-zalk)**2 + 4.* ( zalk * ak23(ji,jj,1) & & / ak13(ji,jj,1) ) * ( 2.* zdic - zalk ) ) zah2 = 0.5 * ak13(ji,jj,1) / zalk * ( ( zdic - zalk ) + zah2 ) zh2co3(ji,jj) = ( 2.* zdic - zalk ) / ( 2.+ ak13(ji,jj,1) / zah2 ) * zfact hi(ji,jj,1) = zah2 * zfact END DO END DO END DO ! -------------- ! COMPUTE FLUXES ! -------------- ! FIRST COMPUTE GAS EXCHANGE COEFFICIENTS ! ------------------------------------------- !CDIR NOVERRCHK DO jj = 1, jpj !CDIR NOVERRCHK DO ji = 1, jpi ztc = MIN( 35., tn(ji,jj,1) ) ztc2 = ztc * ztc ztc3 = ztc * ztc2 ! Compute the schmidt Number both O2 and CO2 zsch_co2 = 2073.1 - 125.62 * ztc + 3.6276 * ztc2 - 0.043126 * ztc3 zsch_o2 = 1953.4 - 128.0 * ztc + 3.9918 * ztc2 - 0.050091 * ztc3 ! wind speed zws = wndm(ji,jj) * wndm(ji,jj) ! Compute the piston velocity for O2 and CO2 zkgwan = 0.3 * zws + 2.5 * ( 0.5246 + 0.016256 * ztc + 0.00049946 * ztc2 ) # if defined key_off_degrad zkgwan = zkgwan * xconv * ( 1.- fr_i(ji,jj) ) * tmask(ji,jj,1) * facvol(ji,jj,1) #else zkgwan = zkgwan * xconv * ( 1.- fr_i(ji,jj) ) * tmask(ji,jj,1) #endif ! compute gas exchange for CO2 and O2 zkgco2(ji,jj) = zkgwan * SQRT( 660./ zsch_co2 ) zkgo2 (ji,jj) = zkgwan * SQRT( 660./ zsch_o2 ) END DO END DO DO jj = 1, jpj DO ji = 1, jpi ! Compute CO2 flux for the sea and air #if ! defined key_cpl_carbon_cycle zfld = atcco2 * tmask(ji,jj,1) * chemc(ji,jj,1) * zkgco2(ji,jj) zflu = zh2co3(ji,jj) * tmask(ji,jj,1) * zkgco2(ji,jj) #else zfld = atm_co2(ji,jj) * tmask(ji,jj,1) * chemc(ji,jj,1) * zkgco2(ji,jj) zflu = zh2co3(ji,jj) * tmask(ji,jj,1) * zkgco2(ji,jj) ! compute flux of carbon oce_co2(ji,jj) = ( zfld - zflu ) * rfact & & * e1t(ji,jj) * e2t(ji,jj) * tmask(ji,jj,1) * 1000. #endif tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) / fse3t(ji,jj,1) ! Compute O2 flux zfld16 = atcox * chemc(ji,jj,2) * tmask(ji,jj,1) * zkgo2(ji,jj) zflu16 = trn(ji,jj,1,jpoxy) * tmask(ji,jj,1) * zkgo2(ji,jj) tra(ji,jj,1,jpoxy) = tra(ji,jj,1,jpoxy) + ( zfld16 - zflu16 ) / fse3t(ji,jj,1) #if defined key_trc_diaadd ! Save diagnostics # if ! defined key_iomput trc2d(ji,jj,jp_pcs0_2d ) = ( zfld - zflu ) * 1000. * tmask(ji,jj,1) trc2d(ji,jj,jp_pcs0_2d + 1) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1) trc2d(ji,jj,jp_pcs0_2d + 2) = zkgco2(ji,jj) * tmask(ji,jj,1) trc2d(ji,jj,jp_pcs0_2d + 3) = ( atcco2 - zh2co3(ji,jj) / ( chemc(ji,jj,1) + rtrn ) ) & & * tmask(ji,jj,1) # else zcflx(ji,jj) = ( zfld - zflu ) * 1000. * tmask(ji,jj,1) zoflx(ji,jj) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1) zkg (ji,jj) = zkgco2(ji,jj) * tmask(ji,jj,1) zdpco2(ji,jj) = ( atcco2 - zh2co3(ji,jj) / ( chemc(ji,jj,1) + rtrn ) ) & & * tmask(ji,jj,1) zdpo2 (ji,jj) = ( atcox - trn(ji,jj,1,jpoxy) / ( chemc(ji,jj,2) + rtrn ) ) & & * tmask(ji,jj,1) # endif #endif END DO END DO #if defined key_cpl_carbon_cycle ! Total Flux of Carbon DO jj = 1, jpj DO ji = 1, jpi t_atm_co2_flx = t_atm_co2_flx + atm_co2(ji,jj) * tmask_i(ji,jj) t_oce_co2_flx = t_oce_co2_flx + oce_co2(ji,jj) * tmask_i(ji,jj) END DO END DO IF( MOD( kt, nspyr ) == 0 ) THEN IF( lk_mpp ) THEN CALL mpp_sum( t_atm_co2_flx ) ! sum over the global domain CALL mpp_sum( t_oce_co2_flx ) ! sum over the global domain ENDIF ! Conversion in GtC/yr ; negative for outgoing from ocean t_oce_co2_flx = (-1.) * t_oce_co2_flx * 12. / 1.e15 ! WRITE(numout,*) ' Atmospheric pCO2 :' WRITE(numout,*) '-------------------- : ',kt,' ',t_atm_co2_flx WRITE(numout,*) '(ppm)' WRITE(numout,*) 'Total Flux of Carbon out of the ocean :' WRITE(numout,*) '-------------------- : ',t_oce_co2_flx WRITE(numout,*) '(GtC/yr)' t_atm_co2_flx = 0. t_oce_co2_flx = 0. # if defined key_iomput CALL iom_put( "tatpco2" , t_atm_co2_flx ) CALL iom_put( "tco2flx" , t_oce_co2_flx ) #endif ENDIF #endif IF(ln_ctl) THEN ! print mean trends (used for debugging) WRITE(charout, FMT="('flx ')") CALL prt_ctl_trc_info(charout) CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) ENDIF # if defined key_trc_diaadd && defined key_iomput CALL iom_put( "Cflx" , zcflx ) CALL iom_put( "Oflx" , zoflx ) CALL iom_put( "Kg" , zkg ) CALL iom_put( "Dpco2", zdpco2 ) CALL iom_put( "Dpo2" , zdpo2 ) #endif END SUBROUTINE p4z_flx SUBROUTINE p4z_flx_init !!---------------------------------------------------------------------- !! *** ROUTINE p4z_flx_init *** !! !! ** Purpose : Initialization of atmospheric conditions !! !! ** Method : Read the nampisext namelist and check the parameters !! called at the first timestep (nittrc000) !! ** input : Namelist nampisext !! !!---------------------------------------------------------------------- NAMELIST/nampisext/ atcco2 REWIND( numnat ) ! read numnat READ ( numnat, nampisext ) IF(lwp) THEN ! control print WRITE(numout,*) ' ' WRITE(numout,*) ' Namelist parameters for air-sea exchange, nampisext' WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' WRITE(numout,*) ' Atmospheric pCO2 atcco2 =', atcco2 ENDIF ! number of time step per year nspyr = INT( nyear_len(1) * rday / rdt ) #if defined key_cpl_carbon_cycle ! Initialization of Flux of Carbon oce_co2(:,:) = 0. t_atm_co2_flx = 0. t_oce_co2_flx = 0. #endif END SUBROUTINE p4z_flx_init #else !!====================================================================== !! Dummy module : No PISCES bio-model !!====================================================================== CONTAINS SUBROUTINE p4z_flx( kt ) ! Empty routine INTEGER, INTENT( in ) :: kt WRITE(*,*) 'p4z_flx: You should not have seen this print! error?', kt END SUBROUTINE p4z_flx #endif !!====================================================================== END MODULE p4zflx