Changeset 3722 for trunk/LMDZ.VENUS/libf


Ignore:
Timestamp:
Apr 14, 2025, 1:25:10 PM (2 months ago)
Author:
flefevre
Message:

Implementation of ClSO2 photolysis (Trabelsi et al., 2024) + revision of ClSO2 kinetics (Croce and Cobos, 2018).

ClSO2 absortion cross-sections must be downloaded from https://owncloud.latmos.ipsl.fr/index.php/s/o3xMPpzqcAijqKJ
and placed in INPUT/cross_sections directory.

Location:
trunk/LMDZ.VENUS/libf/phyvenus
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.VENUS/libf/phyvenus/photochemistry_venus.F90

    r3689 r3722  
    211211                             i_oh, i_ho2, i_h2o2, i_h2o, i_h, i_hcl,                &
    212212                             i_cl, i_clo, i_cl2, i_hocl, i_so2, i_so, i_so3, i_s2,  &
    213                              i_osso_cis, i_osso_trans, i_s2o2_cyc,                  &
     213                             i_osso_cis, i_osso_trans, i_s2o2_cyc, i_clso2,         &
    214214                             i_ocs, i_cocl2, i_h2so4,                               &
    215215                             i_no2, i_no, i_n2, i_n2d,                              &
     
    644644
    645645!===========================================================
     646!      ClSO2 + hv -> Cl + SO2
     647!===========================================================
     648
     649nb_phot = nb_phot + 1
     650
     651indice_phot(nb_phot) = z3spec(1.0, i_clso2, 1.0, i_cl, 1.0, i_so2)
     652
     653!===========================================================
    646654!      OCS + hv -> CO + S
    647655!===========================================================
     
    14051413
    14061414!===========================================================
    1407 !      f028 : ClSO2 + O -> SO2 + ClO
    1408 !===========================================================
    1409 
    1410 nb_reaction_4 = nb_reaction_4 + 1
    1411 
    1412 indice_4(nb_reaction_4) = z4spec(1.0, i_clso2, 1.0, i_o, 1.0, i_so2, 1.0, i_clo)
     1415!      f028 : ClSO2 + O -> SO3 + Cl
     1416!===========================================================
     1417
     1418nb_reaction_4 = nb_reaction_4 + 1
     1419
     1420indice_4(nb_reaction_4) = z4spec(1.0, i_clso2, 1.0, i_o, 1.0, i_so3, 1.0, i_cl)
    14131421
    14141422!===========================================================
     
    35063514      v_4(:,nb_reaction_4) = f027(:)
    35073515
    3508 !---  f028: clso2 + o  -> so2 + clo
     3516!---  f028: clso2 + o  -> cl + so3
     3517
     3518!     mills, phd, 1998 (products clo + so2)
     3519
     3520!     f028(:) = 1.0E-11
     3521
     3522!     croce and cobos, 2018
     3523
     3524      f028(:) = 7.69E-11*(t(:)/250.)**0.093
     3525
     3526      nb_reaction_4 = nb_reaction_4 + 1
     3527      v_4(:,nb_reaction_4) = f028(:)
     3528
     3529!---  f029: clso2 + h  -> so2 + hcl
    35093530
    35103531!     mills, phd, 1998
    35113532
    3512       f028(:) = 1.0E-11
    3513 
    3514       nb_reaction_4 = nb_reaction_4 + 1
    3515       v_4(:,nb_reaction_4) = f028(:)
    3516 
    3517 !---  f029: clso2 + h  -> so2 + hcl
    3518 
    3519 !     mills, phd, 1998
    3520 
    3521       f029(:) = 1.0E-11
     3533!     f029(:) = 1.0E-11
     3534
     3535!     croce and cobos, 2018
     3536
     3537      f029(:) = 2.71E-11*(t(:)/250.)**0.47
    35223538
    35233539      nb_reaction_4 = nb_reaction_4 + 1
     
    35283544!     moses et al. 2002
    35293545
    3530       f030(:) = 5.0E-13
     3546!     f030(:) = 5.0E-13
     3547
     3548      do iz = 1,nz
     3549         ak1 = 2.6E-14*(t(iz)/250.)**0.61
     3550         ak0 = 3.27E-28*(t(iz)/250.)**(-6.35)
     3551
     3552         rate = (ak0*conc(iz))/(1. + ak0*conc(iz)/ak1)
     3553         xpo = 1./(1. + alog10((ak0*conc(iz))/ak1)**2)
     3554         fc = 0.558*exp(-t(iz)/316.) + 0.442*exp(-t(iz)/7442.)
     3555         f030(iz) = rate*fc**xpo
     3556      end do
    35313557
    35323558      nb_reaction_3 = nb_reaction_3 + 1
  • trunk/LMDZ.VENUS/libf/phyvenus/photolysis_mod.F90

    r3689 r3722  
    55! photolysis
    66
    7   integer, save :: nphot = 27             ! number of photolysis
     7  integer, save :: nphot = 28             ! number of photolysis
    88
    99!$OMP THREADPRIVATE(nphot)
    1010
    11   integer, parameter :: nabs  = 24        ! number of absorbing gases
     11  integer, parameter :: nabs  = 25        ! number of absorbing gases
    1212
    1313! spectral grid
     
    4747  real, dimension(nw), save :: xsosso_trans                           ! osso_trans absorption cross-section (cm2)
    4848  real, dimension(nw), save :: xss2o2_cyc                             ! s2o2_cyc absorption cross-section (cm2)
     49  real, dimension(nw), save :: xsclso2                                ! clso2 absorption cross-section (cm2)
    4950  real, dimension(nw), save :: xsocs                                  ! cos absorption cross-section (cm2)
    5051  real, dimension(nw), save :: xscocl2                                ! cocl2 absorption cross-section (cm2)
     
    143144
    144145  call rdxsosso(nw,wl,wc,xsosso_cis,xsosso_trans,xss2o2_cyc)
     146
     147! read and grid clso2 cross-sections
     148
     149  call rdxsclso2(nw,wl,wc,xsclso2)
    145150
    146151! read and grid ocs cross-sections
     
    27042709!==============================================================================
    27052710
     2711      subroutine rdxsclso2(nw, wl, wc, yg)
     2712
     2713!-----------------------------------------------------------------------------*
     2714!=  PURPOSE:                                                                 =*
     2715!=  Read clso2 cross-sections                                                =*
     2716!=  From Trabelsi et al., J. Chem. Phys. 161, 109901 (2024)                  =*
     2717!-----------------------------------------------------------------------------*
     2718!=  PARAMETERS:                                                              =*
     2719!=  NW     - INTEGER, number of specified intervals + 1 in working        (I)=*
     2720!=           wavelength grid                                                 =*
     2721!-----------------------------------------------------------------------------*
     2722
     2723      USE mod_phys_lmdz_para, ONLY: is_master
     2724      USE mod_phys_lmdz_transfert_para, ONLY: bcast
     2725
     2726      IMPLICIT NONE
     2727
     2728!     input
     2729
     2730      integer :: nw                   ! number of wavelength grid points
     2731      real, dimension(nw) :: wl, wc   ! lower and central wavelength for each interval
     2732
     2733!     output
     2734
     2735      real, dimension(nw) :: yg   ! clso2 cross-sections (cm2)
     2736
     2737!     local
     2738
     2739      real, parameter :: deltax = 1.e-4
     2740      integer, parameter :: kdata = 1500
     2741
     2742      real, dimension(kdata) :: x1, y1
     2743      real :: qy, lambda
     2744      integer :: i, iw, n, ierr
     2745      integer :: kin, kout ! input/output logical units
     2746      character*100 fil
     2747
     2748      kin = 10
     2749
     2750!*** cross sections from Trabelsi et al., J. Chem. Phys. 161, 109901 (2024)
     2751
     2752      fil = 'cross_sections/clso2_trabelsi_2024.txt'
     2753      print*, 'section efficace ClSO2: ', fil
     2754
     2755      if (is_master) then
     2756
     2757      n = 1001
     2758
     2759      OPEN(kin,FILE=fil,STATUS='OLD')
     2760
     2761      do i = 1,5
     2762         read(kin,*)
     2763      end do   
     2764      do i = n,1,-1
     2765        read(kin,*) x1(i), y1(i)
     2766      end do
     2767      close(kin)
     2768
     2769      call addpnt(x1,y1,kdata,n,x1(1)*(1.-deltax),0.)
     2770      call addpnt(x1,y1,kdata,n,          0.,0.)
     2771      call addpnt(x1,y1,kdata,n,x1(n)*(1.+deltax),0.)
     2772      call addpnt(x1,y1,kdata,n,        1e38,0.)
     2773
     2774      call inter2(nw,wl,yg,n,x1,y1,ierr)
     2775 
     2776      if (ierr /= 0) then
     2777        write(*,*) ierr, fil
     2778        stop
     2779      end if
     2780
     2781      do iw = 1,nw - 1
     2782         lambda = wc(iw)
     2783         if (lambda > 316.) then  ! photodissociation threshold (tbc)
     2784            yg(iw) = 0.
     2785         end if
     2786!        write(55,'(f8.3,3e12.4)') lambda, yg(iw)
     2787      end do
     2788
     2789      end if !is_master
     2790
     2791      call bcast(yg)
     2792 
     2793      end subroutine rdxsclso2
     2794
     2795!==============================================================================
     2796
    27062797      subroutine rdxsclo(nw, wl, yg)
    27072798
  • trunk/LMDZ.VENUS/libf/phyvenus/photolysis_online.F

    r3689 r3722  
    66     $           i_oh, i_ho2, i_h2o2, i_h2o, i_h, i_hcl,
    77     $           i_cl, i_clo, i_cl2, i_hocl, i_so2, i_so, i_so3, i_s2,
    8      $           i_osso_cis, i_osso_trans, i_s2o2_cyc,
     8     $           i_osso_cis, i_osso_trans, i_s2o2_cyc, i_clso2,
    99     $           i_ocs, i_cocl2, i_h2so4,
    1010     $           i_no2, i_no, i_n2, i_n2d,
     
    2525     $                       i_so3, i_s2,
    2626     $                       i_osso_cis, i_osso_trans, i_s2o2_cyc,
    27      $                       i_ocs, i_cocl2, i_h2so4,
     27     $                       i_clso2, i_ocs, i_cocl2, i_h2so4,
    2828     $                       i_no2, i_no, i_n2, i_n2d
    2929
     
    7272     $           j_h2o, j_h2o2, j_ho2, j_h, j_hcl, j_cl2, j_hocl, j_clo,
    7373     $           j_so2, j_so, j_so3, j_s2, j_osso_cis, j_osso_trans,
    74      $           j_s2o2_cyc, j_ocs, j_cocl2, j_h2so4,
     74     $           j_s2o2_cyc, j_clso2, j_ocs, j_cocl2, j_h2so4,
    7575     $           j_no2, j_no, j_n2, j_h2
    7676
    7777      integer :: a_o2, a_co2, a_o3, a_h2o, a_h2o2, a_ho2, a_hcl, a_cl2,
    7878     $           a_hocl, a_clo, a_so2, a_so, a_so3, a_s2, a_osso_cis,
    79      $           a_osso_trans, a_s2o2_cyc, a_ocs,
     79     $           a_osso_trans, a_s2o2_cyc, a_clso2, a_ocs,
    8080     $           a_cocl2, a_h2so4, a_no2, a_no, a_n2, a_h2
    8181
     
    104104      a_osso_trans = 17     ! osso_trans
    105105      a_s2o2_cyc   = 18     ! s2o2_cyc
    106       a_ocs        = 19     ! ocs
    107       a_cocl2      = 20     ! cocl2
    108       a_h2so4      = 21     ! h2so4
    109       a_no2        = 22     ! no2
    110       a_no         = 23     ! no
    111       a_n2         = 24     ! n2
     106      a_clso2      = 19     ! clso2
     107      a_ocs        = 20     ! ocs
     108      a_cocl2      = 21     ! cocl2
     109      a_h2so4      = 22     ! h2so4
     110      a_no2        = 23     ! no2
     111      a_no         = 24     ! no
     112      a_n2         = 25     ! n2
    112113
    113114!     photodissociation rates numbering.
     
    135136      j_osso_trans = 20     ! osso_trans + hv -> so + so
    136137      j_s2o2_cyc   = 21     ! s2o2_cyc + hv   -> so + so
    137       j_ocs        = 22     ! ocs + hv        -> co + s
    138       j_cocl2      = 23     ! cocl2 + hv      -> 2cl + co
    139       j_h2so4      = 24     ! h2so4 + hv      -> so3 + h2o
    140       j_no2        = 25     ! no2 + hv        -> no + o
    141       j_no         = 26     ! no + hv         -> n + o
    142       j_n2         = 27     ! n2 + hv         -> n(2d) + n
     138      j_clso2      = 22     ! clso2 + hv      -> cl + so2
     139      j_ocs        = 23     ! ocs + hv        -> co + s
     140      j_cocl2      = 24     ! cocl2 + hv      -> 2cl + co
     141      j_h2so4      = 25     ! h2so4 + hv      -> so3 + h2o
     142      j_no2        = 26     ! no2 + hv        -> no + o
     143      j_no         = 27     ! no + hv         -> n + o
     144      j_n2         = 28     ! n2 + hv         -> n(2d) + n
    143145
    144146!     j_hdo_od  =           ! hdo + hv        -> od + h
     
    236238            dtgas(ilay,iw,a_s2o2_cyc) =
    237239     $      colinc(ilay)*rm(ilay,i_s2o2_cyc)*xss2o2_cyc(iw)
     240            dtgas(ilay,iw,a_clso2) =
     241     $      colinc(ilay)*rm(ilay,i_clso2)*xsclso2(iw)
    238242            dtgas(ilay,iw,a_ocs) = colinc(ilay)*rm(ilay,i_ocs)*xsocs(iw)
    239243            dtgas(ilay,iw,a_cocl2) = colinc(ilay)*rm(ilay,i_cocl2)
     
    274278            sj(ilay,iw,j_osso_trans) = xsosso_trans(iw)  ! osso_trans
    275279            sj(ilay,iw,j_s2o2_cyc) = xss2o2_cyc(iw)      ! s2o2_cyc
     280            sj(ilay,iw,j_clso2) = xsclso2(iw)            ! clso2
    276281            sj(ilay,iw,j_ocs) = xsocs(iw)                ! ocs
    277282            sj(ilay,iw,j_cocl2) = xscocl2(iw)            ! cocl2
Note: See TracChangeset for help on using the changeset viewer.