Changeset 2780 for trunk/LMDZ.VENUS


Ignore:
Timestamp:
Jul 22, 2022, 1:41:25 PM (2 years ago)
Author:
flefevre
Message:

Venus PCM: option pour calcul des photolyses on-line (comme pour le Mars PCM)

Comment activer le calcul des photolyses on-line ?

1) recuperer sur occigen les dossiers suivants et les installer dans votre INPUT/ :

/home/flefevre/LMDZ5/INPUT/solar_fluxes
/home/flefevre/LMDZ5/INPUT/cross_sections

2) mettre jonline = .true. dans phyvenus/photochemistry_venus.F90

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

Legend:

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

    r2622 r2780  
    1 subroutine photochemistry_venus(nz, n_lon, ptimestep, p, t, tr, mumean, sza_input, lon, lat, nesp, iter, prod_tr, loss_tr)
     1subroutine photochemistry_venus(nz, n_lon, zlocal, ptimestep, p, t, tr, mumean, sza_input, lon, lat, nesp, iter, prod_tr, loss_tr)
    22
    33use chemparam_mod
     4use photolysis_mod
    45     
    56implicit none
     
    1415real, dimension(nz) :: p          ! pressure (hpa)
    1516real, dimension(nz) :: t          ! temperature (k)
     17real, dimension(nz) :: zlocal     ! altitude (km)
    1618real, dimension(nz) :: mumean     ! mean molecular mass (g/mol)
    1719real :: ptimestep                 ! physics timestep (s)
     
    2527!===================================================================
    2628
    27 real, dimension(nz,nesp) :: tr    ! tracer mixing ratio
     29real, dimension(nz,nesp) :: tr      ! tracer mixing ratio
    2830real, dimension(nz,nesp) :: prod_tr ! production (cm-3.s-1)
    2931real, dimension(nz,nesp) :: loss_tr ! loss       (cm-3.s-1)
     
    3941!===================================================================
    4042
     43! jonline
     44! true : on-line calculation of photodissociation rates ! false : lookup table
     45
     46logical, save :: jonline = .false.
     47
    4148logical, save :: firstcall = .true.
    4249
     
    4451real, dimension(nz)  :: surfice1d, surfdust1d
    4552
    46 ! photolysis lookup table
    47 
    48 integer, parameter :: nj = 19, nztable = 201, nsza = 27, nso2 = 13
     53! photolysis lookup table (case jonline = .false.)
     54! if prior to jvenus.20211025, set nztable = 201 below
     55
     56integer, parameter :: nj = 19, nztable = 281, nsza = 27, nso2 = 13
    4957real, dimension(nso2,nsza,nztable,nj), save :: jphot
    5058real, dimension(nztable), save :: table_colair
     
    96104if (firstcall) then
    97105!===================================================================
    98 !     read photolysis lookup table
     106!     initialisation of photolysis
    99107!===================================================================
    100108
    101    call init_chimie(nj, nztable, nsza, nso2, jphot, table_colair, table_colso2, table_sza)
     109   if (jonline) then
     110      print*, 'Photochemistry: Read UV absorption cross-sections:'
     111      call init_photolysis
     112   else
     113      print*, 'Photochemistry: Read photolysis lookup table:'
     114      call init_chimie(nj, nztable, nsza, nso2, jphot, table_colair, table_colso2, table_sza)
     115   end if
    102116
    103117!===================================================================
     
    132146dist_sol = 0.72333
    133147
    134 call phot(nj, nztable, nsza, nso2, sza_input, dist_sol, mumean, tr(:,i_co2), tr(:,i_so2),         &
    135           jphot, table_colair, table_colso2, table_sza, nz, nb_phot_max, t, p, v_phot)
     148if (jonline) then
     149   if (sza_input <= 95.) then !day at 30 km
     150      call photolysis_online(nz, nb_phot_max, zlocal, p,                 &
     151                             t, mumean, i_co2,i_co, i_o, i_o1d,          &
     152                             i_o2, i_o3, i_oh, i_ho2, i_h2o2, i_h2o,     &
     153                             i_h, i_hcl, i_cl2, i_hocl, i_so2, i_so,     &
     154                             i_so3, i_clo, i_ocs, i_cocl2, i_h2so4, i_cl,&
     155                             nesp, tr, sza_input, dist_sol, v_phot)
     156   else ! night
     157      v_phot(:,:) = 0.
     158   end if
     159else
     160   call phot(nj, nztable, nsza, nso2, sza_input, dist_sol, mumean, tr(:,i_co2), tr(:,i_so2),      &
     161             jphot, table_colair, table_colso2, table_sza, nz, nb_phot_max, t, p, v_phot)
     162end if
    136163
    137164!===================================================================
     
    146173!                 the fraction phychemrat of the physical timestep                           
    147174!===================================================================
    148        
     175
    149176phychemrat = 1
    150177
     
    237264!==================
    238265
    239 IF(n_lon .EQ. 1) THEN
    240 PRINT*,'On est en 1D'
     266!IF(n_lon .EQ. 1) THEN
     267!PRINT*,'On est en 1D'
    241268!PRINT*,"DEBUT rate_save"
    242 CALL rate_save(nz,p(:),t(:),tr(:,:),nesp,v_phot(:,:),v_3(:,:),v_4(:,:))
     269!CALL rate_save(nz,p(:),t(:),tr(:,:),nesp,v_phot(:,:),v_3(:,:),v_4(:,:))
    243270!PRINT*,"FIN rate_save"
    244 END IF
     271!END IF
    245272     
    246273end subroutine photochemistry_venus
     
    31933220LOGICAL, SAVE :: f_call = .true.
    31943221
    3195 integer, parameter :: nb_phot_max = 31
    3196 integer, parameter :: nb_reaction_3_max = 11
    3197 integer, parameter :: nb_reaction_4_max = 84
     3222integer, parameter :: nb_phot_max = 30
     3223integer, parameter :: nb_reaction_3_max = 12
     3224integer, parameter :: nb_reaction_4_max = 87
    31983225     
    31993226real, dimension(n_lev,nb_phot_max) :: vphot
  • trunk/LMDZ.VENUS/libf/phyvenus/physiq_mod.F

    r2686 r2780  
    10611061     $                       latitude_deg,
    10621062     $                       longitude_deg,
     1063     $                       zzlay,
    10631064     $                       nlev,
    10641065     $                       zctime,
  • trunk/LMDZ.VENUS/libf/phyvenus/phytrac_chimie.F

    r2622 r2780  
    66     $                    lat,
    77     $                    lon,
     8     $                    zzlay,
    89     $                    nlev,
    910     $                    pdtphys,
     
    3839      real, dimension(nlon,nlev) :: temp        ! temperature (k)
    3940      real, dimension(nlon,nlev) :: pplay       ! pressure (pa)
     41      real, dimension(nlon,nlev) :: zzlay       ! altitude (m)
    4042      real, dimension(nlon,nlev,nqmax) :: trac  ! tracer mass mixing ratio
    4143
     
    5456!===================================================================
    5557
    56       real :: sza_local   ! solar zenith angle (deg)
     58      real :: sza_local     ! solar zenith angle (deg)
    5759      real :: lon_sun
     60      real :: zlocal(nlev)  ! altitude for photochem (km)
    5861
    5962      integer :: i, iq
     
    8386!        case of tracers re-initialisation with chemistry
    8487!-------------------------------------------------------------------
     88
    8589         if (reinit_trac .and. ok_chem) then
    8690
     
    130134            end if
    131135       
    132 
    133 ! update mmean
     136!           update mmean
     137
    134138            mmean(:,:) = 0.
    135139            do iq = 1,nqmax - nmicro
     
    139143
    140144!           convert volume to mass mixing ratio
     145
    141146            do iq = 1,nqmax - nmicro
    142147               trac(:,:,iq) = trac(:,:,iq)*m_tr(iq)/mmean(:,:)
     
    148153!        case of detailed microphysics without chemistry
    149154!-------------------------------------------------------------------
     155
    150156         if (.not. ok_chem .and. ok_cloud .and. cl_scheme == 2) then
    151157
     
    276282
    277283         do ilon = 1,nlon
     284            zlocal(:)=zzlay(ilon,:)/1000.
    278285
    279286!           solar zenith angle
     
    282289     $                 *cos(lon_sun) + cos(lat_local(ilon))
    283290     $                 *sin(lon_local(ilon))*sin(lon_sun))*180./rpi
    284      
    285             call photochemistry_venus(nlev, nlon, pdtphys,
     291
     292            call photochemistry_venus(nlev, nlon, zlocal, pdtphys,
    286293     $                                pplay(ilon,:)/100.,
    287294     $                                temp(ilon,:),
     
    301308!===================================================================
    302309
    303 ! update mmean
    304             mmean(:,:) = 0.
    305             do iq = 1,nqmax - nmicro
    306                mmean(:,:) = mmean(:,:)+ztrac(:,:,iq)*m_tr(iq)
    307             enddo
    308             rnew(:,:) = 8.314/mmean(:,:)*1.e3     ! J/kg K
     310!     update mmean
     311
     312      mmean(:,:) = 0.
     313      do iq = 1,nqmax - nmicro
     314         mmean(:,:) = mmean(:,:)+ztrac(:,:,iq)*m_tr(iq)
     315      end do
     316      rnew(:,:) = 8.314/mmean(:,:)*1.e3     ! J/kg K
    309317
    310318!===================================================================
    311319!     convert volume to mass mixing ratio / then tendencies in mmr
    312320!===================================================================
     321
    313322!     gas phase
    314323
Note: See TracChangeset for help on using the changeset viewer.