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 7211 – NEMO

Changeset 7211


Ignore:
Timestamp:
2016-11-08T18:17:26+01:00 (7 years ago)
Author:
lovato
Message:

New top interface : Revisited CFC module with formulations from Wanninkhof (2014) + SF6 tracer

Location:
branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/CONFIG/ORCA2_LIM3_TRC/EXP00/iodef.xml

    r7068 r7211  
    147147           <field field_ref="Age"    operation="average" freq_op="1d" > @Age_e3t / @e3t </field> 
    148148           <field field_ref="CFC11"  operation="average" freq_op="1d" > @CFC11_e3t / @e3t </field> 
     149           <field field_ref="CFC12"  operation="average" freq_op="1d" > @CFC12_e3t / @e3t </field> 
     150           <field field_ref="SF6"    operation="average" freq_op="1d" > @SF6_e3t / @e3t </field> 
    149151           <field field_ref="RC14"   operation="average" freq_op="1d" > @RC14_e3t / @e3t </field> 
    150152         </file> 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/CONFIG/ORCA2_LIM3_TRC/EXP00/namelist_top_cfg

    r7198 r7211  
    2323   ln_cfc11      =  .true.      !  Run the CFC11 passive tracer 
    2424   ln_cfc12      =  .false.     !  Run the CFC12 passive tracer 
     25   ln_sf6        =  .false.     !  Run the SF6 passive tracer 
    2526   ln_c14        =  .true.      !  Run the Radiocarbon passive tracer 
    2627/ 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/CONFIG/SHARED/field_def.xml

    r7174 r7211  
    887887       <field id="CFC12"       long_name="Chlorofluoro carbon12 Concentration"      unit="umol/m3" /> 
    888888       <field id="CFC12_e3t"   long_name="CFC12 * e3t"                              unit="umol/m2"  > CFC12 * e3t </field > 
     889 
     890       <!-- SF6 : variables available with ln_sf6 --> 
     891       <field id="SF6"       long_name="Sulfur hexafluoride Concentration"      unit="umol/m3" /> 
     892       <field id="SF6_e3t"   long_name="SF6 * e3t"                              unit="umol/m2"  > SF6 * e3t </field > 
    889893 
    890894       <!-- C14 : variables available with ln_c14 --> 
     
    10251029       <field id="qint_CFC12"   long_name="Cumulative air-sea flux of CFC12"       unit="mol/m2"     /> 
    10261030 
     1031       <!-- SF6 : variables available with ln_sf6 --> 
     1032       <field id="qtr_SF6"      long_name="Air-sea flux of SF6"                    unit="mol/m2/s"   /> 
     1033       <field id="qint_SF6"     long_name="Cumulative air-sea flux of SF6"         unit="mol/m2"     /> 
     1034 
    10271035       <!--  C14 : variables available with ln_c14 --> 
    10281036       <field id="DeltaC14"     long_name="Delta C14"                              unit="permil" grid_ref="grid_T_3D"   /> 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/CONFIG/SHARED/namelist_top_ref

    r7198 r7211  
    3333   ln_cfc11      =  .false.     !  Run the CFC11 passive tracer 
    3434   ln_cfc12      =  .false.     !  Run the CFC12 passive tracer 
     35   ln_sf6        =  .false.     !  Run the SF6 passive tracer 
    3536   ln_c14        =  .false.     !  Run the Radiocarbon passive tracer 
    3637! 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/CONFIG/SHARED/namelist_trc_ref

    r7103 r7211  
    99   ndate_beg  = 300101    !  datedeb1 
    1010   nyear_res  = 1932      !  iannee1 
     11   ! 
     12   ! Formatted file of annual hemisperic CFCs concentration in the atmosphere (ppt) 
     13   clname     = 'CFCs_in_air_CMIP6.dat' 
    1114/ 
    1215! 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/CFC/trcini_cfc.F90

    r7124 r7211  
    1919 
    2020   PUBLIC   trc_ini_cfc   ! called by trcini.F90 module 
    21  
    22    CHARACTER (len=34) ::   clname = 'cfc1112.atm'   ! ??? 
    2321 
    2422   INTEGER  ::   inum                   ! unit number 
     
    5351      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~' 
    5452      ! 
    55       IF(lwp) WRITE(numout,*) 'read of formatted file cfc1112atm' 
     53      IF(lwp) WRITE(numout,*) 'Read annual atmospheric concentratioins from formatted file : ' // TRIM(clname) 
    5654       
    5755      CALL ctl_opn( inum, clname, 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
     
    6664      END DO 
    6765 100  jpyear = jn - 1 - iskip 
    68       IF ( lwp) WRITE(numout,*) '    ', jpyear ,' years read' 
     66      IF ( lwp) WRITE(numout,*) '   ---> ', jpyear ,' years read' 
    6967      !                                ! Allocate CFC arrays 
    7068 
    71       ALLOCATE( p_cfc(jpyear,jphem,2), STAT=ierr ) 
     69      ALLOCATE( p_cfc(jpyear,jphem,3), STAT=ierr ) 
    7270      IF( ierr > 0 ) THEN 
    7371         CALL ctl_stop( 'trc_ini_cfc: unable to allocate p_cfc array' )   ;   RETURN 
     
    8785         IF(lwp) THEN 
    8886            WRITE(numout,*) 
    89             WRITE(numout,*) 'Initialization de qint ; No restart : qint equal zero ' 
     87            WRITE(numout,*) 'Initialisation of qint ; No restart : qint equal zero ' 
    9088         ENDIF 
    9189         qint_cfc(:,:,:) = 0._wp 
     
    105103      jn = 31 
    106104      DO  
    107         READ(inum,*, IOSTAT=io) zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), p_cfc(jn,2,1), p_cfc(jn,2,2) 
     105        READ(inum,*, IOSTAT=io) zyy, p_cfc(jn,1:2,1), p_cfc(jn,1:2,2), p_cfc(jn,1:2,3) 
    108106        IF( io < 0 ) exit 
    109107        jn = jn + 1 
    110108      END DO 
    111109 
    112       p_cfc(32,1:2,1) = 5.e-4      ! modify the values of the first years 
    113       p_cfc(33,1:2,1) = 8.e-4 
    114       p_cfc(34,1:2,1) = 1.e-6 
    115       p_cfc(35,1:2,1) = 2.e-3 
    116       p_cfc(36,1:2,1) = 4.e-3 
    117       p_cfc(37,1:2,1) = 6.e-3 
    118       p_cfc(38,1:2,1) = 8.e-3 
    119       p_cfc(39,1:2,1) = 1.e-2 
     110      !p_cfc(32,1:2,1) = 5.e-4      ! modify the values of the first years 
     111      !p_cfc(33,1:2,1) = 8.e-4 
     112      !p_cfc(34,1:2,1) = 1.e-6 
     113      !p_cfc(35,1:2,1) = 2.e-3 
     114      !p_cfc(36,1:2,1) = 4.e-3 
     115      !p_cfc(37,1:2,1) = 6.e-3 
     116      !p_cfc(38,1:2,1) = 8.e-3 
     117      !p_cfc(39,1:2,1) = 1.e-2 
    120118      IF(lwp) THEN        ! Control print 
    121119         WRITE(numout,*) 
    122          WRITE(numout,*) ' Year   p11HN    p11HS    p12HN    p12HS ' 
     120         WRITE(numout,*) ' Year   c11NH     c11SH     c12NH     c12SH     SF6NH     SF6SH' 
    123121         DO jn = 30, jpyear 
    124             WRITE(numout, '( 1I4, 4F9.2)') jn, p_cfc(jn,1,1), p_cfc(jn,2,1), p_cfc(jn,1,2), p_cfc(jn,2,2) 
     122            WRITE(numout, '( 1I4, 6F10.4)') jn, p_cfc(jn,1:2,1), p_cfc(jn,1:2,2), p_cfc(jn,1:2,3) 
    125123         END DO 
    126124      ENDIF 
     
    144142      ! 
    145143   END SUBROUTINE trc_ini_cfc 
    146     
     144 
    147145   !!====================================================================== 
    148146END MODULE trcini_cfc 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/CFC/trcnam_cfc.F90

    r7124 r7211  
    1414   IMPLICIT NONE 
    1515   PRIVATE 
     16 
     17   CHARACTER(len=34), PUBLIC ::   clname ! Input filename of CFCs atm. concentrations 
    1618 
    1719   PUBLIC   trc_nam_cfc   ! called by trcnam.F90 module 
     
    3941      INTEGER :: jl, jn 
    4042      !! 
    41       NAMELIST/namcfc/ ndate_beg, nyear_res 
     43      NAMELIST/namcfc/ ndate_beg, nyear_res, clname 
    4244      !!---------------------------------------------------------------------- 
     45      ! 
     46      jn = jp_cfc0 - 1 
    4347      ! Variables setting 
    4448      IF( ln_cfc11 ) THEN 
    45          ctrcnm    (jp_cfc0) = 'CFC11' 
    46          ctrcln    (jp_cfc0) = 'Chlorofluoro carbon 11 Concentration' 
    47          ctrcun    (jp_cfc0) = 'umolC/L' 
    48          ln_trc_ini(jp_cfc0) = .false. 
    49          ln_trc_sbc(jp_cfc0) = .false. 
    50          ln_trc_cbc(jp_cfc0) = .false. 
    51          ln_trc_obc(jp_cfc0) = .false. 
     49         jn = jn + 1 
     50         ctrcnm    (jn) = 'CFC11' 
     51         ctrcln    (jn) = 'Chlorofluoro carbon 11 Concentration' 
     52         ctrcun    (jn) = 'umolC/L' 
     53         ln_trc_ini(jn) = .false. 
     54         ln_trc_sbc(jn) = .false. 
     55         ln_trc_cbc(jn) = .false. 
     56         ln_trc_obc(jn) = .false. 
    5257      ENDIF 
    5358      ! 
    5459      IF( ln_cfc12 ) THEN 
    55          ctrcnm    (jp_cfc1) = 'CFC12' 
    56          ctrcln    (jp_cfc1) = 'Chlorofluoro carbon 12 Concentration' 
    57          ctrcun    (jp_cfc1) = 'umolC/L' 
    58          ln_trc_ini(jp_cfc1) = .false. 
    59          ln_trc_sbc(jp_cfc1) = .false. 
    60          ln_trc_cbc(jp_cfc1) = .false. 
    61          ln_trc_obc(jp_cfc1) = .false. 
     60         jn = jn + 1 
     61         ctrcnm    (jn) = 'CFC12' 
     62         ctrcln    (jn) = 'Chlorofluoro carbon 12 Concentration' 
     63         ctrcun    (jn) = 'umolC/L' 
     64         ln_trc_ini(jn) = .false. 
     65         ln_trc_sbc(jn) = .false. 
     66         ln_trc_cbc(jn) = .false. 
     67         ln_trc_obc(jn) = .false. 
     68      ENDIF 
     69      ! 
     70      IF( ln_sf6 ) THEN 
     71         jn = jn + 1 
     72         ctrcnm    (jn) = 'SF6' 
     73         ctrcln    (jn) = 'Sulfur hexafluoride Concentration' 
     74         ctrcun    (jn) = 'umol/L' 
     75         ln_trc_ini(jn) = .false. 
     76         ln_trc_sbc(jn) = .false. 
     77         ln_trc_cbc(jn) = .false. 
     78         ln_trc_obc(jn) = .false. 
    6279      ENDIF 
    6380      ! 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/CFC/trcsms_cfc.F90

    r7192 r7211  
    77   !!  NEMO      1.0  !  2004-03  (C. Ethe) free form + modularity 
    88   !!            2.0  !  2007-12  (C. Ethe, G. Madec)  reorganisation 
     9   !!            4.0  !  2016-11  (T. Lovato) Add SF6, Update Schmidt number 
    910   !!---------------------------------------------------------------------- 
    1011   !!   trc_sms_cfc  :  compute and add CFC suface forcing to CFC trends 
     
    2526 
    2627   INTEGER , PUBLIC, PARAMETER ::   jphem  =   2   ! parameter for the 2 hemispheres 
    27    INTEGER , PUBLIC            ::   jpyear         ! Number of years read in CFC1112 file 
     28   INTEGER , PUBLIC            ::   jpyear         ! Number of years read in input data file (in trcini_cfc) 
    2829   INTEGER , PUBLIC            ::   ndate_beg      ! initial calendar date (aammjj) for CFC 
    2930   INTEGER , PUBLIC            ::   nyear_res      ! restoring time constant (year) 
    3031   INTEGER , PUBLIC            ::   nyear_beg      ! initial year (aa)  
    3132    
    32    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   p_cfc    ! partial hemispheric pressure for CFC 
     33   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   p_cfc    ! partial hemispheric pressure for all CFC 
    3334   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   xphem    ! spatial interpolation factor for patm 
    3435   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qtr_cfc  ! flux at surface 
    3536   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qint_cfc ! cumulative flux  
     37   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   atm_cfc  ! partial hemispheric pressure for used CFC 
    3638   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   patm     ! atmospheric function 
    3739 
    38    REAL(wp), DIMENSION(4,2) ::   soa   ! coefficient for solubility of CFC [mol/l/atm] 
    39    REAL(wp), DIMENSION(3,2) ::   sob   !    "               " 
    40    REAL(wp), DIMENSION(4,2) ::   sca   ! coefficients for schmidt number in degre Celcius 
     40   REAL(wp),         ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   soa      ! coefficient for solubility of CFC [mol/l/atm] 
     41   REAL(wp),         ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sob      !    "               " 
     42   REAL(wp),         ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sca      ! coefficients for schmidt number in degrees Celsius 
    4143       
    4244   !                          ! coefficients for conversion 
     
    7577      INTEGER  ::   im1, im2, ierr 
    7678      REAL(wp) ::   ztap, zdtap         
    77       REAL(wp) ::   zt1, zt2, zt3, zv2 
     79      REAL(wp) ::   zt1, zt2, zt3, zt4, zv2 
    7880      REAL(wp) ::   zsol      ! solubility 
    7981      REAL(wp) ::   zsch      ! schmidt number  
     
    113115         ! time interpolation at time kt 
    114116         DO jm = 1, jphem 
    115             zpatm(jm,jl) = (  p_cfc(iyear_beg, jm, jl) * REAL(im1, wp)  & 
    116                &           +  p_cfc(iyear_end, jm, jl) * REAL(im2, wp) ) / 12. 
     117            zpatm(jm,jl) = (  atm_cfc(iyear_beg, jm, jl) * REAL(im1, wp)  & 
     118               &           +  atm_cfc(iyear_end, jm, jl) * REAL(im2, wp) ) / 12. 
    117119         END DO 
    118120          
     
    141143   
    142144               ! Computation of speed transfert 
    143                !    Schmidt number 
     145               !    Schmidt number revised in Wanninkhof (2014) 
    144146               zt1  = tsn(ji,jj,1,jp_tem) 
    145147               zt2  = zt1 * zt1  
    146148               zt3  = zt1 * zt2 
    147                zsch = sca(1,jl) + sca(2,jl) * zt1 + sca(3,jl) * zt2 + sca(4,jl) * zt3 
    148  
    149                !    speed transfert : formulae of wanninkhof 1992 
     149               zt4  = zt2 * zt2 
     150               zsch = sca(1,jl) + sca(2,jl) * zt1 + sca(3,jl) * zt2 + sca(4,jl) * zt3 + sca(5,jl) * zt4 
     151 
     152               !    speed transfert : formulae revised in Wanninkhof (2014) 
    150153               zv2     = wndm(ji,jj) * wndm(ji,jj) 
    151154               zsch    = zsch / 660. 
    152                zak_cfc = ( 0.39 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1) 
     155               zak_cfc = ( 0.31 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1) 
    153156 
    154157               ! Input function  : speed *( conc. at equil - concen at surface ) 
     
    202205      !!--------------------------------------------------------------------- 
    203206      INTEGER :: jn 
    204  
     207      !!---------------------------------------------------------------------- 
     208      ! 
     209      jn = 0  
    205210      ! coefficient for CFC11  
    206211      !---------------------- 
    207  
    208       ! Solubility 
    209       soa(1,1) = -229.9261  
    210       soa(2,1) =  319.6552 
    211       soa(3,1) =  119.4471 
    212       soa(4,1) =  -1.39165 
    213  
    214       sob(1,1) =  -0.142382 
    215       sob(2,1) =   0.091459 
    216       sob(3,1) =  -0.0157274 
    217  
    218       ! Schmidt number  
    219       sca(1,1) = 3501.8 
    220       sca(2,1) = -210.31 
    221       sca(3,1) =  6.1851 
    222       sca(4,1) = -0.07513 
     212      if ( ln_cfc11 ) then 
     213         jn = jn + 1 
     214         ! Solubility 
     215         soa(1,jn) = -229.9261  
     216         soa(2,jn) =  319.6552 
     217         soa(3,jn) =  119.4471 
     218         soa(4,jn) =  -1.39165 
     219 
     220         sob(1,jn) =  -0.142382 
     221         sob(2,jn) =   0.091459 
     222         sob(3,jn) =  -0.0157274 
     223 
     224         ! Schmidt number  
     225         sca(1,jn) = 3579.2 
     226         sca(2,jn) = -222.63 
     227         sca(3,jn) = 7.5749 
     228         sca(4,jn) = -0.14595 
     229         sca(5,jn) = 0.0011874 
     230 
     231         ! atm. concentration 
     232         atm_cfc(:,:,jn) = p_cfc(:,:,1) 
     233      endif 
    223234 
    224235      ! coefficient for CFC12  
    225236      !---------------------- 
    226  
    227       ! Solubility 
    228       soa(1,2) = -218.0971 
    229       soa(2,2) =  298.9702 
    230       soa(3,2) =  113.8049 
    231       soa(4,2) =  -1.39165 
    232  
    233       sob(1,2) =  -0.143566 
    234       sob(2,2) =   0.091015 
    235       sob(3,2) =  -0.0153924 
    236  
    237       ! schmidt number  
    238       sca(1,2) =  3845.4  
    239       sca(2,2) =  -228.95 
    240       sca(3,2) =  6.1908  
    241       sca(4,2) =  -0.067430 
     237      if ( ln_cfc12 ) then 
     238         jn = jn + 1 
     239         ! Solubility 
     240         soa(1,jn) = -218.0971 
     241         soa(2,jn) =  298.9702 
     242         soa(3,jn) =  113.8049 
     243         soa(4,jn) =  -1.39165 
     244 
     245         sob(1,jn) =  -0.143566 
     246         sob(2,jn) =   0.091015 
     247         sob(3,jn) =  -0.0153924 
     248 
     249         ! schmidt number  
     250         sca(1,jn) = 3828.1 
     251         sca(2,jn) = -249.86 
     252         sca(3,jn) = 8.7603 
     253         sca(4,jn) = -0.1716 
     254         sca(5,jn) = 0.001408 
     255 
     256         ! atm. concentration 
     257         atm_cfc(:,:,jn) = p_cfc(:,:,2) 
     258      endif 
     259 
     260      ! coefficient for SF6 
     261      !---------------------- 
     262      if ( ln_sf6 ) then 
     263         jn = jn + 1 
     264         ! Solubility 
     265         soa(1,jn) = -80.0343 
     266         soa(2,jn) = 117.232 
     267         soa(3,jn) =  29.5817 
     268         soa(4,jn) =   0.0 
     269 
     270         sob(1,jn) =  0.0335183  
     271         sob(2,jn) = -0.0373942  
     272         sob(3,jn) =  0.00774862 
     273 
     274         ! schmidt number 
     275         sca(1,jn) = 3177.5 
     276         sca(2,jn) = -200.57 
     277         sca(3,jn) = 6.8865 
     278         sca(4,jn) = -0.13335 
     279         sca(5,jn) = 0.0010877 
     280   
     281         ! atm. concentration 
     282         atm_cfc(:,:,jn) = p_cfc(:,:,3) 
     283       endif 
    242284 
    243285      IF( ln_rsttr ) THEN 
     
    259301      !!                     ***  ROUTINE trc_sms_cfc_alloc  *** 
    260302      !!---------------------------------------------------------------------- 
    261       ALLOCATE( xphem   (jpi,jpj)        ,     & 
    262          &      qtr_cfc (jpi,jpj,jp_cfc) ,     & 
    263          &      qint_cfc(jpi,jpj,jp_cfc) , STAT=trc_sms_cfc_alloc ) 
     303      ALLOCATE( xphem   (jpi,jpj)        , atm_cfc(jpyear,jphem,jp_cfc)  ,    & 
     304         &      qtr_cfc (jpi,jpj,jp_cfc) , qint_cfc(jpi,jpj,jp_cfc)      ,    & 
     305         &      soa(4,jp_cfc)    ,  sob(3,jp_cfc)   ,  sca(5,jp_cfc)     ,    & 
     306         &      STAT=trc_sms_cfc_alloc ) 
    264307         ! 
    265308      IF( trc_sms_cfc_alloc /= 0 ) CALL ctl_warn('trc_sms_cfc_alloc : failed to allocate arrays.') 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/par_trc.F90

    r7198 r7211  
    3434   LOGICAL, PUBLIC             :: ln_cfc11        !: CFC11 flag  
    3535   LOGICAL, PUBLIC             :: ln_cfc12        !: CFC12 flag  
     36   LOGICAL, PUBLIC             :: ln_sf6          !: SF6 flag  
    3637   LOGICAL, PUBLIC             :: ll_cfc          !: CFC flag  
    3738   LOGICAL, PUBLIC             :: ln_c14          !: C14 flag  
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r7198 r7211  
    145145      INTEGER  ::   ios, ierr, icfc       ! Local integer output status for namelist read 
    146146      !! 
    147       NAMELIST/namtrc/jp_bgc, ln_pisces, ln_my_trc, ln_age, ln_cfc11, ln_cfc12, ln_c14, & 
     147      NAMELIST/namtrc/jp_bgc, ln_pisces, ln_my_trc, ln_age, ln_cfc11, ln_cfc12, ln_sf6, ln_c14, & 
    148148         &            sn_tracer, ln_trcdta, ln_trcdmp, ln_trcdmp_clo, jp_dia3d, jp_dia2d 
    149149      !!--------------------------------------------------------------------- 
     
    168168      IF( ln_pisces .AND. ln_my_trc )   CALL ctl_stop( 'Choose only ONE BGC model - PISCES or MY_TRC' ) 
    169169      IF( .NOT. ln_pisces .AND. .NOT. ln_my_trc )   jp_bgc = 0 
    170       ll_cfc = ln_cfc11 .OR. ln_cfc12 
     170      ll_cfc = ln_cfc11 .OR. ln_cfc12 .OR. ln_sf6 
    171171      ! 
    172172      jptra       =  0 
     
    195195      IF( ln_cfc11 )  jp_cfc = jp_cfc + 1 
    196196      IF( ln_cfc12 )  jp_cfc = jp_cfc + 1 
     197      IF( ln_sf6   )  jp_cfc = jp_cfc + 1 
    197198      IF( ll_cfc )    THEN 
    198199          jptra     = jptra + jp_cfc 
     
    217218         WRITE(numout,*) '   Simulating CFC11 passive tracer              ln_cfc11      = ', ln_cfc11 
    218219         WRITE(numout,*) '   Simulating CFC12 passive tracer              ln_cfc12      = ', ln_cfc12 
     220         WRITE(numout,*) '   Simulating SF6 passive tracer                ln_sf6        = ', ln_sf6 
     221         WRITE(numout,*) '   Total number of CFCs tracers                 jp_cfc        = ', jp_cfc 
    219222         WRITE(numout,*) '   Simulating C14   passive tracer              ln_c14        = ', ln_c14 
    220223         WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta 
Note: See TracChangeset for help on using the changeset viewer.