MODULE trcsms_cfc !!====================================================================== !! *** MODULE trcsms_cfc *** !! TOP : CFC main model !!====================================================================== !! History : - ! 1999-10 (JC. Dutay) original code !! 1.0 ! 2004-03 (C. Ethe) free form + modularity !! 2.0 ! 2007-12 (C. Ethe, G. Madec) reorganisation !!---------------------------------------------------------------------- #if defined key_cfc !!---------------------------------------------------------------------- !! 'key_cfc' CFC tracers !!---------------------------------------------------------------------- !! trc_sms_cfc : compute and add CFC suface forcing to CFC trends !! trc_cfc_cst : sets constants for CFC surface forcing computation !!---------------------------------------------------------------------- USE daymod ! calendar USE oce_trc ! Ocean variables USE par_trc ! TOP parameters USE trc ! TOP variables IMPLICIT NONE PRIVATE PUBLIC trc_sms_cfc ! called in ??? INTEGER , PUBLIC, PARAMETER :: jpyear = 100 ! temporal parameter INTEGER , PUBLIC, PARAMETER :: jphem = 2 ! parameter for the 2 hemispheres INTEGER , PUBLIC :: ndate_beg ! initial calendar date (aammjj) for CFC INTEGER , PUBLIC :: nyear_res ! restoring time constant (year) INTEGER , PUBLIC :: nyear_beg ! initial year (aa) REAL(wp), PUBLIC, DIMENSION(jpyear,jphem, jp_cfc0:jp_cfc1) :: p_cfc ! partial hemispheric pressure for CFC REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: xphem ! spatial interpolation factor for patm REAL(wp), PUBLIC, DIMENSION(jpi,jpj ,jp_cfc0:jp_cfc1) :: qtr ! input function REAL(wp), PUBLIC, DIMENSION(jpi,jpj ,jp_cfc0:jp_cfc1) :: qint ! flux function REAL(wp), DIMENSION(jp_cfc) :: soa1, soa2, soa3, soa4 ! coefficient for solubility of CFC [mol/l/atm] REAL(wp), DIMENSION(jp_cfc) :: sob1, sob2, sob3 ! " " REAL(wp), DIMENSION(jp_cfc) :: sca1, sca2, sca3, sca4 ! coefficients for schmidt number in degre Celcius ! ! coefficients for conversion REAL(wp) :: xconv1 = 1.0 ! conversion from to REAL(wp) :: xconv2 = 0.01/3600. ! conversion from cm/h to m/s: REAL(wp) :: xconv3 = 1.0e+3 ! conversion from mol/l/atm to mol/m3/atm REAL(wp) :: xconv4 = 1.0e-12 ! conversion from mol/m3/atm to mol/m3/pptv REAL(wp) :: xrhoa = 1.22 ! Air density kg/m3 REAL(wp) :: xcd = 1.5e-3 ! drag coefficient !! * Substitutions # include "top_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007) !! $Id: trccfc.F90 776 2007-12-19 14:10:14Z gm $ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE trc_sms_cfc( kt ) !!---------------------------------------------------------------------- !! *** ROUTINE trc_sms_cfc *** !! !! ** Purpose : Compute the surface boundary contition on CFC 11 !! passive tracer associated with air-mer fluxes and add it !! to the general trend of tracers equations. !! !! ** Method : - get the atmospheric partial pressure - given in pico - !! - computation of solubility ( in 1.e-12 mol/l then in 1.e-9 mol/m3) !! - computation of transfert speed ( given in cm/hour ----> cm/s ) !! - the input function is given by : !! speed * ( concentration at equilibrium - concentration at surface ) !! - the input function is in pico-mol/m3/s and the !! CFC concentration in pico-mol/m3 !!---------------------------------------------------------------------- INTEGER, INTENT( in ) :: kt ! ocean time-step index !! INTEGER :: ji, jj, jn, jm INTEGER :: iyear_beg, iyear_end INTEGER :: im1, im2 REAL(wp) :: ztap, zdtap REAL(wp) :: zt1, zt2, zt3, zv2 REAL(wp) :: zsol ! solubility REAL(wp) :: zsch ! schmidt number REAL(wp) :: zpp_cfc ! atmospheric partial pressure of CFC REAL(wp) :: zca_cfc ! concentration at equilibrium REAL(wp) :: zak_cfc ! transfert coefficients REAL(wp) :: ztx, zty, ztau REAL(wp), DIMENSION(jpi,jpj) :: zws ! wind speed REAL(wp), DIMENSION(jphem,jp_cfc) :: zpatm ! atmospheric function !!---------------------------------------------------------------------- IF( kt == nittrc000 ) CALL trc_cfc_cst ! Temporal interpolation ! ---------------------- iyear_beg = nyear + ( nyear_res - 1900 - nyear_beg ) IF ( nmonth <= 6 ) THEN iyear_beg = iyear_beg - 2 + nyear_beg im1 = 6 - nmonth + 1 im2 = 6 + nmonth - 1 ELSE iyear_beg = iyear_beg - 1 + nyear_beg im1 = 12 - nmonth + 7 im2 = nmonth - 7 ENDIF iyear_end = iyear_beg + 1 ! Estimation of wind speed as a function of wind stress !CDIR NOVERRCHK DO jj = 1, jpj !CDIR NOVERRCHK DO ji = 1, jpi ztx = utau(ji,jj) * umask(ji,jj,1) zty = vtau(ji,jj) * vmask(ji,jj,1) ztau = SQRT( ztx * ztx + zty * zty ) zws(ji,jj) = SQRT ( ztau / ( xrhoa * xcd ) ) ENDDO ENDDO ! !------------! DO jn = jp_cfc0, jp_cfc1 ! CFC loop ! ! !------------! ! time interpolation at time kt DO jm = 1, jphem zpatm(jm,jn) = ( p_cfc(iyear_beg, jm, jn) * FLOAT (im1) & & + p_cfc(iyear_end, jm, jn) * FLOAT (im2) ) / 12. END DO ! !------------! DO jj = 1, jpj ! i-j loop ! DO ji = 1, jpi !------------! ! space interpolation zpp_cfc = xphem(ji,jj) * zpatm(1,jn) & & + ( 1.- xphem(ji,jj) ) * zpatm(2,jn) ! Computation of concentration at equilibrium : in picomol/l ! coefficient for solubility for CFC-11/12 in mol/l/atm IF( tmask(ji,jj,1) .GE. 0.5 ) THEN ztap = ( tn(ji,jj,1) + 273.16 ) * 0.01 zdtap = ( sob3(jn) * ztap + sob2(jn) ) * ztap + sob1(jn) zsol = EXP( soa1(jn) + soa2(jn) / ztap + soa3(jn) * LOG( ztap ) & & + soa4(jn) * ztap * ztap + sn(ji,jj,1) * zdtap ) ELSE zsol = 0.e0 ENDIF ! conversion from mol/l/atm to mol/m3/atm and from mol/m3/atm to mol/m3/pptv zsol = xconv4 * xconv3 * zsol * tmask(ji,jj,1) ! concentration at equilibrium zca_cfc = xconv1 * zpp_cfc * zsol * tmask(ji,jj,1) ! Computation of speed transfert ! Schmidt number zt1 = tn(ji,jj,1) zt2 = zt1 * zt1 zt3 = zt1 * zt2 zsch = sca1(jn) + sca2(jn) * zt1 + sca3(jn) * zt2 + sca4(jn) * zt3 ! speed transfert : formulae of wanninkhof 1992 zv2 = zws(ji,jj) * zws(ji,jj) zsch = zsch / 660. zak_cfc = ( 0.39 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1) ! Input function : speed *( conc. at equil - concen at surface ) ! trn in pico-mol/l idem qtr; ak in en m/s qtr(ji,jj,jn) = -zak_cfc * ( trb(ji,jj,1,jn) - zca_cfc ) & #if defined key_off_degrad & * facvol(ji,jj,1) & #endif & * tmask(ji,jj,1) * ( 1. - freeze(ji,jj) ) ! Add the surface flux to the trend tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + qtr(ji,jj,jn) / fse3t(ji,jj,1) ! cumulation of surface flux at each time step qint(ji,jj,jn) = qint (ji,jj,jn) + qtr(ji,jj,jn) * rdt ! !----------------! END DO ! end i-j loop ! END DO !----------------! ! !----------------! END DO ! end CFC loop ! ! !----------------! END SUBROUTINE trc_sms_cfc SUBROUTINE trc_cfc_cst !!--------------------------------------------------------------------- !! *** trc_cfc_cst *** !! !! ** Purpose : sets constants for CFC model !!--------------------------------------------------------------------- INTEGER :: jn !!--------------------------------------------------------------------- DO jn = jp_cfc0, jp_cfc1 IF ( jn == jp11 ) THEN ! coefficient for solubility of CFC11 in mol/l/atm soa1(jn) = -229.9261 soa2(jn) = 319.6552 soa3(jn) = 119.4471 soa4(jn) = -1.39165 sob1(jn) = -0.142382 sob2(jn) = 0.091459 sob3(jn) = -0.0157274 ! coefficients for schmidt number in degre Celcius sca1(jn) = 3501.8 sca2(jn) = -210.31 sca3(jn) = 6.1851 sca4(jn) = -0.07513 ELSE IF( jn == jp12 ) THEN ! coefficient for solubility of CFC12 in mol/l/atm soa1(jn) = -218.0971 soa2(jn) = 298.9702 soa3(jn) = 113.8049 soa4(jn) = -1.39165 sob1(jn) = -0.143566 sob2(jn) = 0.091015 sob3(jn) = -0.0153924 ! coefficients for schmidt number in degre Celcius sca1(jn) = 3845.4 sca2(jn) = -228.95 sca3(jn) = 6.1908 sca4(jn) = -0.067430 ENDIF WRITE(numout,*) 'coefficient for solubility of tracer',ctrcnm(jn) WRITE(numout,*) soa1(jn), soa2(jn),soa3(jn), soa4(jn), & & sob1(jn), sob2(jn),sob3(jn) WRITE(numout,*) WRITE(numout,*) 'coefficient for schmidt of tracer',ctrcnm(jn) WRITE(numout,*) sca1(jn), sca2(jn),sca3(jn), sca4(jn) END DO ! END SUBROUTINE trc_cfc_cst #else !!---------------------------------------------------------------------- !! Dummy module No CFC tracers !!---------------------------------------------------------------------- CONTAINS SUBROUTINE trc_sms_cfc( kt ) ! Empty routine WRITE(*,*) 'trc_sms_cfc: You should not have seen this print! error?', kt END SUBROUTINE trc_sms_cfc #endif !!====================================================================== END MODULE trcsms_cfc